Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (5.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
  ) where
49

    
50
import Control.Applicative
51
import Control.Monad
52
import Control.Monad.Base
53
import Control.Monad.Error
54
import Control.Monad.Reader
55
import Control.Monad.Trans.Control
56
import Data.IORef.Lifted
57

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

    
65
-- * Pure data types used in the monad
66

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

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

    
83
mkDaemonHandle :: FilePath
84
               -> ConfigState
85
               -> GanetiLockAllocation
86
               -> (IO ConfigState -> ResultG (AsyncWorker ()))
87
                  -- ^ A function that creates a worker that asynchronously
88
                  -- saves the configuration to the master file.
89
               -> ResultG DaemonHandle
90
mkDaemonHandle cpath cstat lstat saveWorkerFn = do
91
  ds <- newIORef $ DaemonState cstat lstat
92
  saveWorker <- saveWorkerFn $ dsConfigState `liftM` readIORef ds
93
  return $ DaemonHandle ds cpath saveWorker
94

    
95
-- * The monad and its instances
96

    
97
-- | A type alias for easier referring to the actual content of the monad
98
-- when implementing its instances.
99
type WConfdMonadIntType = ReaderT DaemonHandle IO
100

    
101
-- | The internal part of the monad without error handling.
102
newtype WConfdMonadInt a = WConfdMonadInt
103
  { getWConfdMonadInt :: WConfdMonadIntType a }
104

    
105
instance Functor WConfdMonadInt where
106
  fmap f = WConfdMonadInt . fmap f . getWConfdMonadInt
107

    
108
instance Applicative WConfdMonadInt where
109
  pure = WConfdMonadInt . pure
110
  WConfdMonadInt f <*> WConfdMonadInt k = WConfdMonadInt $ f <*> k
111

    
112
instance Monad WConfdMonadInt where
113
  return = WConfdMonadInt . return
114
  (WConfdMonadInt k) >>= f = WConfdMonadInt $ k >>= getWConfdMonadInt . f
115

    
116
instance MonadIO WConfdMonadInt where
117
  liftIO = WConfdMonadInt . liftIO
118

    
119
instance MonadBase IO WConfdMonadInt where
120
  liftBase = WConfdMonadInt . liftBase
121

    
122
instance MonadBaseControl IO WConfdMonadInt where
123
  newtype StM WConfdMonadInt b = StMWConfdMonadInt
124
    { runStMWConfdMonadInt :: StM WConfdMonadIntType b }
125
  liftBaseWith f = WConfdMonadInt . liftBaseWith
126
                   $ \r -> f (liftM StMWConfdMonadInt . r . getWConfdMonadInt)
127
  restoreM = WConfdMonadInt . restoreM . runStMWConfdMonadInt
128

    
129
instance MonadLog WConfdMonadInt where
130
  logAt p = WConfdMonadInt . logAt p
131

    
132
-- | Runs the internal part of the WConfdMonad monad on a given daemon
133
-- handle.
134
runWConfdMonadInt :: WConfdMonadInt a -> DaemonHandle -> IO a
135
runWConfdMonadInt (WConfdMonadInt k) = runReaderT k
136

    
137
-- | The complete monad with error handling.
138
type WConfdMonad = ResultT GanetiException WConfdMonadInt
139

    
140
-- * Basic functions in the monad
141

    
142
-- | Returns the daemon handle.
143
daemonHandle :: WConfdMonad DaemonHandle
144
daemonHandle = lift . WConfdMonadInt $ ask
145

    
146
-- | Returns the current configuration, given a handle
147
readConfigState :: WConfdMonad ConfigState
148
readConfigState = liftM dsConfigState . readIORef . dhDaemonState
149
                  =<< daemonHandle
150

    
151
-- | Atomically modifies the configuration state in the WConfdMonad.
152
modifyConfigState :: (ConfigState -> (ConfigState, a)) -> WConfdMonad a
153
modifyConfigState f = do
154
  dh <- daemonHandle
155
  -- TODO: Use lenses to modify the daemons state here
156
  let mf ds = let (cs', r) = f (dsConfigState ds)
157
              in (ds { dsConfigState = cs' }, r)
158
  r <- atomicModifyIORef (dhDaemonState dh) mf
159
  -- trigger the config. saving worker and wait for it
160
  logDebug "Triggering config write"
161
  liftBase . triggerAndWait . dhSaveConfigWorker $ dh
162
  logDebug "Config write finished"
163
  -- trigger the config. distribution worker asynchronously
164
  -- TODO
165
  return r
166

    
167
-- | Atomically modifies the lock allocation state in WConfdMonad.
168
modifyLockAllocation :: (GanetiLockAllocation -> (GanetiLockAllocation, a))
169
                     -> WConfdMonad a
170
modifyLockAllocation f = do
171
  dh <- lift . WConfdMonadInt $ ask
172
  let mf ds = let (la', r) = f (dsLockAllocation ds)
173
              in (ds { dsLockAllocation = la' }, r)
174
  atomicModifyIORef (dhDaemonState dh) mf
175
  -- TODO: Trigger the async. lock saving worker