Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (7.7 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 c2b8d366 Klaus Aehlig
  ) where
38 c2b8d366 Klaus Aehlig
39 15208e95 Klaus Aehlig
import Control.Arrow (second, (***))
40 15208e95 Klaus Aehlig
import Control.Monad
41 15208e95 Klaus Aehlig
import Data.Foldable (for_)
42 c2b8d366 Klaus Aehlig
import qualified Data.Map as M
43 c2b8d366 Klaus Aehlig
import Data.Maybe (fromMaybe)
44 c2b8d366 Klaus Aehlig
import qualified Data.Set as S
45 c2b8d366 Klaus Aehlig
46 15208e95 Klaus Aehlig
import Ganeti.BasicTypes
47 15208e95 Klaus Aehlig
48 c2b8d366 Klaus Aehlig
{-
49 c2b8d366 Klaus Aehlig
50 c2b8d366 Klaus Aehlig
This module is parametric in the type of locks and lock owners.
51 c2b8d366 Klaus Aehlig
While we only state minimal requirements for the types, we will
52 c2b8d366 Klaus Aehlig
consistently use the type variable 'a' for the type of locks and
53 c2b8d366 Klaus Aehlig
the variable 'b' for the type of the lock owners throughout this
54 c2b8d366 Klaus Aehlig
module.
55 c2b8d366 Klaus Aehlig
56 c2b8d366 Klaus Aehlig
-}
57 c2b8d366 Klaus Aehlig
58 c2b8d366 Klaus Aehlig
-- | The state of a lock that is taken.
59 c2b8d366 Klaus Aehlig
data AllocationState a = Exclusive a | Shared (S.Set a) deriving (Eq, Show)
60 c2b8d366 Klaus Aehlig
61 c2b8d366 Klaus Aehlig
-- | Data type describing the way a lock can be owned.
62 c2b8d366 Klaus Aehlig
data OwnerState = OwnShared | OwnExclusive deriving (Ord, Eq, Show)
63 c2b8d366 Klaus Aehlig
64 c2b8d366 Klaus Aehlig
{-| Representation of a Lock allocation
65 c2b8d366 Klaus Aehlig
66 c2b8d366 Klaus Aehlig
To keep queries for locks efficient, we keep two
67 c2b8d366 Klaus Aehlig
associations, with the invariant that they fit
68 c2b8d366 Klaus Aehlig
together: the association from locks to their
69 c2b8d366 Klaus Aehlig
allocation state, and the association from an
70 c2b8d366 Klaus Aehlig
owner to the set of locks owned. As we do not
71 c2b8d366 Klaus Aehlig
export the constructor, the problem of keeping
72 c2b8d366 Klaus Aehlig
this invariant reduces to only exporting functions
73 c2b8d366 Klaus Aehlig
that keep the invariant.
74 c2b8d366 Klaus Aehlig
75 c2b8d366 Klaus Aehlig
-}
76 c2b8d366 Klaus Aehlig
77 c2b8d366 Klaus Aehlig
data LockAllocation a b =
78 c2b8d366 Klaus Aehlig
  LockAllocation { laLocks :: M.Map a (AllocationState b)
79 c2b8d366 Klaus Aehlig
                 , laOwned :: M.Map b (M.Map a OwnerState)
80 c2b8d366 Klaus Aehlig
                 }
81 c2b8d366 Klaus Aehlig
  deriving (Eq, Show)
82 c2b8d366 Klaus Aehlig
83 c2b8d366 Klaus Aehlig
-- | A state with all locks being free.
84 c2b8d366 Klaus Aehlig
emptyAllocation :: (Ord a, Ord b) => LockAllocation a b
85 c2b8d366 Klaus Aehlig
emptyAllocation =
86 c2b8d366 Klaus Aehlig
  LockAllocation { laLocks = M.empty
87 c2b8d366 Klaus Aehlig
                 , laOwned = M.empty
88 c2b8d366 Klaus Aehlig
                 }
89 c2b8d366 Klaus Aehlig
90 c6d48e16 Klaus Aehlig
-- | Obtain the locks held by a given owner. The locks are reported
91 c6d48e16 Klaus Aehlig
-- as a map from the owned locks to the form of ownership (OwnShared
92 c6d48e16 Klaus Aehlig
-- or OwnExclusive).
93 c2b8d366 Klaus Aehlig
listLocks :: Ord b => b -> LockAllocation a b -> M.Map a OwnerState
94 c2b8d366 Klaus Aehlig
listLocks owner = fromMaybe M.empty . M.lookup owner . laOwned
95 15208e95 Klaus Aehlig
96 15208e95 Klaus Aehlig
-- | Data Type describing a change request on a single lock.
97 15208e95 Klaus Aehlig
data LockRequest a = LockRequest { lockAffected :: a
98 15208e95 Klaus Aehlig
                                 , lockRequestType :: Maybe OwnerState
99 15208e95 Klaus Aehlig
                                 }
100 15208e95 Klaus Aehlig
                     deriving (Eq, Show)
101 15208e95 Klaus Aehlig
102 15208e95 Klaus Aehlig
-- | Lock request for an exclusive lock.
103 15208e95 Klaus Aehlig
requestExclusive :: a -> LockRequest a
104 15208e95 Klaus Aehlig
requestExclusive lock = LockRequest { lockAffected = lock
105 15208e95 Klaus Aehlig
                                    , lockRequestType = Just OwnExclusive }
106 15208e95 Klaus Aehlig
107 15208e95 Klaus Aehlig
-- | Lock request for a shared lock.
108 15208e95 Klaus Aehlig
requestShared :: a -> LockRequest a
109 15208e95 Klaus Aehlig
requestShared lock = LockRequest { lockAffected = lock
110 15208e95 Klaus Aehlig
                                 , lockRequestType = Just OwnShared }
111 15208e95 Klaus Aehlig
112 15208e95 Klaus Aehlig
-- | Request to release a lock.
113 15208e95 Klaus Aehlig
requestRelease :: a -> LockRequest a
114 15208e95 Klaus Aehlig
requestRelease lock = LockRequest { lockAffected = lock
115 15208e95 Klaus Aehlig
                                  , lockRequestType = Nothing }
116 15208e95 Klaus Aehlig
117 15208e95 Klaus Aehlig
-- | Internal function to update the state according to a single
118 15208e95 Klaus Aehlig
-- lock request, assuming all prerequisites are met.
119 15208e95 Klaus Aehlig
updateLock :: (Ord a, Ord b)
120 15208e95 Klaus Aehlig
           => b
121 15208e95 Klaus Aehlig
           -> LockAllocation a b -> LockRequest a -> LockAllocation a b
122 15208e95 Klaus Aehlig
updateLock owner state (LockRequest lock (Just OwnExclusive)) =
123 15208e95 Klaus Aehlig
  let locks' = M.insert lock (Exclusive owner) $ laLocks state
124 15208e95 Klaus Aehlig
      ownersLocks' = M.insert lock OwnExclusive $ listLocks owner state
125 15208e95 Klaus Aehlig
      owned' = M.insert owner ownersLocks' $ laOwned state
126 15208e95 Klaus Aehlig
  in state { laLocks = locks', laOwned = owned' }
127 15208e95 Klaus Aehlig
updateLock owner state (LockRequest lock (Just OwnShared)) =
128 15208e95 Klaus Aehlig
  let ownersLocks' = M.insert lock OwnShared $ listLocks owner state
129 15208e95 Klaus Aehlig
      owned' = M.insert owner ownersLocks' $ laOwned state
130 15208e95 Klaus Aehlig
      locks = laLocks state
131 15208e95 Klaus Aehlig
      lockState' = case M.lookup lock locks of
132 15208e95 Klaus Aehlig
        Just (Shared s) -> Shared (S.insert owner s)
133 15208e95 Klaus Aehlig
        _ -> Shared $ S.singleton owner
134 15208e95 Klaus Aehlig
      locks' = M.insert lock lockState' locks
135 15208e95 Klaus Aehlig
  in state { laLocks = locks', laOwned = owned' }
136 15208e95 Klaus Aehlig
updateLock owner state (LockRequest lock Nothing) =
137 15208e95 Klaus Aehlig
  let ownersLocks' = M.delete lock $ listLocks owner state
138 15208e95 Klaus Aehlig
      owned = laOwned state
139 15208e95 Klaus Aehlig
      owned' = if M.null ownersLocks'
140 15208e95 Klaus Aehlig
                 then M.delete owner owned
141 15208e95 Klaus Aehlig
                 else M.insert owner ownersLocks' owned
142 15208e95 Klaus Aehlig
      locks = laLocks state
143 15208e95 Klaus Aehlig
      lockRemoved = M.delete lock locks
144 15208e95 Klaus Aehlig
      locks' = case M.lookup lock locks of
145 15208e95 Klaus Aehlig
                 Nothing -> locks
146 15208e95 Klaus Aehlig
                 Just (Exclusive x) ->
147 15208e95 Klaus Aehlig
                   if x == owner then lockRemoved else locks
148 15208e95 Klaus Aehlig
                 Just (Shared s)
149 15208e95 Klaus Aehlig
                   -> let s' = S.delete owner s
150 15208e95 Klaus Aehlig
                      in if S.null s'
151 15208e95 Klaus Aehlig
                        then lockRemoved
152 15208e95 Klaus Aehlig
                        else M.insert lock (Shared s') locks
153 15208e95 Klaus Aehlig
  in state { laLocks = locks', laOwned = owned' }
154 15208e95 Klaus Aehlig
155 15208e95 Klaus Aehlig
-- | Update the locks of an owner according to the given request. Return
156 15208e95 Klaus Aehlig
-- the pair of the new state and the result of the operation, which is the
157 15208e95 Klaus Aehlig
-- the set of owners on which the operation was blocked on. so an empty set is
158 15208e95 Klaus Aehlig
-- success, and the state is updated if, and only if, the returned set is emtpy.
159 15208e95 Klaus Aehlig
-- In that way, it can be used in atomicModifyIORef.
160 15208e95 Klaus Aehlig
updateLocks :: (Ord a, Show a, Ord b)
161 15208e95 Klaus Aehlig
               => b
162 15208e95 Klaus Aehlig
               -> [LockRequest a]
163 15208e95 Klaus Aehlig
               -> LockAllocation a b -> (LockAllocation a b, Result (S.Set b))
164 15208e95 Klaus Aehlig
updateLocks owner reqs state = genericResult ((,) state . Bad) (second Ok) $ do
165 15208e95 Klaus Aehlig
  runListHead (return ())
166 15208e95 Klaus Aehlig
              (fail . (++) "Inconsitent requests for lock " . show) $ do
167 15208e95 Klaus Aehlig
      r <- reqs
168 15208e95 Klaus Aehlig
      r' <- reqs
169 15208e95 Klaus Aehlig
      guard $ r /= r'
170 15208e95 Klaus Aehlig
      guard $ lockAffected r == lockAffected r'
171 15208e95 Klaus Aehlig
      return $ lockAffected r
172 15208e95 Klaus Aehlig
  let current = listLocks owner state
173 15208e95 Klaus Aehlig
  unless (M.null current) $ do
174 15208e95 Klaus Aehlig
    let (highest, _) = M.findMax current
175 15208e95 Klaus Aehlig
        notHolding = not
176 15208e95 Klaus Aehlig
                     . any (uncurry (==) . ((M.lookup `flip` current) *** Just))
177 15208e95 Klaus Aehlig
        orderViolation l = fail $ "Order violation: requesting " ++ show l
178 15208e95 Klaus Aehlig
                                   ++ " while holding " ++ show highest
179 15208e95 Klaus Aehlig
    for_ reqs $ \req -> case req of
180 15208e95 Klaus Aehlig
      LockRequest lock (Just OwnExclusive)
181 15208e95 Klaus Aehlig
        | lock < highest && notHolding [ (lock, OwnExclusive) ]
182 15208e95 Klaus Aehlig
        -> orderViolation lock
183 15208e95 Klaus Aehlig
      LockRequest lock (Just OwnShared)
184 15208e95 Klaus Aehlig
        | lock < highest && notHolding [ (lock, OwnExclusive)
185 15208e95 Klaus Aehlig
                                       , (lock, OwnExclusive)]
186 15208e95 Klaus Aehlig
        -> orderViolation lock
187 15208e95 Klaus Aehlig
      _ -> Ok ()
188 15208e95 Klaus Aehlig
  let blockedOn (LockRequest  _ Nothing) = S.empty
189 15208e95 Klaus Aehlig
      blockedOn (LockRequest lock (Just OwnExclusive)) =
190 15208e95 Klaus Aehlig
        case M.lookup lock (laLocks state) of
191 15208e95 Klaus Aehlig
          Just (Exclusive x) -> S.singleton x
192 15208e95 Klaus Aehlig
          Just (Shared xs) -> xs
193 15208e95 Klaus Aehlig
          _ -> S.empty
194 15208e95 Klaus Aehlig
      blockedOn (LockRequest lock (Just OwnShared)) =
195 15208e95 Klaus Aehlig
        case M.lookup lock (laLocks state) of
196 15208e95 Klaus Aehlig
          Just (Exclusive x) -> S.singleton x
197 15208e95 Klaus Aehlig
          _ -> S.empty
198 15208e95 Klaus Aehlig
  let blocked = S.delete owner . S.unions $ map blockedOn reqs
199 15208e95 Klaus Aehlig
  let state' = foldl (updateLock owner) state reqs
200 15208e95 Klaus Aehlig
  return (if S.null blocked then state' else state, blocked)
201 80004e70 Klaus Aehlig
202 80004e70 Klaus Aehlig
-- | Compute the state after an onwer releases all its locks.
203 80004e70 Klaus Aehlig
freeLocks :: (Lock a, Ord b) => LockAllocation a b -> b -> LockAllocation a b
204 80004e70 Klaus Aehlig
freeLocks state owner =
205 80004e70 Klaus Aehlig
  fst . flip (updateLocks owner) state . map requestRelease . M.keys
206 80004e70 Klaus Aehlig
    $ listLocks owner state