Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Locking / Allocation.hs @ 1ca6b451

History | View | Annotate | Download (10.9 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_, find)
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
import Ganeti.Locking.Types
48

    
49
{-
50

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

    
57
-}
58

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

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

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

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

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

    
83
{-| Representation of a Lock allocation
84

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

    
94
-}
95

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

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

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

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

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

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

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

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

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

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

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

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

    
272
-- | Compute the state after an onwer releases all its locks.
273
freeLocks :: (Lock a, Ord b) => LockAllocation a b -> b -> LockAllocation a b
274
freeLocks state owner =
275
  fst . flip (updateLocks owner) state . map requestRelease . M.keys
276
    $ listLocks owner state