Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (5 kB)

1
{-# LANGUAGE MultiParamTypeClasses, TypeFamilies #-}
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
* working with the client 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
  , ClientState(..)
42
  , WConfdMonadInt
43
  , runWConfdMonadInt
44
  , WConfdMonad
45
  , modifyConfigState
46
  , modifyLockAllocation
47
  ) where
48

    
49
import Control.Applicative
50
import Control.Monad
51
import Control.Monad.Base
52
import Control.Monad.Error
53
import Control.Monad.Trans.Control
54
import Control.Monad.Trans.RWS.Strict
55
import Data.IORef
56

    
57
import Ganeti.BasicTypes
58
import Ganeti.Errors
59
import Ganeti.Locking.Locks
60
import Ganeti.Logging
61
import Ganeti.Types
62
import Ganeti.WConfd.ConfigState
63

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

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

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

    
81
mkDaemonHandle :: FilePath
82
               -> ConfigState
83
               -> GanetiLockAllocation
84
               -> ResultT GanetiException IO DaemonHandle
85
mkDaemonHandle cp cs la =
86
  DaemonHandle <$> liftBase (newIORef $ DaemonState cs la) <*> pure cp
87

    
88
data ClientState = ClientState
89
  { clLiveFilePath :: FilePath
90
  , clJobId :: JobId
91
  }
92

    
93
-- * The monad and its instances
94

    
95
-- | A type alias for easier referring to the actual content of the monad
96
-- when implementing its instances.
97
type WConfdMonadIntType = RWST DaemonHandle () (Maybe ClientState) IO
98

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

    
103
instance Functor WConfdMonadInt where
104
  fmap f = WConfdMonadInt . fmap f . getWConfdMonadInt
105

    
106
instance Applicative WConfdMonadInt where
107
  pure = WConfdMonadInt . pure
108
  WConfdMonadInt f <*> WConfdMonadInt k = WConfdMonadInt $ f <*> k
109

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

    
114
instance MonadIO WConfdMonadInt where
115
  liftIO = WConfdMonadInt . liftIO
116

    
117
instance MonadBase IO WConfdMonadInt where
118
  liftBase = WConfdMonadInt . liftBase
119

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

    
127
instance MonadLog WConfdMonadInt where
128
  logAt p = WConfdMonadInt . logAt p
129

    
130
-- | Runs the internal part of the WConfdMonad monad on a given daemon
131
-- handle.
132
runWConfdMonadInt :: WConfdMonadInt a -> DaemonHandle -> IO a
133
runWConfdMonadInt (WConfdMonadInt k) dhandle =
134
  liftM fst $ evalRWST k dhandle Nothing
135

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

    
139
-- * Basic functions in the monad
140

    
141
-- | Atomically modifies the configuration state in the WConfdMonad.
142
modifyConfigState :: (ConfigState -> (ConfigState, a)) -> WConfdMonad a
143
modifyConfigState f = do
144
  dh <- lift . WConfdMonadInt $ ask
145
  -- TODO: Use lenses to modify the daemons state here
146
  let mf ds = let (cs', r) = f (dsConfigState ds)
147
              in (ds { dsConfigState = cs' }, r)
148
  liftBase $ atomicModifyIORef (dhDaemonState dh) mf
149

    
150
-- | Atomically modifies the lock allocation state in WConfdMonad.
151
modifyLockAllocation :: (GanetiLockAllocation -> (GanetiLockAllocation, a))
152
                     -> WConfdMonad a
153
modifyLockAllocation f = do
154
  dh <- lift . WConfdMonadInt $ ask
155
  let mf ds = let (la', r) = f (dsLockAllocation ds)
156
              in (ds { dsLockAllocation = la' }, r)
157
  liftBase $ atomicModifyIORef (dhDaemonState dh) mf