Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (5.3 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.Instance
30
  ( testHTools_Instance
31
  , genInstanceSmallerThanNode
32
  , Instance.Instance(..)
33
  ) where
34

    
35
import Test.QuickCheck
36

    
37
import Test.Ganeti.TestHelper
38
import Test.Ganeti.TestCommon
39
import Test.Ganeti.HTools.Types ()
40

    
41
import qualified Ganeti.HTools.Instance as Instance
42
import qualified Ganeti.HTools.Node as Node
43
import qualified Ganeti.HTools.Types as Types
44

    
45
-- * Arbitrary instances
46

    
47
-- | Generates a random instance with maximum disk/mem/cpu values.
48
genInstanceSmallerThan :: Int -> Int -> Int -> Gen Instance.Instance
49
genInstanceSmallerThan lim_mem lim_dsk lim_cpu = do
50
  name <- getFQDN
51
  mem <- choose (0, lim_mem)
52
  dsk <- choose (0, lim_dsk)
53
  run_st <- arbitrary
54
  pn <- arbitrary
55
  sn <- arbitrary
56
  vcpus <- choose (0, lim_cpu)
57
  dt <- arbitrary
58
  return $ Instance.create name mem dsk vcpus run_st [] True pn sn dt 1
59

    
60
-- | Generates an instance smaller than a node.
61
genInstanceSmallerThanNode :: Node.Node -> Gen Instance.Instance
62
genInstanceSmallerThanNode node =
63
  genInstanceSmallerThan (Node.availMem node `div` 2)
64
                         (Node.availDisk node `div` 2)
65
                         (Node.availCpu node `div` 2)
66

    
67
-- let's generate a random instance
68
instance Arbitrary Instance.Instance where
69
  arbitrary = genInstanceSmallerThan maxMem maxDsk maxCpu
70

    
71
-- * Test cases
72

    
73
-- Simple instance tests, we only have setter/getters
74

    
75
prop_creat :: Instance.Instance -> Property
76
prop_creat inst =
77
  Instance.name inst ==? Instance.alias inst
78

    
79
prop_setIdx :: Instance.Instance -> Types.Idx -> Property
80
prop_setIdx inst idx =
81
  Instance.idx (Instance.setIdx inst idx) ==? idx
82

    
83
prop_setName :: Instance.Instance -> String -> Bool
84
prop_setName inst name =
85
  Instance.name newinst == name &&
86
  Instance.alias newinst == name
87
    where newinst = Instance.setName inst name
88

    
89
prop_setAlias :: Instance.Instance -> String -> Bool
90
prop_setAlias inst name =
91
  Instance.name newinst == Instance.name inst &&
92
  Instance.alias newinst == name
93
    where newinst = Instance.setAlias inst name
94

    
95
prop_setPri :: Instance.Instance -> Types.Ndx -> Property
96
prop_setPri inst pdx =
97
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
98

    
99
prop_setSec :: Instance.Instance -> Types.Ndx -> Property
100
prop_setSec inst sdx =
101
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
102

    
103
prop_setBoth :: Instance.Instance -> Types.Ndx -> Types.Ndx -> Bool
104
prop_setBoth inst pdx sdx =
105
  Instance.pNode si == pdx && Instance.sNode si == sdx
106
    where si = Instance.setBoth inst pdx sdx
107

    
108
prop_shrinkMG :: Instance.Instance -> Property
109
prop_shrinkMG inst =
110
  Instance.mem inst >= 2 * Types.unitMem ==>
111
    case Instance.shrinkByType inst Types.FailMem of
112
      Types.Ok inst' -> Instance.mem inst' == Instance.mem inst - Types.unitMem
113
      _ -> False
114

    
115
prop_shrinkMF :: Instance.Instance -> Property
116
prop_shrinkMF inst =
117
  forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
118
    let inst' = inst { Instance.mem = mem}
119
    in Types.isBad $ Instance.shrinkByType inst' Types.FailMem
120

    
121
prop_shrinkCG :: Instance.Instance -> Property
122
prop_shrinkCG inst =
123
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
124
    case Instance.shrinkByType inst Types.FailCPU of
125
      Types.Ok inst' ->
126
        Instance.vcpus inst' == Instance.vcpus inst - Types.unitCpu
127
      _ -> False
128

    
129
prop_shrinkCF :: Instance.Instance -> Property
130
prop_shrinkCF inst =
131
  forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
132
    let inst' = inst { Instance.vcpus = vcpus }
133
    in Types.isBad $ Instance.shrinkByType inst' Types.FailCPU
134

    
135
prop_shrinkDG :: Instance.Instance -> Property
136
prop_shrinkDG inst =
137
  Instance.dsk inst >= 2 * Types.unitDsk ==>
138
    case Instance.shrinkByType inst Types.FailDisk of
139
      Types.Ok inst' ->
140
        Instance.dsk inst' == Instance.dsk inst - Types.unitDsk
141
      _ -> False
142

    
143
prop_shrinkDF :: Instance.Instance -> Property
144
prop_shrinkDF inst =
145
  forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
146
    let inst' = inst { Instance.dsk = dsk }
147
    in Types.isBad $ Instance.shrinkByType inst' Types.FailDisk
148

    
149
prop_setMovable :: Instance.Instance -> Bool -> Property
150
prop_setMovable inst m =
151
  Instance.movable inst' ==? m
152
    where inst' = Instance.setMovable inst m
153

    
154
testSuite "HTools/Instance"
155
            [ 'prop_creat
156
            , 'prop_setIdx
157
            , 'prop_setName
158
            , 'prop_setAlias
159
            , 'prop_setPri
160
            , 'prop_setSec
161
            , 'prop_setBoth
162
            , 'prop_shrinkMG
163
            , 'prop_shrinkMF
164
            , 'prop_shrinkCG
165
            , 'prop_shrinkCF
166
            , 'prop_shrinkDG
167
            , 'prop_shrinkDF
168
            , 'prop_setMovable
169
            ]