Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / HTools / Backend / Simu.hs @ 83846468

History | View | Annotate | Download (3.6 kB)

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.Backend.Simu (testHTools_Backend_Simu) where
30

    
31
import Test.QuickCheck hiding (Result)
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 Ganeti.BasicTypes
41
import qualified Ganeti.Constants as C
42
import qualified Ganeti.HTools.Backend.Simu as Simu
43
import qualified Ganeti.HTools.Container as Container
44
import qualified Ganeti.HTools.Group as Group
45
import qualified Ganeti.HTools.Loader as Loader
46
import qualified Ganeti.HTools.Node as Node
47
import qualified Ganeti.HTools.Types as Types
48

    
49
-- | Generates a tuple of specs for simulation.
50
genSimuSpec :: Gen (String, Int, Int, Int, Int)
51
genSimuSpec = do
52
  pol <- elements [C.allocPolicyPreferred,
53
                   C.allocPolicyLastResort, C.allocPolicyUnallocable,
54
                  "p", "a", "u"]
55
 -- should be reasonable (nodes/group), bigger values only complicate
56
 -- the display of failed tests, and we don't care (in this particular
57
 -- test) about big node groups
58
  nodes <- choose (0, 20)
59
  dsk <- choose (0, maxDsk)
60
  mem <- choose (0, maxMem)
61
  cpu <- choose (0, maxCpu)
62
  return (pol, nodes, dsk, mem, cpu)
63

    
64
-- | Checks that given a set of corrects specs, we can load them
65
-- successfully, and that at high-level the values look right.
66
prop_Load :: Property
67
prop_Load =
68
  forAll (choose (0, 10)) $ \ngroups ->
69
  forAll (replicateM ngroups genSimuSpec) $ \specs ->
70
  let strspecs = map (\(p, n, d, m, c) -> printf "%s,%d,%d,%d,%d"
71
                                          p n d m c::String) specs
72
      totnodes = sum $ map (\(_, n, _, _, _) -> n) specs
73
      mdc_in = concatMap (\(_, n, d, m, c) ->
74
                            replicate n (fromIntegral m, fromIntegral d,
75
                                         fromIntegral c,
76
                                         fromIntegral m, fromIntegral d))
77
               specs :: [(Double, Double, Double, Int, Int)]
78
  in case Simu.parseData strspecs of
79
       Bad msg -> failTest $ "Failed to load specs: " ++ msg
80
       Ok (Loader.ClusterData gl nl il tags ipol) ->
81
         let nodes = map snd $ IntMap.toAscList nl
82
             nidx = map Node.idx nodes
83
             mdc_out = map (\n -> (Node.tMem n, Node.tDsk n, Node.tCpu n,
84
                                   Node.fMem n, Node.fDsk n)) nodes
85
         in conjoin [ 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

    
96
testSuite "HTools/Backend/Simu"
97
            [ 'prop_Load
98
            ]