Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (19.6 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
  ) where
31

    
32
import Control.Concurrent
33
import Control.Exception
34
import Control.Monad (forever)
35
import qualified Data.ByteString as B
36
import Data.IORef
37
import Data.List
38
import qualified Data.Map as M
39
import qualified Network.Socket as S
40
import System.Posix.Files
41
import System.Posix.Types
42
import System.Time
43
import qualified Text.JSON as J
44
import System.INotify
45

    
46
import Ganeti.Daemon
47
import Ganeti.HTools.JSON
48
import Ganeti.HTools.Types
49
import Ganeti.HTools.Utils
50
import Ganeti.Objects
51
import Ganeti.Confd
52
import Ganeti.Config
53
import Ganeti.Hash
54
import Ganeti.Logging
55
import qualified Ganeti.Constants as C
56

    
57
-- * Types and constants definitions
58

    
59
-- | What we store as configuration.
60
type CRef = IORef (Result (ConfigData, LinkIpMap))
61

    
62
-- | File stat identifier.
63
type FStat = (EpochTime, FileID, FileOffset)
64

    
65
-- | Null 'FStat' value.
66
nullFStat :: FStat
67
nullFStat = (-1, -1, -1)
68

    
69
-- | A small type alias for readability.
70
type StatusAnswer = (ConfdReplyStatus, J.JSValue)
71

    
72
-- | Reload model data type.
73
data ReloadModel = ReloadNotify      -- ^ We are using notifications
74
                 | ReloadPoll Int    -- ^ We are using polling
75
                   deriving (Eq, Show)
76

    
77
-- | Server state data type.
78
data ServerState = ServerState
79
  { reloadModel  :: ReloadModel
80
  , reloadTime   :: Integer
81
  , reloadFStat  :: FStat
82
  }
83

    
84
-- | Maximum no-reload poll rounds before reverting to inotify.
85
maxIdlePollRounds :: Int
86
maxIdlePollRounds = 2
87

    
88
-- | Reload timeout in microseconds.
89
configReloadTimeout :: Int
90
configReloadTimeout = C.confdConfigReloadTimeout * 1000000
91

    
92
-- | Ratelimit timeout in microseconds.
93
configReloadRatelimit :: Int
94
configReloadRatelimit = C.confdConfigReloadRatelimit * 1000000
95

    
96
-- | Initial poll round.
97
initialPoll :: ReloadModel
98
initialPoll = ReloadPoll 0
99

    
100
-- | Initial server state.
101
initialState :: ServerState
102
initialState = ServerState initialPoll 0 nullFStat
103

    
104
-- | Reload status data type.
105
data ConfigReload = ConfigToDate    -- ^ No need to reload
106
                  | ConfigReloaded  -- ^ Configuration reloaded
107
                  | ConfigIOError   -- ^ Error during configuration reload
108

    
109
-- | Unknown entry standard response.
110
queryUnknownEntry :: StatusAnswer
111
queryUnknownEntry = (ReplyStatusError, J.showJSON ConfdErrorUnknownEntry)
112

    
113
{- not used yet
114
-- | Internal error standard response.
115
queryInternalError :: StatusAnswer
116
queryInternalError = (ReplyStatusError, J.showJSON ConfdErrorInternal)
117
-}
118

    
119
-- | Argument error standard response.
120
queryArgumentError :: StatusAnswer
121
queryArgumentError = (ReplyStatusError, J.showJSON ConfdErrorArgument)
122

    
123
-- | Returns the current time.
124
getCurrentTime :: IO Integer
125
getCurrentTime = do
126
  TOD ctime _ <- getClockTime
127
  return ctime
128

    
129
-- * Confd base functionality
130

    
131
-- | Returns the HMAC key.
132
getClusterHmac :: IO HashKey
133
getClusterHmac = fmap B.unpack $ B.readFile C.confdHmacKey
134

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

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

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

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

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

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

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

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

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

    
226
buildResponse _ (ConfdRequest { confdRqType = ReqNodePipByInstPip }) =
227
  return queryArgumentError
228

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

    
242
-- | Parses a signed request.
243
parseRequest :: HashKey -> String -> Result (String, String, ConfdRequest)
244
parseRequest key str = do
245
  (SignedMessage hmac msg salt) <- fromJResult "parsing request" $ J.decode str
246
  req <- if verifyMac key (Just salt) msg hmac
247
           then fromJResult "parsing message" $ J.decode msg
248
           else Bad "HMAC verification failed"
249
  return (salt, msg, req)
250

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

    
262
-- | Signs a message with a given key and salt.
263
signMessage :: HashKey -> String -> String -> SignedMessage
264
signMessage key salt msg =
265
  SignedMessage { signedMsgMsg  = msg
266
                , signedMsgSalt = salt
267
                , signedMsgHmac = hmac
268
                }
269
    where hmac = computeMac key (Just salt) msg
270

    
271
-- * Configuration handling
272

    
273
-- ** Helper functions
274

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

    
284
-- | Helper function for logging transition into inotify mode.
285
moveToNotify :: IO ReloadModel
286
moveToNotify = do
287
  logInfo "Moving to inotify mode"
288
  return ReloadNotify
289

    
290
-- ** Configuration loading
291

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

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

    
324
-- | Computes the file cache data from a FileStatus structure.
325
buildFileStatus :: FileStatus -> FStat
326
buildFileStatus ofs =
327
    let modt = modificationTime ofs
328
        inum = fileID ofs
329
        fsize = fileSize ofs
330
    in (modt, inum, fsize)
331

    
332
-- | Wrapper over 'buildFileStatus'. This reads the data from the
333
-- filesystem and then builds our cache structure.
334
getFStat :: FilePath -> IO FStat
335
getFStat p = getFileStatus p >>= (return . buildFileStatus)
336

    
337
-- | Check if the file needs reloading
338
needsReload :: FStat -> FilePath -> IO (Maybe FStat)
339
needsReload oldstat path = do
340
  newstat <- getFStat path
341
  return $ if newstat /= oldstat
342
             then Just newstat
343
             else Nothing
344

    
345
-- ** Watcher threads
346

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

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

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

    
383
-- | Short-interval (polling) reload watcher.
384
--
385
-- This is only active when we're in polling mode; it will
386
-- automatically exit when it detects that the state has changed to
387
-- notification.
388
onReloadTimer :: IO Bool -> FilePath -> CRef -> MVar ServerState -> IO ()
389
onReloadTimer inotiaction path cref state = do
390
  continue <- modifyMVar state (onReloadInner inotiaction path cref)
391
  if continue
392
    then do
393
      threadDelay configReloadRatelimit
394
      onReloadTimer inotiaction path cref state
395
    else -- the inotify watch has been re-established, we can exit
396
      return ()
397

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

    
427
-- | Setup inotify watcher.
428
--
429
-- This tries to setup the watch descriptor; in case of any IO errors,
430
-- it will return False.
431
addNotifier :: INotify -> FilePath -> CRef -> MVar ServerState -> IO Bool
432
addNotifier inotify path cref mstate = do
433
  Control.Exception.catch
434
        (addWatch inotify [CloseWrite] path
435
                    (onInotify inotify path cref mstate) >> return True)
436
        (\e -> const (return False) (e::IOError))
437

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

    
453
onInotify inotify path cref mstate _ = do
454
  modifyMVar_ mstate $ \state ->
455
    if (reloadModel state == ReloadNotify)
456
       then do
457
         ctime <- getCurrentTime
458
         (newfstat, _) <- safeUpdateConfig path (reloadFStat state) cref
459
         let state' = state { reloadFStat = newfstat, reloadTime = ctime }
460
         if abs (reloadTime state - ctime) <
461
            fromIntegral C.confdConfigReloadRatelimit
462
           then do
463
             mode <- moveToPolling "too many reloads" inotify path cref mstate
464
             return state' { reloadModel = mode }
465
           else return state'
466
      else return state
467

    
468
-- ** Client input/output handlers
469

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

    
484
-- | Mesage parsing. This can either result in a good, valid message,
485
-- or fail in the Result monad.
486
parseMessage :: HashKey -> String -> Integer
487
             -> Result (String, ConfdRequest)
488
parseMessage hmac msg curtime = do
489
  (salt, origmsg, request) <- parseRequest hmac msg
490
  ts <- tryRead "Parsing timestamp" salt::Result Integer
491
  if (abs (ts - curtime) > (fromIntegral C.confdMaxClockSkew))
492
    then fail "Too old/too new timestamp or clock skew"
493
    else return (origmsg, request)
494

    
495
-- | Inner helper function for a given client. This generates the
496
-- final encoded message (as a string), ready to be sent out to the
497
-- client.
498
respondInner :: Result (ConfigData, LinkIpMap) -> HashKey
499
             -> ConfdRequest -> String
500
respondInner cfg hmac rq =
501
  let rsalt = confdRqRsalt rq
502
      innermsg = serializeResponse (cfg >>= flip buildResponse rq)
503
      innerserialised = J.encodeStrict innermsg
504
      outermsg = signMessage hmac rsalt innerserialised
505
      outerserialised = confdMagicFourcc ++ J.encodeStrict outermsg
506
  in outerserialised
507

    
508
-- | Main listener loop.
509
listener :: S.Socket -> HashKey
510
         -> (S.Socket -> HashKey -> String -> S.SockAddr -> IO ())
511
         -> IO ()
512
listener s hmac resp = do
513
  (msg, _, peer) <- S.recvFrom s 4096
514
  if confdMagicFourcc `isPrefixOf` msg
515
    then (forkIO $ resp s hmac (drop 4 msg) peer) >> return ()
516
    else logDebug "Invalid magic code!" >> return ()
517
  return ()
518

    
519
-- | Main function.
520
main :: DaemonOptions -> IO ()
521
main opts = do
522
  parseresult <- parseAddress opts C.defaultConfdPort
523
  (af_family, bindaddr) <- exitIfBad "parsing bind address" parseresult
524
  s <- S.socket af_family S.Datagram S.defaultProtocol
525
  S.bindSocket s bindaddr
526
  cref <- newIORef (Bad "Configuration not yet loaded")
527
  statemvar <- newMVar initialState
528
  hmac <- getClusterHmac
529
  -- Inotify setup
530
  inotify <- initINotify
531
  let inotiaction = addNotifier inotify C.clusterConfFile cref statemvar
532
  -- fork the timeout timer
533
  _ <- forkIO $ onTimeoutTimer inotiaction C.clusterConfFile cref statemvar
534
  -- fork the polling timer
535
  _ <- forkIO $ onReloadTimer inotiaction C.clusterConfFile cref statemvar
536
  -- and finally enter the responder loop
537
  forever $ listener s hmac (responder cref)