Move JSON.hs and Compat.hs out from under HTools/
[ganeti-local] / htest / Test / Ganeti / HTools / Simu.hs
1 {-# LANGUAGE TemplateHaskell #-}
2 {-# OPTIONS_GHC -fno-warn-orphans #-}
3
4 {-| Unittests for ganeti-htools.
5
6 -}
7
8 {-
9
10 Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11
12 This program is free software; you can redistribute it and/or modify
13 it under the terms of the GNU General Public License as published by
14 the Free Software Foundation; either version 2 of the License, or
15 (at your option) any later version.
16
17 This program is distributed in the hope that it will be useful, but
18 WITHOUT ANY WARRANTY; without even the implied warranty of
19 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 General Public License for more details.
21
22 You should have received a copy of the GNU General Public License
23 along with this program; if not, write to the Free Software
24 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 02110-1301, USA.
26
27 -}
28
29 module Test.Ganeti.HTools.Simu (testSimu) where
30
31 import Test.QuickCheck
32
33 import Control.Monad
34 import qualified Data.IntMap as IntMap
35 import Text.Printf (printf)
36
37 import Test.Ganeti.TestHelper
38 import Test.Ganeti.TestCommon
39
40 import qualified Ganeti.Constants as C
41 import qualified Ganeti.HTools.Container as Container
42 import qualified Ganeti.HTools.Group as Group
43 import qualified Ganeti.HTools.Loader as Loader
44 import qualified Ganeti.HTools.Node as Node
45 import qualified Ganeti.HTools.Simu as Simu
46 import qualified Ganeti.HTools.Types as Types
47
48 -- | Generates a tuple of specs for simulation.
49 genSimuSpec :: Gen (String, Int, Int, Int, Int)
50 genSimuSpec = do
51   pol <- elements [C.allocPolicyPreferred,
52                    C.allocPolicyLastResort, C.allocPolicyUnallocable,
53                   "p", "a", "u"]
54  -- should be reasonable (nodes/group), bigger values only complicate
55  -- the display of failed tests, and we don't care (in this particular
56  -- test) about big node groups
57   nodes <- choose (0, 20)
58   dsk <- choose (0, maxDsk)
59   mem <- choose (0, maxMem)
60   cpu <- choose (0, maxCpu)
61   return (pol, nodes, dsk, mem, cpu)
62
63 -- | Checks that given a set of corrects specs, we can load them
64 -- successfully, and that at high-level the values look right.
65 prop_Simu_Load :: Property
66 prop_Simu_Load =
67   forAll (choose (0, 10)) $ \ngroups ->
68   forAll (replicateM ngroups genSimuSpec) $ \specs ->
69   let strspecs = map (\(p, n, d, m, c) -> printf "%s,%d,%d,%d,%d"
70                                           p n d m c::String) specs
71       totnodes = sum $ map (\(_, n, _, _, _) -> n) specs
72       mdc_in = concatMap (\(_, n, d, m, c) ->
73                             replicate n (fromIntegral m, fromIntegral d,
74                                          fromIntegral c,
75                                          fromIntegral m, fromIntegral d))
76                specs :: [(Double, Double, Double, Int, Int)]
77   in case Simu.parseData strspecs of
78        Types.Bad msg -> failTest $ "Failed to load specs: " ++ msg
79        Types.Ok (Loader.ClusterData gl nl il tags ipol) ->
80          let nodes = map snd $ IntMap.toAscList nl
81              nidx = map Node.idx nodes
82              mdc_out = map (\n -> (Node.tMem n, Node.tDsk n, Node.tCpu n,
83                                    Node.fMem n, Node.fDsk n)) nodes
84          in
85          Container.size gl ==? ngroups .&&.
86          Container.size nl ==? totnodes .&&.
87          Container.size il ==? 0 .&&.
88          length tags ==? 0 .&&.
89          ipol ==? Types.defIPolicy .&&.
90          nidx ==? [1..totnodes] .&&.
91          mdc_in ==? mdc_out .&&.
92          map Group.iPolicy (Container.elems gl) ==?
93              replicate ngroups Types.defIPolicy
94
95 testSuite "Simu"
96             [ 'prop_Simu_Load
97             ]