Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / HTools / Types.hs @ da5f09ef

History | View | Annotate | Download (6.3 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, 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.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
import Test.HUnit
42

    
43
import Control.Applicative
44
import Data.List (sort)
45

    
46
import Test.Ganeti.TestHelper
47
import Test.Ganeti.TestCommon
48
import Test.Ganeti.TestHTools
49
import Test.Ganeti.Types (allDiskTemplates)
50

    
51
import Ganeti.BasicTypes
52
import qualified Ganeti.Constants as C
53
import qualified Ganeti.HTools.Types as Types
54

    
55
{-# ANN module "HLint: ignore Use camelCase" #-}
56

    
57
-- * Helpers
58

    
59
-- * Arbitrary instance
60

    
61
$(genArbitrary ''Types.FailMode)
62

    
63
$(genArbitrary ''Types.EvacMode)
64

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

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

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

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

    
123
-- * Test cases
124

    
125
prop_ISpec_serialisation :: Types.ISpec -> Property
126
prop_ISpec_serialisation = testSerialisation
127

    
128
prop_IPolicy_serialisation :: Types.IPolicy -> Property
129
prop_IPolicy_serialisation = testSerialisation
130

    
131
prop_EvacMode_serialisation :: Types.EvacMode -> Property
132
prop_EvacMode_serialisation = testSerialisation
133

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

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

    
152
-- | Test 'AutoRepairType' ordering is as expected and consistent with Python
153
-- codebase.
154
case_AutoRepairType_sort :: Assertion
155
case_AutoRepairType_sort = do
156
  let expected = [ Types.ArFixStorage
157
                 , Types.ArMigrate
158
                 , Types.ArFailover
159
                 , Types.ArReinstall
160
                 ]
161
      all_hs_raw = map Types.autoRepairTypeToRaw [minBound..maxBound]
162
  assertEqual "Haskell order" expected [minBound..maxBound]
163
  assertEqual "consistent with Python" C.autoRepairAllTypes all_hs_raw
164

    
165
-- | Test 'AutoRepairResult' type is equivalent with Python codebase.
166
case_AutoRepairResult_pyequiv :: Assertion
167
case_AutoRepairResult_pyequiv = do
168
  let all_py_results = sort C.autoRepairAllResults
169
      all_hs_results = sort $
170
                       map Types.autoRepairResultToRaw [minBound..maxBound]
171
  assertEqual "for AutoRepairResult equivalence" all_py_results all_hs_results
172

    
173
testSuite "HTools/Types"
174
            [ 'prop_ISpec_serialisation
175
            , 'prop_IPolicy_serialisation
176
            , 'prop_EvacMode_serialisation
177
            , 'prop_opToResult
178
            , 'prop_eitherToResult
179
            , 'case_AutoRepairType_sort
180
            , 'case_AutoRepairResult_pyequiv
181
            ]