Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Locking / Locks.hs @ 1835fd75

History | View | Annotate | Download (5.7 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
                 | NetworkLockSet
67
                 | Network String
68
                 deriving (Ord, Eq, Show)
69

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

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

    
105
instance J.JSON GanetiLocks where
106
  showJSON = J.JSString . J.toJSString . lockName
107
  readJSON = readEitherString >=> lockFromName
108

    
109

    
110
instance Lock GanetiLocks where
111
  lockImplications BGL = []
112
  lockImplications (Instance _) = [InstanceLockSet, BGL]
113
  lockImplications (NodeGroup _) = [NodeGroupLockSet, BGL]
114
  lockImplications NAL = [NodeAllocLockSet, BGL]
115
  lockImplications (NodeRes _) = [NodeResLockSet, BGL]
116
  lockImplications (Node _) = [NodeLockSet, BGL]
117
  lockImplications (Network _) = [NetworkLockSet, BGL]
118
  lockImplications _ = [BGL]
119

    
120
-- | The type of lock Allocations in Ganeti. In Ganeti, the owner of
121
-- locks are jobs.
122
type GanetiLockAllocation = LockAllocation GanetiLocks (JobId, FilePath)
123

    
124
-- | Load a lock allocation from disk.
125
loadLockAllocation :: FilePath -> ResultG GanetiLockAllocation
126
loadLockAllocation =
127
  liftIO . readFile
128
  >=> fromJResultE "parsing lock allocation" . J.decodeStrict
129

    
130
-- | Write lock allocation to disk, overwriting any previously lock
131
-- allocation stored there.
132
writeLocks :: (MonadBase IO m, MonadError GanetiException m, MonadLog m)
133
           => FilePath -> GanetiLockAllocation -> m ()
134
writeLocks fpath lockAlloc = do
135
  logDebug "Async. lock allocation writer: Starting write"
136
  toErrorBase . liftIO . atomicWriteFile fpath $ J.encode lockAlloc
137
  logDebug "Async. lock allocation writer: written"
138

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