Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Confd / Server.hs @ ea626b33

History | View | Annotate | Download (19.9 kB)

1
{-# LANGUAGE BangPatterns #-}
2

    
3
{-| Implementation of the Ganeti confd server functionality.
4

    
5
-}
6

    
7
{-
8

    
9
Copyright (C) 2011, 2012 Google Inc.
10

    
11
This program is free software; you can redistribute it and/or modify
12
it under the terms of the GNU General Public License as published by
13
the Free Software Foundation; either version 2 of the License, or
14
(at your option) any later version.
15

    
16
This program is distributed in the hope that it will be useful, but
17
WITHOUT ANY WARRANTY; without even the implied warranty of
18
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19
General Public License for more details.
20

    
21
You should have received a copy of the GNU General Public License
22
along with this program; if not, write to the Free Software
23
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24
02110-1301, USA.
25

    
26
-}
27

    
28
module Ganeti.Confd.Server
29
  ( main
30
  , checkMain
31
  , prepMain
32
  ) where
33

    
34
import Control.Concurrent
35
import Control.Exception
36
import Control.Monad (forever, liftM, when)
37
import Data.IORef
38
import Data.List
39
import qualified Data.Map as M
40
import Data.Maybe (fromMaybe)
41
import qualified Network.Socket as S
42
import System.Exit
43
import System.IO
44
import System.Posix.Files
45
import System.Posix.Types
46
import System.Time
47
import qualified Text.JSON as J
48
import System.INotify
49

    
50
import Ganeti.BasicTypes
51
import Ganeti.Errors
52
import Ganeti.Daemon
53
import Ganeti.JSON
54
import Ganeti.Objects
55
import Ganeti.Confd.Types
56
import Ganeti.Confd.Utils
57
import Ganeti.Config
58
import Ganeti.Hash
59
import Ganeti.Logging
60
import qualified Ganeti.Constants as C
61
import qualified Ganeti.Path as Path
62
import Ganeti.Query.Server (prepQueryD, runQueryD)
63
import Ganeti.Utils
64

    
65
-- * Types and constants definitions
66

    
67
-- | What we store as configuration.
68
type CRef = IORef (Result (ConfigData, LinkIpMap))
69

    
70
-- | File stat identifier.
71
type FStat = (EpochTime, FileID, FileOffset)
72

    
73
-- | Null 'FStat' value.
74
nullFStat :: FStat
75
nullFStat = (-1, -1, -1)
76

    
77
-- | A small type alias for readability.
78
type StatusAnswer = (ConfdReplyStatus, J.JSValue)
79

    
80
-- | Reload model data type.
81
data ReloadModel = ReloadNotify      -- ^ We are using notifications
82
                 | ReloadPoll Int    -- ^ We are using polling
83
                   deriving (Eq, Show)
84

    
85
-- | Server state data type.
86
data ServerState = ServerState
87
  { reloadModel  :: ReloadModel
88
  , reloadTime   :: Integer
89
  , reloadFStat  :: FStat
90
  }
91

    
92
-- | Maximum no-reload poll rounds before reverting to inotify.
93
maxIdlePollRounds :: Int
94
maxIdlePollRounds = 2
95

    
96
-- | Reload timeout in microseconds.
97
configReloadTimeout :: Int
98
configReloadTimeout = C.confdConfigReloadTimeout * 1000000
99

    
100
-- | Ratelimit timeout in microseconds.
101
configReloadRatelimit :: Int
102
configReloadRatelimit = C.confdConfigReloadRatelimit * 1000000
103

    
104
-- | Ratelimit timeout in seconds, as an 'Integer'.
105
reloadRatelimitSec :: Integer
106
reloadRatelimitSec = fromIntegral C.confdConfigReloadRatelimit
107

    
108
-- | Initial poll round.
109
initialPoll :: ReloadModel
110
initialPoll = ReloadPoll 0
111

    
112
-- | Initial server state.
113
initialState :: ServerState
114
initialState = ServerState initialPoll 0 nullFStat
115

    
116
-- | Reload status data type.
117
data ConfigReload = ConfigToDate    -- ^ No need to reload
118
                  | ConfigReloaded  -- ^ Configuration reloaded
119
                  | ConfigIOError   -- ^ Error during configuration reload
120

    
121
-- | Unknown entry standard response.
122
queryUnknownEntry :: StatusAnswer
123
queryUnknownEntry = (ReplyStatusError, J.showJSON ConfdErrorUnknownEntry)
124

    
125
{- not used yet
126
-- | Internal error standard response.
127
queryInternalError :: StatusAnswer
128
queryInternalError = (ReplyStatusError, J.showJSON ConfdErrorInternal)
129
-}
130

    
131
-- | Argument error standard response.
132
queryArgumentError :: StatusAnswer
133
queryArgumentError = (ReplyStatusError, J.showJSON ConfdErrorArgument)
134

    
135
-- | Returns the current time.
136
getCurrentTime :: IO Integer
137
getCurrentTime = do
138
  TOD ctime _ <- getClockTime
139
  return ctime
140

    
141
-- | Converter from specific error to a string format.
142
gntErrorToResult :: ErrorResult a -> Result a
143
gntErrorToResult (Bad err) = Bad (show err)
144
gntErrorToResult (Ok x) = Ok x
145

    
146
-- * Confd base functionality
147

    
148
-- | Computes the node role.
149
nodeRole :: ConfigData -> String -> Result ConfdNodeRole
150
nodeRole cfg name =
151
  let cmaster = clusterMasterNode . configCluster $ cfg
152
      mnode = M.lookup name . fromContainer . configNodes $ cfg
153
  in case mnode of
154
       Nothing -> Bad "Node not found"
155
       Just node | cmaster == name -> Ok NodeRoleMaster
156
                 | nodeDrained node -> Ok NodeRoleDrained
157
                 | nodeOffline node -> Ok NodeRoleOffline
158
                 | nodeMasterCandidate node -> Ok NodeRoleCandidate
159
       _ -> Ok NodeRoleRegular
160

    
161
-- | Does an instance ip -> instance -> primary node -> primary ip
162
-- transformation.
163
getNodePipByInstanceIp :: ConfigData
164
                       -> LinkIpMap
165
                       -> String
166
                       -> String
167
                       -> StatusAnswer
168
getNodePipByInstanceIp cfg linkipmap link instip =
169
  case M.lookup instip (M.findWithDefault M.empty link linkipmap) of
170
    Nothing -> queryUnknownEntry
171
    Just instname ->
172
      case getInstPrimaryNode cfg instname of
173
        Bad _ -> queryUnknownEntry -- either instance or node not found
174
        Ok node -> (ReplyStatusOk, J.showJSON (nodePrimaryIp node))
175

    
176
-- | Builds the response to a given query.
177
buildResponse :: (ConfigData, LinkIpMap) -> ConfdRequest -> Result StatusAnswer
178
buildResponse (cfg, _) (ConfdRequest { confdRqType = ReqPing }) =
179
  return (ReplyStatusOk, J.showJSON (configVersion cfg))
180

    
181
buildResponse cdata req@(ConfdRequest { confdRqType = ReqClusterMaster }) =
182
  case confdRqQuery req of
183
    EmptyQuery -> return (ReplyStatusOk, J.showJSON master_name)
184
    PlainQuery _ -> return queryArgumentError
185
    DictQuery reqq -> do
186
      mnode <- gntErrorToResult $ getNode cfg master_name
187
      let fvals = map (\field -> case field of
188
                                   ReqFieldName -> master_name
189
                                   ReqFieldIp -> clusterMasterIp cluster
190
                                   ReqFieldMNodePip -> nodePrimaryIp mnode
191
                      ) (confdReqQFields reqq)
192
      return (ReplyStatusOk, J.showJSON fvals)
193
    where master_name = clusterMasterNode cluster
194
          cluster = configCluster cfg
195
          cfg = fst cdata
196

    
197
buildResponse cdata req@(ConfdRequest { confdRqType = ReqNodeRoleByName }) = do
198
  node_name <- case confdRqQuery req of
199
                 PlainQuery str -> return str
200
                 _ -> fail $ "Invalid query type " ++ show (confdRqQuery req)
201
  role <- nodeRole (fst cdata) node_name
202
  return (ReplyStatusOk, J.showJSON role)
203

    
204
buildResponse cdata (ConfdRequest { confdRqType = ReqNodePipList }) =
205
  -- note: we use foldlWithKey because that's present accross more
206
  -- versions of the library
207
  return (ReplyStatusOk, J.showJSON $
208
          M.foldlWithKey (\accu _ n -> nodePrimaryIp n:accu) []
209
          (fromContainer . configNodes . fst $ cdata))
210

    
211
buildResponse cdata (ConfdRequest { confdRqType = ReqMcPipList }) =
212
  -- note: we use foldlWithKey because that's present accross more
213
  -- versions of the library
214
  return (ReplyStatusOk, J.showJSON $
215
          M.foldlWithKey (\accu _ n -> if nodeMasterCandidate n
216
                                         then nodePrimaryIp n:accu
217
                                         else accu) []
218
          (fromContainer . configNodes . fst $ cdata))
219

    
220
buildResponse (cfg, linkipmap)
221
              req@(ConfdRequest { confdRqType = ReqInstIpsList }) = do
222
  link <- case confdRqQuery req of
223
            PlainQuery str -> return str
224
            EmptyQuery -> return (getDefaultNicLink cfg)
225
            _ -> fail "Invalid query type"
226
  return (ReplyStatusOk, J.showJSON $ getInstancesIpByLink linkipmap link)
227

    
228
buildResponse cdata (ConfdRequest { confdRqType = ReqNodePipByInstPip
229
                                  , confdRqQuery = DictQuery query}) =
230
  let (cfg, linkipmap) = cdata
231
      link = fromMaybe (getDefaultNicLink cfg) (confdReqQLink query)
232
  in case confdReqQIp query of
233
       Just ip -> return $ getNodePipByInstanceIp cfg linkipmap link ip
234
       Nothing -> return (ReplyStatusOk,
235
                          J.showJSON $
236
                           map (getNodePipByInstanceIp cfg linkipmap link)
237
                           (confdReqQIpList query))
238

    
239
buildResponse _ (ConfdRequest { confdRqType = ReqNodePipByInstPip }) =
240
  return queryArgumentError
241

    
242
buildResponse cdata req@(ConfdRequest { confdRqType = ReqNodeDrbd }) = do
243
  let cfg = fst cdata
244
  node_name <- case confdRqQuery req of
245
                 PlainQuery str -> return str
246
                 _ -> fail $ "Invalid query type " ++ show (confdRqQuery req)
247
  node <- gntErrorToResult $ getNode cfg node_name
248
  let minors = concatMap (getInstMinorsForNode (nodeName node)) .
249
               M.elems . fromContainer . configInstances $ cfg
250
      encoded = [J.JSArray [J.showJSON a, J.showJSON b, J.showJSON c,
251
                             J.showJSON d, J.showJSON e, J.showJSON f] |
252
                 (a, b, c, d, e, f) <- minors]
253
  return (ReplyStatusOk, J.showJSON encoded)
254

    
255
-- | Creates a ConfdReply from a given answer.
256
serializeResponse :: Result StatusAnswer -> ConfdReply
257
serializeResponse r =
258
    let (status, result) = case r of
259
                    Bad err -> (ReplyStatusError, J.showJSON err)
260
                    Ok (code, val) -> (code, val)
261
    in ConfdReply { confdReplyProtocol = 1
262
                  , confdReplyStatus   = status
263
                  , confdReplyAnswer   = result
264
                  , confdReplySerial   = 0 }
265

    
266
-- * Configuration handling
267

    
268
-- ** Helper functions
269

    
270
-- | Helper function for logging transition into polling mode.
271
moveToPolling :: String -> INotify -> FilePath -> CRef -> MVar ServerState
272
              -> IO ReloadModel
273
moveToPolling msg inotify path cref mstate = do
274
  logInfo $ "Moving to polling mode: " ++ msg
275
  let inotiaction = addNotifier inotify path cref mstate
276
  _ <- forkIO $ onReloadTimer inotiaction path cref mstate
277
  return initialPoll
278

    
279
-- | Helper function for logging transition into inotify mode.
280
moveToNotify :: IO ReloadModel
281
moveToNotify = do
282
  logInfo "Moving to inotify mode"
283
  return ReloadNotify
284

    
285
-- ** Configuration loading
286

    
287
-- | (Re)loads the configuration.
288
updateConfig :: FilePath -> CRef -> IO ()
289
updateConfig path r = do
290
  newcfg <- loadConfig path
291
  let !newdata = case newcfg of
292
                   Ok !cfg -> Ok (cfg, buildLinkIpInstnameMap cfg)
293
                   Bad _ -> Bad "Cannot load configuration"
294
  writeIORef r newdata
295
  case newcfg of
296
    Ok cfg -> logInfo ("Loaded new config, serial " ++
297
                       show (configSerial cfg))
298
    Bad msg -> logError $ "Failed to load config: " ++ msg
299
  return ()
300

    
301
-- | Wrapper over 'updateConfig' that handles IO errors.
302
safeUpdateConfig :: FilePath -> FStat -> CRef -> IO (FStat, ConfigReload)
303
safeUpdateConfig path oldfstat cref =
304
  Control.Exception.catch
305
        (do
306
          nt <- needsReload oldfstat path
307
          case nt of
308
            Nothing -> return (oldfstat, ConfigToDate)
309
            Just nt' -> do
310
                    updateConfig path cref
311
                    return (nt', ConfigReloaded)
312
        ) (\e -> do
313
             let msg = "Failure during configuration update: " ++
314
                       show (e::IOError)
315
             writeIORef cref (Bad msg)
316
             return (nullFStat, ConfigIOError)
317
          )
318

    
319
-- | Computes the file cache data from a FileStatus structure.
320
buildFileStatus :: FileStatus -> FStat
321
buildFileStatus ofs =
322
    let modt = modificationTime ofs
323
        inum = fileID ofs
324
        fsize = fileSize ofs
325
    in (modt, inum, fsize)
326

    
327
-- | Wrapper over 'buildFileStatus'. This reads the data from the
328
-- filesystem and then builds our cache structure.
329
getFStat :: FilePath -> IO FStat
330
getFStat p = liftM buildFileStatus (getFileStatus p)
331

    
332
-- | Check if the file needs reloading
333
needsReload :: FStat -> FilePath -> IO (Maybe FStat)
334
needsReload oldstat path = do
335
  newstat <- getFStat path
336
  return $ if newstat /= oldstat
337
             then Just newstat
338
             else Nothing
339

    
340
-- ** Watcher threads
341

    
342
-- $watcher
343
-- We have three threads/functions that can mutate the server state:
344
--
345
-- 1. the long-interval watcher ('onTimeoutTimer')
346
--
347
-- 2. the polling watcher ('onReloadTimer')
348
--
349
-- 3. the inotify event handler ('onInotify')
350
--
351
-- All of these will mutate the server state under 'modifyMVar' or
352
-- 'modifyMVar_', so that server transitions are more or less
353
-- atomic. The inotify handler remains active during polling mode, but
354
-- checks for polling mode and doesn't do anything in this case (this
355
-- check is needed even if we would unregister the event handler due
356
-- to how events are serialised).
357

    
358
-- | Long-interval reload watcher.
359
--
360
-- This is on top of the inotify-based triggered reload.
361
onTimeoutTimer :: IO Bool -> FilePath -> CRef -> MVar ServerState -> IO ()
362
onTimeoutTimer inotiaction path cref state = do
363
  threadDelay configReloadTimeout
364
  modifyMVar_ state (onTimeoutInner path cref)
365
  _ <- inotiaction
366
  onTimeoutTimer inotiaction path cref state
367

    
368
-- | Inner onTimeout handler.
369
--
370
-- This mutates the server state under a modifyMVar_ call. It never
371
-- changes the reload model, just does a safety reload and tried to
372
-- re-establish the inotify watcher.
373
onTimeoutInner :: FilePath -> CRef -> ServerState -> IO ServerState
374
onTimeoutInner path cref state  = do
375
  (newfstat, _) <- safeUpdateConfig path (reloadFStat state) cref
376
  return state { reloadFStat = newfstat }
377

    
378
-- | Short-interval (polling) reload watcher.
379
--
380
-- This is only active when we're in polling mode; it will
381
-- automatically exit when it detects that the state has changed to
382
-- notification.
383
onReloadTimer :: IO Bool -> FilePath -> CRef -> MVar ServerState -> IO ()
384
onReloadTimer inotiaction path cref state = do
385
  continue <- modifyMVar state (onReloadInner inotiaction path cref)
386
  when continue $
387
    do threadDelay configReloadRatelimit
388
       onReloadTimer inotiaction path cref state
389
  -- the inotify watch has been re-established, we can exit
390

    
391
-- | Inner onReload handler.
392
--
393
-- This again mutates the state under a modifyMVar call, and also
394
-- returns whether the thread should continue or not.
395
onReloadInner :: IO Bool -> FilePath -> CRef -> ServerState
396
              -> IO (ServerState, Bool)
397
onReloadInner _ _ _ state@(ServerState { reloadModel = ReloadNotify } ) =
398
  return (state, False)
399
onReloadInner inotiaction path cref
400
              state@(ServerState { reloadModel = ReloadPoll pround } ) = do
401
  (newfstat, reload) <- safeUpdateConfig path (reloadFStat state) cref
402
  let state' = state { reloadFStat = newfstat }
403
  -- compute new poll model based on reload data; however, failure to
404
  -- re-establish the inotifier means we stay on polling
405
  newmode <- case reload of
406
               ConfigToDate ->
407
                 if pround >= maxIdlePollRounds
408
                   then do -- try to switch to notify
409
                     result <- inotiaction
410
                     if result
411
                       then moveToNotify
412
                       else return initialPoll
413
                   else return (ReloadPoll (pround + 1))
414
               _ -> return initialPoll
415
  let continue = case newmode of
416
                   ReloadNotify -> False
417
                   _            -> True
418
  return (state' { reloadModel = newmode }, continue)
419

    
420
-- the following hint is because hlint doesn't understand our const
421
-- (return False) is so that we can give a signature to 'e'
422
{-# ANN addNotifier "HLint: ignore Evaluate" #-}
423
-- | Setup inotify watcher.
424
--
425
-- This tries to setup the watch descriptor; in case of any IO errors,
426
-- it will return False.
427
addNotifier :: INotify -> FilePath -> CRef -> MVar ServerState -> IO Bool
428
addNotifier inotify path cref mstate =
429
  Control.Exception.catch
430
        (addWatch inotify [CloseWrite] path
431
                    (onInotify inotify path cref mstate) >> return True)
432
        (\e -> const (return False) (e::IOError))
433

    
434
-- | Inotify event handler.
435
onInotify :: INotify -> String -> CRef -> MVar ServerState -> Event -> IO ()
436
onInotify inotify path cref mstate Ignored = do
437
  logInfo "File lost, trying to re-establish notifier"
438
  modifyMVar_ mstate $ \state -> do
439
    result <- addNotifier inotify path cref mstate
440
    (newfstat, _) <- safeUpdateConfig path (reloadFStat state) cref
441
    let state' = state { reloadFStat = newfstat }
442
    if result
443
      then return state' -- keep notify
444
      else do
445
        mode <- moveToPolling "cannot re-establish inotify watch" inotify
446
                  path cref mstate
447
        return state' { reloadModel = mode }
448

    
449
onInotify inotify path cref mstate _ =
450
  modifyMVar_ mstate $ \state ->
451
    if reloadModel state == ReloadNotify
452
       then do
453
         ctime <- getCurrentTime
454
         (newfstat, _) <- safeUpdateConfig path (reloadFStat state) cref
455
         let state' = state { reloadFStat = newfstat, reloadTime = ctime }
456
         if abs (reloadTime state - ctime) < reloadRatelimitSec
457
           then do
458
             mode <- moveToPolling "too many reloads" inotify path cref mstate
459
             return state' { reloadModel = mode }
460
           else return state'
461
      else return state
462

    
463
-- ** Client input/output handlers
464

    
465
-- | Main loop for a given client.
466
responder :: CRef -> S.Socket -> HashKey -> String -> S.SockAddr -> IO ()
467
responder cfgref socket hmac msg peer = do
468
  ctime <- getCurrentTime
469
  case parseMessage hmac msg ctime of
470
    Ok (origmsg, rq) -> do
471
              logDebug $ "Processing request: " ++ rStripSpace origmsg
472
              mcfg <- readIORef cfgref
473
              let response = respondInner mcfg hmac rq
474
              _ <- S.sendTo socket response peer
475
              return ()
476
    Bad err -> logInfo $ "Failed to parse incoming message: " ++ err
477
  return ()
478

    
479
-- | Inner helper function for a given client. This generates the
480
-- final encoded message (as a string), ready to be sent out to the
481
-- client.
482
respondInner :: Result (ConfigData, LinkIpMap) -> HashKey
483
             -> ConfdRequest -> String
484
respondInner cfg hmac rq =
485
  let rsalt = confdRqRsalt rq
486
      innermsg = serializeResponse (cfg >>= flip buildResponse rq)
487
      innerserialised = J.encodeStrict innermsg
488
      outermsg = signMessage hmac rsalt innerserialised
489
      outerserialised = confdMagicFourcc ++ J.encodeStrict outermsg
490
  in outerserialised
491

    
492
-- | Main listener loop.
493
listener :: S.Socket -> HashKey
494
         -> (S.Socket -> HashKey -> String -> S.SockAddr -> IO ())
495
         -> IO ()
496
listener s hmac resp = do
497
  (msg, _, peer) <- S.recvFrom s 4096
498
  if confdMagicFourcc `isPrefixOf` msg
499
    then forkIO (resp s hmac (drop 4 msg) peer) >> return ()
500
    else logDebug "Invalid magic code!" >> return ()
501
  return ()
502

    
503
-- | Extract the configuration from our IORef.
504
configReader :: CRef -> IO (Result ConfigData)
505
configReader cref = do
506
  cdata <- readIORef cref
507
  return $ liftM fst cdata
508

    
509
-- | Type alias for prepMain results
510
type PrepResult = (S.Socket, (FilePath, S.Socket),
511
                   IORef (Result (ConfigData, LinkIpMap)))
512

    
513
-- | Check function for confd.
514
checkMain :: CheckFn (S.Family, S.SockAddr)
515
checkMain opts = do
516
  parseresult <- parseAddress opts C.defaultConfdPort
517
  case parseresult of
518
    Bad msg -> do
519
      hPutStrLn stderr $ "parsing bind address: " ++ msg
520
      return . Left $ ExitFailure 1
521
    Ok v -> return $ Right v
522

    
523
-- | Prepare function for confd.
524
prepMain :: PrepFn (S.Family, S.SockAddr) PrepResult
525
prepMain _ (af_family, bindaddr) = do
526
  s <- S.socket af_family S.Datagram S.defaultProtocol
527
  S.bindSocket s bindaddr
528
  -- prepare the queryd listener
529
  query_data <- prepQueryD Nothing
530
  cref <- newIORef (Bad "Configuration not yet loaded")
531
  return (s, query_data, cref)
532

    
533
-- | Main function.
534
main :: MainFn (S.Family, S.SockAddr) PrepResult
535
main _ _ (s, query_data, cref) = do
536
  statemvar <- newMVar initialState
537
  hmac <- getClusterHmac
538
  -- Inotify setup
539
  inotify <- initINotify
540
  conf_file <- Path.clusterConfFile
541
  let inotiaction = addNotifier inotify conf_file cref statemvar
542
  -- fork the timeout timer
543
  _ <- forkIO $ onTimeoutTimer inotiaction conf_file cref statemvar
544
  -- fork the polling timer
545
  _ <- forkIO $ onReloadTimer inotiaction conf_file cref statemvar
546
  -- launch the queryd listener
547
  _ <- forkIO $ runQueryD query_data (configReader cref)
548
  -- and finally enter the responder loop
549
  forever $ listener s hmac (responder cref)