Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / Instance.hs @ 51000365

History | View | Annotate | Download (5.3 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 e1ee7d5a Iustin Pop
module Test.Ganeti.HTools.Instance
30 e09c1fa0 Iustin Pop
  ( testHTools_Instance
31 e1ee7d5a Iustin Pop
  , genInstanceSmallerThanNode
32 e1ee7d5a Iustin Pop
  , Instance.Instance(..)
33 e1ee7d5a Iustin Pop
  ) where
34 e1ee7d5a Iustin Pop
35 e1ee7d5a Iustin Pop
import Test.QuickCheck
36 e1ee7d5a Iustin Pop
37 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHelper
38 e1ee7d5a Iustin Pop
import Test.Ganeti.TestCommon
39 e1ee7d5a Iustin Pop
import Test.Ganeti.HTools.Types ()
40 e1ee7d5a Iustin Pop
41 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
42 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Node as Node
43 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Types as Types
44 e1ee7d5a Iustin Pop
45 e1ee7d5a Iustin Pop
-- * Arbitrary instances
46 e1ee7d5a Iustin Pop
47 e1ee7d5a Iustin Pop
-- | Generates a random instance with maximum disk/mem/cpu values.
48 e1ee7d5a Iustin Pop
genInstanceSmallerThan :: Int -> Int -> Int -> Gen Instance.Instance
49 e1ee7d5a Iustin Pop
genInstanceSmallerThan lim_mem lim_dsk lim_cpu = do
50 e1ee7d5a Iustin Pop
  name <- getFQDN
51 e1ee7d5a Iustin Pop
  mem <- choose (0, lim_mem)
52 e1ee7d5a Iustin Pop
  dsk <- choose (0, lim_dsk)
53 e1ee7d5a Iustin Pop
  run_st <- arbitrary
54 e1ee7d5a Iustin Pop
  pn <- arbitrary
55 e1ee7d5a Iustin Pop
  sn <- arbitrary
56 e1ee7d5a Iustin Pop
  vcpus <- choose (0, lim_cpu)
57 e1ee7d5a Iustin Pop
  dt <- arbitrary
58 e1ee7d5a Iustin Pop
  return $ Instance.create name mem dsk vcpus run_st [] True pn sn dt 1
59 e1ee7d5a Iustin Pop
60 e1ee7d5a Iustin Pop
-- | Generates an instance smaller than a node.
61 e1ee7d5a Iustin Pop
genInstanceSmallerThanNode :: Node.Node -> Gen Instance.Instance
62 e1ee7d5a Iustin Pop
genInstanceSmallerThanNode node =
63 e1ee7d5a Iustin Pop
  genInstanceSmallerThan (Node.availMem node `div` 2)
64 e1ee7d5a Iustin Pop
                         (Node.availDisk node `div` 2)
65 e1ee7d5a Iustin Pop
                         (Node.availCpu node `div` 2)
66 e1ee7d5a Iustin Pop
67 e1ee7d5a Iustin Pop
-- let's generate a random instance
68 e1ee7d5a Iustin Pop
instance Arbitrary Instance.Instance where
69 e1ee7d5a Iustin Pop
  arbitrary = genInstanceSmallerThan maxMem maxDsk maxCpu
70 e1ee7d5a Iustin Pop
71 e1ee7d5a Iustin Pop
-- * Test cases
72 e1ee7d5a Iustin Pop
73 e1ee7d5a Iustin Pop
-- Simple instance tests, we only have setter/getters
74 e1ee7d5a Iustin Pop
75 20bc5360 Iustin Pop
prop_creat :: Instance.Instance -> Property
76 20bc5360 Iustin Pop
prop_creat inst =
77 e1ee7d5a Iustin Pop
  Instance.name inst ==? Instance.alias inst
78 e1ee7d5a Iustin Pop
79 20bc5360 Iustin Pop
prop_setIdx :: Instance.Instance -> Types.Idx -> Property
80 20bc5360 Iustin Pop
prop_setIdx inst idx =
81 e1ee7d5a Iustin Pop
  Instance.idx (Instance.setIdx inst idx) ==? idx
82 e1ee7d5a Iustin Pop
83 20bc5360 Iustin Pop
prop_setName :: Instance.Instance -> String -> Bool
84 20bc5360 Iustin Pop
prop_setName inst name =
85 e1ee7d5a Iustin Pop
  Instance.name newinst == name &&
86 e1ee7d5a Iustin Pop
  Instance.alias newinst == name
87 e1ee7d5a Iustin Pop
    where newinst = Instance.setName inst name
88 e1ee7d5a Iustin Pop
89 20bc5360 Iustin Pop
prop_setAlias :: Instance.Instance -> String -> Bool
90 20bc5360 Iustin Pop
prop_setAlias inst name =
91 e1ee7d5a Iustin Pop
  Instance.name newinst == Instance.name inst &&
92 e1ee7d5a Iustin Pop
  Instance.alias newinst == name
93 e1ee7d5a Iustin Pop
    where newinst = Instance.setAlias inst name
94 e1ee7d5a Iustin Pop
95 20bc5360 Iustin Pop
prop_setPri :: Instance.Instance -> Types.Ndx -> Property
96 20bc5360 Iustin Pop
prop_setPri inst pdx =
97 e1ee7d5a Iustin Pop
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
98 e1ee7d5a Iustin Pop
99 20bc5360 Iustin Pop
prop_setSec :: Instance.Instance -> Types.Ndx -> Property
100 20bc5360 Iustin Pop
prop_setSec inst sdx =
101 e1ee7d5a Iustin Pop
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
102 e1ee7d5a Iustin Pop
103 20bc5360 Iustin Pop
prop_setBoth :: Instance.Instance -> Types.Ndx -> Types.Ndx -> Bool
104 20bc5360 Iustin Pop
prop_setBoth inst pdx sdx =
105 e1ee7d5a Iustin Pop
  Instance.pNode si == pdx && Instance.sNode si == sdx
106 e1ee7d5a Iustin Pop
    where si = Instance.setBoth inst pdx sdx
107 e1ee7d5a Iustin Pop
108 20bc5360 Iustin Pop
prop_shrinkMG :: Instance.Instance -> Property
109 20bc5360 Iustin Pop
prop_shrinkMG inst =
110 e1ee7d5a Iustin Pop
  Instance.mem inst >= 2 * Types.unitMem ==>
111 e1ee7d5a Iustin Pop
    case Instance.shrinkByType inst Types.FailMem of
112 e1ee7d5a Iustin Pop
      Types.Ok inst' -> Instance.mem inst' == Instance.mem inst - Types.unitMem
113 e1ee7d5a Iustin Pop
      _ -> False
114 e1ee7d5a Iustin Pop
115 20bc5360 Iustin Pop
prop_shrinkMF :: Instance.Instance -> Property
116 20bc5360 Iustin Pop
prop_shrinkMF inst =
117 e1ee7d5a Iustin Pop
  forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
118 e1ee7d5a Iustin Pop
    let inst' = inst { Instance.mem = mem}
119 e1ee7d5a Iustin Pop
    in Types.isBad $ Instance.shrinkByType inst' Types.FailMem
120 e1ee7d5a Iustin Pop
121 20bc5360 Iustin Pop
prop_shrinkCG :: Instance.Instance -> Property
122 20bc5360 Iustin Pop
prop_shrinkCG inst =
123 e1ee7d5a Iustin Pop
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
124 e1ee7d5a Iustin Pop
    case Instance.shrinkByType inst Types.FailCPU of
125 e1ee7d5a Iustin Pop
      Types.Ok inst' ->
126 e1ee7d5a Iustin Pop
        Instance.vcpus inst' == Instance.vcpus inst - Types.unitCpu
127 e1ee7d5a Iustin Pop
      _ -> False
128 e1ee7d5a Iustin Pop
129 20bc5360 Iustin Pop
prop_shrinkCF :: Instance.Instance -> Property
130 20bc5360 Iustin Pop
prop_shrinkCF inst =
131 e1ee7d5a Iustin Pop
  forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
132 e1ee7d5a Iustin Pop
    let inst' = inst { Instance.vcpus = vcpus }
133 e1ee7d5a Iustin Pop
    in Types.isBad $ Instance.shrinkByType inst' Types.FailCPU
134 e1ee7d5a Iustin Pop
135 20bc5360 Iustin Pop
prop_shrinkDG :: Instance.Instance -> Property
136 20bc5360 Iustin Pop
prop_shrinkDG inst =
137 e1ee7d5a Iustin Pop
  Instance.dsk inst >= 2 * Types.unitDsk ==>
138 e1ee7d5a Iustin Pop
    case Instance.shrinkByType inst Types.FailDisk of
139 e1ee7d5a Iustin Pop
      Types.Ok inst' ->
140 e1ee7d5a Iustin Pop
        Instance.dsk inst' == Instance.dsk inst - Types.unitDsk
141 e1ee7d5a Iustin Pop
      _ -> False
142 e1ee7d5a Iustin Pop
143 20bc5360 Iustin Pop
prop_shrinkDF :: Instance.Instance -> Property
144 20bc5360 Iustin Pop
prop_shrinkDF inst =
145 e1ee7d5a Iustin Pop
  forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
146 e1ee7d5a Iustin Pop
    let inst' = inst { Instance.dsk = dsk }
147 e1ee7d5a Iustin Pop
    in Types.isBad $ Instance.shrinkByType inst' Types.FailDisk
148 e1ee7d5a Iustin Pop
149 20bc5360 Iustin Pop
prop_setMovable :: Instance.Instance -> Bool -> Property
150 20bc5360 Iustin Pop
prop_setMovable inst m =
151 e1ee7d5a Iustin Pop
  Instance.movable inst' ==? m
152 e1ee7d5a Iustin Pop
    where inst' = Instance.setMovable inst m
153 e1ee7d5a Iustin Pop
154 e09c1fa0 Iustin Pop
testSuite "HTools/Instance"
155 20bc5360 Iustin Pop
            [ 'prop_creat
156 20bc5360 Iustin Pop
            , 'prop_setIdx
157 20bc5360 Iustin Pop
            , 'prop_setName
158 20bc5360 Iustin Pop
            , 'prop_setAlias
159 20bc5360 Iustin Pop
            , 'prop_setPri
160 20bc5360 Iustin Pop
            , 'prop_setSec
161 20bc5360 Iustin Pop
            , 'prop_setBoth
162 20bc5360 Iustin Pop
            , 'prop_shrinkMG
163 20bc5360 Iustin Pop
            , 'prop_shrinkMF
164 20bc5360 Iustin Pop
            , 'prop_shrinkCG
165 20bc5360 Iustin Pop
            , 'prop_shrinkCF
166 20bc5360 Iustin Pop
            , 'prop_shrinkDG
167 20bc5360 Iustin Pop
            , 'prop_shrinkDF
168 20bc5360 Iustin Pop
            , 'prop_setMovable
169 e1ee7d5a Iustin Pop
            ]