Statistics
| Branch: | Tag: | Revision:

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

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 Prelude hiding (catch)
41
import System.Posix.Files
42
import System.Posix.Types
43
import System.Time
44
import qualified Text.JSON as J
45
import System.INotify
46

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

    
58
-- * Types and constants definitions
59

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
130
-- * Confd base functionality
131

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
272
-- * Configuration handling
273

    
274
-- ** Helper functions
275

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

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

    
291
-- ** Configuration loading
292

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

    
307
-- | Wrapper over 'updateConfig' that handles IO errors.
308
safeUpdateConfig :: FilePath -> FStat -> CRef -> IO (FStat, ConfigReload)
309
safeUpdateConfig path oldfstat cref = do
310
  catch (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
  catch (addWatch inotify [CloseWrite] path
434
                    (onInotify inotify path cref mstate) >> return True)
435
        (\e -> const (return False) (e::IOError))
436

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

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

    
467
-- ** Client input/output handlers
468

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

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

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

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

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