Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Locking / Locks.hs @ ec2355ad

History | View | Annotate | Download (3.9 kB)

1
{-# LANGUAGE ViewPatterns #-}
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
  ) where
33

    
34
import Control.Monad ((>=>))
35
import Data.List (stripPrefix)
36
import qualified Text.JSON as J
37

    
38

    
39
import Ganeti.BasicTypes
40
import Ganeti.Errors (ResultG)
41
import Ganeti.JSON (readEitherString, fromJResultE)
42
import Ganeti.Locking.Allocation
43
import Ganeti.Locking.Types
44
import Ganeti.Types
45

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

    
62
-- | Provide teh String representation of a lock
63
lockName :: GanetiLocks -> String
64
lockName BGL = "cluster/BGL"
65
lockName ClusterLockSet = "cluster/[lockset]"
66
lockName InstanceLockSet = "instance/[lockset]"
67
lockName (Instance uuid) = "instance/" ++ uuid
68
lockName NodeGroupLockSet = "nodegroup/[lockset]"
69
lockName (NodeGroup uuid) = "nodegroup/" ++ uuid
70
lockName NodeAllocLockSet = "node-alloc/[lockset]"
71
lockName NAL = "node-alloc/NAL"
72
lockName NodeResLockSet = "node-res/[lockset]"
73
lockName (NodeRes uuid) = "node-res/" ++ uuid
74
lockName NodeLockSet = "node/[lockset]"
75
lockName (Node uuid) = "node/" ++ uuid
76

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

    
93
instance J.JSON GanetiLocks where
94
  showJSON = J.JSString . J.toJSString . lockName
95
  readJSON = readEitherString >=> lockFromName
96

    
97

    
98
instance Lock GanetiLocks where
99
  lockImplications BGL = []
100
  lockImplications (Instance _) = [InstanceLockSet, BGL]
101
  lockImplications (NodeGroup _) = [NodeGroupLockSet, BGL]
102
  lockImplications NAL = [NodeAllocLockSet, BGL]
103
  lockImplications (NodeRes _) = [NodeResLockSet, BGL]
104
  lockImplications (Node _) = [NodeLockSet, BGL]
105
  lockImplications _ = [BGL]
106

    
107
-- | The type of lock Allocations in Ganeti. In Ganeti, the owner of
108
-- locks are jobs.
109
type GanetiLockAllocation = LockAllocation GanetiLocks (JobId, FilePath)
110

    
111
-- | Load a lock allocation from disk.
112
loadLockAllocation :: FilePath -> ResultG GanetiLockAllocation
113
loadLockAllocation =
114
  liftIO . readFile
115
  >=> fromJResultE "parsing lock allocation" . J.decodeStrict