Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Locking / Allocation.hs @ d8216f2d

History | View | Annotate | Download (11.8 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
  , intersectLocks
38
  ) where
39

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

    
47
import Ganeti.BasicTypes
48
import Ganeti.Locking.Types
49

    
50
{-
51

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

    
58
-}
59

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

    
63
-- | Type describing indirect ownership on a lock. We keep the set
64
-- of all (lock, owner)-pairs for locks that are implied in the given
65
-- lock, annotated with the type of ownership (shared or exclusive).
66
type IndirectOwners a b = M.Map (a, b) OwnerState
67

    
68
-- | The state of a lock that is taken. Besides the state of the lock
69
-- itself, we also keep track of all other lock allocation that affect
70
-- the given lock by means of implication.
71
data AllocationState a b = Exclusive b (IndirectOwners a b)
72
                         | Shared (S.Set b) (IndirectOwners a b)
73
                         deriving (Eq, Show)
74

    
75
-- | Compute the set of indirect owners from the information about
76
-- indirect ownership.
77
indirectOwners :: (Ord a, Ord b) => M.Map (a, b) OwnerState -> S.Set b
78
indirectOwners = S.map snd . M.keysSet
79

    
80
-- | Compute the (zero or one-elment) set of exclusive indirect owners.
81
indirectExclusives :: (Ord a, Ord b) => M.Map (a, b) OwnerState -> S.Set b
82
indirectExclusives = indirectOwners . M.filter (== OwnExclusive)
83

    
84
{-| Representation of a Lock allocation
85

    
86
To keep queries for locks efficient, we keep two
87
associations, with the invariant that they fit
88
together: the association from locks to their
89
allocation state, and the association from an
90
owner to the set of locks owned. As we do not
91
export the constructor, the problem of keeping
92
this invariant reduces to only exporting functions
93
that keep the invariant.
94

    
95
-}
96

    
97
data LockAllocation a b =
98
  LockAllocation { laLocks :: M.Map a (AllocationState a b)
99
                 , laOwned :: M.Map b (M.Map a OwnerState)
100
                 }
101
  deriving (Eq, Show)
102

    
103
-- | A state with all locks being free.
104
emptyAllocation :: (Ord a, Ord b) => LockAllocation a b
105
emptyAllocation =
106
  LockAllocation { laLocks = M.empty
107
                 , laOwned = M.empty
108
                 }
109

    
110
-- | Obtain the locks held by a given owner. The locks are reported
111
-- as a map from the owned locks to the form of ownership (OwnShared
112
-- or OwnExclusive).
113
listLocks :: Ord b => b -> LockAllocation a b -> M.Map a OwnerState
114
listLocks owner = fromMaybe M.empty . M.lookup owner . laOwned
115

    
116
-- | Data Type describing a change request on a single lock.
117
data LockRequest a = LockRequest { lockAffected :: a
118
                                 , lockRequestType :: Maybe OwnerState
119
                                 }
120
                     deriving (Eq, Show)
121

    
122
-- | Lock request for an exclusive lock.
123
requestExclusive :: a -> LockRequest a
124
requestExclusive lock = LockRequest { lockAffected = lock
125
                                    , lockRequestType = Just OwnExclusive }
126

    
127
-- | Lock request for a shared lock.
128
requestShared :: a -> LockRequest a
129
requestShared lock = LockRequest { lockAffected = lock
130
                                 , lockRequestType = Just OwnShared }
131

    
132
-- | Request to release a lock.
133
requestRelease :: a -> LockRequest a
134
requestRelease lock = LockRequest { lockAffected = lock
135
                                  , lockRequestType = Nothing }
136

    
137
-- | Update the Allocation state of a lock according to a given
138
-- function.
139
updateAllocState :: (Ord a, Ord b)
140
                  => (Maybe (AllocationState a b) -> AllocationState a b)
141
                  -> LockAllocation a b -> a -> LockAllocation a b
142
updateAllocState f state lock =
143
  let locks' = M.alter (find (/= Shared S.empty M.empty) . Just . f)
144
                        lock (laLocks state)
145
  in state { laLocks = locks' }
146

    
147
-- | Internal function to update the state according to a single
148
-- lock request, assuming all prerequisites are met.
149
updateLock :: (Ord a, Ord b)
150
           => b
151
           -> LockAllocation a b -> LockRequest a -> LockAllocation a b
152
updateLock owner state (LockRequest lock (Just OwnExclusive)) =
153
  let locks = laLocks state
154
      lockstate' = case M.lookup lock locks of
155
        Just (Exclusive _ i) -> Exclusive owner i
156
        Just (Shared _ i) -> Exclusive owner i
157
        Nothing -> Exclusive owner M.empty
158
      locks' = M.insert lock lockstate' locks
159
      ownersLocks' = M.insert lock OwnExclusive $ listLocks owner state
160
      owned' = M.insert owner ownersLocks' $ laOwned state
161
  in state { laLocks = locks', laOwned = owned' }
162
updateLock owner state (LockRequest lock (Just OwnShared)) =
163
  let ownersLocks' = M.insert lock OwnShared $ listLocks owner state
164
      owned' = M.insert owner ownersLocks' $ laOwned state
165
      locks = laLocks state
166
      lockState' = case M.lookup lock locks of
167
        Just (Exclusive _ i) -> Shared (S.singleton owner) i
168
        Just (Shared s i) -> Shared (S.insert owner s) i
169
        _ -> Shared (S.singleton owner) M.empty
170
      locks' = M.insert lock lockState' locks
171
  in state { laLocks = locks', laOwned = owned' }
172
updateLock owner state (LockRequest lock Nothing) =
173
  let ownersLocks' = M.delete lock $ listLocks owner state
174
      owned = laOwned state
175
      owned' = if M.null ownersLocks'
176
                 then M.delete owner owned
177
                 else M.insert owner ownersLocks' owned
178
      update (Just (Exclusive x i)) = if x == owner
179
                                        then Shared S.empty i
180
                                        else Exclusive x i
181
      update (Just (Shared s i)) = Shared (S.delete owner s) i
182
      update Nothing = Shared S.empty M.empty
183
  in updateAllocState update (state { laOwned = owned' }) lock
184

    
185
-- | Update the set of indirect ownerships of a lock by the given function.
186
updateIndirectSet :: (Ord a, Ord b)
187
                  => (IndirectOwners a b -> IndirectOwners a b)
188
                  -> LockAllocation a b -> a -> LockAllocation a b
189
updateIndirectSet f =
190
  let update (Just (Exclusive x i)) = Exclusive x (f i)
191
      update (Just (Shared s i)) = Shared s (f i)
192
      update Nothing = Shared S.empty (f M.empty)
193
  in updateAllocState update
194

    
195
-- | Update all indirect onwerships of a given lock.
196
updateIndirects :: (Lock a, Ord b)
197
                => b
198
                -> LockAllocation a b -> LockRequest a -> LockAllocation a b
199
updateIndirects owner state req =
200
  let lock = lockAffected req
201
      fn = case lockRequestType req of
202
             Nothing -> M.delete (lock, owner)
203
             Just tp -> M.insert (lock, owner) tp
204
  in foldl (updateIndirectSet fn) state $ lockImplications lock
205

    
206
-- | Update the locks of an owner according to the given request. Return
207
-- the pair of the new state and the result of the operation, which is the
208
-- the set of owners on which the operation was blocked on. so an empty set is
209
-- success, and the state is updated if, and only if, the returned set is emtpy.
210
-- In that way, it can be used in atomicModifyIORef.
211
updateLocks :: (Lock a, Ord b)
212
            => b
213
            -> [LockRequest a]
214
            -> LockAllocation a b -> (LockAllocation a b, Result (S.Set b))
215
updateLocks owner reqs state = genericResult ((,) state . Bad) (second Ok) $ do
216
  unless ((==) (length reqs) . S.size . S.fromList $ map lockAffected reqs)
217
    . runListHead (return ())
218
                  (fail . (++) "Inconsitent requests for lock " . show) $ do
219
      r <- reqs
220
      r' <- reqs
221
      guard $ r /= r'
222
      guard $ lockAffected r == lockAffected r'
223
      return $ lockAffected r
224
  let current = listLocks owner state
225
  unless (M.null current) $ do
226
    let (highest, _) = M.findMax current
227
        notHolding = not
228
                     . any (uncurry (==) . ((M.lookup `flip` current) *** Just))
229
        orderViolation l = fail $ "Order violation: requesting " ++ show l
230
                                   ++ " while holding " ++ show highest
231
    for_ reqs $ \req -> case req of
232
      LockRequest lock (Just OwnExclusive)
233
        | lock < highest && notHolding [ (lock, OwnExclusive) ]
234
        -> orderViolation lock
235
      LockRequest lock (Just OwnShared)
236
        | lock < highest && notHolding [ (lock, OwnExclusive)
237
                                       , (lock, OwnExclusive)]
238
        -> orderViolation lock
239
      _ -> Ok ()
240
  let sharedsHeld = M.keysSet $ M.filter (== OwnShared) current
241
      exclusivesRequested = map lockAffected
242
                            . filter ((== Just OwnExclusive) . lockRequestType)
243
                            $ reqs
244
  runListHead (return ()) fail $ do
245
    x <- exclusivesRequested
246
    i <- lockImplications x
247
    guard $ S.member i sharedsHeld
248
    return $ "Order violation: requesting exclusively " ++ show x
249
              ++ " while holding a shared lock on the group lock " ++ show i
250
              ++ " it belongs to."
251
  let blockedOn (LockRequest  _ Nothing) = S.empty
252
      blockedOn (LockRequest lock (Just OwnExclusive)) =
253
        case M.lookup lock (laLocks state) of
254
          Just (Exclusive x i) ->
255
            S.singleton x `S.union` indirectOwners i
256
          Just (Shared xs i) ->
257
            xs `S.union` indirectOwners i
258
          _ -> S.empty
259
      blockedOn (LockRequest lock (Just OwnShared)) =
260
        case M.lookup lock (laLocks state) of
261
          Just (Exclusive x i) ->
262
            S.singleton x `S.union` indirectExclusives i
263
          Just (Shared _ i) -> indirectExclusives i
264
          _ -> S.empty
265
  let indirectBlocked Nothing _ = S.empty
266
      indirectBlocked (Just OwnShared) lock =
267
        case M.lookup lock (laLocks state) of
268
          Just (Exclusive x _) -> S.singleton x
269
          _ -> S.empty
270
      indirectBlocked (Just OwnExclusive) lock =
271
        case M.lookup lock (laLocks state) of
272
          Just (Exclusive x _) -> S.singleton x
273
          Just (Shared xs _) -> xs
274
          _ -> S.empty
275
  let direct = S.unions $ map blockedOn reqs
276
      indirect = reqs >>= \req ->
277
        map (indirectBlocked (lockRequestType req))
278
          . lockImplications $ lockAffected req
279
  let blocked = S.delete owner . S.unions $ direct:indirect
280
  let state' = foldl (updateLock owner) state reqs
281
      state'' = foldl (updateIndirects owner) state' reqs
282
  return (if S.null blocked then state'' else state, blocked)
283

    
284
-- | Compute the state after an onwer releases all its locks.
285
freeLocks :: (Lock a, Ord b) => LockAllocation a b -> b -> LockAllocation a b
286
freeLocks state owner =
287
  fst . flip (updateLocks owner) state . map requestRelease . M.keys
288
    $ listLocks owner state
289

    
290
-- | Restrict the locks of a user to a given set.
291
intersectLocks :: (Lock a, Ord b) => b -> [a]
292
               -> LockAllocation a b -> LockAllocation a b
293
intersectLocks owner locks state =
294
  let lockset = S.fromList locks
295
      toFree = filter (not . flip S.member lockset)
296
                 . M.keys $ listLocks owner state
297
  in fst $ updateLocks owner (map requestRelease toFree) state