module Ganeti.Locking.Waiting
( LockWaiting
, ExtWaiting
, emptyWaiting
, updateLocks
, updateLocksWaiting
, safeUpdateLocksWaiting
, getAllocation
, getPendingOwners
, hasPendingRequest
, removePendingRequest
, releaseResources
, getPendingRequests
, extRepr
, fromExtRepr
, freeLocksPredicate
, downGradeLocksPredicate
, intersectLocks
, opportunisticLockUnion
, guardedOpportunisticLockUnion
) where
import Control.Arrow ((&&&), (***), second)
import Control.Monad (liftM)
import Data.List (sort, foldl')
import qualified Data.Map as M
import Data.Maybe (fromMaybe)
import qualified Data.Set as S
import qualified Text.JSON as J
import Ganeti.BasicTypes
import qualified Ganeti.Locking.Allocation as L
import Ganeti.Locking.Types (Lock)
data LockWaiting a b c =
LockWaiting { lwAllocation :: L.LockAllocation a b
, lwPending :: M.Map b (S.Set (c, b, [L.LockRequest a]))
, lwPendingOwners :: M.Map b (b, (c, b, [L.LockRequest a]))
} deriving Show
emptyWaiting :: (Ord a, Ord b, Ord c) => LockWaiting a b c
emptyWaiting =
LockWaiting { lwAllocation = L.emptyAllocation
, lwPending = M.empty
, lwPendingOwners = M.empty
}
getPendingOwners :: LockWaiting a b c -> S.Set b
getPendingOwners = M.keysSet . lwPendingOwners
hasPendingRequest :: Ord b => b -> LockWaiting a b c -> Bool
hasPendingRequest owner = M.member owner . lwPendingOwners
getAllocation :: LockWaiting a b c -> L.LockAllocation a b
getAllocation = lwAllocation
getPendingRequests :: (Ord a, Ord b, Ord c)
=> LockWaiting a b c -> S.Set (c, b, [L.LockRequest a])
getPendingRequests = S.unions . M.elems . lwPending
type ExtWaiting a b c = (L.LockAllocation a b, S.Set (c, b, [L.LockRequest a]))
extRepr :: (Ord a, Ord b, Ord c)
=> LockWaiting a b c -> ExtWaiting a b c
extRepr = getAllocation &&& getPendingRequests
tryFulfillRequest :: (Lock a, Ord b, Ord c)
=> (LockWaiting a b c, S.Set b)
-> (c, b, [L.LockRequest a])
-> (LockWaiting a b c, S.Set b)
tryFulfillRequest (waiting, toNotify) (prio, owner, req) =
let (waiting', (_, newNotify)) = updateLocksWaiting' prio owner req waiting
in (waiting', toNotify `S.union` newNotify)
revisitRequests :: (Lock a, Ord b, Ord c)
=> S.Set b
-> S.Set b
-> LockWaiting a b c
-> (S.Set b, LockWaiting a b c)
revisitRequests notify todo state =
let getRequests (pending, reqs) owner =
(M.delete owner pending
, fromMaybe S.empty (M.lookup owner pending) `S.union` reqs)
(pending', requests) = S.foldl' getRequests (lwPending state, S.empty)
todo
revisitedOwners = S.map (\(_, o, _) -> o) requests
pendingOwners' = S.foldl' (flip M.delete) (lwPendingOwners state)
revisitedOwners
state' = state { lwPending = pending', lwPendingOwners = pendingOwners' }
(!state'', !notify') = S.foldl' tryFulfillRequest (state', notify)
requests
done = notify `S.union` todo
!newTodo = notify' S.\\ done
in if S.null todo
then (notify, state)
else revisitRequests done newTodo state''
updateLocks' :: (Lock a, Ord b, Ord c)
=> b
-> [L.LockRequest a]
-> LockWaiting a b c
-> (LockWaiting a b c, (Result (S.Set b), S.Set b))
updateLocks' owner reqs state =
let (!allocation', !result) = L.updateLocks owner reqs (lwAllocation state)
state' = state { lwAllocation = allocation' }
(!notify, !state'') = revisitRequests S.empty (S.singleton owner) state'
in if M.member owner $ lwPendingOwners state
then ( state
, (Bad "cannot update locks while having pending requests", S.empty)
)
else if result /= Ok S.empty
then (state, (result, S.empty))
else let pendingOwners' = lwPendingOwners state''
toNotify = S.filter (not . flip M.member pendingOwners')
notify
in (state'', (result, toNotify))
updateLocksWaiting' :: (Lock a, Ord b, Ord c)
=> c
-> b
-> [L.LockRequest a]
-> LockWaiting a b c
-> (LockWaiting a b c, (Result (S.Set b), S.Set b))
updateLocksWaiting' prio owner reqs state =
let (state', (result, notify)) = updateLocks' owner reqs state
!state'' = case result of
Bad _ -> state'
Ok empty | S.null empty -> state'
Ok blocked -> let blocker = S.findMin blocked
owners = M.insert owner (blocker, (prio, owner, reqs))
$ lwPendingOwners state
pendingEntry = S.insert (prio, owner, reqs)
. fromMaybe S.empty
. M.lookup blocker
$ lwPending state
pending = M.insert blocker pendingEntry
$ lwPending state
in state' { lwPendingOwners = owners
, lwPending = pending
}
in (state'', (result, notify))
requestFulfilled :: (Ord a, Ord b)
=> b -> [L.LockRequest a] -> LockWaiting a b c -> Bool
requestFulfilled owner req state =
let locks = L.listLocks owner $ lwAllocation state
isFulfilled r = M.lookup (L.lockAffected r) locks
== L.lockRequestType r
in not (hasPendingRequest owner state) && all isFulfilled req
updateLocks :: (Lock a, Ord b, Ord c)
=> b
-> [L.LockRequest a]
-> LockWaiting a b c
-> (LockWaiting a b c, (Result (S.Set b), S.Set b))
updateLocks owner req state =
if requestFulfilled owner req state
then (state, (Ok S.empty, S.empty))
else second (second $ S.delete owner) $ updateLocks' owner req state
updateLocksWaiting :: (Lock a, Ord b, Ord c)
=> c
-> b
-> [L.LockRequest a]
-> LockWaiting a b c
-> (LockWaiting a b c, (Result (S.Set b), S.Set b))
updateLocksWaiting prio owner req state =
if requestFulfilled owner req state
then (state, (Ok S.empty, S.empty))
else second (second $ S.delete owner)
$ updateLocksWaiting' prio owner req state
removePendingRequest :: (Lock a, Ord b, Ord c)
=> b -> LockWaiting a b c -> LockWaiting a b c
removePendingRequest owner state =
let pendingOwners = lwPendingOwners state
pending = lwPending state
in case M.lookup owner pendingOwners of
Nothing -> state
Just (blocker, entry) ->
let byBlocker = fromMaybe S.empty . M.lookup blocker $ pending
byBlocker' = S.delete entry byBlocker
pending' = if S.null byBlocker'
then M.delete blocker pending
else M.insert blocker byBlocker' pending
in state { lwPendingOwners = M.delete owner pendingOwners
, lwPending = pending'
}
safeUpdateLocksWaiting :: (Lock a, Ord b, Ord c)
=> c
-> b
-> [L.LockRequest a]
-> LockWaiting a b c
-> (LockWaiting a b c, (Result (S.Set b), S.Set b))
safeUpdateLocksWaiting prio owner req state =
if hasPendingRequest owner state
&& S.singleton req
== (S.map (\(_, _, r) -> r)
. S.filter (\(_, b, _) -> b == owner) $ getPendingRequests state)
then let (_, answer) = updateLocksWaiting prio owner req
$ removePendingRequest owner state
in (state, answer)
else updateLocksWaiting prio owner req state
releaseResources :: (Lock a, Ord b, Ord c)
=> b -> LockWaiting a b c -> (LockWaiting a b c, S.Set b)
releaseResources owner state =
let state' = removePendingRequest owner state
request = map L.requestRelease
. M.keys . L.listLocks owner $ getAllocation state'
(state'', (_, notify)) = updateLocks owner request state'
in (state'', notify)
fromExtRepr :: (Lock a, Ord b, Ord c)
=> ExtWaiting a b c -> LockWaiting a b c
fromExtRepr (alloc, pending) =
S.foldl' (\s (prio, owner, req) ->
fst $ updateLocksWaiting prio owner req s)
(emptyWaiting { lwAllocation = alloc })
pending
instance (Lock a, J.JSON a, Ord b, J.JSON b, Show b, Ord c, J.JSON c)
=> J.JSON (LockWaiting a b c) where
showJSON = J.showJSON . extRepr
readJSON = liftM fromExtRepr . J.readJSON
manipulateLocksPredicate :: (Lock a, Ord b, Ord c)
=> (a -> L.LockRequest a)
-> (a -> Bool)
-> b
-> LockWaiting a b c -> (LockWaiting a b c, S.Set b)
manipulateLocksPredicate req prop owner state =
second snd . flip (updateLocks owner) (removePendingRequest owner state)
. map req . filter prop . M.keys
. L.listLocks owner $ getAllocation state
freeLocksPredicate :: (Lock a, Ord b, Ord c)
=> (a -> Bool)
-> b
-> LockWaiting a b c -> (LockWaiting a b c, S.Set b)
freeLocksPredicate = manipulateLocksPredicate L.requestRelease
downGradeLocksPredicate :: (Lock a, Ord b, Ord c)
=> (a -> Bool)
-> b
-> LockWaiting a b c -> (LockWaiting a b c, S.Set b)
downGradeLocksPredicate = manipulateLocksPredicate L.requestShared
intersectLocks :: (Lock a, Ord b, Ord c)
=> [a]
-> b
-> LockWaiting a b c -> (LockWaiting a b c, S.Set b)
intersectLocks locks = freeLocksPredicate (not . flip elem locks)
opportunisticLockUnion :: (Lock a, Ord b, Ord c)
=> b
-> [(a, L.OwnerState)]
-> LockWaiting a b c
-> (LockWaiting a b c, ([a], S.Set b))
opportunisticLockUnion owner reqs state =
let locks = L.listLocks owner $ getAllocation state
reqs' = sort $ filter (uncurry (<) . (flip M.lookup locks *** Just)) reqs
maybeAllocate (s, success) (lock, ownstate) =
let (s', (result, _)) =
updateLocks owner
[(if ownstate == L.OwnShared
then L.requestShared
else L.requestExclusive) lock]
s
in (s', if result == Ok S.empty then lock:success else success)
in second (flip (,) S.empty) $ foldl' maybeAllocate (state, []) reqs'
guardedOpportunisticLockUnion :: (Lock a, Ord b, Ord c)
=> Int
-> b
-> [(a, L.OwnerState)]
-> LockWaiting a b c
-> (LockWaiting a b c, ([a], S.Set b))
guardedOpportunisticLockUnion count owner reqs state =
let (state', (acquired, toNotify)) = opportunisticLockUnion owner reqs state
in if length acquired < count
then (state, ([], S.empty))
else (state', (acquired, toNotify))