Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / Instance.hs @ 61899e64

History | View | Annotate | Download (5.4 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
  , genInstanceSmallerThan
33
  , Instance.Instance(..)
34
  ) where
35

    
36
import Test.QuickCheck hiding (Result)
37

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

    
42
import Ganeti.BasicTypes
43
import qualified Ganeti.HTools.Instance as Instance
44
import qualified Ganeti.HTools.Node as Node
45
import qualified Ganeti.HTools.Types as Types
46

    
47
-- * Arbitrary instances
48

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

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

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

    
73
-- * Test cases
74

    
75
-- Simple instance tests, we only have setter/getters
76

    
77
prop_creat :: Instance.Instance -> Property
78
prop_creat inst =
79
  Instance.name inst ==? Instance.alias inst
80

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

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

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

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

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

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

    
110
prop_shrinkMG :: Instance.Instance -> Property
111
prop_shrinkMG inst =
112
  Instance.mem inst >= 2 * Types.unitMem ==>
113
    case Instance.shrinkByType inst Types.FailMem of
114
      Ok inst' -> Instance.mem inst' ==? Instance.mem inst - Types.unitMem
115
      Bad msg -> failTest msg
116

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

    
123
prop_shrinkCG :: Instance.Instance -> Property
124
prop_shrinkCG inst =
125
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
126
    case Instance.shrinkByType inst Types.FailCPU of
127
      Ok inst' -> Instance.vcpus inst' ==? Instance.vcpus inst - Types.unitCpu
128
      Bad msg -> failTest msg
129

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

    
136
prop_shrinkDG :: Instance.Instance -> Property
137
prop_shrinkDG inst =
138
  Instance.dsk inst >= 2 * Types.unitDsk ==>
139
    case Instance.shrinkByType inst Types.FailDisk of
140
      Ok inst' -> Instance.dsk inst' ==? Instance.dsk inst - Types.unitDsk
141
      Bad msg -> failTest msg
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 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
            ]