Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / WConfd / Monad.hs @ 3e80d1b7

History | View | Annotate | Download (6 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
  , readLockAllocation
49
  ) where
50

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

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

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

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

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

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

    
96
-- * The monad and its instances
97

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

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

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

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

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

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

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

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

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

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

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

    
141
-- * Basic functions in the monad
142

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

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

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

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

    
178
-- | Read the lock allocation state.
179
readLockAllocation :: WConfdMonad GanetiLockAllocation
180
readLockAllocation = liftM dsLockAllocation . readIORef . dhDaemonState
181
                     =<< daemonHandle