Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / HTools / Instance.hs @ 241cea1e

History | View | Annotate | Download (7 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 50c302ca Guido Trotter
  , genInstanceMaybeBiggerThanNode
33 fb243105 Iustin Pop
  , genInstanceSmallerThan
34 9f80119c Guido Trotter
  , genInstanceOnNodeList
35 bdb7dbbb Guido Trotter
  , genInstanceList
36 e1ee7d5a Iustin Pop
  , Instance.Instance(..)
37 e1ee7d5a Iustin Pop
  ) where
38 e1ee7d5a Iustin Pop
39 01e52493 Iustin Pop
import Test.QuickCheck hiding (Result)
40 e1ee7d5a Iustin Pop
41 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHelper
42 e1ee7d5a Iustin Pop
import Test.Ganeti.TestCommon
43 e1ee7d5a Iustin Pop
import Test.Ganeti.HTools.Types ()
44 e1ee7d5a Iustin Pop
45 01e52493 Iustin Pop
import Ganeti.BasicTypes
46 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
47 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Node as Node
48 9f80119c Guido Trotter
import qualified Ganeti.HTools.Container as Container
49 bdb7dbbb Guido Trotter
import qualified Ganeti.HTools.Loader as Loader
50 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Types as Types
51 e1ee7d5a Iustin Pop
52 e1ee7d5a Iustin Pop
-- * Arbitrary instances
53 e1ee7d5a Iustin Pop
54 e1ee7d5a Iustin Pop
-- | Generates a random instance with maximum disk/mem/cpu values.
55 e1ee7d5a Iustin Pop
genInstanceSmallerThan :: Int -> Int -> Int -> Gen Instance.Instance
56 e1ee7d5a Iustin Pop
genInstanceSmallerThan lim_mem lim_dsk lim_cpu = do
57 5006418e Iustin Pop
  name <- genFQDN
58 e1ee7d5a Iustin Pop
  mem <- choose (0, lim_mem)
59 e1ee7d5a Iustin Pop
  dsk <- choose (0, lim_dsk)
60 e1ee7d5a Iustin Pop
  run_st <- arbitrary
61 e1ee7d5a Iustin Pop
  pn <- arbitrary
62 e1ee7d5a Iustin Pop
  sn <- arbitrary
63 e1ee7d5a Iustin Pop
  vcpus <- choose (0, lim_cpu)
64 e1ee7d5a Iustin Pop
  dt <- arbitrary
65 241cea1e Klaus Aehlig
  return $ Instance.create name mem dsk [dsk] vcpus run_st [] True pn sn dt 1
66 e1ee7d5a Iustin Pop
67 e1ee7d5a Iustin Pop
-- | Generates an instance smaller than a node.
68 e1ee7d5a Iustin Pop
genInstanceSmallerThanNode :: Node.Node -> Gen Instance.Instance
69 e1ee7d5a Iustin Pop
genInstanceSmallerThanNode node =
70 e1ee7d5a Iustin Pop
  genInstanceSmallerThan (Node.availMem node `div` 2)
71 e1ee7d5a Iustin Pop
                         (Node.availDisk node `div` 2)
72 e1ee7d5a Iustin Pop
                         (Node.availCpu node `div` 2)
73 e1ee7d5a Iustin Pop
74 50c302ca Guido Trotter
-- | Generates an instance possibly bigger than a node.
75 50c302ca Guido Trotter
genInstanceMaybeBiggerThanNode :: Node.Node -> Gen Instance.Instance
76 50c302ca Guido Trotter
genInstanceMaybeBiggerThanNode node =
77 50c302ca Guido Trotter
  genInstanceSmallerThan (Node.availMem  node + Types.unitMem * 2)
78 50c302ca Guido Trotter
                         (Node.availDisk node + Types.unitDsk * 3)
79 50c302ca Guido Trotter
                         (Node.availCpu  node + Types.unitCpu * 4)
80 50c302ca Guido Trotter
81 9f80119c Guido Trotter
-- | Generates an instance with nodes on a node list.
82 9f80119c Guido Trotter
-- The following rules are respected:
83 9f80119c Guido Trotter
-- 1. The instance is never bigger than its primary node
84 9f80119c Guido Trotter
-- 2. If possible the instance has different pnode and snode
85 9f80119c Guido Trotter
-- 3. Else disk templates which require secondary nodes are disabled
86 9f80119c Guido Trotter
genInstanceOnNodeList :: Node.List -> Gen Instance.Instance
87 9f80119c Guido Trotter
genInstanceOnNodeList nl = do
88 9f80119c Guido Trotter
  let nsize = Container.size nl
89 9f80119c Guido Trotter
  pnode <- choose (0, nsize-1)
90 9f80119c Guido Trotter
  let (snodefilter, dtfilter) =
91 9f80119c Guido Trotter
        if nsize >= 2
92 9f80119c Guido Trotter
          then ((/= pnode), const True)
93 9f80119c Guido Trotter
          else (const True, not . Instance.hasSecondary)
94 9f80119c Guido Trotter
  snode <- choose (0, nsize-1) `suchThat` snodefilter
95 9f80119c Guido Trotter
  i <- genInstanceSmallerThanNode (Container.find pnode nl) `suchThat` dtfilter
96 9f80119c Guido Trotter
  return $ i { Instance.pNode = pnode, Instance.sNode = snode }
97 9f80119c Guido Trotter
98 bdb7dbbb Guido Trotter
-- | Generates an instance list given an instance generator.
99 bdb7dbbb Guido Trotter
genInstanceList :: Gen Instance.Instance -> Gen Instance.List
100 bdb7dbbb Guido Trotter
genInstanceList igen = fmap (snd . Loader.assignIndices) names_instances
101 bdb7dbbb Guido Trotter
    where names_instances =
102 bdb7dbbb Guido Trotter
            (fmap . map) (\n -> (Instance.name n, n)) $ listOf igen
103 bdb7dbbb Guido Trotter
104 e1ee7d5a Iustin Pop
-- let's generate a random instance
105 e1ee7d5a Iustin Pop
instance Arbitrary Instance.Instance where
106 e1ee7d5a Iustin Pop
  arbitrary = genInstanceSmallerThan maxMem maxDsk maxCpu
107 e1ee7d5a Iustin Pop
108 e1ee7d5a Iustin Pop
-- * Test cases
109 e1ee7d5a Iustin Pop
110 e1ee7d5a Iustin Pop
-- Simple instance tests, we only have setter/getters
111 e1ee7d5a Iustin Pop
112 20bc5360 Iustin Pop
prop_creat :: Instance.Instance -> Property
113 20bc5360 Iustin Pop
prop_creat inst =
114 e1ee7d5a Iustin Pop
  Instance.name inst ==? Instance.alias inst
115 e1ee7d5a Iustin Pop
116 20bc5360 Iustin Pop
prop_setIdx :: Instance.Instance -> Types.Idx -> Property
117 20bc5360 Iustin Pop
prop_setIdx inst idx =
118 e1ee7d5a Iustin Pop
  Instance.idx (Instance.setIdx inst idx) ==? idx
119 e1ee7d5a Iustin Pop
120 20bc5360 Iustin Pop
prop_setName :: Instance.Instance -> String -> Bool
121 20bc5360 Iustin Pop
prop_setName inst name =
122 e1ee7d5a Iustin Pop
  Instance.name newinst == name &&
123 e1ee7d5a Iustin Pop
  Instance.alias newinst == name
124 e1ee7d5a Iustin Pop
    where newinst = Instance.setName inst name
125 e1ee7d5a Iustin Pop
126 20bc5360 Iustin Pop
prop_setAlias :: Instance.Instance -> String -> Bool
127 20bc5360 Iustin Pop
prop_setAlias inst name =
128 e1ee7d5a Iustin Pop
  Instance.name newinst == Instance.name inst &&
129 e1ee7d5a Iustin Pop
  Instance.alias newinst == name
130 e1ee7d5a Iustin Pop
    where newinst = Instance.setAlias inst name
131 e1ee7d5a Iustin Pop
132 20bc5360 Iustin Pop
prop_setPri :: Instance.Instance -> Types.Ndx -> Property
133 20bc5360 Iustin Pop
prop_setPri inst pdx =
134 e1ee7d5a Iustin Pop
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
135 e1ee7d5a Iustin Pop
136 20bc5360 Iustin Pop
prop_setSec :: Instance.Instance -> Types.Ndx -> Property
137 20bc5360 Iustin Pop
prop_setSec inst sdx =
138 e1ee7d5a Iustin Pop
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
139 e1ee7d5a Iustin Pop
140 20bc5360 Iustin Pop
prop_setBoth :: Instance.Instance -> Types.Ndx -> Types.Ndx -> Bool
141 20bc5360 Iustin Pop
prop_setBoth inst pdx sdx =
142 e1ee7d5a Iustin Pop
  Instance.pNode si == pdx && Instance.sNode si == sdx
143 e1ee7d5a Iustin Pop
    where si = Instance.setBoth inst pdx sdx
144 e1ee7d5a Iustin Pop
145 20bc5360 Iustin Pop
prop_shrinkMG :: Instance.Instance -> Property
146 20bc5360 Iustin Pop
prop_shrinkMG inst =
147 e1ee7d5a Iustin Pop
  Instance.mem inst >= 2 * Types.unitMem ==>
148 e1ee7d5a Iustin Pop
    case Instance.shrinkByType inst Types.FailMem of
149 01e52493 Iustin Pop
      Ok inst' -> Instance.mem inst' ==? Instance.mem inst - Types.unitMem
150 01e52493 Iustin Pop
      Bad msg -> failTest msg
151 e1ee7d5a Iustin Pop
152 20bc5360 Iustin Pop
prop_shrinkMF :: Instance.Instance -> Property
153 20bc5360 Iustin Pop
prop_shrinkMF inst =
154 e1ee7d5a Iustin Pop
  forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
155 e1ee7d5a Iustin Pop
    let inst' = inst { Instance.mem = mem}
156 01e52493 Iustin Pop
    in isBad $ Instance.shrinkByType inst' Types.FailMem
157 e1ee7d5a Iustin Pop
158 20bc5360 Iustin Pop
prop_shrinkCG :: Instance.Instance -> Property
159 20bc5360 Iustin Pop
prop_shrinkCG inst =
160 e1ee7d5a Iustin Pop
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
161 e1ee7d5a Iustin Pop
    case Instance.shrinkByType inst Types.FailCPU of
162 01e52493 Iustin Pop
      Ok inst' -> Instance.vcpus inst' ==? Instance.vcpus inst - Types.unitCpu
163 01e52493 Iustin Pop
      Bad msg -> failTest msg
164 e1ee7d5a Iustin Pop
165 20bc5360 Iustin Pop
prop_shrinkCF :: Instance.Instance -> Property
166 20bc5360 Iustin Pop
prop_shrinkCF inst =
167 e1ee7d5a Iustin Pop
  forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
168 e1ee7d5a Iustin Pop
    let inst' = inst { Instance.vcpus = vcpus }
169 01e52493 Iustin Pop
    in isBad $ Instance.shrinkByType inst' Types.FailCPU
170 e1ee7d5a Iustin Pop
171 20bc5360 Iustin Pop
prop_shrinkDG :: Instance.Instance -> Property
172 20bc5360 Iustin Pop
prop_shrinkDG inst =
173 e1ee7d5a Iustin Pop
  Instance.dsk inst >= 2 * Types.unitDsk ==>
174 e1ee7d5a Iustin Pop
    case Instance.shrinkByType inst Types.FailDisk of
175 01e52493 Iustin Pop
      Ok inst' -> Instance.dsk inst' ==? Instance.dsk inst - Types.unitDsk
176 01e52493 Iustin Pop
      Bad msg -> failTest msg
177 e1ee7d5a Iustin Pop
178 20bc5360 Iustin Pop
prop_shrinkDF :: Instance.Instance -> Property
179 20bc5360 Iustin Pop
prop_shrinkDF inst =
180 e1ee7d5a Iustin Pop
  forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
181 e1ee7d5a Iustin Pop
    let inst' = inst { Instance.dsk = dsk }
182 01e52493 Iustin Pop
    in isBad $ Instance.shrinkByType inst' Types.FailDisk
183 e1ee7d5a Iustin Pop
184 20bc5360 Iustin Pop
prop_setMovable :: Instance.Instance -> Bool -> Property
185 20bc5360 Iustin Pop
prop_setMovable inst m =
186 e1ee7d5a Iustin Pop
  Instance.movable inst' ==? m
187 e1ee7d5a Iustin Pop
    where inst' = Instance.setMovable inst m
188 e1ee7d5a Iustin Pop
189 e09c1fa0 Iustin Pop
testSuite "HTools/Instance"
190 20bc5360 Iustin Pop
            [ 'prop_creat
191 20bc5360 Iustin Pop
            , 'prop_setIdx
192 20bc5360 Iustin Pop
            , 'prop_setName
193 20bc5360 Iustin Pop
            , 'prop_setAlias
194 20bc5360 Iustin Pop
            , 'prop_setPri
195 20bc5360 Iustin Pop
            , 'prop_setSec
196 20bc5360 Iustin Pop
            , 'prop_setBoth
197 20bc5360 Iustin Pop
            , 'prop_shrinkMG
198 20bc5360 Iustin Pop
            , 'prop_shrinkMF
199 20bc5360 Iustin Pop
            , 'prop_shrinkCG
200 20bc5360 Iustin Pop
            , 'prop_shrinkCF
201 20bc5360 Iustin Pop
            , 'prop_shrinkDG
202 20bc5360 Iustin Pop
            , 'prop_shrinkDF
203 20bc5360 Iustin Pop
            , 'prop_setMovable
204 e1ee7d5a Iustin Pop
            ]