Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (6.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
  , dhSaveConfigWorker
41
  , mkDaemonHandle
42
  , WConfdMonadInt
43
  , runWConfdMonadInt
44
  , WConfdMonad
45
  , daemonHandle
46
  , modifyConfigState
47
  , readConfigState
48
  , modifyLockAllocation
49
  , modifyLockAllocation_
50
  , readLockAllocation
51
  ) where
52

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

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

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

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

    
79
$(makeCustomLenses ''DaemonState)
80

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

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

    
107
-- * The monad and its instances
108

    
109
-- | A type alias for easier referring to the actual content of the monad
110
-- when implementing its instances.
111
type WConfdMonadIntType = ReaderT DaemonHandle IO
112

    
113
-- | The internal part of the monad without error handling.
114
newtype WConfdMonadInt a = WConfdMonadInt
115
  { getWConfdMonadInt :: WConfdMonadIntType a }
116

    
117
instance Functor WConfdMonadInt where
118
  fmap f = WConfdMonadInt . fmap f . getWConfdMonadInt
119

    
120
instance Applicative WConfdMonadInt where
121
  pure = WConfdMonadInt . pure
122
  WConfdMonadInt f <*> WConfdMonadInt k = WConfdMonadInt $ f <*> k
123

    
124
instance Monad WConfdMonadInt where
125
  return = WConfdMonadInt . return
126
  (WConfdMonadInt k) >>= f = WConfdMonadInt $ k >>= getWConfdMonadInt . f
127

    
128
instance MonadIO WConfdMonadInt where
129
  liftIO = WConfdMonadInt . liftIO
130

    
131
instance MonadBase IO WConfdMonadInt where
132
  liftBase = WConfdMonadInt . liftBase
133

    
134
instance MonadBaseControl IO WConfdMonadInt where
135
  newtype StM WConfdMonadInt b = StMWConfdMonadInt
136
    { runStMWConfdMonadInt :: StM WConfdMonadIntType b }
137
  liftBaseWith f = WConfdMonadInt . liftBaseWith
138
                   $ \r -> f (liftM StMWConfdMonadInt . r . getWConfdMonadInt)
139
  restoreM = WConfdMonadInt . restoreM . runStMWConfdMonadInt
140

    
141
instance MonadLog WConfdMonadInt where
142
  logAt p = WConfdMonadInt . logAt p
143

    
144
-- | Runs the internal part of the WConfdMonad monad on a given daemon
145
-- handle.
146
runWConfdMonadInt :: WConfdMonadInt a -> DaemonHandle -> IO a
147
runWConfdMonadInt (WConfdMonadInt k) = runReaderT k
148

    
149
-- | The complete monad with error handling.
150
type WConfdMonad = ResultT GanetiException WConfdMonadInt
151

    
152
-- * Basic functions in the monad
153

    
154
-- | Returns the daemon handle.
155
daemonHandle :: WConfdMonad DaemonHandle
156
daemonHandle = lift . WConfdMonadInt $ ask
157

    
158
-- | Returns the current configuration, given a handle
159
readConfigState :: WConfdMonad ConfigState
160
readConfigState = liftM dsConfigState . readIORef . dhDaemonState
161
                  =<< daemonHandle
162

    
163
-- | Atomically modifies the configuration state in the WConfdMonad.
164
modifyConfigState :: (ConfigState -> (ConfigState, a)) -> WConfdMonad a
165
modifyConfigState f = do
166
  dh <- daemonHandle
167
  let modCS cs = let (cs', r) = f cs
168
                  in ((r, cs /= cs'), cs')
169
  let mf = traverseOf dsConfigStateL modCS
170
  (r, modified) <- atomicModifyIORef (dhDaemonState dh) (swap . mf)
171
  when modified $ do
172
    -- trigger the config. saving worker and wait for it
173
    logDebug "Triggering config write"
174
    liftBase . triggerAndWait . dhSaveConfigWorker $ dh
175
    logDebug "Config write finished"
176
    -- trigger the config. distribution worker asynchronously
177
    -- TODO
178
  return r
179

    
180
-- | Atomically modifies the lock allocation state in WConfdMonad.
181
modifyLockAllocation :: (GanetiLockAllocation -> (GanetiLockAllocation, a))
182
                     -> WConfdMonad a
183
modifyLockAllocation f = do
184
  dh <- lift . WConfdMonadInt $ ask
185
  r <- atomicModifyIORef (dhDaemonState dh)
186
                         (swap . traverseOf dsLockAllocationL (swap . f))
187
  logDebug "Triggering lock state write"
188
  liftBase . triggerAndWait . dhSaveLocksWorker $ dh
189
  logDebug "Lock write finished"
190
  return r
191

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

    
198
-- | Read the lock allocation state.
199
readLockAllocation :: WConfdMonad GanetiLockAllocation
200
readLockAllocation = liftM dsLockAllocation . readIORef . dhDaemonState
201
                     =<< daemonHandle