Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / Types.hs @ 7022db83

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.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
$(genArbitrary ''Types.AllocPolicy)
60

    
61
$(genArbitrary ''Types.DiskTemplate)
62

    
63
$(genArbitrary ''Types.FailMode)
64

    
65
$(genArbitrary ''Types.EvacMode)
66

    
67
instance Arbitrary a => Arbitrary (Types.OpResult a) where
68
  arbitrary = arbitrary >>= \c ->
69
              if c
70
                then Types.OpGood <$> arbitrary
71
                else Types.OpFail <$> arbitrary
72

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

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

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

    
123
-- * Test cases
124

    
125
prop_AllocPolicy_serialisation :: Types.AllocPolicy -> Property
126
prop_AllocPolicy_serialisation = testSerialisation
127

    
128
prop_DiskTemplate_serialisation :: Types.DiskTemplate -> Property
129
prop_DiskTemplate_serialisation = testSerialisation
130

    
131
prop_ISpec_serialisation :: Types.ISpec -> Property
132
prop_ISpec_serialisation = testSerialisation
133

    
134
prop_IPolicy_serialisation :: Types.IPolicy -> Property
135
prop_IPolicy_serialisation = testSerialisation
136

    
137
prop_EvacMode_serialisation :: Types.EvacMode -> Property
138
prop_EvacMode_serialisation = testSerialisation
139

    
140
prop_opToResult :: Types.OpResult Int -> Bool
141
prop_opToResult op =
142
  case op of
143
    Types.OpFail _ -> Types.isBad r
144
    Types.OpGood v -> case r of
145
                        Types.Bad _ -> False
146
                        Types.Ok v' -> v == v'
147
  where r = Types.opToResult op
148

    
149
prop_eitherToResult :: Either String Int -> Bool
150
prop_eitherToResult ei =
151
  case ei of
152
    Left _ -> Types.isBad r
153
    Right v -> case r of
154
                 Types.Bad _ -> False
155
                 Types.Ok v' -> v == v'
156
    where r = Types.eitherToResult ei
157

    
158
testSuite "HTools/Types"
159
            [ 'prop_AllocPolicy_serialisation
160
            , 'prop_DiskTemplate_serialisation
161
            , 'prop_ISpec_serialisation
162
            , 'prop_IPolicy_serialisation
163
            , 'prop_EvacMode_serialisation
164
            , 'prop_opToResult
165
            , 'prop_eitherToResult
166
            ]