Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / ConfigReader.hs @ 218e3b0f

History | View | Annotate | Download (11.6 kB)

1
{-# LANGUAGE BangPatterns #-}
2

    
3
{-| Implementation of configuration reader with watching support.
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.ConfigReader
29
  ( ConfigReader
30
  , initConfigReader
31
  ) where
32

    
33
import Control.Concurrent
34
import Control.Exception
35
import Control.Monad (liftM, unless)
36
import Data.IORef
37
import System.Posix.Files
38
import System.Posix.Types
39
import System.INotify
40

    
41
import Ganeti.BasicTypes
42
import Ganeti.Objects
43
import Ganeti.Confd.Utils
44
import Ganeti.Config
45
import Ganeti.Logging
46
import qualified Ganeti.Constants as C
47
import qualified Ganeti.Path as Path
48
import Ganeti.Utils
49

    
50
-- | A type for functions that can return the configuration when
51
-- executed.
52
type ConfigReader = IO (Result ConfigData)
53

    
54
-- | File stat identifier.
55
type FStat = (EpochTime, FileID, FileOffset)
56

    
57
-- | Null 'FStat' value.
58
nullFStat :: FStat
59
nullFStat = (-1, -1, -1)
60

    
61
-- | Reload model data type.
62
data ReloadModel = ReloadNotify      -- ^ We are using notifications
63
                 | ReloadPoll Int    -- ^ We are using polling
64
                   deriving (Eq, Show)
65

    
66
-- | Server state data type.
67
data ServerState = ServerState
68
  { reloadModel  :: ReloadModel
69
  , reloadTime   :: Integer      -- ^ Reload time (epoch) in microseconds
70
  , reloadFStat  :: FStat
71
  }
72

    
73
-- | Maximum no-reload poll rounds before reverting to inotify.
74
maxIdlePollRounds :: Int
75
maxIdlePollRounds = 3
76

    
77
-- | Reload timeout in microseconds.
78
watchInterval :: Int
79
watchInterval = C.confdConfigReloadTimeout * 1000000
80

    
81
-- | Ratelimit timeout in microseconds.
82
pollInterval :: Int
83
pollInterval = C.confdConfigReloadRatelimit
84

    
85
-- | Ratelimit timeout in microseconds, as an 'Integer'.
86
reloadRatelimit :: Integer
87
reloadRatelimit = fromIntegral C.confdConfigReloadRatelimit
88

    
89
-- | Initial poll round.
90
initialPoll :: ReloadModel
91
initialPoll = ReloadPoll 0
92

    
93
-- | Reload status data type.
94
data ConfigReload = ConfigToDate    -- ^ No need to reload
95
                  | ConfigReloaded  -- ^ Configuration reloaded
96
                  | ConfigIOError   -- ^ Error during configuration reload
97
                    deriving (Eq)
98

    
99
-- * Configuration handling
100

    
101
-- ** Helper functions
102

    
103
-- | Helper function for logging transition into polling mode.
104
moveToPolling :: String -> INotify -> FilePath -> (Result ConfigData -> IO ())
105
              -> MVar ServerState -> IO ReloadModel
106
moveToPolling msg inotify path save_fn mstate = do
107
  logInfo $ "Moving to polling mode: " ++ msg
108
  let inotiaction = addNotifier inotify path save_fn mstate
109
  _ <- forkIO $ onPollTimer inotiaction path save_fn mstate
110
  return initialPoll
111

    
112
-- | Helper function for logging transition into inotify mode.
113
moveToNotify :: IO ReloadModel
114
moveToNotify = do
115
  logInfo "Moving to inotify mode"
116
  return ReloadNotify
117

    
118
-- ** Configuration loading
119

    
120
-- | (Re)loads the configuration.
121
updateConfig :: FilePath -> (Result ConfigData -> IO ()) -> IO ()
122
updateConfig path save_fn = do
123
  newcfg <- loadConfig path
124
  let !newdata = case newcfg of
125
                   Ok !cfg -> Ok cfg
126
                   Bad _ -> Bad "Cannot load configuration"
127
  save_fn newdata
128
  case newcfg of
129
    Ok cfg -> logInfo ("Loaded new config, serial " ++
130
                       show (configSerial cfg))
131
    Bad msg -> logError $ "Failed to load config: " ++ msg
132
  return ()
133

    
134
-- | Wrapper over 'updateConfig' that handles IO errors.
135
safeUpdateConfig :: FilePath -> FStat -> (Result ConfigData -> IO ())
136
                 -> IO (FStat, ConfigReload)
137
safeUpdateConfig path oldfstat save_fn =
138
  Control.Exception.catch
139
        (do
140
          nt <- needsReload oldfstat path
141
          case nt of
142
            Nothing -> return (oldfstat, ConfigToDate)
143
            Just nt' -> do
144
                    updateConfig path save_fn
145
                    return (nt', ConfigReloaded)
146
        ) (\e -> do
147
             let msg = "Failure during configuration update: " ++
148
                       show (e::IOError)
149
             save_fn $ Bad msg
150
             return (nullFStat, ConfigIOError)
151
          )
152

    
153
-- | Computes the file cache data from a FileStatus structure.
154
buildFileStatus :: FileStatus -> FStat
155
buildFileStatus ofs =
156
    let modt = modificationTime ofs
157
        inum = fileID ofs
158
        fsize = fileSize ofs
159
    in (modt, inum, fsize)
160

    
161
-- | Wrapper over 'buildFileStatus'. This reads the data from the
162
-- filesystem and then builds our cache structure.
163
getFStat :: FilePath -> IO FStat
164
getFStat p = liftM buildFileStatus (getFileStatus p)
165

    
166
-- | Check if the file needs reloading
167
needsReload :: FStat -> FilePath -> IO (Maybe FStat)
168
needsReload oldstat path = do
169
  newstat <- getFStat path
170
  return $ if newstat /= oldstat
171
             then Just newstat
172
             else Nothing
173

    
174
-- ** Watcher threads
175

    
176
-- $watcher
177
-- We have three threads/functions that can mutate the server state:
178
--
179
-- 1. the long-interval watcher ('onWatcherTimer')
180
--
181
-- 2. the polling watcher ('onPollTimer')
182
--
183
-- 3. the inotify event handler ('onInotify')
184
--
185
-- All of these will mutate the server state under 'modifyMVar' or
186
-- 'modifyMVar_', so that server transitions are more or less
187
-- atomic. The inotify handler remains active during polling mode, but
188
-- checks for polling mode and doesn't do anything in this case (this
189
-- check is needed even if we would unregister the event handler due
190
-- to how events are serialised).
191

    
192
-- | Long-interval reload watcher.
193
--
194
-- This is on top of the inotify-based triggered reload.
195
onWatcherTimer :: IO Bool -> FilePath -> (Result ConfigData -> IO ())
196
               -> MVar ServerState -> IO ()
197
onWatcherTimer inotiaction path save_fn state = do
198
  threadDelay watchInterval
199
  logDebug "Watcher timer fired"
200
  modifyMVar_ state (onWatcherInner path save_fn)
201
  _ <- inotiaction
202
  onWatcherTimer inotiaction path save_fn state
203

    
204
-- | Inner onWatcher handler.
205
--
206
-- This mutates the server state under a modifyMVar_ call. It never
207
-- changes the reload model, just does a safety reload and tried to
208
-- re-establish the inotify watcher.
209
onWatcherInner :: FilePath -> (Result ConfigData -> IO ()) -> ServerState
210
               -> IO ServerState
211
onWatcherInner path save_fn state  = do
212
  (newfstat, _) <- safeUpdateConfig path (reloadFStat state) save_fn
213
  return state { reloadFStat = newfstat }
214

    
215
-- | Short-interval (polling) reload watcher.
216
--
217
-- This is only active when we're in polling mode; it will
218
-- automatically exit when it detects that the state has changed to
219
-- notification.
220
onPollTimer :: IO Bool -> FilePath -> (Result ConfigData -> IO ())
221
            -> MVar ServerState -> IO ()
222
onPollTimer inotiaction path save_fn state = do
223
  threadDelay pollInterval
224
  logDebug "Poll timer fired"
225
  continue <- modifyMVar state (onPollInner inotiaction path save_fn)
226
  if continue
227
    then onPollTimer inotiaction path save_fn state
228
    else logDebug "Inotify watch active, polling thread exiting"
229

    
230
-- | Inner onPoll handler.
231
--
232
-- This again mutates the state under a modifyMVar call, and also
233
-- returns whether the thread should continue or not.
234
onPollInner :: IO Bool -> FilePath -> (Result ConfigData -> IO ())
235
            -> ServerState -> IO (ServerState, Bool)
236
onPollInner _ _ _ state@(ServerState { reloadModel = ReloadNotify } ) =
237
  return (state, False)
238
onPollInner inotiaction path save_fn
239
            state@(ServerState { reloadModel = ReloadPoll pround } ) = do
240
  (newfstat, reload) <- safeUpdateConfig path (reloadFStat state) save_fn
241
  let state' = state { reloadFStat = newfstat }
242
  -- compute new poll model based on reload data; however, failure to
243
  -- re-establish the inotifier means we stay on polling
244
  newmode <- case reload of
245
               ConfigToDate ->
246
                 if pround >= maxIdlePollRounds
247
                   then do -- try to switch to notify
248
                     result <- inotiaction
249
                     if result
250
                       then moveToNotify
251
                       else return initialPoll
252
                   else return (ReloadPoll (pround + 1))
253
               _ -> return initialPoll
254
  let continue = case newmode of
255
                   ReloadNotify -> False
256
                   _            -> True
257
  return (state' { reloadModel = newmode }, continue)
258

    
259
-- the following hint is because hlint doesn't understand our const
260
-- (return False) is so that we can give a signature to 'e'
261
{-# ANN addNotifier "HLint: ignore Evaluate" #-}
262
-- | Setup inotify watcher.
263
--
264
-- This tries to setup the watch descriptor; in case of any IO errors,
265
-- it will return False.
266
addNotifier :: INotify -> FilePath -> (Result ConfigData -> IO ())
267
            -> MVar ServerState -> IO Bool
268
addNotifier inotify path save_fn mstate =
269
  Control.Exception.catch
270
        (addWatch inotify [CloseWrite] path
271
            (onInotify inotify path save_fn mstate) >> return True)
272
        (\e -> const (return False) (e::IOError))
273

    
274
-- | Inotify event handler.
275
onInotify :: INotify -> String -> (Result ConfigData -> IO ())
276
          -> MVar ServerState -> Event -> IO ()
277
onInotify inotify path save_fn mstate Ignored = do
278
  logDebug "File lost, trying to re-establish notifier"
279
  modifyMVar_ mstate $ \state -> do
280
    result <- addNotifier inotify path save_fn mstate
281
    (newfstat, _) <- safeUpdateConfig path (reloadFStat state) save_fn
282
    let state' = state { reloadFStat = newfstat }
283
    if result
284
      then return state' -- keep notify
285
      else do
286
        mode <- moveToPolling "cannot re-establish inotify watch" inotify
287
                  path save_fn mstate
288
        return state' { reloadModel = mode }
289

    
290
onInotify inotify path save_fn mstate _ =
291
  modifyMVar_ mstate $ \state ->
292
    if reloadModel state == ReloadNotify
293
       then do
294
         ctime <- getCurrentTimeUSec
295
         (newfstat, _) <- safeUpdateConfig path (reloadFStat state) save_fn
296
         let state' = state { reloadFStat = newfstat, reloadTime = ctime }
297
         if abs (reloadTime state - ctime) < reloadRatelimit
298
           then do
299
             mode <- moveToPolling "too many reloads" inotify path save_fn
300
                                   mstate
301
             return state' { reloadModel = mode }
302
           else return state'
303
      else return state
304

    
305
initConfigReader :: (Result ConfigData -> a) -> IORef a -> IO ()
306
initConfigReader cfg_transform ioref = do
307
  let save_fn = writeIORef ioref . cfg_transform
308

    
309
  -- Inotify setup
310
  inotify <- initINotify
311
  -- try to load the configuration, if possible
312
  conf_file <- Path.clusterConfFile
313
  (fstat, reloaded) <- safeUpdateConfig conf_file nullFStat save_fn
314
  ctime <- getCurrentTime
315
  statemvar <- newMVar $ ServerState ReloadNotify ctime fstat
316
  let inotiaction = addNotifier inotify conf_file save_fn statemvar
317
  has_inotify <- if reloaded == ConfigReloaded
318
                   then inotiaction
319
                   else return False
320
  if has_inotify
321
    then logInfo "Starting up in inotify mode"
322
    else do
323
      -- inotify was not enabled, we need to update the reload model
324
      logInfo "Starting up in polling mode"
325
      modifyMVar_ statemvar
326
        (\state -> return state { reloadModel = initialPoll })
327
  -- fork the timeout timer
328
  _ <- forkIO $ onWatcherTimer inotiaction conf_file save_fn statemvar
329
  -- fork the polling timer
330
  unless has_inotify $ do
331
    _ <- forkIO $ onPollTimer inotiaction conf_file save_fn statemvar
332
    return ()