Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Locking / Locks.hs @ 1310339c

History | View | Annotate | Download (5.3 kB)

1
{-# LANGUAGE ViewPatterns, FlexibleContexts #-}
2

    
3
{-| Ganeti lock structure
4

    
5
-}
6

    
7
{-
8

    
9
Copyright (C) 2014 Google Inc.
10

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

    
16
This program is distributed in the hope that it will be useful, but
17
WITHOUT ANY WARRANTY; without even the implied warranty of
18
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19
General Public License for more details.
20

    
21
You should have received a copy of the GNU General Public License
22
along with this program; if not, write to the Free Software
23
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24
02110-1301, USA.
25

    
26
-}
27

    
28
module Ganeti.Locking.Locks
29
  ( GanetiLocks(..)
30
  , GanetiLockAllocation
31
  , loadLockAllocation
32
  , writeLocksAsyncTask
33
  ) where
34

    
35
import Control.Monad ((>=>))
36
import Control.Monad.Base (MonadBase, liftBase)
37
import Control.Monad.Error (MonadError, catchError)
38
import Data.List (stripPrefix)
39
import qualified Text.JSON as J
40

    
41

    
42
import Ganeti.BasicTypes
43
import Ganeti.Errors (ResultG, GanetiException)
44
import Ganeti.JSON (readEitherString, fromJResultE)
45
import Ganeti.Locking.Allocation
46
import Ganeti.Locking.Types
47
import Ganeti.Logging.Lifted (MonadLog, logDebug, logEmergency)
48
import Ganeti.Types
49
import Ganeti.Utils.Atomic
50
import Ganeti.Utils.AsyncWorker
51

    
52
-- | The type of Locks available in Ganeti. The order of this type
53
-- is the lock oder.
54
data GanetiLocks = BGL
55
                 | ClusterLockSet
56
                 | InstanceLockSet
57
                 | Instance String
58
                 | NodeAllocLockSet
59
                 | NAL
60
                 | NodeGroupLockSet
61
                 | NodeGroup String
62
                 | NodeLockSet
63
                 | Node String
64
                 | NodeResLockSet
65
                 | NodeRes String
66
                 deriving (Ord, Eq, Show)
67

    
68
-- | Provide the String representation of a lock
69
lockName :: GanetiLocks -> String
70
lockName BGL = "cluster/BGL"
71
lockName ClusterLockSet = "cluster/[lockset]"
72
lockName InstanceLockSet = "instance/[lockset]"
73
lockName NodeAllocLockSet = "node-alloc/[lockset]"
74
lockName NAL = "node-alloc/NAL"
75
lockName (Instance uuid) = "instance/" ++ uuid
76
lockName NodeGroupLockSet = "nodegroup/[lockset]"
77
lockName (NodeGroup uuid) = "nodegroup/" ++ uuid
78
lockName NodeLockSet = "node/[lockset]"
79
lockName (Node uuid) = "node/" ++ uuid
80
lockName NodeResLockSet = "node-res/[lockset]"
81
lockName (NodeRes uuid) = "node-res/" ++ uuid
82

    
83
-- | Obtain a lock from its name.
84
lockFromName :: String -> J.Result GanetiLocks
85
lockFromName "cluster/BGL" = return BGL
86
lockFromName "cluster/[lockset]" = return ClusterLockSet
87
lockFromName "instance/[lockset]" = return InstanceLockSet
88
lockFromName (stripPrefix "instance/" -> Just uuid) = return $ Instance uuid
89
lockFromName "nodegroup/[lockset]" = return NodeGroupLockSet
90
lockFromName (stripPrefix "nodegroup/" -> Just uuid) = return $ NodeGroup uuid
91
lockFromName "node-alloc/[lockset]" = return NodeAllocLockSet
92
lockFromName "node-alloc/NAL" = return NAL
93
lockFromName "node-res/[lockset]" = return NodeResLockSet
94
lockFromName (stripPrefix "node-res/" -> Just uuid) = return $ NodeRes uuid
95
lockFromName "node/[lockset]" = return NodeLockSet
96
lockFromName (stripPrefix "node/" -> Just uuid) = return $ Node uuid
97
lockFromName n = fail $ "Unknown lock name '" ++ n ++ "'"
98

    
99
instance J.JSON GanetiLocks where
100
  showJSON = J.JSString . J.toJSString . lockName
101
  readJSON = readEitherString >=> lockFromName
102

    
103

    
104
instance Lock GanetiLocks where
105
  lockImplications BGL = []
106
  lockImplications (Instance _) = [InstanceLockSet, BGL]
107
  lockImplications (NodeGroup _) = [NodeGroupLockSet, BGL]
108
  lockImplications NAL = [NodeAllocLockSet, BGL]
109
  lockImplications (NodeRes _) = [NodeResLockSet, BGL]
110
  lockImplications (Node _) = [NodeLockSet, BGL]
111
  lockImplications _ = [BGL]
112

    
113
-- | The type of lock Allocations in Ganeti. In Ganeti, the owner of
114
-- locks are jobs.
115
type GanetiLockAllocation = LockAllocation GanetiLocks (JobId, FilePath)
116

    
117
-- | Load a lock allocation from disk.
118
loadLockAllocation :: FilePath -> ResultG GanetiLockAllocation
119
loadLockAllocation =
120
  liftIO . readFile
121
  >=> fromJResultE "parsing lock allocation" . J.decodeStrict
122

    
123
-- | Write lock allocation to disk, overwriting any previously lock
124
-- allocation stored there.
125
writeLocks :: (MonadBase IO m, MonadError GanetiException m, MonadLog m)
126
           => FilePath -> GanetiLockAllocation -> m ()
127
writeLocks fpath lockAlloc = do
128
  logDebug "Async. lock allocation writer: Starting write"
129
  toErrorBase . liftIO . atomicWriteFile fpath $ J.encode lockAlloc
130
  logDebug "Async. lock allocation writer: written"
131

    
132
-- | Construct an asynchronous worker whose action is to save the
133
-- current state of the lock allocation.
134
-- The worker's action reads the lock allocation using the given @IO@
135
-- action. Any inbetween changes to the file are tacitly ignored.
136
writeLocksAsyncTask :: FilePath -- ^ Path to the lock file
137
                    -> IO GanetiLockAllocation -- ^ An action to read the
138
                                               -- current lock allocation
139
                    -> ResultG (AsyncWorker ())
140
writeLocksAsyncTask fpath lockAllocAction = mkAsyncWorker $
141
  catchError (do
142
    locks <- liftBase lockAllocAction
143
    writeLocks fpath locks
144
  ) (logEmergency . (++) "Can't write lock allocation status: " . show)