Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Confd / Server.hs @ 29a30533

History | View | Annotate | Download (19.7 kB)

1 358a0a8f Iustin Pop
{-# LANGUAGE BangPatterns #-}
2 358a0a8f Iustin Pop
3 358a0a8f Iustin Pop
{-| Implementation of the Ganeti confd server functionality.
4 358a0a8f Iustin Pop
5 358a0a8f Iustin Pop
-}
6 358a0a8f Iustin Pop
7 358a0a8f Iustin Pop
{-
8 358a0a8f Iustin Pop
9 19cff311 Iustin Pop
Copyright (C) 2011, 2012 Google Inc.
10 358a0a8f Iustin Pop
11 358a0a8f Iustin Pop
This program is free software; you can redistribute it and/or modify
12 358a0a8f Iustin Pop
it under the terms of the GNU General Public License as published by
13 358a0a8f Iustin Pop
the Free Software Foundation; either version 2 of the License, or
14 358a0a8f Iustin Pop
(at your option) any later version.
15 358a0a8f Iustin Pop
16 358a0a8f Iustin Pop
This program is distributed in the hope that it will be useful, but
17 358a0a8f Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
18 358a0a8f Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 358a0a8f Iustin Pop
General Public License for more details.
20 358a0a8f Iustin Pop
21 358a0a8f Iustin Pop
You should have received a copy of the GNU General Public License
22 358a0a8f Iustin Pop
along with this program; if not, write to the Free Software
23 358a0a8f Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 358a0a8f Iustin Pop
02110-1301, USA.
25 358a0a8f Iustin Pop
26 358a0a8f Iustin Pop
-}
27 358a0a8f Iustin Pop
28 358a0a8f Iustin Pop
module Ganeti.Confd.Server
29 358a0a8f Iustin Pop
  ( main
30 2ac2e420 Iustin Pop
  , checkMain
31 2ac2e420 Iustin Pop
  , prepMain
32 358a0a8f Iustin Pop
  ) where
33 358a0a8f Iustin Pop
34 358a0a8f Iustin Pop
import Control.Concurrent
35 79ac58fa Iustin Pop
import Control.Exception
36 2cdaf225 Iustin Pop
import Control.Monad (forever, liftM, when)
37 358a0a8f Iustin Pop
import Data.IORef
38 358a0a8f Iustin Pop
import Data.List
39 358a0a8f Iustin Pop
import qualified Data.Map as M
40 2cdaf225 Iustin Pop
import Data.Maybe (fromMaybe)
41 358a0a8f Iustin Pop
import qualified Network.Socket as S
42 ef3de7b0 Iustin Pop
import System.Exit
43 ef3de7b0 Iustin Pop
import System.IO
44 358a0a8f Iustin Pop
import System.Posix.Files
45 358a0a8f Iustin Pop
import System.Posix.Types
46 358a0a8f Iustin Pop
import System.Time
47 358a0a8f Iustin Pop
import qualified Text.JSON as J
48 358a0a8f Iustin Pop
import System.INotify
49 358a0a8f Iustin Pop
50 4cd79ca8 Iustin Pop
import Ganeti.BasicTypes
51 5183e8be Iustin Pop
import Ganeti.Errors
52 358a0a8f Iustin Pop
import Ganeti.Daemon
53 f3baf5ef Iustin Pop
import Ganeti.JSON
54 358a0a8f Iustin Pop
import Ganeti.Objects
55 cdc2392b Iustin Pop
import Ganeti.Confd.Types
56 62377cf5 Iustin Pop
import Ganeti.Confd.Utils
57 358a0a8f Iustin Pop
import Ganeti.Config
58 358a0a8f Iustin Pop
import Ganeti.Hash
59 358a0a8f Iustin Pop
import Ganeti.Logging
60 358a0a8f Iustin Pop
import qualified Ganeti.Constants as C
61 9eeb0aa5 Michael Hanselmann
import qualified Ganeti.Path as Path
62 4c3f55b8 Iustin Pop
import Ganeti.Query.Server (prepQueryD, runQueryD)
63 358a0a8f Iustin Pop
64 358a0a8f Iustin Pop
-- * Types and constants definitions
65 358a0a8f Iustin Pop
66 358a0a8f Iustin Pop
-- | What we store as configuration.
67 358a0a8f Iustin Pop
type CRef = IORef (Result (ConfigData, LinkIpMap))
68 358a0a8f Iustin Pop
69 358a0a8f Iustin Pop
-- | File stat identifier.
70 358a0a8f Iustin Pop
type FStat = (EpochTime, FileID, FileOffset)
71 358a0a8f Iustin Pop
72 358a0a8f Iustin Pop
-- | Null 'FStat' value.
73 358a0a8f Iustin Pop
nullFStat :: FStat
74 358a0a8f Iustin Pop
nullFStat = (-1, -1, -1)
75 358a0a8f Iustin Pop
76 358a0a8f Iustin Pop
-- | A small type alias for readability.
77 358a0a8f Iustin Pop
type StatusAnswer = (ConfdReplyStatus, J.JSValue)
78 358a0a8f Iustin Pop
79 358a0a8f Iustin Pop
-- | Reload model data type.
80 358a0a8f Iustin Pop
data ReloadModel = ReloadNotify      -- ^ We are using notifications
81 358a0a8f Iustin Pop
                 | ReloadPoll Int    -- ^ We are using polling
82 358a0a8f Iustin Pop
                   deriving (Eq, Show)
83 358a0a8f Iustin Pop
84 358a0a8f Iustin Pop
-- | Server state data type.
85 358a0a8f Iustin Pop
data ServerState = ServerState
86 358a0a8f Iustin Pop
  { reloadModel  :: ReloadModel
87 358a0a8f Iustin Pop
  , reloadTime   :: Integer
88 358a0a8f Iustin Pop
  , reloadFStat  :: FStat
89 358a0a8f Iustin Pop
  }
90 358a0a8f Iustin Pop
91 358a0a8f Iustin Pop
-- | Maximum no-reload poll rounds before reverting to inotify.
92 358a0a8f Iustin Pop
maxIdlePollRounds :: Int
93 358a0a8f Iustin Pop
maxIdlePollRounds = 2
94 358a0a8f Iustin Pop
95 358a0a8f Iustin Pop
-- | Reload timeout in microseconds.
96 358a0a8f Iustin Pop
configReloadTimeout :: Int
97 358a0a8f Iustin Pop
configReloadTimeout = C.confdConfigReloadTimeout * 1000000
98 358a0a8f Iustin Pop
99 358a0a8f Iustin Pop
-- | Ratelimit timeout in microseconds.
100 358a0a8f Iustin Pop
configReloadRatelimit :: Int
101 358a0a8f Iustin Pop
configReloadRatelimit = C.confdConfigReloadRatelimit * 1000000
102 358a0a8f Iustin Pop
103 358a0a8f Iustin Pop
-- | Initial poll round.
104 358a0a8f Iustin Pop
initialPoll :: ReloadModel
105 358a0a8f Iustin Pop
initialPoll = ReloadPoll 0
106 358a0a8f Iustin Pop
107 358a0a8f Iustin Pop
-- | Initial server state.
108 358a0a8f Iustin Pop
initialState :: ServerState
109 358a0a8f Iustin Pop
initialState = ServerState initialPoll 0 nullFStat
110 358a0a8f Iustin Pop
111 358a0a8f Iustin Pop
-- | Reload status data type.
112 358a0a8f Iustin Pop
data ConfigReload = ConfigToDate    -- ^ No need to reload
113 358a0a8f Iustin Pop
                  | ConfigReloaded  -- ^ Configuration reloaded
114 358a0a8f Iustin Pop
                  | ConfigIOError   -- ^ Error during configuration reload
115 358a0a8f Iustin Pop
116 358a0a8f Iustin Pop
-- | Unknown entry standard response.
117 358a0a8f Iustin Pop
queryUnknownEntry :: StatusAnswer
118 358a0a8f Iustin Pop
queryUnknownEntry = (ReplyStatusError, J.showJSON ConfdErrorUnknownEntry)
119 358a0a8f Iustin Pop
120 358a0a8f Iustin Pop
{- not used yet
121 358a0a8f Iustin Pop
-- | Internal error standard response.
122 358a0a8f Iustin Pop
queryInternalError :: StatusAnswer
123 358a0a8f Iustin Pop
queryInternalError = (ReplyStatusError, J.showJSON ConfdErrorInternal)
124 358a0a8f Iustin Pop
-}
125 358a0a8f Iustin Pop
126 358a0a8f Iustin Pop
-- | Argument error standard response.
127 358a0a8f Iustin Pop
queryArgumentError :: StatusAnswer
128 358a0a8f Iustin Pop
queryArgumentError = (ReplyStatusError, J.showJSON ConfdErrorArgument)
129 358a0a8f Iustin Pop
130 358a0a8f Iustin Pop
-- | Returns the current time.
131 358a0a8f Iustin Pop
getCurrentTime :: IO Integer
132 358a0a8f Iustin Pop
getCurrentTime = do
133 358a0a8f Iustin Pop
  TOD ctime _ <- getClockTime
134 358a0a8f Iustin Pop
  return ctime
135 358a0a8f Iustin Pop
136 5183e8be Iustin Pop
-- | Converter from specific error to a string format.
137 5183e8be Iustin Pop
gntErrorToResult :: ErrorResult a -> Result a
138 5183e8be Iustin Pop
gntErrorToResult (Bad err) = Bad (show err)
139 5183e8be Iustin Pop
gntErrorToResult (Ok x) = Ok x
140 5183e8be Iustin Pop
141 358a0a8f Iustin Pop
-- * Confd base functionality
142 358a0a8f Iustin Pop
143 358a0a8f Iustin Pop
-- | Computes the node role.
144 358a0a8f Iustin Pop
nodeRole :: ConfigData -> String -> Result ConfdNodeRole
145 358a0a8f Iustin Pop
nodeRole cfg name =
146 358a0a8f Iustin Pop
  let cmaster = clusterMasterNode . configCluster $ cfg
147 84835174 Iustin Pop
      mnode = M.lookup name . fromContainer . configNodes $ cfg
148 358a0a8f Iustin Pop
  in case mnode of
149 358a0a8f Iustin Pop
       Nothing -> Bad "Node not found"
150 358a0a8f Iustin Pop
       Just node | cmaster == name -> Ok NodeRoleMaster
151 358a0a8f Iustin Pop
                 | nodeDrained node -> Ok NodeRoleDrained
152 358a0a8f Iustin Pop
                 | nodeOffline node -> Ok NodeRoleOffline
153 358a0a8f Iustin Pop
                 | nodeMasterCandidate node -> Ok NodeRoleCandidate
154 358a0a8f Iustin Pop
       _ -> Ok NodeRoleRegular
155 358a0a8f Iustin Pop
156 358a0a8f Iustin Pop
-- | Does an instance ip -> instance -> primary node -> primary ip
157 358a0a8f Iustin Pop
-- transformation.
158 358a0a8f Iustin Pop
getNodePipByInstanceIp :: ConfigData
159 358a0a8f Iustin Pop
                       -> LinkIpMap
160 358a0a8f Iustin Pop
                       -> String
161 358a0a8f Iustin Pop
                       -> String
162 358a0a8f Iustin Pop
                       -> StatusAnswer
163 358a0a8f Iustin Pop
getNodePipByInstanceIp cfg linkipmap link instip =
164 358a0a8f Iustin Pop
  case M.lookup instip (M.findWithDefault M.empty link linkipmap) of
165 358a0a8f Iustin Pop
    Nothing -> queryUnknownEntry
166 358a0a8f Iustin Pop
    Just instname ->
167 358a0a8f Iustin Pop
      case getInstPrimaryNode cfg instname of
168 358a0a8f Iustin Pop
        Bad _ -> queryUnknownEntry -- either instance or node not found
169 358a0a8f Iustin Pop
        Ok node -> (ReplyStatusOk, J.showJSON (nodePrimaryIp node))
170 358a0a8f Iustin Pop
171 358a0a8f Iustin Pop
-- | Builds the response to a given query.
172 358a0a8f Iustin Pop
buildResponse :: (ConfigData, LinkIpMap) -> ConfdRequest -> Result StatusAnswer
173 358a0a8f Iustin Pop
buildResponse (cfg, _) (ConfdRequest { confdRqType = ReqPing }) =
174 358a0a8f Iustin Pop
  return (ReplyStatusOk, J.showJSON (configVersion cfg))
175 358a0a8f Iustin Pop
176 358a0a8f Iustin Pop
buildResponse cdata req@(ConfdRequest { confdRqType = ReqClusterMaster }) =
177 358a0a8f Iustin Pop
  case confdRqQuery req of
178 358a0a8f Iustin Pop
    EmptyQuery -> return (ReplyStatusOk, J.showJSON master_name)
179 358a0a8f Iustin Pop
    PlainQuery _ -> return queryArgumentError
180 358a0a8f Iustin Pop
    DictQuery reqq -> do
181 5183e8be Iustin Pop
      mnode <- gntErrorToResult $ getNode cfg master_name
182 5183e8be Iustin Pop
      let fvals = map (\field -> case field of
183 5183e8be Iustin Pop
                                   ReqFieldName -> master_name
184 5183e8be Iustin Pop
                                   ReqFieldIp -> clusterMasterIp cluster
185 5183e8be Iustin Pop
                                   ReqFieldMNodePip -> nodePrimaryIp mnode
186 5183e8be Iustin Pop
                      ) (confdReqQFields reqq)
187 358a0a8f Iustin Pop
      return (ReplyStatusOk, J.showJSON fvals)
188 358a0a8f Iustin Pop
    where master_name = clusterMasterNode cluster
189 358a0a8f Iustin Pop
          cluster = configCluster cfg
190 358a0a8f Iustin Pop
          cfg = fst cdata
191 358a0a8f Iustin Pop
192 358a0a8f Iustin Pop
buildResponse cdata req@(ConfdRequest { confdRqType = ReqNodeRoleByName }) = do
193 358a0a8f Iustin Pop
  node_name <- case confdRqQuery req of
194 358a0a8f Iustin Pop
                 PlainQuery str -> return str
195 358a0a8f Iustin Pop
                 _ -> fail $ "Invalid query type " ++ show (confdRqQuery req)
196 358a0a8f Iustin Pop
  role <- nodeRole (fst cdata) node_name
197 358a0a8f Iustin Pop
  return (ReplyStatusOk, J.showJSON role)
198 358a0a8f Iustin Pop
199 358a0a8f Iustin Pop
buildResponse cdata (ConfdRequest { confdRqType = ReqNodePipList }) =
200 358a0a8f Iustin Pop
  -- note: we use foldlWithKey because that's present accross more
201 358a0a8f Iustin Pop
  -- versions of the library
202 358a0a8f Iustin Pop
  return (ReplyStatusOk, J.showJSON $
203 358a0a8f Iustin Pop
          M.foldlWithKey (\accu _ n -> nodePrimaryIp n:accu) []
204 84835174 Iustin Pop
          (fromContainer . configNodes . fst $ cdata))
205 358a0a8f Iustin Pop
206 358a0a8f Iustin Pop
buildResponse cdata (ConfdRequest { confdRqType = ReqMcPipList }) =
207 358a0a8f Iustin Pop
  -- note: we use foldlWithKey because that's present accross more
208 358a0a8f Iustin Pop
  -- versions of the library
209 358a0a8f Iustin Pop
  return (ReplyStatusOk, J.showJSON $
210 358a0a8f Iustin Pop
          M.foldlWithKey (\accu _ n -> if nodeMasterCandidate n
211 358a0a8f Iustin Pop
                                         then nodePrimaryIp n:accu
212 358a0a8f Iustin Pop
                                         else accu) []
213 84835174 Iustin Pop
          (fromContainer . configNodes . fst $ cdata))
214 358a0a8f Iustin Pop
215 358a0a8f Iustin Pop
buildResponse (cfg, linkipmap)
216 358a0a8f Iustin Pop
              req@(ConfdRequest { confdRqType = ReqInstIpsList }) = do
217 358a0a8f Iustin Pop
  link <- case confdRqQuery req of
218 358a0a8f Iustin Pop
            PlainQuery str -> return str
219 358a0a8f Iustin Pop
            EmptyQuery -> return (getDefaultNicLink cfg)
220 358a0a8f Iustin Pop
            _ -> fail "Invalid query type"
221 358a0a8f Iustin Pop
  return (ReplyStatusOk, J.showJSON $ getInstancesIpByLink linkipmap link)
222 358a0a8f Iustin Pop
223 358a0a8f Iustin Pop
buildResponse cdata (ConfdRequest { confdRqType = ReqNodePipByInstPip
224 358a0a8f Iustin Pop
                                  , confdRqQuery = DictQuery query}) =
225 358a0a8f Iustin Pop
  let (cfg, linkipmap) = cdata
226 2cdaf225 Iustin Pop
      link = fromMaybe (getDefaultNicLink cfg) (confdReqQLink query)
227 358a0a8f Iustin Pop
  in case confdReqQIp query of
228 358a0a8f Iustin Pop
       Just ip -> return $ getNodePipByInstanceIp cfg linkipmap link ip
229 358a0a8f Iustin Pop
       Nothing -> return (ReplyStatusOk,
230 358a0a8f Iustin Pop
                          J.showJSON $
231 358a0a8f Iustin Pop
                           map (getNodePipByInstanceIp cfg linkipmap link)
232 358a0a8f Iustin Pop
                           (confdReqQIpList query))
233 358a0a8f Iustin Pop
234 358a0a8f Iustin Pop
buildResponse _ (ConfdRequest { confdRqType = ReqNodePipByInstPip }) =
235 358a0a8f Iustin Pop
  return queryArgumentError
236 358a0a8f Iustin Pop
237 d81ec8b7 Iustin Pop
buildResponse cdata req@(ConfdRequest { confdRqType = ReqNodeDrbd }) = do
238 d81ec8b7 Iustin Pop
  let cfg = fst cdata
239 d81ec8b7 Iustin Pop
  node_name <- case confdRqQuery req of
240 d81ec8b7 Iustin Pop
                 PlainQuery str -> return str
241 d81ec8b7 Iustin Pop
                 _ -> fail $ "Invalid query type " ++ show (confdRqQuery req)
242 5183e8be Iustin Pop
  node <- gntErrorToResult $ getNode cfg node_name
243 d81ec8b7 Iustin Pop
  let minors = concatMap (getInstMinorsForNode (nodeName node)) .
244 84835174 Iustin Pop
               M.elems . fromContainer . configInstances $ cfg
245 d81ec8b7 Iustin Pop
      encoded = [J.JSArray [J.showJSON a, J.showJSON b, J.showJSON c,
246 d81ec8b7 Iustin Pop
                             J.showJSON d, J.showJSON e, J.showJSON f] |
247 d81ec8b7 Iustin Pop
                 (a, b, c, d, e, f) <- minors]
248 d81ec8b7 Iustin Pop
  return (ReplyStatusOk, J.showJSON encoded)
249 d81ec8b7 Iustin Pop
250 358a0a8f Iustin Pop
-- | Creates a ConfdReply from a given answer.
251 358a0a8f Iustin Pop
serializeResponse :: Result StatusAnswer -> ConfdReply
252 358a0a8f Iustin Pop
serializeResponse r =
253 358a0a8f Iustin Pop
    let (status, result) = case r of
254 358a0a8f Iustin Pop
                    Bad err -> (ReplyStatusError, J.showJSON err)
255 358a0a8f Iustin Pop
                    Ok (code, val) -> (code, val)
256 358a0a8f Iustin Pop
    in ConfdReply { confdReplyProtocol = 1
257 358a0a8f Iustin Pop
                  , confdReplyStatus   = status
258 358a0a8f Iustin Pop
                  , confdReplyAnswer   = result
259 358a0a8f Iustin Pop
                  , confdReplySerial   = 0 }
260 358a0a8f Iustin Pop
261 358a0a8f Iustin Pop
-- * Configuration handling
262 358a0a8f Iustin Pop
263 358a0a8f Iustin Pop
-- ** Helper functions
264 358a0a8f Iustin Pop
265 358a0a8f Iustin Pop
-- | Helper function for logging transition into polling mode.
266 358a0a8f Iustin Pop
moveToPolling :: String -> INotify -> FilePath -> CRef -> MVar ServerState
267 358a0a8f Iustin Pop
              -> IO ReloadModel
268 358a0a8f Iustin Pop
moveToPolling msg inotify path cref mstate = do
269 358a0a8f Iustin Pop
  logInfo $ "Moving to polling mode: " ++ msg
270 358a0a8f Iustin Pop
  let inotiaction = addNotifier inotify path cref mstate
271 358a0a8f Iustin Pop
  _ <- forkIO $ onReloadTimer inotiaction path cref mstate
272 358a0a8f Iustin Pop
  return initialPoll
273 358a0a8f Iustin Pop
274 358a0a8f Iustin Pop
-- | Helper function for logging transition into inotify mode.
275 358a0a8f Iustin Pop
moveToNotify :: IO ReloadModel
276 358a0a8f Iustin Pop
moveToNotify = do
277 358a0a8f Iustin Pop
  logInfo "Moving to inotify mode"
278 358a0a8f Iustin Pop
  return ReloadNotify
279 358a0a8f Iustin Pop
280 358a0a8f Iustin Pop
-- ** Configuration loading
281 358a0a8f Iustin Pop
282 358a0a8f Iustin Pop
-- | (Re)loads the configuration.
283 358a0a8f Iustin Pop
updateConfig :: FilePath -> CRef -> IO ()
284 358a0a8f Iustin Pop
updateConfig path r = do
285 358a0a8f Iustin Pop
  newcfg <- loadConfig path
286 358a0a8f Iustin Pop
  let !newdata = case newcfg of
287 358a0a8f Iustin Pop
                   Ok !cfg -> Ok (cfg, buildLinkIpInstnameMap cfg)
288 358a0a8f Iustin Pop
                   Bad _ -> Bad "Cannot load configuration"
289 358a0a8f Iustin Pop
  writeIORef r newdata
290 358a0a8f Iustin Pop
  case newcfg of
291 358a0a8f Iustin Pop
    Ok cfg -> logInfo ("Loaded new config, serial " ++
292 358a0a8f Iustin Pop
                       show (configSerial cfg))
293 358a0a8f Iustin Pop
    Bad msg -> logError $ "Failed to load config: " ++ msg
294 358a0a8f Iustin Pop
  return ()
295 358a0a8f Iustin Pop
296 358a0a8f Iustin Pop
-- | Wrapper over 'updateConfig' that handles IO errors.
297 358a0a8f Iustin Pop
safeUpdateConfig :: FilePath -> FStat -> CRef -> IO (FStat, ConfigReload)
298 5b11f8db Iustin Pop
safeUpdateConfig path oldfstat cref =
299 1251817b Iustin Pop
  Control.Exception.catch
300 1251817b Iustin Pop
        (do
301 358a0a8f Iustin Pop
          nt <- needsReload oldfstat path
302 358a0a8f Iustin Pop
          case nt of
303 358a0a8f Iustin Pop
            Nothing -> return (oldfstat, ConfigToDate)
304 358a0a8f Iustin Pop
            Just nt' -> do
305 358a0a8f Iustin Pop
                    updateConfig path cref
306 358a0a8f Iustin Pop
                    return (nt', ConfigReloaded)
307 358a0a8f Iustin Pop
        ) (\e -> do
308 79ac58fa Iustin Pop
             let msg = "Failure during configuration update: " ++
309 79ac58fa Iustin Pop
                       show (e::IOError)
310 358a0a8f Iustin Pop
             writeIORef cref (Bad msg)
311 358a0a8f Iustin Pop
             return (nullFStat, ConfigIOError)
312 358a0a8f Iustin Pop
          )
313 358a0a8f Iustin Pop
314 358a0a8f Iustin Pop
-- | Computes the file cache data from a FileStatus structure.
315 358a0a8f Iustin Pop
buildFileStatus :: FileStatus -> FStat
316 358a0a8f Iustin Pop
buildFileStatus ofs =
317 358a0a8f Iustin Pop
    let modt = modificationTime ofs
318 358a0a8f Iustin Pop
        inum = fileID ofs
319 358a0a8f Iustin Pop
        fsize = fileSize ofs
320 358a0a8f Iustin Pop
    in (modt, inum, fsize)
321 358a0a8f Iustin Pop
322 358a0a8f Iustin Pop
-- | Wrapper over 'buildFileStatus'. This reads the data from the
323 358a0a8f Iustin Pop
-- filesystem and then builds our cache structure.
324 358a0a8f Iustin Pop
getFStat :: FilePath -> IO FStat
325 2cdaf225 Iustin Pop
getFStat p = liftM buildFileStatus (getFileStatus p)
326 358a0a8f Iustin Pop
327 358a0a8f Iustin Pop
-- | Check if the file needs reloading
328 358a0a8f Iustin Pop
needsReload :: FStat -> FilePath -> IO (Maybe FStat)
329 358a0a8f Iustin Pop
needsReload oldstat path = do
330 358a0a8f Iustin Pop
  newstat <- getFStat path
331 358a0a8f Iustin Pop
  return $ if newstat /= oldstat
332 358a0a8f Iustin Pop
             then Just newstat
333 358a0a8f Iustin Pop
             else Nothing
334 358a0a8f Iustin Pop
335 358a0a8f Iustin Pop
-- ** Watcher threads
336 358a0a8f Iustin Pop
337 358a0a8f Iustin Pop
-- $watcher
338 358a0a8f Iustin Pop
-- We have three threads/functions that can mutate the server state:
339 358a0a8f Iustin Pop
--
340 358a0a8f Iustin Pop
-- 1. the long-interval watcher ('onTimeoutTimer')
341 358a0a8f Iustin Pop
--
342 358a0a8f Iustin Pop
-- 2. the polling watcher ('onReloadTimer')
343 358a0a8f Iustin Pop
--
344 358a0a8f Iustin Pop
-- 3. the inotify event handler ('onInotify')
345 358a0a8f Iustin Pop
--
346 358a0a8f Iustin Pop
-- All of these will mutate the server state under 'modifyMVar' or
347 358a0a8f Iustin Pop
-- 'modifyMVar_', so that server transitions are more or less
348 358a0a8f Iustin Pop
-- atomic. The inotify handler remains active during polling mode, but
349 358a0a8f Iustin Pop
-- checks for polling mode and doesn't do anything in this case (this
350 358a0a8f Iustin Pop
-- check is needed even if we would unregister the event handler due
351 358a0a8f Iustin Pop
-- to how events are serialised).
352 358a0a8f Iustin Pop
353 358a0a8f Iustin Pop
-- | Long-interval reload watcher.
354 358a0a8f Iustin Pop
--
355 358a0a8f Iustin Pop
-- This is on top of the inotify-based triggered reload.
356 358a0a8f Iustin Pop
onTimeoutTimer :: IO Bool -> FilePath -> CRef -> MVar ServerState -> IO ()
357 358a0a8f Iustin Pop
onTimeoutTimer inotiaction path cref state = do
358 358a0a8f Iustin Pop
  threadDelay configReloadTimeout
359 358a0a8f Iustin Pop
  modifyMVar_ state (onTimeoutInner path cref)
360 358a0a8f Iustin Pop
  _ <- inotiaction
361 358a0a8f Iustin Pop
  onTimeoutTimer inotiaction path cref state
362 358a0a8f Iustin Pop
363 358a0a8f Iustin Pop
-- | Inner onTimeout handler.
364 358a0a8f Iustin Pop
--
365 358a0a8f Iustin Pop
-- This mutates the server state under a modifyMVar_ call. It never
366 358a0a8f Iustin Pop
-- changes the reload model, just does a safety reload and tried to
367 358a0a8f Iustin Pop
-- re-establish the inotify watcher.
368 358a0a8f Iustin Pop
onTimeoutInner :: FilePath -> CRef -> ServerState -> IO ServerState
369 358a0a8f Iustin Pop
onTimeoutInner path cref state  = do
370 358a0a8f Iustin Pop
  (newfstat, _) <- safeUpdateConfig path (reloadFStat state) cref
371 358a0a8f Iustin Pop
  return state { reloadFStat = newfstat }
372 358a0a8f Iustin Pop
373 358a0a8f Iustin Pop
-- | Short-interval (polling) reload watcher.
374 358a0a8f Iustin Pop
--
375 358a0a8f Iustin Pop
-- This is only active when we're in polling mode; it will
376 358a0a8f Iustin Pop
-- automatically exit when it detects that the state has changed to
377 358a0a8f Iustin Pop
-- notification.
378 358a0a8f Iustin Pop
onReloadTimer :: IO Bool -> FilePath -> CRef -> MVar ServerState -> IO ()
379 358a0a8f Iustin Pop
onReloadTimer inotiaction path cref state = do
380 358a0a8f Iustin Pop
  continue <- modifyMVar state (onReloadInner inotiaction path cref)
381 2cdaf225 Iustin Pop
  when continue $
382 2cdaf225 Iustin Pop
    do threadDelay configReloadRatelimit
383 2cdaf225 Iustin Pop
       onReloadTimer inotiaction path cref state
384 2cdaf225 Iustin Pop
  -- the inotify watch has been re-established, we can exit
385 358a0a8f Iustin Pop
386 358a0a8f Iustin Pop
-- | Inner onReload handler.
387 358a0a8f Iustin Pop
--
388 358a0a8f Iustin Pop
-- This again mutates the state under a modifyMVar call, and also
389 358a0a8f Iustin Pop
-- returns whether the thread should continue or not.
390 358a0a8f Iustin Pop
onReloadInner :: IO Bool -> FilePath -> CRef -> ServerState
391 358a0a8f Iustin Pop
              -> IO (ServerState, Bool)
392 358a0a8f Iustin Pop
onReloadInner _ _ _ state@(ServerState { reloadModel = ReloadNotify } ) =
393 358a0a8f Iustin Pop
  return (state, False)
394 358a0a8f Iustin Pop
onReloadInner inotiaction path cref
395 358a0a8f Iustin Pop
              state@(ServerState { reloadModel = ReloadPoll pround } ) = do
396 358a0a8f Iustin Pop
  (newfstat, reload) <- safeUpdateConfig path (reloadFStat state) cref
397 358a0a8f Iustin Pop
  let state' = state { reloadFStat = newfstat }
398 358a0a8f Iustin Pop
  -- compute new poll model based on reload data; however, failure to
399 358a0a8f Iustin Pop
  -- re-establish the inotifier means we stay on polling
400 358a0a8f Iustin Pop
  newmode <- case reload of
401 358a0a8f Iustin Pop
               ConfigToDate ->
402 358a0a8f Iustin Pop
                 if pround >= maxIdlePollRounds
403 358a0a8f Iustin Pop
                   then do -- try to switch to notify
404 358a0a8f Iustin Pop
                     result <- inotiaction
405 358a0a8f Iustin Pop
                     if result
406 358a0a8f Iustin Pop
                       then moveToNotify
407 358a0a8f Iustin Pop
                       else return initialPoll
408 358a0a8f Iustin Pop
                   else return (ReloadPoll (pround + 1))
409 358a0a8f Iustin Pop
               _ -> return initialPoll
410 358a0a8f Iustin Pop
  let continue = case newmode of
411 358a0a8f Iustin Pop
                   ReloadNotify -> False
412 358a0a8f Iustin Pop
                   _            -> True
413 358a0a8f Iustin Pop
  return (state' { reloadModel = newmode }, continue)
414 358a0a8f Iustin Pop
415 2cdaf225 Iustin Pop
-- the following hint is because hlint doesn't understand our const
416 2cdaf225 Iustin Pop
-- (return False) is so that we can give a signature to 'e'
417 2cdaf225 Iustin Pop
{-# ANN addNotifier "HLint: ignore Evaluate" #-}
418 358a0a8f Iustin Pop
-- | Setup inotify watcher.
419 358a0a8f Iustin Pop
--
420 358a0a8f Iustin Pop
-- This tries to setup the watch descriptor; in case of any IO errors,
421 358a0a8f Iustin Pop
-- it will return False.
422 358a0a8f Iustin Pop
addNotifier :: INotify -> FilePath -> CRef -> MVar ServerState -> IO Bool
423 5b11f8db Iustin Pop
addNotifier inotify path cref mstate =
424 1251817b Iustin Pop
  Control.Exception.catch
425 1251817b Iustin Pop
        (addWatch inotify [CloseWrite] path
426 358a0a8f Iustin Pop
                    (onInotify inotify path cref mstate) >> return True)
427 79ac58fa Iustin Pop
        (\e -> const (return False) (e::IOError))
428 358a0a8f Iustin Pop
429 358a0a8f Iustin Pop
-- | Inotify event handler.
430 358a0a8f Iustin Pop
onInotify :: INotify -> String -> CRef -> MVar ServerState -> Event -> IO ()
431 358a0a8f Iustin Pop
onInotify inotify path cref mstate Ignored = do
432 358a0a8f Iustin Pop
  logInfo "File lost, trying to re-establish notifier"
433 358a0a8f Iustin Pop
  modifyMVar_ mstate $ \state -> do
434 358a0a8f Iustin Pop
    result <- addNotifier inotify path cref mstate
435 358a0a8f Iustin Pop
    (newfstat, _) <- safeUpdateConfig path (reloadFStat state) cref
436 358a0a8f Iustin Pop
    let state' = state { reloadFStat = newfstat }
437 358a0a8f Iustin Pop
    if result
438 358a0a8f Iustin Pop
      then return state' -- keep notify
439 358a0a8f Iustin Pop
      else do
440 358a0a8f Iustin Pop
        mode <- moveToPolling "cannot re-establish inotify watch" inotify
441 358a0a8f Iustin Pop
                  path cref mstate
442 358a0a8f Iustin Pop
        return state' { reloadModel = mode }
443 358a0a8f Iustin Pop
444 5b11f8db Iustin Pop
onInotify inotify path cref mstate _ =
445 358a0a8f Iustin Pop
  modifyMVar_ mstate $ \state ->
446 5b11f8db Iustin Pop
    if reloadModel state == ReloadNotify
447 358a0a8f Iustin Pop
       then do
448 358a0a8f Iustin Pop
         ctime <- getCurrentTime
449 358a0a8f Iustin Pop
         (newfstat, _) <- safeUpdateConfig path (reloadFStat state) cref
450 358a0a8f Iustin Pop
         let state' = state { reloadFStat = newfstat, reloadTime = ctime }
451 358a0a8f Iustin Pop
         if abs (reloadTime state - ctime) <
452 358a0a8f Iustin Pop
            fromIntegral C.confdConfigReloadRatelimit
453 358a0a8f Iustin Pop
           then do
454 358a0a8f Iustin Pop
             mode <- moveToPolling "too many reloads" inotify path cref mstate
455 358a0a8f Iustin Pop
             return state' { reloadModel = mode }
456 358a0a8f Iustin Pop
           else return state'
457 358a0a8f Iustin Pop
      else return state
458 358a0a8f Iustin Pop
459 358a0a8f Iustin Pop
-- ** Client input/output handlers
460 358a0a8f Iustin Pop
461 358a0a8f Iustin Pop
-- | Main loop for a given client.
462 358a0a8f Iustin Pop
responder :: CRef -> S.Socket -> HashKey -> String -> S.SockAddr -> IO ()
463 358a0a8f Iustin Pop
responder cfgref socket hmac msg peer = do
464 358a0a8f Iustin Pop
  ctime <- getCurrentTime
465 358a0a8f Iustin Pop
  case parseMessage hmac msg ctime of
466 358a0a8f Iustin Pop
    Ok (origmsg, rq) -> do
467 358a0a8f Iustin Pop
              logDebug $ "Processing request: " ++ origmsg
468 358a0a8f Iustin Pop
              mcfg <- readIORef cfgref
469 358a0a8f Iustin Pop
              let response = respondInner mcfg hmac rq
470 358a0a8f Iustin Pop
              _ <- S.sendTo socket response peer
471 358a0a8f Iustin Pop
              return ()
472 358a0a8f Iustin Pop
    Bad err -> logInfo $ "Failed to parse incoming message: " ++ err
473 358a0a8f Iustin Pop
  return ()
474 358a0a8f Iustin Pop
475 358a0a8f Iustin Pop
-- | Inner helper function for a given client. This generates the
476 358a0a8f Iustin Pop
-- final encoded message (as a string), ready to be sent out to the
477 358a0a8f Iustin Pop
-- client.
478 358a0a8f Iustin Pop
respondInner :: Result (ConfigData, LinkIpMap) -> HashKey
479 358a0a8f Iustin Pop
             -> ConfdRequest -> String
480 358a0a8f Iustin Pop
respondInner cfg hmac rq =
481 358a0a8f Iustin Pop
  let rsalt = confdRqRsalt rq
482 358a0a8f Iustin Pop
      innermsg = serializeResponse (cfg >>= flip buildResponse rq)
483 358a0a8f Iustin Pop
      innerserialised = J.encodeStrict innermsg
484 358a0a8f Iustin Pop
      outermsg = signMessage hmac rsalt innerserialised
485 358a0a8f Iustin Pop
      outerserialised = confdMagicFourcc ++ J.encodeStrict outermsg
486 358a0a8f Iustin Pop
  in outerserialised
487 358a0a8f Iustin Pop
488 358a0a8f Iustin Pop
-- | Main listener loop.
489 358a0a8f Iustin Pop
listener :: S.Socket -> HashKey
490 358a0a8f Iustin Pop
         -> (S.Socket -> HashKey -> String -> S.SockAddr -> IO ())
491 358a0a8f Iustin Pop
         -> IO ()
492 358a0a8f Iustin Pop
listener s hmac resp = do
493 358a0a8f Iustin Pop
  (msg, _, peer) <- S.recvFrom s 4096
494 358a0a8f Iustin Pop
  if confdMagicFourcc `isPrefixOf` msg
495 5b11f8db Iustin Pop
    then forkIO (resp s hmac (drop 4 msg) peer) >> return ()
496 358a0a8f Iustin Pop
    else logDebug "Invalid magic code!" >> return ()
497 358a0a8f Iustin Pop
  return ()
498 358a0a8f Iustin Pop
499 1bf11fff Iustin Pop
-- | Extract the configuration from our IORef.
500 1bf11fff Iustin Pop
configReader :: CRef -> IO (Result ConfigData)
501 1bf11fff Iustin Pop
configReader cref = do
502 1bf11fff Iustin Pop
  cdata <- readIORef cref
503 1bf11fff Iustin Pop
  return $ liftM fst cdata
504 1bf11fff Iustin Pop
505 ef3de7b0 Iustin Pop
-- | Type alias for prepMain results
506 ef3de7b0 Iustin Pop
type PrepResult = (S.Socket, (FilePath, S.Socket),
507 ef3de7b0 Iustin Pop
                   IORef (Result (ConfigData, LinkIpMap)))
508 ef3de7b0 Iustin Pop
509 2ac2e420 Iustin Pop
-- | Check function for confd.
510 ef3de7b0 Iustin Pop
checkMain :: CheckFn (S.Family, S.SockAddr)
511 ef3de7b0 Iustin Pop
checkMain opts = do
512 ef3de7b0 Iustin Pop
  parseresult <- parseAddress opts C.defaultConfdPort
513 ef3de7b0 Iustin Pop
  case parseresult of
514 ef3de7b0 Iustin Pop
    Bad msg -> do
515 ef3de7b0 Iustin Pop
      hPutStrLn stderr $ "parsing bind address: " ++ msg
516 ef3de7b0 Iustin Pop
      return . Left $ ExitFailure 1
517 ef3de7b0 Iustin Pop
    Ok v -> return $ Right v
518 2ac2e420 Iustin Pop
519 2ac2e420 Iustin Pop
-- | Prepare function for confd.
520 ef3de7b0 Iustin Pop
prepMain :: PrepFn (S.Family, S.SockAddr) PrepResult
521 ef3de7b0 Iustin Pop
prepMain _ (af_family, bindaddr) = do
522 19cff311 Iustin Pop
  s <- S.socket af_family S.Datagram S.defaultProtocol
523 19cff311 Iustin Pop
  S.bindSocket s bindaddr
524 ef3de7b0 Iustin Pop
  -- prepare the queryd listener
525 ef3de7b0 Iustin Pop
  query_data <- prepQueryD Nothing
526 358a0a8f Iustin Pop
  cref <- newIORef (Bad "Configuration not yet loaded")
527 ef3de7b0 Iustin Pop
  return (s, query_data, cref)
528 ef3de7b0 Iustin Pop
529 ef3de7b0 Iustin Pop
-- | Main function.
530 ef3de7b0 Iustin Pop
main :: MainFn (S.Family, S.SockAddr) PrepResult
531 ef3de7b0 Iustin Pop
main _ _ (s, query_data, cref) = do
532 358a0a8f Iustin Pop
  statemvar <- newMVar initialState
533 358a0a8f Iustin Pop
  hmac <- getClusterHmac
534 358a0a8f Iustin Pop
  -- Inotify setup
535 358a0a8f Iustin Pop
  inotify <- initINotify
536 29a30533 Iustin Pop
  conf_file <- Path.clusterConfFile
537 29a30533 Iustin Pop
  let inotiaction = addNotifier inotify conf_file cref statemvar
538 358a0a8f Iustin Pop
  -- fork the timeout timer
539 29a30533 Iustin Pop
  _ <- forkIO $ onTimeoutTimer inotiaction conf_file cref statemvar
540 358a0a8f Iustin Pop
  -- fork the polling timer
541 29a30533 Iustin Pop
  _ <- forkIO $ onReloadTimer inotiaction conf_file cref statemvar
542 1bf11fff Iustin Pop
  -- launch the queryd listener
543 4c3f55b8 Iustin Pop
  _ <- forkIO $ runQueryD query_data (configReader cref)
544 358a0a8f Iustin Pop
  -- and finally enter the responder loop
545 358a0a8f Iustin Pop
  forever $ listener s hmac (responder cref)