module Test.Ganeti.SlotMap
( testSlotMap
, genSlotLimit
, genTestKey
, overfullKeys
) where
import Prelude hiding (all)
import Control.Applicative
import Control.Monad
import Data.Foldable (all)
import qualified Data.Map as Map
import Data.Map (Map, member, keys, keysSet)
import Data.Set (Set, size, union)
import qualified Data.Set as Set
import Data.Traversable (traverse)
import Test.HUnit
import Test.QuickCheck
import Test.Ganeti.TestCommon
import Test.Ganeti.TestHelper
import Test.Ganeti.Types ()
import Ganeti.SlotMap
genSlotLimit :: Gen Int
genSlotLimit = frequency [ (9, choose (1, 5))
, (1, choose (1, 100))
]
instance Arbitrary Slot where
arbitrary = do
limit <- genSlotLimit
occ <- choose (0, limit * 2)
return $ Slot occ limit
genSlotCount :: Gen Int
genSlotCount = slotOccupied <$> arbitrary
resampleFittingSlot :: Slot -> Gen Slot
resampleFittingSlot (Slot _ limit) = do
occ <- choose (0, limit)
return $ Slot occ limit
type TestKey = String
genTestKey :: Gen TestKey
genTestKey = frequency [ (9, elements ["a", "b", "c", "d", "e"])
, (1, genPrintableAsciiString)
]
listSizeGen :: Gen Int
listSizeGen = frequency [ (9, choose (1, 5))
, (1, choose (1, 100))
]
genSlotMap :: (Ord a) => Gen a -> Gen (SlotMap a)
genSlotMap keyGen = do
n <- listSizeGen
Map.fromList <$> vectorOf n ((,) <$> keyGen <*> arbitrary)
genCountMap :: (Ord a) => Gen a -> Gen (CountMap a)
genCountMap keyGen = do
n <- listSizeGen
Map.fromList <$> vectorOf n ((,) <$> keyGen <*> genSlotCount)
overfullKeys :: (Ord a) => SlotMap a -> Set a
overfullKeys sm =
Set.fromList [ a | (a, Slot occ limit) <- Map.toList sm, occ > limit ]
genFittingSlotMap :: (Ord a) => Gen a -> Gen (SlotMap a)
genFittingSlotMap keyGen = do
slotMap <- traverse resampleFittingSlot =<< genSlotMap keyGen
when (isOverfull slotMap) $ error "BUG: FittingSlotMap Gen is wrong"
return slotMap
case_isOverfull :: Assertion
case_isOverfull = do
assertBool "overfull"
. isOverfull $ Map.fromList [("buck", Slot 3 2)]
assertBool "not overfull"
. not . isOverfull $ Map.fromList [("buck", Slot 2 2)]
assertBool "empty"
. not . isOverfull $ (Map.fromList [] :: SlotMap TestKey)
case_occupySlots_examples :: Assertion
case_occupySlots_examples = do
let a n = ("a", Slot n 2)
let b n = ("b", Slot n 4)
let sm = Map.fromList [a 1, b 2]
cm = Map.fromList [("a", 1), ("b", 1), ("c", 5)]
assertEqual "fitting occupySlots"
(sm `occupySlots` cm)
(Map.fromList [a 2, b 3, ("c", Slot 5 0)])
keyUnion :: (Ord a) => Map a b -> Map a c -> Set a
keyUnion a b = keysSet a `union` keysSet b
prop_occupySlots :: Property
prop_occupySlots =
forAll arbitrary $ \(sm :: SlotMap Int, cm :: CountMap Int) ->
let smOcc = sm `occupySlots` cm
in conjoin
[ counterexample "input keys are preserved" $
all (`member` smOcc) (keyUnion sm cm)
, counterexample "all keys must come from the input keys" $
all (`Set.member` keyUnion sm cm) (keys smOcc)
]
case_hasSlotsFor_examples :: Assertion
case_hasSlotsFor_examples = do
let a n = ("a", Slot n 2)
let b n = ("b", Slot n 4)
let c n = ("c", Slot n 8)
let sm = Map.fromList [a 1, b 2]
assertBool "fits" $
sm `hasSlotsFor` Map.fromList [("a", 1), ("b", 1)]
assertBool "doesn't fit"
. not $ sm `hasSlotsFor` Map.fromList [("a", 1), ("b", 3)]
let smOverfull = Map.fromList [a 1, b 2, c 10]
assertBool "fits (untouched keys overfull)" $
isOverfull smOverfull
&& smOverfull `hasSlotsFor` Map.fromList [("a", 1), ("b", 1)]
assertBool "empty fitting" $
Map.empty `hasSlotsFor` (Map.empty :: CountMap TestKey)
assertBool "empty not fitting"
. not $ Map.empty `hasSlotsFor` Map.fromList [("a", 1), ("b", 100)]
assertBool "empty not fitting"
. not $ Map.empty `hasSlotsFor` Map.fromList [("a", 1)]
prop_hasSlotsFor_fitting :: Property
prop_hasSlotsFor_fitting =
forAll (genFittingSlotMap genTestKey) $ \sm ->
forAll (genCountMap genTestKey) $ \cm ->
sm `hasSlotsFor` cm ==? not (isOverfull $ sm `occupySlots` cm)
prop_hasSlotsFor :: Property
prop_hasSlotsFor =
let
genMaps = resize 10 $ do
sm1 <- genSlotMap genTestKey
sm2 <- sized $ \n -> resize (n `div` 3) (genSlotMap genTestKey)
frequency [ (1, return (sm1, sm1))
, (9, return (sm1, sm2)) ]
in forAll genMaps $ \(sm1, sm2) ->
let fits = sm1 `hasSlotsFor` toCountMap sm2
smOcc = sm1 `occupySlots` toCountMap sm2
oldOverfullBucks = overfullKeys sm1
newOverfullBucks = overfullKeys smOcc
in conjoin
[ counterexample "if there's enough extra space, then the new\
\ overfull keys must be as before" $
fits ==> (newOverfullBucks ==? oldOverfullBucks)
, counterexample "joining SlotMaps must not change the number of\
\ overfull keys (but may change their slot\
\ counts"
. property $ size newOverfullBucks >= size oldOverfullBucks
]
testSuite "SlotMap"
[ 'case_isOverfull
, 'case_occupySlots_examples
, 'prop_occupySlots
, 'case_hasSlotsFor_examples
, 'prop_hasSlotsFor_fitting
, 'prop_hasSlotsFor
]