Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / Types.hs @ 63b068c1

History | View | Annotate | Download (5.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 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.Types
30
  ( testHTools_Types
31
  , Types.AllocPolicy(..)
32
  , Types.DiskTemplate(..)
33
  , Types.FailMode(..)
34
  , Types.EvacMode(..)
35
  , Types.OpResult(..)
36
  , Types.ISpec(..)
37
  , Types.IPolicy(..)
38
  , nullIPolicy
39
  ) where
40

    
41
import Test.QuickCheck
42

    
43
import Control.Applicative
44

    
45
import Test.Ganeti.TestHelper
46
import Test.Ganeti.TestCommon
47
import Test.Ganeti.TestHTools
48

    
49
import qualified Ganeti.HTools.Types as Types
50

    
51
-- * Helpers
52

    
53
-- | All disk templates (used later)
54
allDiskTemplates :: [Types.DiskTemplate]
55
allDiskTemplates = [minBound..maxBound]
56

    
57
-- * Arbitrary instance
58

    
59
instance Arbitrary Types.AllocPolicy where
60
  arbitrary = elements [minBound..maxBound]
61

    
62
instance Arbitrary Types.DiskTemplate where
63
  arbitrary = elements [minBound..maxBound]
64

    
65
instance Arbitrary Types.FailMode where
66
  arbitrary = elements [minBound..maxBound]
67

    
68
instance Arbitrary Types.EvacMode where
69
  arbitrary = elements [minBound..maxBound]
70

    
71
instance Arbitrary a => Arbitrary (Types.OpResult a) where
72
  arbitrary = arbitrary >>= \c ->
73
              if c
74
                then Types.OpGood <$> arbitrary
75
                else Types.OpFail <$> arbitrary
76

    
77
instance Arbitrary Types.ISpec where
78
  arbitrary = do
79
    mem_s <- arbitrary::Gen (NonNegative Int)
80
    dsk_c <- arbitrary::Gen (NonNegative Int)
81
    dsk_s <- arbitrary::Gen (NonNegative Int)
82
    cpu_c <- arbitrary::Gen (NonNegative Int)
83
    nic_c <- arbitrary::Gen (NonNegative Int)
84
    su    <- arbitrary::Gen (NonNegative Int)
85
    return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
86
                       , Types.iSpecCpuCount   = fromIntegral cpu_c
87
                       , Types.iSpecDiskSize   = fromIntegral dsk_s
88
                       , Types.iSpecDiskCount  = fromIntegral dsk_c
89
                       , Types.iSpecNicCount   = fromIntegral nic_c
90
                       , Types.iSpecSpindleUse = fromIntegral su
91
                       }
92

    
93
-- | Generates an ispec bigger than the given one.
94
genBiggerISpec :: Types.ISpec -> Gen Types.ISpec
95
genBiggerISpec imin = do
96
  mem_s <- choose (Types.iSpecMemorySize imin, maxBound)
97
  dsk_c <- choose (Types.iSpecDiskCount imin, maxBound)
98
  dsk_s <- choose (Types.iSpecDiskSize imin, maxBound)
99
  cpu_c <- choose (Types.iSpecCpuCount imin, maxBound)
100
  nic_c <- choose (Types.iSpecNicCount imin, maxBound)
101
  su    <- choose (Types.iSpecSpindleUse imin, maxBound)
102
  return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
103
                     , Types.iSpecCpuCount   = fromIntegral cpu_c
104
                     , Types.iSpecDiskSize   = fromIntegral dsk_s
105
                     , Types.iSpecDiskCount  = fromIntegral dsk_c
106
                     , Types.iSpecNicCount   = fromIntegral nic_c
107
                     , Types.iSpecSpindleUse = fromIntegral su
108
                     }
109

    
110
instance Arbitrary Types.IPolicy where
111
  arbitrary = do
112
    imin <- arbitrary
113
    istd <- genBiggerISpec imin
114
    imax <- genBiggerISpec istd
115
    num_tmpl <- choose (0, length allDiskTemplates)
116
    dts  <- genUniquesList num_tmpl
117
    vcpu_ratio <- choose (1.0, maxVcpuRatio)
118
    spindle_ratio <- choose (1.0, maxSpindleRatio)
119
    return Types.IPolicy { Types.iPolicyMinSpec = imin
120
                         , Types.iPolicyStdSpec = istd
121
                         , Types.iPolicyMaxSpec = imax
122
                         , Types.iPolicyDiskTemplates = dts
123
                         , Types.iPolicyVcpuRatio = vcpu_ratio
124
                         , Types.iPolicySpindleRatio = spindle_ratio
125
                         }
126

    
127
-- * Test cases
128

    
129
prop_AllocPolicy_serialisation :: Types.AllocPolicy -> Property
130
prop_AllocPolicy_serialisation = testSerialisation
131

    
132
prop_DiskTemplate_serialisation :: Types.DiskTemplate -> Property
133
prop_DiskTemplate_serialisation = testSerialisation
134

    
135
prop_ISpec_serialisation :: Types.ISpec -> Property
136
prop_ISpec_serialisation = testSerialisation
137

    
138
prop_IPolicy_serialisation :: Types.IPolicy -> Property
139
prop_IPolicy_serialisation = testSerialisation
140

    
141
prop_EvacMode_serialisation :: Types.EvacMode -> Property
142
prop_EvacMode_serialisation = testSerialisation
143

    
144
prop_opToResult :: Types.OpResult Int -> Bool
145
prop_opToResult op =
146
  case op of
147
    Types.OpFail _ -> Types.isBad r
148
    Types.OpGood v -> case r of
149
                        Types.Bad _ -> False
150
                        Types.Ok v' -> v == v'
151
  where r = Types.opToResult op
152

    
153
prop_eitherToResult :: Either String Int -> Bool
154
prop_eitherToResult ei =
155
  case ei of
156
    Left _ -> Types.isBad r
157
    Right v -> case r of
158
                 Types.Bad _ -> False
159
                 Types.Ok v' -> v == v'
160
    where r = Types.eitherToResult ei
161

    
162
testSuite "HTools/Types"
163
            [ 'prop_AllocPolicy_serialisation
164
            , 'prop_DiskTemplate_serialisation
165
            , 'prop_ISpec_serialisation
166
            , 'prop_IPolicy_serialisation
167
            , 'prop_EvacMode_serialisation
168
            , 'prop_opToResult
169
            , 'prop_eitherToResult
170
            ]