module Test.Ganeti.HTools.Backend.Simu (testHTools_Backend_Simu) where
import Test.QuickCheck hiding (Result)
import Control.Monad
import qualified Data.IntMap as IntMap
import Text.Printf (printf)
import Test.Ganeti.TestHelper
import Test.Ganeti.TestCommon
import Ganeti.BasicTypes
import qualified Ganeti.Constants as C
import qualified Ganeti.HTools.Backend.Simu as Simu
import qualified Ganeti.HTools.Container as Container
import qualified Ganeti.HTools.Group as Group
import qualified Ganeti.HTools.Loader as Loader
import qualified Ganeti.HTools.Node as Node
import qualified Ganeti.HTools.Types as Types
genSimuSpec :: Gen (String, Int, Int, Int, Int)
genSimuSpec = do
pol <- elements [C.allocPolicyPreferred,
C.allocPolicyLastResort, C.allocPolicyUnallocable,
"p", "a", "u"]
nodes <- choose (0, 20)
dsk <- choose (0, maxDsk)
mem <- choose (0, maxMem)
cpu <- choose (0, maxCpu)
return (pol, nodes, dsk, mem, cpu)
prop_Load :: Property
prop_Load =
forAll (choose (0, 10)) $ \ngroups ->
forAll (replicateM ngroups genSimuSpec) $ \specs ->
let strspecs = map (\(p, n, d, m, c) -> printf "%s,%d,%d,%d,%d"
p n d m c::String) specs
totnodes = sum $ map (\(_, n, _, _, _) -> n) specs
mdc_in = concatMap (\(_, n, d, m, c) ->
replicate n (fromIntegral m, fromIntegral d,
fromIntegral c,
fromIntegral m, fromIntegral d))
specs :: [(Double, Double, Double, Int, Int)]
in case Simu.parseData strspecs of
Bad msg -> failTest $ "Failed to load specs: " ++ msg
Ok (Loader.ClusterData gl nl il tags ipol) ->
let nodes = map snd $ IntMap.toAscList nl
nidx = map Node.idx nodes
mdc_out = map (\n -> (Node.tMem n, Node.tDsk n, Node.tCpu n,
Node.fMem n, Node.fDsk n)) nodes
in conjoin [ Container.size gl ==? ngroups
, Container.size nl ==? totnodes
, Container.size il ==? 0
, length tags ==? 0
, ipol ==? Types.defIPolicy
, nidx ==? [1..totnodes]
, mdc_in ==? mdc_out
, map Group.iPolicy (Container.elems gl) ==?
replicate ngroups Types.defIPolicy
]
testSuite "HTools/Backend/Simu"
[ 'prop_Load
]