Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (11.6 kB)

1 218e3b0f Thomas Thrainer
{-# LANGUAGE BangPatterns #-}
2 218e3b0f Thomas Thrainer
3 218e3b0f Thomas Thrainer
{-| Implementation of configuration reader with watching support.
4 218e3b0f Thomas Thrainer
5 218e3b0f Thomas Thrainer
-}
6 218e3b0f Thomas Thrainer
7 218e3b0f Thomas Thrainer
{-
8 218e3b0f Thomas Thrainer
9 218e3b0f Thomas Thrainer
Copyright (C) 2011, 2012, 2013 Google Inc.
10 218e3b0f Thomas Thrainer
11 218e3b0f Thomas Thrainer
This program is free software; you can redistribute it and/or modify
12 218e3b0f Thomas Thrainer
it under the terms of the GNU General Public License as published by
13 218e3b0f Thomas Thrainer
the Free Software Foundation; either version 2 of the License, or
14 218e3b0f Thomas Thrainer
(at your option) any later version.
15 218e3b0f Thomas Thrainer
16 218e3b0f Thomas Thrainer
This program is distributed in the hope that it will be useful, but
17 218e3b0f Thomas Thrainer
WITHOUT ANY WARRANTY; without even the implied warranty of
18 218e3b0f Thomas Thrainer
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 218e3b0f Thomas Thrainer
General Public License for more details.
20 218e3b0f Thomas Thrainer
21 218e3b0f Thomas Thrainer
You should have received a copy of the GNU General Public License
22 218e3b0f Thomas Thrainer
along with this program; if not, write to the Free Software
23 218e3b0f Thomas Thrainer
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 218e3b0f Thomas Thrainer
02110-1301, USA.
25 218e3b0f Thomas Thrainer
26 218e3b0f Thomas Thrainer
-}
27 218e3b0f Thomas Thrainer
28 218e3b0f Thomas Thrainer
module Ganeti.ConfigReader
29 218e3b0f Thomas Thrainer
  ( ConfigReader
30 218e3b0f Thomas Thrainer
  , initConfigReader
31 218e3b0f Thomas Thrainer
  ) where
32 218e3b0f Thomas Thrainer
33 218e3b0f Thomas Thrainer
import Control.Concurrent
34 218e3b0f Thomas Thrainer
import Control.Exception
35 218e3b0f Thomas Thrainer
import Control.Monad (liftM, unless)
36 218e3b0f Thomas Thrainer
import Data.IORef
37 218e3b0f Thomas Thrainer
import System.Posix.Files
38 218e3b0f Thomas Thrainer
import System.Posix.Types
39 218e3b0f Thomas Thrainer
import System.INotify
40 218e3b0f Thomas Thrainer
41 218e3b0f Thomas Thrainer
import Ganeti.BasicTypes
42 218e3b0f Thomas Thrainer
import Ganeti.Objects
43 218e3b0f Thomas Thrainer
import Ganeti.Confd.Utils
44 218e3b0f Thomas Thrainer
import Ganeti.Config
45 218e3b0f Thomas Thrainer
import Ganeti.Logging
46 218e3b0f Thomas Thrainer
import qualified Ganeti.Constants as C
47 218e3b0f Thomas Thrainer
import qualified Ganeti.Path as Path
48 218e3b0f Thomas Thrainer
import Ganeti.Utils
49 218e3b0f Thomas Thrainer
50 218e3b0f Thomas Thrainer
-- | A type for functions that can return the configuration when
51 218e3b0f Thomas Thrainer
-- executed.
52 218e3b0f Thomas Thrainer
type ConfigReader = IO (Result ConfigData)
53 218e3b0f Thomas Thrainer
54 218e3b0f Thomas Thrainer
-- | File stat identifier.
55 218e3b0f Thomas Thrainer
type FStat = (EpochTime, FileID, FileOffset)
56 218e3b0f Thomas Thrainer
57 218e3b0f Thomas Thrainer
-- | Null 'FStat' value.
58 218e3b0f Thomas Thrainer
nullFStat :: FStat
59 218e3b0f Thomas Thrainer
nullFStat = (-1, -1, -1)
60 218e3b0f Thomas Thrainer
61 218e3b0f Thomas Thrainer
-- | Reload model data type.
62 218e3b0f Thomas Thrainer
data ReloadModel = ReloadNotify      -- ^ We are using notifications
63 218e3b0f Thomas Thrainer
                 | ReloadPoll Int    -- ^ We are using polling
64 218e3b0f Thomas Thrainer
                   deriving (Eq, Show)
65 218e3b0f Thomas Thrainer
66 218e3b0f Thomas Thrainer
-- | Server state data type.
67 218e3b0f Thomas Thrainer
data ServerState = ServerState
68 218e3b0f Thomas Thrainer
  { reloadModel  :: ReloadModel
69 218e3b0f Thomas Thrainer
  , reloadTime   :: Integer      -- ^ Reload time (epoch) in microseconds
70 218e3b0f Thomas Thrainer
  , reloadFStat  :: FStat
71 218e3b0f Thomas Thrainer
  }
72 218e3b0f Thomas Thrainer
73 218e3b0f Thomas Thrainer
-- | Maximum no-reload poll rounds before reverting to inotify.
74 218e3b0f Thomas Thrainer
maxIdlePollRounds :: Int
75 218e3b0f Thomas Thrainer
maxIdlePollRounds = 3
76 218e3b0f Thomas Thrainer
77 218e3b0f Thomas Thrainer
-- | Reload timeout in microseconds.
78 218e3b0f Thomas Thrainer
watchInterval :: Int
79 218e3b0f Thomas Thrainer
watchInterval = C.confdConfigReloadTimeout * 1000000
80 218e3b0f Thomas Thrainer
81 218e3b0f Thomas Thrainer
-- | Ratelimit timeout in microseconds.
82 218e3b0f Thomas Thrainer
pollInterval :: Int
83 218e3b0f Thomas Thrainer
pollInterval = C.confdConfigReloadRatelimit
84 218e3b0f Thomas Thrainer
85 218e3b0f Thomas Thrainer
-- | Ratelimit timeout in microseconds, as an 'Integer'.
86 218e3b0f Thomas Thrainer
reloadRatelimit :: Integer
87 218e3b0f Thomas Thrainer
reloadRatelimit = fromIntegral C.confdConfigReloadRatelimit
88 218e3b0f Thomas Thrainer
89 218e3b0f Thomas Thrainer
-- | Initial poll round.
90 218e3b0f Thomas Thrainer
initialPoll :: ReloadModel
91 218e3b0f Thomas Thrainer
initialPoll = ReloadPoll 0
92 218e3b0f Thomas Thrainer
93 218e3b0f Thomas Thrainer
-- | Reload status data type.
94 218e3b0f Thomas Thrainer
data ConfigReload = ConfigToDate    -- ^ No need to reload
95 218e3b0f Thomas Thrainer
                  | ConfigReloaded  -- ^ Configuration reloaded
96 218e3b0f Thomas Thrainer
                  | ConfigIOError   -- ^ Error during configuration reload
97 218e3b0f Thomas Thrainer
                    deriving (Eq)
98 218e3b0f Thomas Thrainer
99 218e3b0f Thomas Thrainer
-- * Configuration handling
100 218e3b0f Thomas Thrainer
101 218e3b0f Thomas Thrainer
-- ** Helper functions
102 218e3b0f Thomas Thrainer
103 218e3b0f Thomas Thrainer
-- | Helper function for logging transition into polling mode.
104 218e3b0f Thomas Thrainer
moveToPolling :: String -> INotify -> FilePath -> (Result ConfigData -> IO ())
105 218e3b0f Thomas Thrainer
              -> MVar ServerState -> IO ReloadModel
106 218e3b0f Thomas Thrainer
moveToPolling msg inotify path save_fn mstate = do
107 218e3b0f Thomas Thrainer
  logInfo $ "Moving to polling mode: " ++ msg
108 218e3b0f Thomas Thrainer
  let inotiaction = addNotifier inotify path save_fn mstate
109 218e3b0f Thomas Thrainer
  _ <- forkIO $ onPollTimer inotiaction path save_fn mstate
110 218e3b0f Thomas Thrainer
  return initialPoll
111 218e3b0f Thomas Thrainer
112 218e3b0f Thomas Thrainer
-- | Helper function for logging transition into inotify mode.
113 218e3b0f Thomas Thrainer
moveToNotify :: IO ReloadModel
114 218e3b0f Thomas Thrainer
moveToNotify = do
115 218e3b0f Thomas Thrainer
  logInfo "Moving to inotify mode"
116 218e3b0f Thomas Thrainer
  return ReloadNotify
117 218e3b0f Thomas Thrainer
118 218e3b0f Thomas Thrainer
-- ** Configuration loading
119 218e3b0f Thomas Thrainer
120 218e3b0f Thomas Thrainer
-- | (Re)loads the configuration.
121 218e3b0f Thomas Thrainer
updateConfig :: FilePath -> (Result ConfigData -> IO ()) -> IO ()
122 218e3b0f Thomas Thrainer
updateConfig path save_fn = do
123 218e3b0f Thomas Thrainer
  newcfg <- loadConfig path
124 218e3b0f Thomas Thrainer
  let !newdata = case newcfg of
125 218e3b0f Thomas Thrainer
                   Ok !cfg -> Ok cfg
126 218e3b0f Thomas Thrainer
                   Bad _ -> Bad "Cannot load configuration"
127 218e3b0f Thomas Thrainer
  save_fn newdata
128 218e3b0f Thomas Thrainer
  case newcfg of
129 218e3b0f Thomas Thrainer
    Ok cfg -> logInfo ("Loaded new config, serial " ++
130 218e3b0f Thomas Thrainer
                       show (configSerial cfg))
131 218e3b0f Thomas Thrainer
    Bad msg -> logError $ "Failed to load config: " ++ msg
132 218e3b0f Thomas Thrainer
  return ()
133 218e3b0f Thomas Thrainer
134 218e3b0f Thomas Thrainer
-- | Wrapper over 'updateConfig' that handles IO errors.
135 218e3b0f Thomas Thrainer
safeUpdateConfig :: FilePath -> FStat -> (Result ConfigData -> IO ())
136 218e3b0f Thomas Thrainer
                 -> IO (FStat, ConfigReload)
137 218e3b0f Thomas Thrainer
safeUpdateConfig path oldfstat save_fn =
138 218e3b0f Thomas Thrainer
  Control.Exception.catch
139 218e3b0f Thomas Thrainer
        (do
140 218e3b0f Thomas Thrainer
          nt <- needsReload oldfstat path
141 218e3b0f Thomas Thrainer
          case nt of
142 218e3b0f Thomas Thrainer
            Nothing -> return (oldfstat, ConfigToDate)
143 218e3b0f Thomas Thrainer
            Just nt' -> do
144 218e3b0f Thomas Thrainer
                    updateConfig path save_fn
145 218e3b0f Thomas Thrainer
                    return (nt', ConfigReloaded)
146 218e3b0f Thomas Thrainer
        ) (\e -> do
147 218e3b0f Thomas Thrainer
             let msg = "Failure during configuration update: " ++
148 218e3b0f Thomas Thrainer
                       show (e::IOError)
149 218e3b0f Thomas Thrainer
             save_fn $ Bad msg
150 218e3b0f Thomas Thrainer
             return (nullFStat, ConfigIOError)
151 218e3b0f Thomas Thrainer
          )
152 218e3b0f Thomas Thrainer
153 218e3b0f Thomas Thrainer
-- | Computes the file cache data from a FileStatus structure.
154 218e3b0f Thomas Thrainer
buildFileStatus :: FileStatus -> FStat
155 218e3b0f Thomas Thrainer
buildFileStatus ofs =
156 218e3b0f Thomas Thrainer
    let modt = modificationTime ofs
157 218e3b0f Thomas Thrainer
        inum = fileID ofs
158 218e3b0f Thomas Thrainer
        fsize = fileSize ofs
159 218e3b0f Thomas Thrainer
    in (modt, inum, fsize)
160 218e3b0f Thomas Thrainer
161 218e3b0f Thomas Thrainer
-- | Wrapper over 'buildFileStatus'. This reads the data from the
162 218e3b0f Thomas Thrainer
-- filesystem and then builds our cache structure.
163 218e3b0f Thomas Thrainer
getFStat :: FilePath -> IO FStat
164 218e3b0f Thomas Thrainer
getFStat p = liftM buildFileStatus (getFileStatus p)
165 218e3b0f Thomas Thrainer
166 218e3b0f Thomas Thrainer
-- | Check if the file needs reloading
167 218e3b0f Thomas Thrainer
needsReload :: FStat -> FilePath -> IO (Maybe FStat)
168 218e3b0f Thomas Thrainer
needsReload oldstat path = do
169 218e3b0f Thomas Thrainer
  newstat <- getFStat path
170 218e3b0f Thomas Thrainer
  return $ if newstat /= oldstat
171 218e3b0f Thomas Thrainer
             then Just newstat
172 218e3b0f Thomas Thrainer
             else Nothing
173 218e3b0f Thomas Thrainer
174 218e3b0f Thomas Thrainer
-- ** Watcher threads
175 218e3b0f Thomas Thrainer
176 218e3b0f Thomas Thrainer
-- $watcher
177 218e3b0f Thomas Thrainer
-- We have three threads/functions that can mutate the server state:
178 218e3b0f Thomas Thrainer
--
179 218e3b0f Thomas Thrainer
-- 1. the long-interval watcher ('onWatcherTimer')
180 218e3b0f Thomas Thrainer
--
181 218e3b0f Thomas Thrainer
-- 2. the polling watcher ('onPollTimer')
182 218e3b0f Thomas Thrainer
--
183 218e3b0f Thomas Thrainer
-- 3. the inotify event handler ('onInotify')
184 218e3b0f Thomas Thrainer
--
185 218e3b0f Thomas Thrainer
-- All of these will mutate the server state under 'modifyMVar' or
186 218e3b0f Thomas Thrainer
-- 'modifyMVar_', so that server transitions are more or less
187 218e3b0f Thomas Thrainer
-- atomic. The inotify handler remains active during polling mode, but
188 218e3b0f Thomas Thrainer
-- checks for polling mode and doesn't do anything in this case (this
189 218e3b0f Thomas Thrainer
-- check is needed even if we would unregister the event handler due
190 218e3b0f Thomas Thrainer
-- to how events are serialised).
191 218e3b0f Thomas Thrainer
192 218e3b0f Thomas Thrainer
-- | Long-interval reload watcher.
193 218e3b0f Thomas Thrainer
--
194 218e3b0f Thomas Thrainer
-- This is on top of the inotify-based triggered reload.
195 218e3b0f Thomas Thrainer
onWatcherTimer :: IO Bool -> FilePath -> (Result ConfigData -> IO ())
196 218e3b0f Thomas Thrainer
               -> MVar ServerState -> IO ()
197 218e3b0f Thomas Thrainer
onWatcherTimer inotiaction path save_fn state = do
198 218e3b0f Thomas Thrainer
  threadDelay watchInterval
199 218e3b0f Thomas Thrainer
  logDebug "Watcher timer fired"
200 218e3b0f Thomas Thrainer
  modifyMVar_ state (onWatcherInner path save_fn)
201 218e3b0f Thomas Thrainer
  _ <- inotiaction
202 218e3b0f Thomas Thrainer
  onWatcherTimer inotiaction path save_fn state
203 218e3b0f Thomas Thrainer
204 218e3b0f Thomas Thrainer
-- | Inner onWatcher handler.
205 218e3b0f Thomas Thrainer
--
206 218e3b0f Thomas Thrainer
-- This mutates the server state under a modifyMVar_ call. It never
207 218e3b0f Thomas Thrainer
-- changes the reload model, just does a safety reload and tried to
208 218e3b0f Thomas Thrainer
-- re-establish the inotify watcher.
209 218e3b0f Thomas Thrainer
onWatcherInner :: FilePath -> (Result ConfigData -> IO ()) -> ServerState
210 218e3b0f Thomas Thrainer
               -> IO ServerState
211 218e3b0f Thomas Thrainer
onWatcherInner path save_fn state  = do
212 218e3b0f Thomas Thrainer
  (newfstat, _) <- safeUpdateConfig path (reloadFStat state) save_fn
213 218e3b0f Thomas Thrainer
  return state { reloadFStat = newfstat }
214 218e3b0f Thomas Thrainer
215 218e3b0f Thomas Thrainer
-- | Short-interval (polling) reload watcher.
216 218e3b0f Thomas Thrainer
--
217 218e3b0f Thomas Thrainer
-- This is only active when we're in polling mode; it will
218 218e3b0f Thomas Thrainer
-- automatically exit when it detects that the state has changed to
219 218e3b0f Thomas Thrainer
-- notification.
220 218e3b0f Thomas Thrainer
onPollTimer :: IO Bool -> FilePath -> (Result ConfigData -> IO ())
221 218e3b0f Thomas Thrainer
            -> MVar ServerState -> IO ()
222 218e3b0f Thomas Thrainer
onPollTimer inotiaction path save_fn state = do
223 218e3b0f Thomas Thrainer
  threadDelay pollInterval
224 218e3b0f Thomas Thrainer
  logDebug "Poll timer fired"
225 218e3b0f Thomas Thrainer
  continue <- modifyMVar state (onPollInner inotiaction path save_fn)
226 218e3b0f Thomas Thrainer
  if continue
227 218e3b0f Thomas Thrainer
    then onPollTimer inotiaction path save_fn state
228 218e3b0f Thomas Thrainer
    else logDebug "Inotify watch active, polling thread exiting"
229 218e3b0f Thomas Thrainer
230 218e3b0f Thomas Thrainer
-- | Inner onPoll handler.
231 218e3b0f Thomas Thrainer
--
232 218e3b0f Thomas Thrainer
-- This again mutates the state under a modifyMVar call, and also
233 218e3b0f Thomas Thrainer
-- returns whether the thread should continue or not.
234 218e3b0f Thomas Thrainer
onPollInner :: IO Bool -> FilePath -> (Result ConfigData -> IO ())
235 218e3b0f Thomas Thrainer
            -> ServerState -> IO (ServerState, Bool)
236 218e3b0f Thomas Thrainer
onPollInner _ _ _ state@(ServerState { reloadModel = ReloadNotify } ) =
237 218e3b0f Thomas Thrainer
  return (state, False)
238 218e3b0f Thomas Thrainer
onPollInner inotiaction path save_fn
239 218e3b0f Thomas Thrainer
            state@(ServerState { reloadModel = ReloadPoll pround } ) = do
240 218e3b0f Thomas Thrainer
  (newfstat, reload) <- safeUpdateConfig path (reloadFStat state) save_fn
241 218e3b0f Thomas Thrainer
  let state' = state { reloadFStat = newfstat }
242 218e3b0f Thomas Thrainer
  -- compute new poll model based on reload data; however, failure to
243 218e3b0f Thomas Thrainer
  -- re-establish the inotifier means we stay on polling
244 218e3b0f Thomas Thrainer
  newmode <- case reload of
245 218e3b0f Thomas Thrainer
               ConfigToDate ->
246 218e3b0f Thomas Thrainer
                 if pround >= maxIdlePollRounds
247 218e3b0f Thomas Thrainer
                   then do -- try to switch to notify
248 218e3b0f Thomas Thrainer
                     result <- inotiaction
249 218e3b0f Thomas Thrainer
                     if result
250 218e3b0f Thomas Thrainer
                       then moveToNotify
251 218e3b0f Thomas Thrainer
                       else return initialPoll
252 218e3b0f Thomas Thrainer
                   else return (ReloadPoll (pround + 1))
253 218e3b0f Thomas Thrainer
               _ -> return initialPoll
254 218e3b0f Thomas Thrainer
  let continue = case newmode of
255 218e3b0f Thomas Thrainer
                   ReloadNotify -> False
256 218e3b0f Thomas Thrainer
                   _            -> True
257 218e3b0f Thomas Thrainer
  return (state' { reloadModel = newmode }, continue)
258 218e3b0f Thomas Thrainer
259 218e3b0f Thomas Thrainer
-- the following hint is because hlint doesn't understand our const
260 218e3b0f Thomas Thrainer
-- (return False) is so that we can give a signature to 'e'
261 218e3b0f Thomas Thrainer
{-# ANN addNotifier "HLint: ignore Evaluate" #-}
262 218e3b0f Thomas Thrainer
-- | Setup inotify watcher.
263 218e3b0f Thomas Thrainer
--
264 218e3b0f Thomas Thrainer
-- This tries to setup the watch descriptor; in case of any IO errors,
265 218e3b0f Thomas Thrainer
-- it will return False.
266 218e3b0f Thomas Thrainer
addNotifier :: INotify -> FilePath -> (Result ConfigData -> IO ())
267 218e3b0f Thomas Thrainer
            -> MVar ServerState -> IO Bool
268 218e3b0f Thomas Thrainer
addNotifier inotify path save_fn mstate =
269 218e3b0f Thomas Thrainer
  Control.Exception.catch
270 218e3b0f Thomas Thrainer
        (addWatch inotify [CloseWrite] path
271 218e3b0f Thomas Thrainer
            (onInotify inotify path save_fn mstate) >> return True)
272 218e3b0f Thomas Thrainer
        (\e -> const (return False) (e::IOError))
273 218e3b0f Thomas Thrainer
274 218e3b0f Thomas Thrainer
-- | Inotify event handler.
275 218e3b0f Thomas Thrainer
onInotify :: INotify -> String -> (Result ConfigData -> IO ())
276 218e3b0f Thomas Thrainer
          -> MVar ServerState -> Event -> IO ()
277 218e3b0f Thomas Thrainer
onInotify inotify path save_fn mstate Ignored = do
278 218e3b0f Thomas Thrainer
  logDebug "File lost, trying to re-establish notifier"
279 218e3b0f Thomas Thrainer
  modifyMVar_ mstate $ \state -> do
280 218e3b0f Thomas Thrainer
    result <- addNotifier inotify path save_fn mstate
281 218e3b0f Thomas Thrainer
    (newfstat, _) <- safeUpdateConfig path (reloadFStat state) save_fn
282 218e3b0f Thomas Thrainer
    let state' = state { reloadFStat = newfstat }
283 218e3b0f Thomas Thrainer
    if result
284 218e3b0f Thomas Thrainer
      then return state' -- keep notify
285 218e3b0f Thomas Thrainer
      else do
286 218e3b0f Thomas Thrainer
        mode <- moveToPolling "cannot re-establish inotify watch" inotify
287 218e3b0f Thomas Thrainer
                  path save_fn mstate
288 218e3b0f Thomas Thrainer
        return state' { reloadModel = mode }
289 218e3b0f Thomas Thrainer
290 218e3b0f Thomas Thrainer
onInotify inotify path save_fn mstate _ =
291 218e3b0f Thomas Thrainer
  modifyMVar_ mstate $ \state ->
292 218e3b0f Thomas Thrainer
    if reloadModel state == ReloadNotify
293 218e3b0f Thomas Thrainer
       then do
294 218e3b0f Thomas Thrainer
         ctime <- getCurrentTimeUSec
295 218e3b0f Thomas Thrainer
         (newfstat, _) <- safeUpdateConfig path (reloadFStat state) save_fn
296 218e3b0f Thomas Thrainer
         let state' = state { reloadFStat = newfstat, reloadTime = ctime }
297 218e3b0f Thomas Thrainer
         if abs (reloadTime state - ctime) < reloadRatelimit
298 218e3b0f Thomas Thrainer
           then do
299 218e3b0f Thomas Thrainer
             mode <- moveToPolling "too many reloads" inotify path save_fn
300 218e3b0f Thomas Thrainer
                                   mstate
301 218e3b0f Thomas Thrainer
             return state' { reloadModel = mode }
302 218e3b0f Thomas Thrainer
           else return state'
303 218e3b0f Thomas Thrainer
      else return state
304 218e3b0f Thomas Thrainer
305 218e3b0f Thomas Thrainer
initConfigReader :: (Result ConfigData -> a) -> IORef a -> IO ()
306 218e3b0f Thomas Thrainer
initConfigReader cfg_transform ioref = do
307 218e3b0f Thomas Thrainer
  let save_fn = writeIORef ioref . cfg_transform
308 218e3b0f Thomas Thrainer
309 218e3b0f Thomas Thrainer
  -- Inotify setup
310 218e3b0f Thomas Thrainer
  inotify <- initINotify
311 218e3b0f Thomas Thrainer
  -- try to load the configuration, if possible
312 218e3b0f Thomas Thrainer
  conf_file <- Path.clusterConfFile
313 218e3b0f Thomas Thrainer
  (fstat, reloaded) <- safeUpdateConfig conf_file nullFStat save_fn
314 218e3b0f Thomas Thrainer
  ctime <- getCurrentTime
315 218e3b0f Thomas Thrainer
  statemvar <- newMVar $ ServerState ReloadNotify ctime fstat
316 218e3b0f Thomas Thrainer
  let inotiaction = addNotifier inotify conf_file save_fn statemvar
317 218e3b0f Thomas Thrainer
  has_inotify <- if reloaded == ConfigReloaded
318 218e3b0f Thomas Thrainer
                   then inotiaction
319 218e3b0f Thomas Thrainer
                   else return False
320 218e3b0f Thomas Thrainer
  if has_inotify
321 218e3b0f Thomas Thrainer
    then logInfo "Starting up in inotify mode"
322 218e3b0f Thomas Thrainer
    else do
323 218e3b0f Thomas Thrainer
      -- inotify was not enabled, we need to update the reload model
324 218e3b0f Thomas Thrainer
      logInfo "Starting up in polling mode"
325 218e3b0f Thomas Thrainer
      modifyMVar_ statemvar
326 218e3b0f Thomas Thrainer
        (\state -> return state { reloadModel = initialPoll })
327 218e3b0f Thomas Thrainer
  -- fork the timeout timer
328 218e3b0f Thomas Thrainer
  _ <- forkIO $ onWatcherTimer inotiaction conf_file save_fn statemvar
329 218e3b0f Thomas Thrainer
  -- fork the polling timer
330 218e3b0f Thomas Thrainer
  unless has_inotify $ do
331 218e3b0f Thomas Thrainer
    _ <- forkIO $ onPollTimer inotiaction conf_file save_fn statemvar
332 218e3b0f Thomas Thrainer
    return ()