Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (11.8 kB)

1 c2b8d366 Klaus Aehlig
{-| Implementation of lock allocation.
2 c2b8d366 Klaus Aehlig
3 c2b8d366 Klaus Aehlig
-}
4 c2b8d366 Klaus Aehlig
5 c2b8d366 Klaus Aehlig
{-
6 c2b8d366 Klaus Aehlig
7 c2b8d366 Klaus Aehlig
Copyright (C) 2014 Google Inc.
8 c2b8d366 Klaus Aehlig
9 c2b8d366 Klaus Aehlig
This program is free software; you can redistribute it and/or modify
10 c2b8d366 Klaus Aehlig
it under the terms of the GNU General Public License as published by
11 c2b8d366 Klaus Aehlig
the Free Software Foundation; either version 2 of the License, or
12 c2b8d366 Klaus Aehlig
(at your option) any later version.
13 c2b8d366 Klaus Aehlig
14 c2b8d366 Klaus Aehlig
This program is distributed in the hope that it will be useful, but
15 c2b8d366 Klaus Aehlig
WITHOUT ANY WARRANTY; without even the implied warranty of
16 c2b8d366 Klaus Aehlig
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 c2b8d366 Klaus Aehlig
General Public License for more details.
18 c2b8d366 Klaus Aehlig
19 c2b8d366 Klaus Aehlig
You should have received a copy of the GNU General Public License
20 c2b8d366 Klaus Aehlig
along with this program; if not, write to the Free Software
21 c2b8d366 Klaus Aehlig
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 c2b8d366 Klaus Aehlig
02110-1301, USA.
23 c2b8d366 Klaus Aehlig
24 c2b8d366 Klaus Aehlig
-}
25 c2b8d366 Klaus Aehlig
26 c2b8d366 Klaus Aehlig
module Ganeti.Locking.Allocation
27 c2b8d366 Klaus Aehlig
  ( LockAllocation
28 c2b8d366 Klaus Aehlig
  , emptyAllocation
29 c2b8d366 Klaus Aehlig
  , OwnerState(..)
30 c2b8d366 Klaus Aehlig
  , listLocks
31 15208e95 Klaus Aehlig
  , LockRequest(..)
32 15208e95 Klaus Aehlig
  , requestExclusive
33 15208e95 Klaus Aehlig
  , requestShared
34 15208e95 Klaus Aehlig
  , requestRelease
35 15208e95 Klaus Aehlig
  , updateLocks
36 80004e70 Klaus Aehlig
  , freeLocks
37 d8216f2d Klaus Aehlig
  , intersectLocks
38 c2b8d366 Klaus Aehlig
  ) where
39 c2b8d366 Klaus Aehlig
40 15208e95 Klaus Aehlig
import Control.Arrow (second, (***))
41 15208e95 Klaus Aehlig
import Control.Monad
42 381889dc Klaus Aehlig
import Data.Foldable (for_, find)
43 c2b8d366 Klaus Aehlig
import qualified Data.Map as M
44 c2b8d366 Klaus Aehlig
import Data.Maybe (fromMaybe)
45 c2b8d366 Klaus Aehlig
import qualified Data.Set as S
46 c2b8d366 Klaus Aehlig
47 15208e95 Klaus Aehlig
import Ganeti.BasicTypes
48 381889dc Klaus Aehlig
import Ganeti.Locking.Types
49 15208e95 Klaus Aehlig
50 c2b8d366 Klaus Aehlig
{-
51 c2b8d366 Klaus Aehlig
52 c2b8d366 Klaus Aehlig
This module is parametric in the type of locks and lock owners.
53 c2b8d366 Klaus Aehlig
While we only state minimal requirements for the types, we will
54 c2b8d366 Klaus Aehlig
consistently use the type variable 'a' for the type of locks and
55 c2b8d366 Klaus Aehlig
the variable 'b' for the type of the lock owners throughout this
56 c2b8d366 Klaus Aehlig
module.
57 c2b8d366 Klaus Aehlig
58 c2b8d366 Klaus Aehlig
-}
59 c2b8d366 Klaus Aehlig
60 c2b8d366 Klaus Aehlig
-- | Data type describing the way a lock can be owned.
61 c2b8d366 Klaus Aehlig
data OwnerState = OwnShared | OwnExclusive deriving (Ord, Eq, Show)
62 c2b8d366 Klaus Aehlig
63 381889dc Klaus Aehlig
-- | Type describing indirect ownership on a lock. We keep the set
64 381889dc Klaus Aehlig
-- of all (lock, owner)-pairs for locks that are implied in the given
65 381889dc Klaus Aehlig
-- lock, annotated with the type of ownership (shared or exclusive).
66 381889dc Klaus Aehlig
type IndirectOwners a b = M.Map (a, b) OwnerState
67 381889dc Klaus Aehlig
68 381889dc Klaus Aehlig
-- | The state of a lock that is taken. Besides the state of the lock
69 381889dc Klaus Aehlig
-- itself, we also keep track of all other lock allocation that affect
70 381889dc Klaus Aehlig
-- the given lock by means of implication.
71 381889dc Klaus Aehlig
data AllocationState a b = Exclusive b (IndirectOwners a b)
72 381889dc Klaus Aehlig
                         | Shared (S.Set b) (IndirectOwners a b)
73 381889dc Klaus Aehlig
                         deriving (Eq, Show)
74 381889dc Klaus Aehlig
75 381889dc Klaus Aehlig
-- | Compute the set of indirect owners from the information about
76 381889dc Klaus Aehlig
-- indirect ownership.
77 381889dc Klaus Aehlig
indirectOwners :: (Ord a, Ord b) => M.Map (a, b) OwnerState -> S.Set b
78 381889dc Klaus Aehlig
indirectOwners = S.map snd . M.keysSet
79 381889dc Klaus Aehlig
80 381889dc Klaus Aehlig
-- | Compute the (zero or one-elment) set of exclusive indirect owners.
81 381889dc Klaus Aehlig
indirectExclusives :: (Ord a, Ord b) => M.Map (a, b) OwnerState -> S.Set b
82 381889dc Klaus Aehlig
indirectExclusives = indirectOwners . M.filter (== OwnExclusive)
83 381889dc Klaus Aehlig
84 c2b8d366 Klaus Aehlig
{-| Representation of a Lock allocation
85 c2b8d366 Klaus Aehlig
86 c2b8d366 Klaus Aehlig
To keep queries for locks efficient, we keep two
87 c2b8d366 Klaus Aehlig
associations, with the invariant that they fit
88 c2b8d366 Klaus Aehlig
together: the association from locks to their
89 c2b8d366 Klaus Aehlig
allocation state, and the association from an
90 c2b8d366 Klaus Aehlig
owner to the set of locks owned. As we do not
91 c2b8d366 Klaus Aehlig
export the constructor, the problem of keeping
92 c2b8d366 Klaus Aehlig
this invariant reduces to only exporting functions
93 c2b8d366 Klaus Aehlig
that keep the invariant.
94 c2b8d366 Klaus Aehlig
95 c2b8d366 Klaus Aehlig
-}
96 c2b8d366 Klaus Aehlig
97 c2b8d366 Klaus Aehlig
data LockAllocation a b =
98 381889dc Klaus Aehlig
  LockAllocation { laLocks :: M.Map a (AllocationState a b)
99 c2b8d366 Klaus Aehlig
                 , laOwned :: M.Map b (M.Map a OwnerState)
100 c2b8d366 Klaus Aehlig
                 }
101 c2b8d366 Klaus Aehlig
  deriving (Eq, Show)
102 c2b8d366 Klaus Aehlig
103 c2b8d366 Klaus Aehlig
-- | A state with all locks being free.
104 c2b8d366 Klaus Aehlig
emptyAllocation :: (Ord a, Ord b) => LockAllocation a b
105 c2b8d366 Klaus Aehlig
emptyAllocation =
106 c2b8d366 Klaus Aehlig
  LockAllocation { laLocks = M.empty
107 c2b8d366 Klaus Aehlig
                 , laOwned = M.empty
108 c2b8d366 Klaus Aehlig
                 }
109 c2b8d366 Klaus Aehlig
110 c6d48e16 Klaus Aehlig
-- | Obtain the locks held by a given owner. The locks are reported
111 c6d48e16 Klaus Aehlig
-- as a map from the owned locks to the form of ownership (OwnShared
112 c6d48e16 Klaus Aehlig
-- or OwnExclusive).
113 c2b8d366 Klaus Aehlig
listLocks :: Ord b => b -> LockAllocation a b -> M.Map a OwnerState
114 c2b8d366 Klaus Aehlig
listLocks owner = fromMaybe M.empty . M.lookup owner . laOwned
115 15208e95 Klaus Aehlig
116 15208e95 Klaus Aehlig
-- | Data Type describing a change request on a single lock.
117 15208e95 Klaus Aehlig
data LockRequest a = LockRequest { lockAffected :: a
118 15208e95 Klaus Aehlig
                                 , lockRequestType :: Maybe OwnerState
119 15208e95 Klaus Aehlig
                                 }
120 15208e95 Klaus Aehlig
                     deriving (Eq, Show)
121 15208e95 Klaus Aehlig
122 15208e95 Klaus Aehlig
-- | Lock request for an exclusive lock.
123 15208e95 Klaus Aehlig
requestExclusive :: a -> LockRequest a
124 15208e95 Klaus Aehlig
requestExclusive lock = LockRequest { lockAffected = lock
125 15208e95 Klaus Aehlig
                                    , lockRequestType = Just OwnExclusive }
126 15208e95 Klaus Aehlig
127 15208e95 Klaus Aehlig
-- | Lock request for a shared lock.
128 15208e95 Klaus Aehlig
requestShared :: a -> LockRequest a
129 15208e95 Klaus Aehlig
requestShared lock = LockRequest { lockAffected = lock
130 15208e95 Klaus Aehlig
                                 , lockRequestType = Just OwnShared }
131 15208e95 Klaus Aehlig
132 15208e95 Klaus Aehlig
-- | Request to release a lock.
133 15208e95 Klaus Aehlig
requestRelease :: a -> LockRequest a
134 15208e95 Klaus Aehlig
requestRelease lock = LockRequest { lockAffected = lock
135 15208e95 Klaus Aehlig
                                  , lockRequestType = Nothing }
136 15208e95 Klaus Aehlig
137 381889dc Klaus Aehlig
-- | Update the Allocation state of a lock according to a given
138 381889dc Klaus Aehlig
-- function.
139 381889dc Klaus Aehlig
updateAllocState :: (Ord a, Ord b)
140 381889dc Klaus Aehlig
                  => (Maybe (AllocationState a b) -> AllocationState a b)
141 381889dc Klaus Aehlig
                  -> LockAllocation a b -> a -> LockAllocation a b
142 381889dc Klaus Aehlig
updateAllocState f state lock =
143 381889dc Klaus Aehlig
  let locks' = M.alter (find (/= Shared S.empty M.empty) . Just . f)
144 381889dc Klaus Aehlig
                        lock (laLocks state)
145 381889dc Klaus Aehlig
  in state { laLocks = locks' }
146 381889dc Klaus Aehlig
147 15208e95 Klaus Aehlig
-- | Internal function to update the state according to a single
148 15208e95 Klaus Aehlig
-- lock request, assuming all prerequisites are met.
149 15208e95 Klaus Aehlig
updateLock :: (Ord a, Ord b)
150 15208e95 Klaus Aehlig
           => b
151 15208e95 Klaus Aehlig
           -> LockAllocation a b -> LockRequest a -> LockAllocation a b
152 15208e95 Klaus Aehlig
updateLock owner state (LockRequest lock (Just OwnExclusive)) =
153 381889dc Klaus Aehlig
  let locks = laLocks state
154 381889dc Klaus Aehlig
      lockstate' = case M.lookup lock locks of
155 381889dc Klaus Aehlig
        Just (Exclusive _ i) -> Exclusive owner i
156 381889dc Klaus Aehlig
        Just (Shared _ i) -> Exclusive owner i
157 381889dc Klaus Aehlig
        Nothing -> Exclusive owner M.empty
158 381889dc Klaus Aehlig
      locks' = M.insert lock lockstate' locks
159 15208e95 Klaus Aehlig
      ownersLocks' = M.insert lock OwnExclusive $ listLocks owner state
160 15208e95 Klaus Aehlig
      owned' = M.insert owner ownersLocks' $ laOwned state
161 15208e95 Klaus Aehlig
  in state { laLocks = locks', laOwned = owned' }
162 15208e95 Klaus Aehlig
updateLock owner state (LockRequest lock (Just OwnShared)) =
163 15208e95 Klaus Aehlig
  let ownersLocks' = M.insert lock OwnShared $ listLocks owner state
164 15208e95 Klaus Aehlig
      owned' = M.insert owner ownersLocks' $ laOwned state
165 15208e95 Klaus Aehlig
      locks = laLocks state
166 15208e95 Klaus Aehlig
      lockState' = case M.lookup lock locks of
167 381889dc Klaus Aehlig
        Just (Exclusive _ i) -> Shared (S.singleton owner) i
168 381889dc Klaus Aehlig
        Just (Shared s i) -> Shared (S.insert owner s) i
169 381889dc Klaus Aehlig
        _ -> Shared (S.singleton owner) M.empty
170 15208e95 Klaus Aehlig
      locks' = M.insert lock lockState' locks
171 15208e95 Klaus Aehlig
  in state { laLocks = locks', laOwned = owned' }
172 15208e95 Klaus Aehlig
updateLock owner state (LockRequest lock Nothing) =
173 15208e95 Klaus Aehlig
  let ownersLocks' = M.delete lock $ listLocks owner state
174 15208e95 Klaus Aehlig
      owned = laOwned state
175 15208e95 Klaus Aehlig
      owned' = if M.null ownersLocks'
176 15208e95 Klaus Aehlig
                 then M.delete owner owned
177 15208e95 Klaus Aehlig
                 else M.insert owner ownersLocks' owned
178 381889dc Klaus Aehlig
      update (Just (Exclusive x i)) = if x == owner
179 381889dc Klaus Aehlig
                                        then Shared S.empty i
180 381889dc Klaus Aehlig
                                        else Exclusive x i
181 381889dc Klaus Aehlig
      update (Just (Shared s i)) = Shared (S.delete owner s) i
182 381889dc Klaus Aehlig
      update Nothing = Shared S.empty M.empty
183 381889dc Klaus Aehlig
  in updateAllocState update (state { laOwned = owned' }) lock
184 381889dc Klaus Aehlig
185 381889dc Klaus Aehlig
-- | Update the set of indirect ownerships of a lock by the given function.
186 381889dc Klaus Aehlig
updateIndirectSet :: (Ord a, Ord b)
187 381889dc Klaus Aehlig
                  => (IndirectOwners a b -> IndirectOwners a b)
188 381889dc Klaus Aehlig
                  -> LockAllocation a b -> a -> LockAllocation a b
189 381889dc Klaus Aehlig
updateIndirectSet f =
190 381889dc Klaus Aehlig
  let update (Just (Exclusive x i)) = Exclusive x (f i)
191 381889dc Klaus Aehlig
      update (Just (Shared s i)) = Shared s (f i)
192 381889dc Klaus Aehlig
      update Nothing = Shared S.empty (f M.empty)
193 381889dc Klaus Aehlig
  in updateAllocState update
194 381889dc Klaus Aehlig
195 381889dc Klaus Aehlig
-- | Update all indirect onwerships of a given lock.
196 381889dc Klaus Aehlig
updateIndirects :: (Lock a, Ord b)
197 381889dc Klaus Aehlig
                => b
198 381889dc Klaus Aehlig
                -> LockAllocation a b -> LockRequest a -> LockAllocation a b
199 381889dc Klaus Aehlig
updateIndirects owner state req =
200 381889dc Klaus Aehlig
  let lock = lockAffected req
201 381889dc Klaus Aehlig
      fn = case lockRequestType req of
202 381889dc Klaus Aehlig
             Nothing -> M.delete (lock, owner)
203 381889dc Klaus Aehlig
             Just tp -> M.insert (lock, owner) tp
204 381889dc Klaus Aehlig
  in foldl (updateIndirectSet fn) state $ lockImplications lock
205 15208e95 Klaus Aehlig
206 15208e95 Klaus Aehlig
-- | Update the locks of an owner according to the given request. Return
207 15208e95 Klaus Aehlig
-- the pair of the new state and the result of the operation, which is the
208 15208e95 Klaus Aehlig
-- the set of owners on which the operation was blocked on. so an empty set is
209 15208e95 Klaus Aehlig
-- success, and the state is updated if, and only if, the returned set is emtpy.
210 15208e95 Klaus Aehlig
-- In that way, it can be used in atomicModifyIORef.
211 381889dc Klaus Aehlig
updateLocks :: (Lock a, Ord b)
212 381889dc Klaus Aehlig
            => b
213 381889dc Klaus Aehlig
            -> [LockRequest a]
214 381889dc Klaus Aehlig
            -> LockAllocation a b -> (LockAllocation a b, Result (S.Set b))
215 15208e95 Klaus Aehlig
updateLocks owner reqs state = genericResult ((,) state . Bad) (second Ok) $ do
216 1ca6b451 Klaus Aehlig
  unless ((==) (length reqs) . S.size . S.fromList $ map lockAffected reqs)
217 1ca6b451 Klaus Aehlig
    . runListHead (return ())
218 1ca6b451 Klaus Aehlig
                  (fail . (++) "Inconsitent requests for lock " . show) $ do
219 15208e95 Klaus Aehlig
      r <- reqs
220 15208e95 Klaus Aehlig
      r' <- reqs
221 15208e95 Klaus Aehlig
      guard $ r /= r'
222 15208e95 Klaus Aehlig
      guard $ lockAffected r == lockAffected r'
223 15208e95 Klaus Aehlig
      return $ lockAffected r
224 15208e95 Klaus Aehlig
  let current = listLocks owner state
225 15208e95 Klaus Aehlig
  unless (M.null current) $ do
226 15208e95 Klaus Aehlig
    let (highest, _) = M.findMax current
227 15208e95 Klaus Aehlig
        notHolding = not
228 15208e95 Klaus Aehlig
                     . any (uncurry (==) . ((M.lookup `flip` current) *** Just))
229 15208e95 Klaus Aehlig
        orderViolation l = fail $ "Order violation: requesting " ++ show l
230 15208e95 Klaus Aehlig
                                   ++ " while holding " ++ show highest
231 15208e95 Klaus Aehlig
    for_ reqs $ \req -> case req of
232 15208e95 Klaus Aehlig
      LockRequest lock (Just OwnExclusive)
233 15208e95 Klaus Aehlig
        | lock < highest && notHolding [ (lock, OwnExclusive) ]
234 15208e95 Klaus Aehlig
        -> orderViolation lock
235 15208e95 Klaus Aehlig
      LockRequest lock (Just OwnShared)
236 15208e95 Klaus Aehlig
        | lock < highest && notHolding [ (lock, OwnExclusive)
237 15208e95 Klaus Aehlig
                                       , (lock, OwnExclusive)]
238 15208e95 Klaus Aehlig
        -> orderViolation lock
239 15208e95 Klaus Aehlig
      _ -> Ok ()
240 956b83d6 Klaus Aehlig
  let sharedsHeld = M.keysSet $ M.filter (== OwnShared) current
241 956b83d6 Klaus Aehlig
      exclusivesRequested = map lockAffected
242 956b83d6 Klaus Aehlig
                            . filter ((== Just OwnExclusive) . lockRequestType)
243 956b83d6 Klaus Aehlig
                            $ reqs
244 956b83d6 Klaus Aehlig
  runListHead (return ()) fail $ do
245 956b83d6 Klaus Aehlig
    x <- exclusivesRequested
246 956b83d6 Klaus Aehlig
    i <- lockImplications x
247 956b83d6 Klaus Aehlig
    guard $ S.member i sharedsHeld
248 956b83d6 Klaus Aehlig
    return $ "Order violation: requesting exclusively " ++ show x
249 956b83d6 Klaus Aehlig
              ++ " while holding a shared lock on the group lock " ++ show i
250 956b83d6 Klaus Aehlig
              ++ " it belongs to."
251 15208e95 Klaus Aehlig
  let blockedOn (LockRequest  _ Nothing) = S.empty
252 15208e95 Klaus Aehlig
      blockedOn (LockRequest lock (Just OwnExclusive)) =
253 15208e95 Klaus Aehlig
        case M.lookup lock (laLocks state) of
254 381889dc Klaus Aehlig
          Just (Exclusive x i) ->
255 381889dc Klaus Aehlig
            S.singleton x `S.union` indirectOwners i
256 381889dc Klaus Aehlig
          Just (Shared xs i) ->
257 381889dc Klaus Aehlig
            xs `S.union` indirectOwners i
258 15208e95 Klaus Aehlig
          _ -> S.empty
259 15208e95 Klaus Aehlig
      blockedOn (LockRequest lock (Just OwnShared)) =
260 15208e95 Klaus Aehlig
        case M.lookup lock (laLocks state) of
261 381889dc Klaus Aehlig
          Just (Exclusive x i) ->
262 381889dc Klaus Aehlig
            S.singleton x `S.union` indirectExclusives i
263 381889dc Klaus Aehlig
          Just (Shared _ i) -> indirectExclusives i
264 381889dc Klaus Aehlig
          _ -> S.empty
265 381889dc Klaus Aehlig
  let indirectBlocked Nothing _ = S.empty
266 381889dc Klaus Aehlig
      indirectBlocked (Just OwnShared) lock =
267 381889dc Klaus Aehlig
        case M.lookup lock (laLocks state) of
268 381889dc Klaus Aehlig
          Just (Exclusive x _) -> S.singleton x
269 381889dc Klaus Aehlig
          _ -> S.empty
270 381889dc Klaus Aehlig
      indirectBlocked (Just OwnExclusive) lock =
271 381889dc Klaus Aehlig
        case M.lookup lock (laLocks state) of
272 381889dc Klaus Aehlig
          Just (Exclusive x _) -> S.singleton x
273 381889dc Klaus Aehlig
          Just (Shared xs _) -> xs
274 15208e95 Klaus Aehlig
          _ -> S.empty
275 381889dc Klaus Aehlig
  let direct = S.unions $ map blockedOn reqs
276 381889dc Klaus Aehlig
      indirect = reqs >>= \req ->
277 381889dc Klaus Aehlig
        map (indirectBlocked (lockRequestType req))
278 381889dc Klaus Aehlig
          . lockImplications $ lockAffected req
279 381889dc Klaus Aehlig
  let blocked = S.delete owner . S.unions $ direct:indirect
280 15208e95 Klaus Aehlig
  let state' = foldl (updateLock owner) state reqs
281 381889dc Klaus Aehlig
      state'' = foldl (updateIndirects owner) state' reqs
282 381889dc Klaus Aehlig
  return (if S.null blocked then state'' else state, blocked)
283 80004e70 Klaus Aehlig
284 80004e70 Klaus Aehlig
-- | Compute the state after an onwer releases all its locks.
285 80004e70 Klaus Aehlig
freeLocks :: (Lock a, Ord b) => LockAllocation a b -> b -> LockAllocation a b
286 80004e70 Klaus Aehlig
freeLocks state owner =
287 80004e70 Klaus Aehlig
  fst . flip (updateLocks owner) state . map requestRelease . M.keys
288 80004e70 Klaus Aehlig
    $ listLocks owner state
289 d8216f2d Klaus Aehlig
290 d8216f2d Klaus Aehlig
-- | Restrict the locks of a user to a given set.
291 d8216f2d Klaus Aehlig
intersectLocks :: (Lock a, Ord b) => b -> [a]
292 d8216f2d Klaus Aehlig
               -> LockAllocation a b -> LockAllocation a b
293 d8216f2d Klaus Aehlig
intersectLocks owner locks state =
294 d8216f2d Klaus Aehlig
  let lockset = S.fromList locks
295 d8216f2d Klaus Aehlig
      toFree = filter (not . flip S.member lockset)
296 d8216f2d Klaus Aehlig
                 . M.keys $ listLocks owner state
297 d8216f2d Klaus Aehlig
  in fst $ updateLocks owner (map requestRelease toFree) state