Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / HTools / Instance.hs @ 8f467ab0

History | View | Annotate | Download (7.6 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, 2013 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
  , genInstanceMaybeBiggerThanNode
33
  , genInstanceOnNodeList
34
  , genInstanceList
35
  , Instance.Instance(..)
36
  ) where
37

    
38
import Control.Applicative ((<$>))
39
import Control.Monad (liftM)
40
import Test.QuickCheck hiding (Result)
41

    
42
import Test.Ganeti.TestHelper
43
import Test.Ganeti.TestCommon
44
import Test.Ganeti.HTools.Types ()
45

    
46
import Ganeti.BasicTypes
47
import qualified Ganeti.HTools.Instance as Instance
48
import qualified Ganeti.HTools.Node as Node
49
import qualified Ganeti.HTools.Container as Container
50
import qualified Ganeti.HTools.Loader as Loader
51
import qualified Ganeti.HTools.Types as Types
52

    
53
-- * Arbitrary instances
54

    
55
-- | Generates a random instance with maximum disk/mem/cpu values.
56
genInstanceSmallerThan :: Int -> Int -> Int -> Maybe Int ->
57
                          Gen Instance.Instance
58
genInstanceSmallerThan lim_mem lim_dsk lim_cpu lim_spin = do
59
  name <- genFQDN
60
  mem <- choose (0, lim_mem)
61
  dsk <- choose (0, lim_dsk)
62
  run_st <- arbitrary
63
  pn <- arbitrary
64
  sn <- arbitrary
65
  vcpus <- choose (0, lim_cpu)
66
  dt <- arbitrary
67
  spindles <- case lim_spin of
68
    Nothing -> genMaybe $ choose (0, maxSpindles)
69
    Just ls -> liftM Just $ choose (0, ls)
70
  let disk = Instance.Disk dsk spindles
71
  return $ Instance.create
72
    name mem dsk [disk] vcpus run_st [] True pn sn dt 1 []
73

    
74
-- | Generates an instance smaller than a node.
75
genInstanceSmallerThanNode :: Node.Node -> Gen Instance.Instance
76
genInstanceSmallerThanNode node =
77
  genInstanceSmallerThan (Node.availMem node `div` 2)
78
                         (Node.availDisk node `div` 2)
79
                         (Node.availCpu node `div` 2)
80
                         (if Node.exclStorage node
81
                          then Just $ Node.fSpindles node `div` 2
82
                          else Nothing)
83

    
84
-- | Generates an instance possibly bigger than a node.
85
genInstanceMaybeBiggerThanNode :: Node.Node -> Gen Instance.Instance
86
genInstanceMaybeBiggerThanNode node =
87
  genInstanceSmallerThan (Node.availMem  node + Types.unitMem * 2)
88
                         (Node.availDisk node + Types.unitDsk * 3)
89
                         (Node.availCpu  node + Types.unitCpu * 4)
90
                         (if Node.exclStorage node
91
                          then Just $ Node.fSpindles node +
92
                               Types.unitSpindle * 5
93
                          else Nothing)
94

    
95
-- | Generates an instance with nodes on a node list.
96
-- The following rules are respected:
97
-- 1. The instance is never bigger than its primary node
98
-- 2. If possible the instance has different pnode and snode
99
-- 3. Else disk templates which require secondary nodes are disabled
100
genInstanceOnNodeList :: Node.List -> Gen Instance.Instance
101
genInstanceOnNodeList nl = do
102
  let nsize = Container.size nl
103
  pnode <- choose (0, nsize-1)
104
  let (snodefilter, dtfilter) =
105
        if nsize >= 2
106
          then ((/= pnode), const True)
107
          else (const True, not . Instance.hasSecondary)
108
  snode <- choose (0, nsize-1) `suchThat` snodefilter
109
  i <- genInstanceSmallerThanNode (Container.find pnode nl) `suchThat` dtfilter
110
  return $ i { Instance.pNode = pnode, Instance.sNode = snode }
111

    
112
-- | Generates an instance list given an instance generator.
113
genInstanceList :: Gen Instance.Instance -> Gen Instance.List
114
genInstanceList igen = fmap (snd . Loader.assignIndices) names_instances
115
    where names_instances =
116
            map (\n -> (Instance.name n, n)) <$> listOf igen
117

    
118
-- let's generate a random instance
119
instance Arbitrary Instance.Instance where
120
  arbitrary = genInstanceSmallerThan maxMem maxDsk maxCpu Nothing
121

    
122
-- * Test cases
123

    
124
-- Simple instance tests, we only have setter/getters
125

    
126
prop_creat :: Instance.Instance -> Property
127
prop_creat inst =
128
  Instance.name inst ==? Instance.alias inst
129

    
130
prop_setIdx :: Instance.Instance -> Types.Idx -> Property
131
prop_setIdx inst idx =
132
  Instance.idx (Instance.setIdx inst idx) ==? idx
133

    
134
prop_setName :: Instance.Instance -> String -> Bool
135
prop_setName inst name =
136
  Instance.name newinst == name &&
137
  Instance.alias newinst == name
138
    where newinst = Instance.setName inst name
139

    
140
prop_setAlias :: Instance.Instance -> String -> Bool
141
prop_setAlias inst name =
142
  Instance.name newinst == Instance.name inst &&
143
  Instance.alias newinst == name
144
    where newinst = Instance.setAlias inst name
145

    
146
prop_setPri :: Instance.Instance -> Types.Ndx -> Property
147
prop_setPri inst pdx =
148
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
149

    
150
prop_setSec :: Instance.Instance -> Types.Ndx -> Property
151
prop_setSec inst sdx =
152
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
153

    
154
prop_setBoth :: Instance.Instance -> Types.Ndx -> Types.Ndx -> Bool
155
prop_setBoth inst pdx sdx =
156
  Instance.pNode si == pdx && Instance.sNode si == sdx
157
    where si = Instance.setBoth inst pdx sdx
158

    
159
prop_shrinkMG :: Instance.Instance -> Property
160
prop_shrinkMG inst =
161
  Instance.mem inst >= 2 * Types.unitMem ==>
162
    case Instance.shrinkByType inst Types.FailMem of
163
      Ok inst' -> Instance.mem inst' ==? Instance.mem inst - Types.unitMem
164
      Bad msg -> failTest msg
165

    
166
prop_shrinkMF :: Instance.Instance -> Property
167
prop_shrinkMF inst =
168
  forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
169
    let inst' = inst { Instance.mem = mem}
170
    in isBad $ Instance.shrinkByType inst' Types.FailMem
171

    
172
prop_shrinkCG :: Instance.Instance -> Property
173
prop_shrinkCG inst =
174
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
175
    case Instance.shrinkByType inst Types.FailCPU of
176
      Ok inst' -> Instance.vcpus inst' ==? Instance.vcpus inst - Types.unitCpu
177
      Bad msg -> failTest msg
178

    
179
prop_shrinkCF :: Instance.Instance -> Property
180
prop_shrinkCF inst =
181
  forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
182
    let inst' = inst { Instance.vcpus = vcpus }
183
    in isBad $ Instance.shrinkByType inst' Types.FailCPU
184

    
185
prop_shrinkDG :: Instance.Instance -> Property
186
prop_shrinkDG inst =
187
  Instance.dsk inst >= 2 * Types.unitDsk ==>
188
    case Instance.shrinkByType inst Types.FailDisk of
189
      Ok inst' -> Instance.dsk inst' ==? Instance.dsk inst - Types.unitDsk
190
      Bad msg -> failTest msg
191

    
192
prop_shrinkDF :: Instance.Instance -> Property
193
prop_shrinkDF inst =
194
  forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
195
    let inst' = inst { Instance.dsk = dsk
196
                     , Instance.disks = [Instance.Disk dsk Nothing] }
197
    in isBad $ Instance.shrinkByType inst' Types.FailDisk
198

    
199
prop_setMovable :: Instance.Instance -> Bool -> Property
200
prop_setMovable inst m =
201
  Instance.movable inst' ==? m
202
    where inst' = Instance.setMovable inst m
203

    
204
testSuite "HTools/Instance"
205
            [ 'prop_creat
206
            , 'prop_setIdx
207
            , 'prop_setName
208
            , 'prop_setAlias
209
            , 'prop_setPri
210
            , 'prop_setSec
211
            , 'prop_setBoth
212
            , 'prop_shrinkMG
213
            , 'prop_shrinkMF
214
            , 'prop_shrinkCG
215
            , 'prop_shrinkCF
216
            , 'prop_shrinkDG
217
            , 'prop_shrinkDF
218
            , 'prop_setMovable
219
            ]