Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / WConfd / Monad.hs @ a8b9a6e3

History | View | Annotate | Download (7.8 kB)

1
{-# LANGUAGE MultiParamTypeClasses, TypeFamilies, FlexibleContexts #-}
2
{-# LANGUAGE TemplateHaskell #-}
3

    
4
{-| All RPC calls are run within this monad.
5

    
6
It encapsulates:
7

    
8
* IO operations,
9
* failures,
10
* working with the daemon state.
11

    
12
Code that is specific either to the configuration or the lock management, should
13
go into their corresponding dedicated modules.
14
-}
15

    
16
{-
17

    
18
Copyright (C) 2014 Google Inc.
19

    
20
This program is free software; you can redistribute it and/or modify
21
it under the terms of the GNU General Public License as published by
22
the Free Software Foundation; either version 2 of the License, or
23
(at your option) any later version.
24

    
25
This program is distributed in the hope that it will be useful, but
26
WITHOUT ANY WARRANTY; without even the implied warranty of
27
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
28
General Public License for more details.
29

    
30
You should have received a copy of the GNU General Public License
31
along with this program; if not, write to the Free Software
32
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
33
02110-1301, USA.
34

    
35
-}
36

    
37
module Ganeti.WConfd.Monad
38
  ( DaemonHandle
39
  , dhConfigPath
40
  , mkDaemonHandle
41
  , WConfdMonadInt
42
  , runWConfdMonadInt
43
  , WConfdMonad
44
  , daemonHandle
45
  , modifyConfigState
46
  , readConfigState
47
  , modifyLockAllocation
48
  , modifyLockAllocation_
49
  , readLockAllocation
50
  ) where
51

    
52
import Control.Applicative
53
import Control.Monad
54
import Control.Monad.Base
55
import Control.Monad.Error
56
import Control.Monad.Reader
57
import Control.Monad.Trans.Control
58
import Data.IORef.Lifted
59
import Data.Tuple (swap)
60

    
61
import Ganeti.BasicTypes
62
import Ganeti.Errors
63
import Ganeti.Lens
64
import Ganeti.Locking.Locks
65
import Ganeti.Logging
66
import Ganeti.Utils.AsyncWorker
67
import Ganeti.WConfd.ConfigState
68

    
69
-- * Pure data types used in the monad
70

    
71
-- | The state of the daemon, capturing both the configuration state and the
72
-- locking state.
73
data DaemonState = DaemonState
74
  { dsConfigState :: ConfigState
75
  , dsLockAllocation :: GanetiLockAllocation
76
  }
77

    
78
$(makeCustomLenses ''DaemonState)
79

    
80
data DaemonHandle = DaemonHandle
81
  { dhDaemonState :: IORef DaemonState -- ^ The current state of the daemon
82
  , dhConfigPath :: FilePath           -- ^ The configuration file path
83
  -- all static information that doesn't change during the life-time of the
84
  -- daemon should go here;
85
  -- all IDs of threads that do asynchronous work should probably also go here
86
  , dhSaveConfigWorker :: AsyncWorker ()
87
  , dhDistMCsWorker :: AsyncWorker ()
88
  , dhDistSSConfWorker :: AsyncWorker ()
89
  , dhSaveLocksWorker :: AsyncWorker ()
90
  }
91

    
92
mkDaemonHandle :: FilePath
93
               -> ConfigState
94
               -> GanetiLockAllocation
95
               -> (IO ConfigState -> ResultG (AsyncWorker ()))
96
                  -- ^ A function that creates a worker that asynchronously
97
                  -- saves the configuration to the master file.
98
               -> (IO ConfigState -> ResultG (AsyncWorker ()))
99
                  -- ^ A function that creates a worker that asynchronously
100
                  -- distributes the configuration to master candidates
101
               -> (IO ConfigState -> ResultG (AsyncWorker ()))
102
                  -- ^ A function that creates a worker that asynchronously
103
                  -- distributes SSConf to nodes
104
               -> (IO GanetiLockAllocation -> ResultG (AsyncWorker ()))
105
                  -- ^ A function that creates a worker that asynchronously
106
                  -- saves the lock allocation state.
107
               -> ResultG DaemonHandle
108
mkDaemonHandle cpath cstat lstat
109
               saveWorkerFn distMCsWorkerFn distSSConfWorkerFn
110
               saveLockWorkerFn = do
111
  ds <- newIORef $ DaemonState cstat lstat
112
  let readConfigIO = dsConfigState `liftM` readIORef ds :: IO ConfigState
113

    
114
  saveWorker <- saveWorkerFn readConfigIO
115
  ssconfWorker <- distSSConfWorkerFn readConfigIO
116
  distMCsWorker <- distMCsWorkerFn readConfigIO
117

    
118
  saveLockWorker <- saveLockWorkerFn $ dsLockAllocation `liftM` readIORef ds
119

    
120
  return $ DaemonHandle ds cpath saveWorker distMCsWorker ssconfWorker
121
                                 saveLockWorker
122

    
123
-- * The monad and its instances
124

    
125
-- | A type alias for easier referring to the actual content of the monad
126
-- when implementing its instances.
127
type WConfdMonadIntType = ReaderT DaemonHandle IO
128

    
129
-- | The internal part of the monad without error handling.
130
newtype WConfdMonadInt a = WConfdMonadInt
131
  { getWConfdMonadInt :: WConfdMonadIntType a }
132

    
133
instance Functor WConfdMonadInt where
134
  fmap f = WConfdMonadInt . fmap f . getWConfdMonadInt
135

    
136
instance Applicative WConfdMonadInt where
137
  pure = WConfdMonadInt . pure
138
  WConfdMonadInt f <*> WConfdMonadInt k = WConfdMonadInt $ f <*> k
139

    
140
instance Monad WConfdMonadInt where
141
  return = WConfdMonadInt . return
142
  (WConfdMonadInt k) >>= f = WConfdMonadInt $ k >>= getWConfdMonadInt . f
143

    
144
instance MonadIO WConfdMonadInt where
145
  liftIO = WConfdMonadInt . liftIO
146

    
147
instance MonadBase IO WConfdMonadInt where
148
  liftBase = WConfdMonadInt . liftBase
149

    
150
instance MonadBaseControl IO WConfdMonadInt where
151
  newtype StM WConfdMonadInt b = StMWConfdMonadInt
152
    { runStMWConfdMonadInt :: StM WConfdMonadIntType b }
153
  liftBaseWith f = WConfdMonadInt . liftBaseWith
154
                   $ \r -> f (liftM StMWConfdMonadInt . r . getWConfdMonadInt)
155
  restoreM = WConfdMonadInt . restoreM . runStMWConfdMonadInt
156

    
157
instance MonadLog WConfdMonadInt where
158
  logAt p = WConfdMonadInt . logAt p
159

    
160
-- | Runs the internal part of the WConfdMonad monad on a given daemon
161
-- handle.
162
runWConfdMonadInt :: WConfdMonadInt a -> DaemonHandle -> IO a
163
runWConfdMonadInt (WConfdMonadInt k) = runReaderT k
164

    
165
-- | The complete monad with error handling.
166
type WConfdMonad = ResultT GanetiException WConfdMonadInt
167

    
168
-- * Basic functions in the monad
169

    
170
-- | Returns the daemon handle.
171
daemonHandle :: WConfdMonad DaemonHandle
172
daemonHandle = lift . WConfdMonadInt $ ask
173

    
174
-- | Returns the current configuration, given a handle
175
readConfigState :: WConfdMonad ConfigState
176
readConfigState = liftM dsConfigState . readIORef . dhDaemonState
177
                  =<< daemonHandle
178

    
179
-- | Atomically modifies the configuration state in the WConfdMonad.
180
modifyConfigState :: (ConfigState -> (ConfigState, a)) -> WConfdMonad a
181
modifyConfigState f = do
182
  dh <- daemonHandle
183
  let modCS cs = let (cs', r) = f cs
184
                  in ((r, cs /= cs'), cs')
185
  let mf = traverseOf dsConfigStateL modCS
186
  (r, modified) <- atomicModifyIORef (dhDaemonState dh) (swap . mf)
187
  when modified $ do
188
    -- trigger the config. saving worker and wait for it
189
    logDebug "Triggering config write"
190
    liftBase . triggerAndWait . dhSaveConfigWorker $ dh
191
    logDebug "Config write finished"
192
    -- trigger the config. distribution worker synchronously
193
    -- TODO: figure out what configuration changes need synchronous updates
194
    -- and otherwise use asynchronous triggers
195
    _ <- liftBase . triggerAndWaitMany $ [ dhDistMCsWorker dh
196
                                         , dhDistSSConfWorker dh
197
                                         ]
198
    return ()
199
  return r
200

    
201
-- | Atomically modifies the lock allocation state in WConfdMonad.
202
modifyLockAllocation :: (GanetiLockAllocation -> (GanetiLockAllocation, a))
203
                     -> WConfdMonad a
204
modifyLockAllocation f = do
205
  dh <- lift . WConfdMonadInt $ ask
206
  r <- atomicModifyIORef (dhDaemonState dh)
207
                         (swap . traverseOf dsLockAllocationL (swap . f))
208
  logDebug "Triggering lock state write"
209
  liftBase . triggerAndWait . dhSaveLocksWorker $ dh
210
  logDebug "Lock write finished"
211
  return r
212

    
213
-- | Atomically modifies the lock allocation state in WConfdMonad, not
214
-- producing any result
215
modifyLockAllocation_ :: (GanetiLockAllocation -> GanetiLockAllocation)
216
                      -> WConfdMonad ()
217
modifyLockAllocation_ = modifyLockAllocation . (flip (,) () .)
218

    
219
-- | Read the lock allocation state.
220
readLockAllocation :: WConfdMonad GanetiLockAllocation
221
readLockAllocation = liftM dsLockAllocation . readIORef . dhDaemonState
222
                     =<< daemonHandle