Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (5.3 kB)

1 61fd6337 Klaus Aehlig
{-# LANGUAGE ViewPatterns, FlexibleContexts #-}
2 ec2355ad Klaus Aehlig
3 95eb97c8 Klaus Aehlig
{-| Ganeti lock structure
4 95eb97c8 Klaus Aehlig
5 95eb97c8 Klaus Aehlig
-}
6 95eb97c8 Klaus Aehlig
7 95eb97c8 Klaus Aehlig
{-
8 95eb97c8 Klaus Aehlig
9 95eb97c8 Klaus Aehlig
Copyright (C) 2014 Google Inc.
10 95eb97c8 Klaus Aehlig
11 95eb97c8 Klaus Aehlig
This program is free software; you can redistribute it and/or modify
12 95eb97c8 Klaus Aehlig
it under the terms of the GNU General Public License as published by
13 95eb97c8 Klaus Aehlig
the Free Software Foundation; either version 2 of the License, or
14 95eb97c8 Klaus Aehlig
(at your option) any later version.
15 95eb97c8 Klaus Aehlig
16 95eb97c8 Klaus Aehlig
This program is distributed in the hope that it will be useful, but
17 95eb97c8 Klaus Aehlig
WITHOUT ANY WARRANTY; without even the implied warranty of
18 95eb97c8 Klaus Aehlig
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 95eb97c8 Klaus Aehlig
General Public License for more details.
20 95eb97c8 Klaus Aehlig
21 95eb97c8 Klaus Aehlig
You should have received a copy of the GNU General Public License
22 95eb97c8 Klaus Aehlig
along with this program; if not, write to the Free Software
23 95eb97c8 Klaus Aehlig
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 95eb97c8 Klaus Aehlig
02110-1301, USA.
25 95eb97c8 Klaus Aehlig
26 95eb97c8 Klaus Aehlig
-}
27 95eb97c8 Klaus Aehlig
28 95eb97c8 Klaus Aehlig
module Ganeti.Locking.Locks
29 95eb97c8 Klaus Aehlig
  ( GanetiLocks(..)
30 95eb97c8 Klaus Aehlig
  , GanetiLockAllocation
31 c8751a72 Klaus Aehlig
  , loadLockAllocation
32 61fd6337 Klaus Aehlig
  , writeLocksAsyncTask
33 95eb97c8 Klaus Aehlig
  ) where
34 95eb97c8 Klaus Aehlig
35 79786c6b Klaus Aehlig
import Control.Monad ((>=>))
36 61fd6337 Klaus Aehlig
import Control.Monad.Base (MonadBase, liftBase)
37 61fd6337 Klaus Aehlig
import Control.Monad.Error (MonadError, catchError)
38 ec2355ad Klaus Aehlig
import Data.List (stripPrefix)
39 15a53b1e Klaus Aehlig
import qualified Text.JSON as J
40 15a53b1e Klaus Aehlig
41 c8751a72 Klaus Aehlig
42 c8751a72 Klaus Aehlig
import Ganeti.BasicTypes
43 61fd6337 Klaus Aehlig
import Ganeti.Errors (ResultG, GanetiException)
44 79786c6b Klaus Aehlig
import Ganeti.JSON (readEitherString, fromJResultE)
45 95eb97c8 Klaus Aehlig
import Ganeti.Locking.Allocation
46 75033afd Klaus Aehlig
import Ganeti.Locking.Types
47 61fd6337 Klaus Aehlig
import Ganeti.Logging.Lifted (MonadLog, logDebug, logEmergency)
48 95eb97c8 Klaus Aehlig
import Ganeti.Types
49 61fd6337 Klaus Aehlig
import Ganeti.Utils.Atomic
50 61fd6337 Klaus Aehlig
import Ganeti.Utils.AsyncWorker
51 95eb97c8 Klaus Aehlig
52 95eb97c8 Klaus Aehlig
-- | The type of Locks available in Ganeti. The order of this type
53 95eb97c8 Klaus Aehlig
-- is the lock oder.
54 ec2355ad Klaus Aehlig
data GanetiLocks = BGL
55 ec2355ad Klaus Aehlig
                 | ClusterLockSet
56 ec2355ad Klaus Aehlig
                 | InstanceLockSet
57 ec2355ad Klaus Aehlig
                 | Instance String
58 ec2355ad Klaus Aehlig
                 | NodeAllocLockSet
59 ec2355ad Klaus Aehlig
                 | NAL
60 1310339c Klaus Aehlig
                 | NodeGroupLockSet
61 1310339c Klaus Aehlig
                 | NodeGroup String
62 ec2355ad Klaus Aehlig
                 | NodeLockSet
63 ec2355ad Klaus Aehlig
                 | Node String
64 1310339c Klaus Aehlig
                 | NodeResLockSet
65 1310339c Klaus Aehlig
                 | NodeRes String
66 ec2355ad Klaus Aehlig
                 deriving (Ord, Eq, Show)
67 95eb97c8 Klaus Aehlig
68 1310339c Klaus Aehlig
-- | Provide the String representation of a lock
69 79786c6b Klaus Aehlig
lockName :: GanetiLocks -> String
70 79786c6b Klaus Aehlig
lockName BGL = "cluster/BGL"
71 ec2355ad Klaus Aehlig
lockName ClusterLockSet = "cluster/[lockset]"
72 ec2355ad Klaus Aehlig
lockName InstanceLockSet = "instance/[lockset]"
73 1310339c Klaus Aehlig
lockName NodeAllocLockSet = "node-alloc/[lockset]"
74 1310339c Klaus Aehlig
lockName NAL = "node-alloc/NAL"
75 ec2355ad Klaus Aehlig
lockName (Instance uuid) = "instance/" ++ uuid
76 ec2355ad Klaus Aehlig
lockName NodeGroupLockSet = "nodegroup/[lockset]"
77 ec2355ad Klaus Aehlig
lockName (NodeGroup uuid) = "nodegroup/" ++ uuid
78 ec2355ad Klaus Aehlig
lockName NodeLockSet = "node/[lockset]"
79 ec2355ad Klaus Aehlig
lockName (Node uuid) = "node/" ++ uuid
80 1310339c Klaus Aehlig
lockName NodeResLockSet = "node-res/[lockset]"
81 1310339c Klaus Aehlig
lockName (NodeRes uuid) = "node-res/" ++ uuid
82 15a53b1e Klaus Aehlig
83 79786c6b Klaus Aehlig
-- | Obtain a lock from its name.
84 79786c6b Klaus Aehlig
lockFromName :: String -> J.Result GanetiLocks
85 79786c6b Klaus Aehlig
lockFromName "cluster/BGL" = return BGL
86 ec2355ad Klaus Aehlig
lockFromName "cluster/[lockset]" = return ClusterLockSet
87 ec2355ad Klaus Aehlig
lockFromName "instance/[lockset]" = return InstanceLockSet
88 ec2355ad Klaus Aehlig
lockFromName (stripPrefix "instance/" -> Just uuid) = return $ Instance uuid
89 ec2355ad Klaus Aehlig
lockFromName "nodegroup/[lockset]" = return NodeGroupLockSet
90 ec2355ad Klaus Aehlig
lockFromName (stripPrefix "nodegroup/" -> Just uuid) = return $ NodeGroup uuid
91 ec2355ad Klaus Aehlig
lockFromName "node-alloc/[lockset]" = return NodeAllocLockSet
92 ec2355ad Klaus Aehlig
lockFromName "node-alloc/NAL" = return NAL
93 ec2355ad Klaus Aehlig
lockFromName "node-res/[lockset]" = return NodeResLockSet
94 ec2355ad Klaus Aehlig
lockFromName (stripPrefix "node-res/" -> Just uuid) = return $ NodeRes uuid
95 ec2355ad Klaus Aehlig
lockFromName "node/[lockset]" = return NodeLockSet
96 ec2355ad Klaus Aehlig
lockFromName (stripPrefix "node/" -> Just uuid) = return $ Node uuid
97 79786c6b Klaus Aehlig
lockFromName n = fail $ "Unknown lock name '" ++ n ++ "'"
98 15a53b1e Klaus Aehlig
99 15a53b1e Klaus Aehlig
instance J.JSON GanetiLocks where
100 79786c6b Klaus Aehlig
  showJSON = J.JSString . J.toJSString . lockName
101 79786c6b Klaus Aehlig
  readJSON = readEitherString >=> lockFromName
102 15a53b1e Klaus Aehlig
103 15a53b1e Klaus Aehlig
104 75033afd Klaus Aehlig
instance Lock GanetiLocks where
105 75033afd Klaus Aehlig
  lockImplications BGL = []
106 ec2355ad Klaus Aehlig
  lockImplications (Instance _) = [InstanceLockSet, BGL]
107 ec2355ad Klaus Aehlig
  lockImplications (NodeGroup _) = [NodeGroupLockSet, BGL]
108 ec2355ad Klaus Aehlig
  lockImplications NAL = [NodeAllocLockSet, BGL]
109 ec2355ad Klaus Aehlig
  lockImplications (NodeRes _) = [NodeResLockSet, BGL]
110 ec2355ad Klaus Aehlig
  lockImplications (Node _) = [NodeLockSet, BGL]
111 ec2355ad Klaus Aehlig
  lockImplications _ = [BGL]
112 75033afd Klaus Aehlig
113 95eb97c8 Klaus Aehlig
-- | The type of lock Allocations in Ganeti. In Ganeti, the owner of
114 95eb97c8 Klaus Aehlig
-- locks are jobs.
115 e1e36b88 Klaus Aehlig
type GanetiLockAllocation = LockAllocation GanetiLocks (JobId, FilePath)
116 c8751a72 Klaus Aehlig
117 c8751a72 Klaus Aehlig
-- | Load a lock allocation from disk.
118 c8751a72 Klaus Aehlig
loadLockAllocation :: FilePath -> ResultG GanetiLockAllocation
119 c8751a72 Klaus Aehlig
loadLockAllocation =
120 c8751a72 Klaus Aehlig
  liftIO . readFile
121 c8751a72 Klaus Aehlig
  >=> fromJResultE "parsing lock allocation" . J.decodeStrict
122 61fd6337 Klaus Aehlig
123 61fd6337 Klaus Aehlig
-- | Write lock allocation to disk, overwriting any previously lock
124 61fd6337 Klaus Aehlig
-- allocation stored there.
125 61fd6337 Klaus Aehlig
writeLocks :: (MonadBase IO m, MonadError GanetiException m, MonadLog m)
126 61fd6337 Klaus Aehlig
           => FilePath -> GanetiLockAllocation -> m ()
127 61fd6337 Klaus Aehlig
writeLocks fpath lockAlloc = do
128 61fd6337 Klaus Aehlig
  logDebug "Async. lock allocation writer: Starting write"
129 61fd6337 Klaus Aehlig
  toErrorBase . liftIO . atomicWriteFile fpath $ J.encode lockAlloc
130 61fd6337 Klaus Aehlig
  logDebug "Async. lock allocation writer: written"
131 61fd6337 Klaus Aehlig
132 61fd6337 Klaus Aehlig
-- | Construct an asynchronous worker whose action is to save the
133 61fd6337 Klaus Aehlig
-- current state of the lock allocation.
134 61fd6337 Klaus Aehlig
-- The worker's action reads the lock allocation using the given @IO@
135 61fd6337 Klaus Aehlig
-- action. Any inbetween changes to the file are tacitly ignored.
136 61fd6337 Klaus Aehlig
writeLocksAsyncTask :: FilePath -- ^ Path to the lock file
137 61fd6337 Klaus Aehlig
                    -> IO GanetiLockAllocation -- ^ An action to read the
138 61fd6337 Klaus Aehlig
                                               -- current lock allocation
139 61fd6337 Klaus Aehlig
                    -> ResultG (AsyncWorker ())
140 61fd6337 Klaus Aehlig
writeLocksAsyncTask fpath lockAllocAction = mkAsyncWorker $
141 61fd6337 Klaus Aehlig
  catchError (do
142 61fd6337 Klaus Aehlig
    locks <- liftBase lockAllocAction
143 61fd6337 Klaus Aehlig
    writeLocks fpath locks
144 61fd6337 Klaus Aehlig
  ) (logEmergency . (++) "Can't write lock allocation status: " . show)