Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / Types.hs @ df8578fb

History | View | Annotate | Download (5.1 kB)

1
{-# LANGUAGE TemplateHaskell, FlexibleInstances, TypeSynonymInstances #-}
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.ISpec(..)
36
  , Types.IPolicy(..)
37
  , nullIPolicy
38
  ) where
39

    
40
import Test.QuickCheck hiding (Result)
41

    
42
import Control.Applicative
43

    
44
import Test.Ganeti.TestHelper
45
import Test.Ganeti.TestCommon
46
import Test.Ganeti.TestHTools
47
import Test.Ganeti.Types ()
48

    
49
import Ganeti.BasicTypes
50
import qualified Ganeti.HTools.Types as Types
51

    
52
-- * Helpers
53

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

    
58
-- * Arbitrary instance
59

    
60
$(genArbitrary ''Types.FailMode)
61

    
62
$(genArbitrary ''Types.EvacMode)
63

    
64
instance Arbitrary a => Arbitrary (Types.OpResult a) where
65
  arbitrary = arbitrary >>= \c ->
66
              if c
67
                then Ok  <$> arbitrary
68
                else Bad <$> arbitrary
69

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

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

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

    
120
-- * Test cases
121

    
122
prop_ISpec_serialisation :: Types.ISpec -> Property
123
prop_ISpec_serialisation = testSerialisation
124

    
125
prop_IPolicy_serialisation :: Types.IPolicy -> Property
126
prop_IPolicy_serialisation = testSerialisation
127

    
128
prop_EvacMode_serialisation :: Types.EvacMode -> Property
129
prop_EvacMode_serialisation = testSerialisation
130

    
131
prop_opToResult :: Types.OpResult Int -> Property
132
prop_opToResult op =
133
  case op of
134
    Bad _ -> printTestCase ("expected bad but got " ++ show r) $ isBad r
135
    Ok v  -> case r of
136
               Bad msg -> failTest ("expected Ok but got Bad " ++ msg)
137
               Ok v' -> v ==? v'
138
  where r = Types.opToResult op
139

    
140
prop_eitherToResult :: Either String Int -> Bool
141
prop_eitherToResult ei =
142
  case ei of
143
    Left _ -> isBad r
144
    Right v -> case r of
145
                 Bad _ -> False
146
                 Ok v' -> v == v'
147
    where r = eitherToResult ei
148

    
149
testSuite "HTools/Types"
150
            [ 'prop_ISpec_serialisation
151
            , 'prop_IPolicy_serialisation
152
            , 'prop_EvacMode_serialisation
153
            , 'prop_opToResult
154
            , 'prop_eitherToResult
155
            ]