Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / HTools / Backend / Simu.hs @ 06c2fb4a

History | View | Annotate | Download (3.6 kB)

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