Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Confd / Server.hs @ c62df702

History | View | Annotate | Download (20.2 kB)

1
{-# LANGUAGE BangPatterns #-}
2

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

    
5
-}
6

    
7
{-
8

    
9
Copyright (C) 2011, 2012, 2013 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, unless)
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 qualified Text.JSON as J
47
import System.INotify
48

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

    
64
-- * Types and constants definitions
65

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

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

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

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

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

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

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

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

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

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

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

    
111
-- | Reload status data type.
112
data ConfigReload = ConfigToDate    -- ^ No need to reload
113
                  | ConfigReloaded  -- ^ Configuration reloaded
114
                  | ConfigIOError   -- ^ Error during configuration reload
115
                    deriving (Eq)
116

    
117
-- | Unknown entry standard response.
118
queryUnknownEntry :: StatusAnswer
119
queryUnknownEntry = (ReplyStatusError, J.showJSON ConfdErrorUnknownEntry)
120

    
121
{- not used yet
122
-- | Internal error standard response.
123
queryInternalError :: StatusAnswer
124
queryInternalError = (ReplyStatusError, J.showJSON ConfdErrorInternal)
125
-}
126

    
127
-- | Argument error standard response.
128
queryArgumentError :: StatusAnswer
129
queryArgumentError = (ReplyStatusError, J.showJSON ConfdErrorArgument)
130

    
131
-- | Converter from specific error to a string format.
132
gntErrorToResult :: ErrorResult a -> Result a
133
gntErrorToResult (Bad err) = Bad (show err)
134
gntErrorToResult (Ok x) = Ok x
135

    
136
-- * Confd base functionality
137

    
138
-- | Computes the node role.
139
nodeRole :: ConfigData -> String -> Result ConfdNodeRole
140
nodeRole cfg name =
141
  let cmaster = clusterMasterNode . configCluster $ cfg
142
      mnode = M.lookup name . fromContainer . configNodes $ cfg
143
  in case mnode of
144
       Nothing -> Bad "Node not found"
145
       Just node | cmaster == name -> Ok NodeRoleMaster
146
                 | nodeDrained node -> Ok NodeRoleDrained
147
                 | nodeOffline node -> Ok NodeRoleOffline
148
                 | nodeMasterCandidate node -> Ok NodeRoleCandidate
149
       _ -> Ok NodeRoleRegular
150

    
151
-- | Does an instance ip -> instance -> primary node -> primary ip
152
-- transformation.
153
getNodePipByInstanceIp :: ConfigData
154
                       -> LinkIpMap
155
                       -> String
156
                       -> String
157
                       -> StatusAnswer
158
getNodePipByInstanceIp cfg linkipmap link instip =
159
  case M.lookup instip (M.findWithDefault M.empty link linkipmap) of
160
    Nothing -> queryUnknownEntry
161
    Just instname ->
162
      case getInstPrimaryNode cfg instname of
163
        Bad _ -> queryUnknownEntry -- either instance or node not found
164
        Ok node -> (ReplyStatusOk, J.showJSON (nodePrimaryIp node))
165

    
166
-- | Builds the response to a given query.
167
buildResponse :: (ConfigData, LinkIpMap) -> ConfdRequest -> Result StatusAnswer
168
buildResponse (cfg, _) (ConfdRequest { confdRqType = ReqPing }) =
169
  return (ReplyStatusOk, J.showJSON (configVersion cfg))
170

    
171
buildResponse cdata req@(ConfdRequest { confdRqType = ReqClusterMaster }) =
172
  case confdRqQuery req of
173
    EmptyQuery -> return (ReplyStatusOk, J.showJSON master_name)
174
    PlainQuery _ -> return queryArgumentError
175
    DictQuery reqq -> do
176
      mnode <- gntErrorToResult $ getNode cfg master_name
177
      let fvals = map (\field -> case field of
178
                                   ReqFieldName -> master_name
179
                                   ReqFieldIp -> clusterMasterIp cluster
180
                                   ReqFieldMNodePip -> nodePrimaryIp mnode
181
                      ) (confdReqQFields reqq)
182
      return (ReplyStatusOk, J.showJSON fvals)
183
    where master_name = clusterMasterNode cluster
184
          cluster = configCluster cfg
185
          cfg = fst cdata
186

    
187
buildResponse cdata req@(ConfdRequest { confdRqType = ReqNodeRoleByName }) = do
188
  node_name <- case confdRqQuery req of
189
                 PlainQuery str -> return str
190
                 _ -> fail $ "Invalid query type " ++ show (confdRqQuery req)
191
  role <- nodeRole (fst cdata) node_name
192
  return (ReplyStatusOk, J.showJSON role)
193

    
194
buildResponse cdata (ConfdRequest { confdRqType = ReqNodePipList }) =
195
  -- note: we use foldlWithKey because that's present accross more
196
  -- versions of the library
197
  return (ReplyStatusOk, J.showJSON $
198
          M.foldlWithKey (\accu _ n -> nodePrimaryIp n:accu) []
199
          (fromContainer . configNodes . fst $ cdata))
200

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

    
210
buildResponse (cfg, linkipmap)
211
              req@(ConfdRequest { confdRqType = ReqInstIpsList }) = do
212
  link <- case confdRqQuery req of
213
            PlainQuery str -> return str
214
            EmptyQuery -> return (getDefaultNicLink cfg)
215
            _ -> fail "Invalid query type"
216
  return (ReplyStatusOk, J.showJSON $ getInstancesIpByLink linkipmap link)
217

    
218
buildResponse cdata (ConfdRequest { confdRqType = ReqNodePipByInstPip
219
                                  , confdRqQuery = DictQuery query}) =
220
  let (cfg, linkipmap) = cdata
221
      link = fromMaybe (getDefaultNicLink cfg) (confdReqQLink query)
222
  in case confdReqQIp query of
223
       Just ip -> return $ getNodePipByInstanceIp cfg linkipmap link ip
224
       Nothing -> return (ReplyStatusOk,
225
                          J.showJSON $
226
                           map (getNodePipByInstanceIp cfg linkipmap link)
227
                           (confdReqQIpList query))
228

    
229
buildResponse _ (ConfdRequest { confdRqType = ReqNodePipByInstPip }) =
230
  return queryArgumentError
231

    
232
buildResponse cdata req@(ConfdRequest { confdRqType = ReqNodeDrbd }) = do
233
  let cfg = fst cdata
234
  node_name <- case confdRqQuery req of
235
                 PlainQuery str -> return str
236
                 _ -> fail $ "Invalid query type " ++ show (confdRqQuery req)
237
  node <- gntErrorToResult $ getNode cfg node_name
238
  let minors = concatMap (getInstMinorsForNode (nodeName node)) .
239
               M.elems . fromContainer . configInstances $ cfg
240
      encoded = [J.JSArray [J.showJSON a, J.showJSON b, J.showJSON c,
241
                             J.showJSON d, J.showJSON e, J.showJSON f] |
242
                 (a, b, c, d, e, f) <- minors]
243
  return (ReplyStatusOk, J.showJSON encoded)
244

    
245
-- | Creates a ConfdReply from a given answer.
246
serializeResponse :: Result StatusAnswer -> ConfdReply
247
serializeResponse r =
248
    let (status, result) = case r of
249
                    Bad err -> (ReplyStatusError, J.showJSON err)
250
                    Ok (code, val) -> (code, val)
251
    in ConfdReply { confdReplyProtocol = 1
252
                  , confdReplyStatus   = status
253
                  , confdReplyAnswer   = result
254
                  , confdReplySerial   = 0 }
255

    
256
-- * Configuration handling
257

    
258
-- ** Helper functions
259

    
260
-- | Helper function for logging transition into polling mode.
261
moveToPolling :: String -> INotify -> FilePath -> CRef -> MVar ServerState
262
              -> IO ReloadModel
263
moveToPolling msg inotify path cref mstate = do
264
  logInfo $ "Moving to polling mode: " ++ msg
265
  let inotiaction = addNotifier inotify path cref mstate
266
  _ <- forkIO $ onReloadTimer inotiaction path cref mstate
267
  return initialPoll
268

    
269
-- | Helper function for logging transition into inotify mode.
270
moveToNotify :: IO ReloadModel
271
moveToNotify = do
272
  logInfo "Moving to inotify mode"
273
  return ReloadNotify
274

    
275
-- ** Configuration loading
276

    
277
-- | (Re)loads the configuration.
278
updateConfig :: FilePath -> CRef -> IO ()
279
updateConfig path r = do
280
  newcfg <- loadConfig path
281
  let !newdata = case newcfg of
282
                   Ok !cfg -> Ok (cfg, buildLinkIpInstnameMap cfg)
283
                   Bad _ -> Bad "Cannot load configuration"
284
  writeIORef r newdata
285
  case newcfg of
286
    Ok cfg -> logInfo ("Loaded new config, serial " ++
287
                       show (configSerial cfg))
288
    Bad msg -> logError $ "Failed to load config: " ++ msg
289
  return ()
290

    
291
-- | Wrapper over 'updateConfig' that handles IO errors.
292
safeUpdateConfig :: FilePath -> FStat -> CRef -> IO (FStat, ConfigReload)
293
safeUpdateConfig path oldfstat cref =
294
  Control.Exception.catch
295
        (do
296
          nt <- needsReload oldfstat path
297
          case nt of
298
            Nothing -> return (oldfstat, ConfigToDate)
299
            Just nt' -> do
300
                    updateConfig path cref
301
                    return (nt', ConfigReloaded)
302
        ) (\e -> do
303
             let msg = "Failure during configuration update: " ++
304
                       show (e::IOError)
305
             writeIORef cref (Bad msg)
306
             return (nullFStat, ConfigIOError)
307
          )
308

    
309
-- | Computes the file cache data from a FileStatus structure.
310
buildFileStatus :: FileStatus -> FStat
311
buildFileStatus ofs =
312
    let modt = modificationTime ofs
313
        inum = fileID ofs
314
        fsize = fileSize ofs
315
    in (modt, inum, fsize)
316

    
317
-- | Wrapper over 'buildFileStatus'. This reads the data from the
318
-- filesystem and then builds our cache structure.
319
getFStat :: FilePath -> IO FStat
320
getFStat p = liftM buildFileStatus (getFileStatus p)
321

    
322
-- | Check if the file needs reloading
323
needsReload :: FStat -> FilePath -> IO (Maybe FStat)
324
needsReload oldstat path = do
325
  newstat <- getFStat path
326
  return $ if newstat /= oldstat
327
             then Just newstat
328
             else Nothing
329

    
330
-- ** Watcher threads
331

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

    
348
-- | Long-interval reload watcher.
349
--
350
-- This is on top of the inotify-based triggered reload.
351
onTimeoutTimer :: IO Bool -> FilePath -> CRef -> MVar ServerState -> IO ()
352
onTimeoutTimer inotiaction path cref state = do
353
  threadDelay configReloadTimeout
354
  modifyMVar_ state (onTimeoutInner path cref)
355
  _ <- inotiaction
356
  onTimeoutTimer inotiaction path cref state
357

    
358
-- | Inner onTimeout handler.
359
--
360
-- This mutates the server state under a modifyMVar_ call. It never
361
-- changes the reload model, just does a safety reload and tried to
362
-- re-establish the inotify watcher.
363
onTimeoutInner :: FilePath -> CRef -> ServerState -> IO ServerState
364
onTimeoutInner path cref state  = do
365
  (newfstat, _) <- safeUpdateConfig path (reloadFStat state) cref
366
  return state { reloadFStat = newfstat }
367

    
368
-- | Short-interval (polling) reload watcher.
369
--
370
-- This is only active when we're in polling mode; it will
371
-- automatically exit when it detects that the state has changed to
372
-- notification.
373
onReloadTimer :: IO Bool -> FilePath -> CRef -> MVar ServerState -> IO ()
374
onReloadTimer inotiaction path cref state = do
375
  continue <- modifyMVar state (onReloadInner inotiaction path cref)
376
  when continue $
377
    do threadDelay configReloadRatelimit
378
       onReloadTimer inotiaction path cref state
379
  -- the inotify watch has been re-established, we can exit
380

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

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

    
424
-- | Inotify event handler.
425
onInotify :: INotify -> String -> CRef -> MVar ServerState -> Event -> IO ()
426
onInotify inotify path cref mstate Ignored = do
427
  logDebug "File lost, trying to re-establish notifier"
428
  modifyMVar_ mstate $ \state -> do
429
    result <- addNotifier inotify path cref mstate
430
    (newfstat, _) <- safeUpdateConfig path (reloadFStat state) cref
431
    let state' = state { reloadFStat = newfstat }
432
    if result
433
      then return state' -- keep notify
434
      else do
435
        mode <- moveToPolling "cannot re-establish inotify watch" inotify
436
                  path cref mstate
437
        return state' { reloadModel = mode }
438

    
439
onInotify inotify path cref mstate _ =
440
  modifyMVar_ mstate $ \state ->
441
    if reloadModel state == ReloadNotify
442
       then do
443
         ctime <- getCurrentTime
444
         (newfstat, _) <- safeUpdateConfig path (reloadFStat state) cref
445
         let state' = state { reloadFStat = newfstat, reloadTime = ctime }
446
         if abs (reloadTime state - ctime) < reloadRatelimitSec
447
           then do
448
             mode <- moveToPolling "too many reloads" inotify path cref mstate
449
             return state' { reloadModel = mode }
450
           else return state'
451
      else return state
452

    
453
-- ** Client input/output handlers
454

    
455
-- | Main loop for a given client.
456
responder :: CRef -> S.Socket -> HashKey -> String -> S.SockAddr -> IO ()
457
responder cfgref socket hmac msg peer = do
458
  ctime <- getCurrentTime
459
  case parseRequest hmac msg ctime of
460
    Ok (origmsg, rq) -> do
461
              logDebug $ "Processing request: " ++ rStripSpace origmsg
462
              mcfg <- readIORef cfgref
463
              let response = respondInner mcfg hmac rq
464
              _ <- S.sendTo socket response peer
465
              return ()
466
    Bad err -> logInfo $ "Failed to parse incoming message: " ++ err
467
  return ()
468

    
469
-- | Inner helper function for a given client. This generates the
470
-- final encoded message (as a string), ready to be sent out to the
471
-- client.
472
respondInner :: Result (ConfigData, LinkIpMap) -> HashKey
473
             -> ConfdRequest -> String
474
respondInner cfg hmac rq =
475
  let rsalt = confdRqRsalt rq
476
      innermsg = serializeResponse (cfg >>= flip buildResponse rq)
477
      innerserialised = J.encodeStrict innermsg
478
      outermsg = signMessage hmac rsalt innerserialised
479
      outerserialised = confdMagicFourcc ++ J.encodeStrict outermsg
480
  in outerserialised
481

    
482
-- | Main listener loop.
483
listener :: S.Socket -> HashKey
484
         -> (S.Socket -> HashKey -> String -> S.SockAddr -> IO ())
485
         -> IO ()
486
listener s hmac resp = do
487
  (msg, _, peer) <- S.recvFrom s 4096
488
  if confdMagicFourcc `isPrefixOf` msg
489
    then forkIO (resp s hmac (drop 4 msg) peer) >> return ()
490
    else logDebug "Invalid magic code!" >> return ()
491
  return ()
492

    
493
-- | Extract the configuration from our IORef.
494
configReader :: CRef -> IO (Result ConfigData)
495
configReader cref = do
496
  cdata <- readIORef cref
497
  return $ liftM fst cdata
498

    
499
-- | Type alias for prepMain results
500
type PrepResult = (S.Socket, (FilePath, S.Socket),
501
                   IORef (Result (ConfigData, LinkIpMap)))
502

    
503
-- | Check function for confd.
504
checkMain :: CheckFn (S.Family, S.SockAddr)
505
checkMain opts = do
506
  parseresult <- parseAddress opts C.defaultConfdPort
507
  case parseresult of
508
    Bad msg -> do
509
      hPutStrLn stderr $ "parsing bind address: " ++ msg
510
      return . Left $ ExitFailure 1
511
    Ok v -> return $ Right v
512

    
513
-- | Prepare function for confd.
514
prepMain :: PrepFn (S.Family, S.SockAddr) PrepResult
515
prepMain _ (af_family, bindaddr) = do
516
  s <- S.socket af_family S.Datagram S.defaultProtocol
517
  S.bindSocket s bindaddr
518
  -- prepare the queryd listener
519
  query_data <- prepQueryD Nothing
520
  cref <- newIORef (Bad "Configuration not yet loaded")
521
  return (s, query_data, cref)
522

    
523
-- | Main function.
524
main :: MainFn (S.Family, S.SockAddr) PrepResult
525
main _ _ (s, query_data, cref) = do
526
  -- Inotify setup
527
  inotify <- initINotify
528
  -- try to load the configuration, if possible
529
  conf_file <- Path.clusterConfFile
530
  (fstat, reloaded) <- safeUpdateConfig conf_file nullFStat cref
531
  ctime <- getCurrentTime
532
  statemvar <- newMVar $ ServerState ReloadNotify ctime fstat
533
  let inotiaction = addNotifier inotify conf_file cref statemvar
534
  has_inotify <- if reloaded == ConfigReloaded
535
                   then inotiaction
536
                   else return False
537
  if has_inotify
538
    then logInfo "Starting up in inotify mode"
539
    else do
540
      -- inotify was not enabled, we need to update the reload model
541
      logInfo "Starting up in polling mode"
542
      modifyMVar_ statemvar
543
        (\state -> return state { reloadModel = initialPoll })
544
  hmac <- getClusterHmac
545
  -- fork the timeout timer
546
  _ <- forkIO $ onTimeoutTimer inotiaction conf_file cref statemvar
547
  -- fork the polling timer
548
  unless has_inotify $ do
549
    _ <- forkIO $ onReloadTimer inotiaction conf_file cref statemvar
550
    return ()
551
  -- launch the queryd listener
552
  _ <- forkIO $ runQueryD query_data (configReader cref)
553
  -- and finally enter the responder loop
554
  forever $ listener s hmac (responder cref)