module Test.Ganeti.Locking.Allocation
( testLocking_Allocation
, TestLock
, TestOwner
, requestSucceeded
) where
import Control.Applicative
import qualified Data.Foldable as F
import qualified Data.Map as M
import Data.Maybe (fromMaybe)
import qualified Data.Set as S
import qualified Text.JSON as J
import Test.QuickCheck
import Test.Ganeti.TestCommon
import Test.Ganeti.TestHelper
import Ganeti.BasicTypes
import Ganeti.Locking.Allocation
import Ganeti.Locking.Types
data TestOwner = TestOwner Int deriving (Ord, Eq, Show)
instance Arbitrary TestOwner where
arbitrary = TestOwner <$> choose (0, 2)
data TestLock = TestBigLock
| TestCollectionLockA
| TestLockA Int
| TestCollectionLockB
| TestLockB Int
deriving (Ord, Eq, Show, Read)
instance Arbitrary TestLock where
arbitrary = frequency [ (1, elements [ TestBigLock
, TestCollectionLockA
, TestCollectionLockB
])
, (2, TestLockA <$> choose (0, 2))
, (2, TestLockB <$> choose (0, 2))
]
instance Lock TestLock where
lockImplications (TestLockA _) = [TestCollectionLockA, TestBigLock]
lockImplications (TestLockB _) = [TestCollectionLockB, TestBigLock]
lockImplications TestBigLock = []
lockImplications _ = [TestBigLock]
instance Arbitrary OwnerState where
arbitrary = elements [OwnShared, OwnExclusive]
instance Arbitrary a => Arbitrary (LockRequest a) where
arbitrary = LockRequest <$> arbitrary <*> genMaybe arbitrary
data UpdateRequest b a = UpdateRequest b [LockRequest a]
| FreeLockRequest b
deriving Show
instance (Arbitrary a, Arbitrary b) => Arbitrary (UpdateRequest a b) where
arbitrary =
frequency [ (4, UpdateRequest <$> arbitrary <*> (choose (1, 4) >>= vector))
, (1, FreeLockRequest <$> arbitrary)
]
asAllocTrans :: (Lock a, Ord b, Show b)
=> LockAllocation a b -> UpdateRequest b a -> LockAllocation a b
asAllocTrans state (UpdateRequest owner updates) =
fst $ updateLocks owner updates state
asAllocTrans state (FreeLockRequest owner) = freeLocks state owner
foldUpdates :: (Lock a, Ord b, Show b)
=> [UpdateRequest b a] -> LockAllocation a b
foldUpdates = foldl asAllocTrans emptyAllocation
instance (Arbitrary a, Lock a, Arbitrary b, Ord b, Show b)
=> Arbitrary (LockAllocation a b) where
arbitrary = foldUpdates <$> (choose (0, 8) >>= vector)
prop_LocksDisjoint :: Property
prop_LocksDisjoint =
forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
forAll (arbitrary :: Gen TestOwner) $ \a ->
forAll (arbitrary `suchThat` (/= a)) $ \b ->
let aExclusive = M.keysSet . M.filter (== OwnExclusive) $ listLocks a state
bAll = M.keysSet $ listLocks b state
in counterexample
(show a ++ "'s exclusive lock" ++ " is not respected by " ++ show b)
(S.null $ S.intersection aExclusive bAll)
prop_LockslistComplete :: Property
prop_LockslistComplete =
forAll (arbitrary :: Gen TestOwner) $ \a ->
forAll ((arbitrary :: Gen (LockAllocation TestLock TestOwner))
`suchThat` (not . M.null . listLocks a)) $ \state ->
counterexample "All owned locks must be mentioned in the all-locks list" $
let allLocks = listAllLocks state in
all (`elem` allLocks) (M.keys $ listLocks a state)
prop_LocksAllOwnersSubsetLockslist :: Property
prop_LocksAllOwnersSubsetLockslist =
forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
counterexample "The list of all active locks must contain all locks mentioned\
\ in the locks state" $
S.isSubsetOf (S.fromList . map fst $ listAllLocksOwners state)
(S.fromList $ listAllLocks state)
prop_LocksAllOwnersComplete :: Property
prop_LocksAllOwnersComplete =
forAll (arbitrary :: Gen TestOwner) $ \a ->
forAll ((arbitrary :: Gen (LockAllocation TestLock TestOwner))
`suchThat` (not . M.null . listLocks a)) $ \state ->
counterexample "Owned locks must be mentioned in list of all locks' state" $
let allLocksState = listAllLocksOwners state
in flip all (M.toList $ listLocks a state) $ \(lock, ownership) ->
elem (a, ownership) . fromMaybe [] $ lookup lock allLocksState
prop_LocksAllOwnersSound :: Property
prop_LocksAllOwnersSound =
forAll ((arbitrary :: Gen (LockAllocation TestLock TestOwner))
`suchThat` (not . null . listAllLocksOwners)) $ \state ->
counterexample "All locks mentioned in listAllLocksOwners must be owned by\
\ the mentioned owner" .
flip all (listAllLocksOwners state) $ \(lock, owners) ->
flip all owners $ \(owner, ownership) -> holdsLock owner lock ownership state
prop_LockImplicationX :: Property
prop_LockImplicationX =
forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
forAll (arbitrary :: Gen TestOwner) $ \a ->
forAll (arbitrary `suchThat` (/= a)) $ \b ->
let bExclusive = M.keysSet . M.filter (== OwnExclusive) $ listLocks b state
in counterexample "Others cannot have an exclusive lock on an implied lock" .
flip all (M.keys $ listLocks a state) $ \lock ->
flip all (lockImplications lock) $ \impliedlock ->
not $ S.member impliedlock bExclusive
prop_LockImplicationS :: Property
prop_LockImplicationS =
forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
forAll (arbitrary :: Gen TestOwner) $ \a ->
forAll (arbitrary `suchThat` (/= a)) $ \b ->
let aExclusive = M.keys . M.filter (== OwnExclusive) $ listLocks a state
bAll = M.keysSet $ listLocks b state
in counterexample "Others cannot hold locks implied by an exclusive lock" .
flip all aExclusive $ \lock ->
flip all (lockImplications lock) $ \impliedlock ->
not $ S.member impliedlock bAll
prop_LocksStable :: Property
prop_LocksStable =
forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
forAll (arbitrary :: Gen TestOwner) $ \a ->
forAll (arbitrary `suchThat` (/= a)) $ \b ->
forAll (arbitrary :: Gen [LockRequest TestLock]) $ \request ->
let (state', _) = updateLocks b request state
in (listLocks a state ==? listLocks a state')
requestSucceeded :: Ord a => M.Map a OwnerState -> LockRequest a -> Bool
requestSucceeded owned (LockRequest lock status) = M.lookup lock owned == status
prop_LockupdateAtomic :: Property
prop_LockupdateAtomic =
forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
forAll (arbitrary :: Gen TestOwner) $ \a ->
forAll (arbitrary :: Gen [LockRequest TestLock]) $ \request ->
let (state', result) = updateLocks a request state
in if result == Ok S.empty
then counterexample
("Update succeeded, but in final state " ++ show state'
++ "not all locks are as requested")
$ let owned = listLocks a state'
in all (requestSucceeded owned) request
else counterexample
("Update failed, but state changed to " ++ show state')
(state == state')
prop_LockReleaseSucceeds :: Property
prop_LockReleaseSucceeds =
forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
forAll (arbitrary :: Gen TestOwner) $ \a ->
forAll (arbitrary :: Gen TestLock) $ \lock ->
let (_, result) = updateLocks a [requestRelease lock] state
in counterexample
("Releasing a lock has to suceed uncondiationally, but got "
++ show result)
(isOk result)
prop_BlockSufficient :: Property
prop_BlockSufficient =
forAll (arbitrary :: Gen TestOwner) $ \a ->
forAll (arbitrary :: Gen TestLock) $ \lock ->
forAll (elements [ [requestShared lock]
, [requestExclusive lock]]) $ \request ->
forAll ((arbitrary :: Gen (LockAllocation TestLock TestOwner))
`suchThat` (genericResult (const False) (not . S.null)
. snd . updateLocks a request)) $ \state ->
let (_, result) = updateLocks a request state
blockedOn = genericResult (const S.empty) id result
in counterexample "After all blockers release, a request must succeed"
. isOk . snd . updateLocks a request $ F.foldl freeLocks state blockedOn
prop_BlockNecessary :: Property
prop_BlockNecessary =
forAll (arbitrary :: Gen TestOwner) $ \a ->
forAll (arbitrary :: Gen TestLock) $ \lock ->
forAll (arbitrary `suchThat` (/= lock)) $ \lock' ->
forAll (elements [ [requestShared lock, requestShared lock']
, [requestExclusive lock]]) $ \request ->
forAll ((arbitrary :: Gen (LockAllocation TestLock TestOwner))
`suchThat` (genericResult (const False) ((>= 2) . S.size)
. snd . updateLocks a request)) $ \state ->
let (_, result) = updateLocks a request state
blockers = genericResult (const S.empty) id result
in counterexample "Each blocker alone must block the request"
. flip all (S.elems blockers) $ \blocker ->
(==) (Ok $ S.singleton blocker) . snd . updateLocks a request
. F.foldl freeLocks state
$ S.filter (/= blocker) blockers
instance J.JSON TestOwner where
showJSON (TestOwner x) = J.showJSON x
readJSON = (>>= return . TestOwner) . J.readJSON
instance J.JSON TestLock where
showJSON = J.showJSON . show
readJSON = (>>= return . read) . J.readJSON
prop_ReadShow :: Property
prop_ReadShow =
forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
J.readJSON (J.showJSON state) ==? J.Ok state
prop_OwnerComplete :: Property
prop_OwnerComplete =
forAll (arbitrary :: Gen (LockAllocation TestLock TestOwner)) $ \state ->
foldl freeLocks state (lockOwners state) ==? emptyAllocation
prop_OwnerSound :: Property
prop_OwnerSound =
forAll ((arbitrary :: Gen (LockAllocation TestLock TestOwner))
`suchThat` (not . null . lockOwners)) $ \state ->
counterexample "All subjects listed as owners must own at least one lock"
. flip all (lockOwners state) $ \owner ->
not . M.null $ listLocks owner state
prop_ReadShowRequest :: Property
prop_ReadShowRequest =
forAll (arbitrary :: Gen (LockRequest TestLock)) $ \state ->
J.readJSON (J.showJSON state) ==? J.Ok state
testSuite "Locking/Allocation"
[ 'prop_LocksDisjoint
, 'prop_LockslistComplete
, 'prop_LocksAllOwnersSubsetLockslist
, 'prop_LocksAllOwnersComplete
, 'prop_LocksAllOwnersSound
, 'prop_LockImplicationX
, 'prop_LockImplicationS
, 'prop_LocksStable
, 'prop_LockupdateAtomic
, 'prop_LockReleaseSucceeds
, 'prop_BlockSufficient
, 'prop_BlockNecessary
, 'prop_ReadShow
, 'prop_OwnerComplete
, 'prop_OwnerSound
, 'prop_ReadShowRequest
]