Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Locking / Allocation.hs @ 80004e70

History | View | Annotate | Download (7.7 kB)

1
{-| Implementation of lock allocation.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2014 Google Inc.
8

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

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

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

    
24
-}
25

    
26
module Ganeti.Locking.Allocation
27
  ( LockAllocation
28
  , emptyAllocation
29
  , OwnerState(..)
30
  , listLocks
31
  , LockRequest(..)
32
  , requestExclusive
33
  , requestShared
34
  , requestRelease
35
  , updateLocks
36
  , freeLocks
37
  ) where
38

    
39
import Control.Arrow (second, (***))
40
import Control.Monad
41
import Data.Foldable (for_)
42
import qualified Data.Map as M
43
import Data.Maybe (fromMaybe)
44
import qualified Data.Set as S
45

    
46
import Ganeti.BasicTypes
47

    
48
{-
49

    
50
This module is parametric in the type of locks and lock owners.
51
While we only state minimal requirements for the types, we will
52
consistently use the type variable 'a' for the type of locks and
53
the variable 'b' for the type of the lock owners throughout this
54
module.
55

    
56
-}
57

    
58
-- | The state of a lock that is taken.
59
data AllocationState a = Exclusive a | Shared (S.Set a) deriving (Eq, Show)
60

    
61
-- | Data type describing the way a lock can be owned.
62
data OwnerState = OwnShared | OwnExclusive deriving (Ord, Eq, Show)
63

    
64
{-| Representation of a Lock allocation
65

    
66
To keep queries for locks efficient, we keep two
67
associations, with the invariant that they fit
68
together: the association from locks to their
69
allocation state, and the association from an
70
owner to the set of locks owned. As we do not
71
export the constructor, the problem of keeping
72
this invariant reduces to only exporting functions
73
that keep the invariant.
74

    
75
-}
76

    
77
data LockAllocation a b =
78
  LockAllocation { laLocks :: M.Map a (AllocationState b)
79
                 , laOwned :: M.Map b (M.Map a OwnerState)
80
                 }
81
  deriving (Eq, Show)
82

    
83
-- | A state with all locks being free.
84
emptyAllocation :: (Ord a, Ord b) => LockAllocation a b
85
emptyAllocation =
86
  LockAllocation { laLocks = M.empty
87
                 , laOwned = M.empty
88
                 }
89

    
90
-- | Obtain the locks held by a given owner. The locks are reported
91
-- as a map from the owned locks to the form of ownership (OwnShared
92
-- or OwnExclusive).
93
listLocks :: Ord b => b -> LockAllocation a b -> M.Map a OwnerState
94
listLocks owner = fromMaybe M.empty . M.lookup owner . laOwned
95

    
96
-- | Data Type describing a change request on a single lock.
97
data LockRequest a = LockRequest { lockAffected :: a
98
                                 , lockRequestType :: Maybe OwnerState
99
                                 }
100
                     deriving (Eq, Show)
101

    
102
-- | Lock request for an exclusive lock.
103
requestExclusive :: a -> LockRequest a
104
requestExclusive lock = LockRequest { lockAffected = lock
105
                                    , lockRequestType = Just OwnExclusive }
106

    
107
-- | Lock request for a shared lock.
108
requestShared :: a -> LockRequest a
109
requestShared lock = LockRequest { lockAffected = lock
110
                                 , lockRequestType = Just OwnShared }
111

    
112
-- | Request to release a lock.
113
requestRelease :: a -> LockRequest a
114
requestRelease lock = LockRequest { lockAffected = lock
115
                                  , lockRequestType = Nothing }
116

    
117
-- | Internal function to update the state according to a single
118
-- lock request, assuming all prerequisites are met.
119
updateLock :: (Ord a, Ord b)
120
           => b
121
           -> LockAllocation a b -> LockRequest a -> LockAllocation a b
122
updateLock owner state (LockRequest lock (Just OwnExclusive)) =
123
  let locks' = M.insert lock (Exclusive owner) $ laLocks state
124
      ownersLocks' = M.insert lock OwnExclusive $ listLocks owner state
125
      owned' = M.insert owner ownersLocks' $ laOwned state
126
  in state { laLocks = locks', laOwned = owned' }
127
updateLock owner state (LockRequest lock (Just OwnShared)) =
128
  let ownersLocks' = M.insert lock OwnShared $ listLocks owner state
129
      owned' = M.insert owner ownersLocks' $ laOwned state
130
      locks = laLocks state
131
      lockState' = case M.lookup lock locks of
132
        Just (Shared s) -> Shared (S.insert owner s)
133
        _ -> Shared $ S.singleton owner
134
      locks' = M.insert lock lockState' locks
135
  in state { laLocks = locks', laOwned = owned' }
136
updateLock owner state (LockRequest lock Nothing) =
137
  let ownersLocks' = M.delete lock $ listLocks owner state
138
      owned = laOwned state
139
      owned' = if M.null ownersLocks'
140
                 then M.delete owner owned
141
                 else M.insert owner ownersLocks' owned
142
      locks = laLocks state
143
      lockRemoved = M.delete lock locks
144
      locks' = case M.lookup lock locks of
145
                 Nothing -> locks
146
                 Just (Exclusive x) ->
147
                   if x == owner then lockRemoved else locks
148
                 Just (Shared s)
149
                   -> let s' = S.delete owner s
150
                      in if S.null s'
151
                        then lockRemoved
152
                        else M.insert lock (Shared s') locks
153
  in state { laLocks = locks', laOwned = owned' }
154

    
155
-- | Update the locks of an owner according to the given request. Return
156
-- the pair of the new state and the result of the operation, which is the
157
-- the set of owners on which the operation was blocked on. so an empty set is
158
-- success, and the state is updated if, and only if, the returned set is emtpy.
159
-- In that way, it can be used in atomicModifyIORef.
160
updateLocks :: (Ord a, Show a, Ord b)
161
               => b
162
               -> [LockRequest a]
163
               -> LockAllocation a b -> (LockAllocation a b, Result (S.Set b))
164
updateLocks owner reqs state = genericResult ((,) state . Bad) (second Ok) $ do
165
  runListHead (return ())
166
              (fail . (++) "Inconsitent requests for lock " . show) $ do
167
      r <- reqs
168
      r' <- reqs
169
      guard $ r /= r'
170
      guard $ lockAffected r == lockAffected r'
171
      return $ lockAffected r
172
  let current = listLocks owner state
173
  unless (M.null current) $ do
174
    let (highest, _) = M.findMax current
175
        notHolding = not
176
                     . any (uncurry (==) . ((M.lookup `flip` current) *** Just))
177
        orderViolation l = fail $ "Order violation: requesting " ++ show l
178
                                   ++ " while holding " ++ show highest
179
    for_ reqs $ \req -> case req of
180
      LockRequest lock (Just OwnExclusive)
181
        | lock < highest && notHolding [ (lock, OwnExclusive) ]
182
        -> orderViolation lock
183
      LockRequest lock (Just OwnShared)
184
        | lock < highest && notHolding [ (lock, OwnExclusive)
185
                                       , (lock, OwnExclusive)]
186
        -> orderViolation lock
187
      _ -> Ok ()
188
  let blockedOn (LockRequest  _ Nothing) = S.empty
189
      blockedOn (LockRequest lock (Just OwnExclusive)) =
190
        case M.lookup lock (laLocks state) of
191
          Just (Exclusive x) -> S.singleton x
192
          Just (Shared xs) -> xs
193
          _ -> S.empty
194
      blockedOn (LockRequest lock (Just OwnShared)) =
195
        case M.lookup lock (laLocks state) of
196
          Just (Exclusive x) -> S.singleton x
197
          _ -> S.empty
198
  let blocked = S.delete owner . S.unions $ map blockedOn reqs
199
  let state' = foldl (updateLock owner) state reqs
200
  return (if S.null blocked then state' else state, blocked)
201

    
202
-- | Compute the state after an onwer releases all its locks.
203
freeLocks :: (Lock a, Ord b) => LockAllocation a b -> b -> LockAllocation a b
204
freeLocks state owner =
205
  fst . flip (updateLocks owner) state . map requestRelease . M.keys
206
    $ listLocks owner state