Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / WConfd / Monad.hs @ 0d1d2d22

History | View | Annotate | Download (6.8 kB)

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

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

    
5
It encapsulates:
6

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

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

    
15
{-
16

    
17
Copyright (C) 2014 Google Inc.
18

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

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

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

    
34
-}
35

    
36
module Ganeti.WConfd.Monad
37
  ( DaemonHandle
38
  , dhConfigPath
39
  , dhSaveConfigWorker
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

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

    
67
-- * Pure data types used in the monad
68

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

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

    
86
mkDaemonHandle :: FilePath
87
               -> ConfigState
88
               -> GanetiLockAllocation
89
               -> (IO ConfigState -> ResultG (AsyncWorker ()))
90
                  -- ^ A function that creates a worker that asynchronously
91
                  -- saves the configuration to the master file.
92
               -> (IO GanetiLockAllocation -> ResultG (AsyncWorker ()))
93
                  -- ^ A function that creates a worker that asynchronously
94
                  -- saves the lock allocation state.
95
               -> ResultG DaemonHandle
96
mkDaemonHandle cpath cstat lstat saveConfigWorkerFn saveLockWorkerFn = do
97
  ds <- newIORef $ DaemonState cstat lstat
98
  saveConfigWorker <- saveConfigWorkerFn $ dsConfigState `liftM` readIORef ds
99
  saveLockWorker <- saveLockWorkerFn $ dsLockAllocation `liftM` readIORef ds
100
  return $ DaemonHandle ds cpath saveConfigWorker saveLockWorker
101

    
102
-- * The monad and its instances
103

    
104
-- | A type alias for easier referring to the actual content of the monad
105
-- when implementing its instances.
106
type WConfdMonadIntType = ReaderT DaemonHandle IO
107

    
108
-- | The internal part of the monad without error handling.
109
newtype WConfdMonadInt a = WConfdMonadInt
110
  { getWConfdMonadInt :: WConfdMonadIntType a }
111

    
112
instance Functor WConfdMonadInt where
113
  fmap f = WConfdMonadInt . fmap f . getWConfdMonadInt
114

    
115
instance Applicative WConfdMonadInt where
116
  pure = WConfdMonadInt . pure
117
  WConfdMonadInt f <*> WConfdMonadInt k = WConfdMonadInt $ f <*> k
118

    
119
instance Monad WConfdMonadInt where
120
  return = WConfdMonadInt . return
121
  (WConfdMonadInt k) >>= f = WConfdMonadInt $ k >>= getWConfdMonadInt . f
122

    
123
instance MonadIO WConfdMonadInt where
124
  liftIO = WConfdMonadInt . liftIO
125

    
126
instance MonadBase IO WConfdMonadInt where
127
  liftBase = WConfdMonadInt . liftBase
128

    
129
instance MonadBaseControl IO WConfdMonadInt where
130
  newtype StM WConfdMonadInt b = StMWConfdMonadInt
131
    { runStMWConfdMonadInt :: StM WConfdMonadIntType b }
132
  liftBaseWith f = WConfdMonadInt . liftBaseWith
133
                   $ \r -> f (liftM StMWConfdMonadInt . r . getWConfdMonadInt)
134
  restoreM = WConfdMonadInt . restoreM . runStMWConfdMonadInt
135

    
136
instance MonadLog WConfdMonadInt where
137
  logAt p = WConfdMonadInt . logAt p
138

    
139
-- | Runs the internal part of the WConfdMonad monad on a given daemon
140
-- handle.
141
runWConfdMonadInt :: WConfdMonadInt a -> DaemonHandle -> IO a
142
runWConfdMonadInt (WConfdMonadInt k) = runReaderT k
143

    
144
-- | The complete monad with error handling.
145
type WConfdMonad = ResultT GanetiException WConfdMonadInt
146

    
147
-- * Basic functions in the monad
148

    
149
-- | Returns the daemon handle.
150
daemonHandle :: WConfdMonad DaemonHandle
151
daemonHandle = lift . WConfdMonadInt $ ask
152

    
153
-- | Returns the current configuration, given a handle
154
readConfigState :: WConfdMonad ConfigState
155
readConfigState = liftM dsConfigState . readIORef . dhDaemonState
156
                  =<< daemonHandle
157

    
158
-- | Atomically modifies the configuration state in the WConfdMonad.
159
modifyConfigState :: (ConfigState -> (ConfigState, a)) -> WConfdMonad a
160
modifyConfigState f = do
161
  dh <- daemonHandle
162
  -- TODO: Use lenses to modify the daemons state here
163
  let mf ds = let cs = dsConfigState ds
164
                  (cs', r) = f cs
165
              in (ds { dsConfigState = cs' }, (r, cs /= cs'))
166
  (r, modified) <- atomicModifyIORef (dhDaemonState dh) mf
167
  when modified $ do
168
    -- trigger the config. saving worker and wait for it
169
    logDebug "Triggering config write"
170
    liftBase . triggerAndWait . dhSaveConfigWorker $ dh
171
    logDebug "Config write finished"
172
    -- trigger the config. distribution worker asynchronously
173
    -- TODO
174
  return r
175

    
176
-- | Atomically modifies the lock allocation state in WConfdMonad.
177
modifyLockAllocation :: (GanetiLockAllocation -> (GanetiLockAllocation, a))
178
                     -> WConfdMonad a
179
modifyLockAllocation f = do
180
  dh <- lift . WConfdMonadInt $ ask
181
  let mf ds = let (la', r) = f (dsLockAllocation ds)
182
              in (ds { dsLockAllocation = la' }, r)
183
  r <- atomicModifyIORef (dhDaemonState dh) mf
184
  logDebug "Triggering lock state write"
185
  liftBase . triggerAndWait . dhSaveLocksWorker $ dh
186
  logDebug "Lock write finished"
187
  return r
188

    
189
-- | Atomically modifies the lock allocation state in WConfdMonad, not
190
-- producing any result
191
modifyLockAllocation_ :: (GanetiLockAllocation -> GanetiLockAllocation)
192
                      -> WConfdMonad ()
193
modifyLockAllocation_ = modifyLockAllocation . (flip (,) () .)
194

    
195
-- | Read the lock allocation state.
196
readLockAllocation :: WConfdMonad GanetiLockAllocation
197
readLockAllocation = liftM dsLockAllocation . readIORef . dhDaemonState
198
                     =<< daemonHandle