Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (7.5 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
  ) where
37

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

    
45
import Ganeti.BasicTypes
46

    
47
{-
48

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

    
55
-}
56

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

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

    
63
{-| Representation of a Lock allocation
64

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

    
74
-}
75

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

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

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

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

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

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

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

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

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