Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (6.3 kB)

1 a8038349 Iustin Pop
{-# LANGUAGE TemplateHaskell, FlexibleInstances, TypeSynonymInstances #-}
2 e1ee7d5a Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 e1ee7d5a Iustin Pop
4 e1ee7d5a Iustin Pop
{-| Unittests for ganeti-htools.
5 e1ee7d5a Iustin Pop
6 e1ee7d5a Iustin Pop
-}
7 e1ee7d5a Iustin Pop
8 e1ee7d5a Iustin Pop
{-
9 e1ee7d5a Iustin Pop
10 3cbd5808 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
11 e1ee7d5a Iustin Pop
12 e1ee7d5a Iustin Pop
This program is free software; you can redistribute it and/or modify
13 e1ee7d5a Iustin Pop
it under the terms of the GNU General Public License as published by
14 e1ee7d5a Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 e1ee7d5a Iustin Pop
(at your option) any later version.
16 e1ee7d5a Iustin Pop
17 e1ee7d5a Iustin Pop
This program is distributed in the hope that it will be useful, but
18 e1ee7d5a Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 e1ee7d5a Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 e1ee7d5a Iustin Pop
General Public License for more details.
21 e1ee7d5a Iustin Pop
22 e1ee7d5a Iustin Pop
You should have received a copy of the GNU General Public License
23 e1ee7d5a Iustin Pop
along with this program; if not, write to the Free Software
24 e1ee7d5a Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 e1ee7d5a Iustin Pop
02110-1301, USA.
26 e1ee7d5a Iustin Pop
27 e1ee7d5a Iustin Pop
-}
28 e1ee7d5a Iustin Pop
29 e1ee7d5a Iustin Pop
module Test.Ganeti.HTools.Types
30 e09c1fa0 Iustin Pop
  ( testHTools_Types
31 e1ee7d5a Iustin Pop
  , Types.AllocPolicy(..)
32 e1ee7d5a Iustin Pop
  , Types.DiskTemplate(..)
33 e1ee7d5a Iustin Pop
  , Types.FailMode(..)
34 e1ee7d5a Iustin Pop
  , Types.EvacMode(..)
35 e1ee7d5a Iustin Pop
  , Types.ISpec(..)
36 e1ee7d5a Iustin Pop
  , Types.IPolicy(..)
37 e1ee7d5a Iustin Pop
  , nullIPolicy
38 e1ee7d5a Iustin Pop
  ) where
39 e1ee7d5a Iustin Pop
40 01e52493 Iustin Pop
import Test.QuickCheck hiding (Result)
41 3e77a36c Dato Simó
import Test.HUnit
42 e1ee7d5a Iustin Pop
43 e1ee7d5a Iustin Pop
import Control.Applicative
44 3e77a36c Dato Simó
import Data.List (sort)
45 e1ee7d5a Iustin Pop
46 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHelper
47 e1ee7d5a Iustin Pop
import Test.Ganeti.TestCommon
48 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHTools
49 3cbd5808 Iustin Pop
import Test.Ganeti.Types (allDiskTemplates)
50 e1ee7d5a Iustin Pop
51 01e52493 Iustin Pop
import Ganeti.BasicTypes
52 3e77a36c Dato Simó
import qualified Ganeti.Constants as C
53 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Types as Types
54 e1ee7d5a Iustin Pop
55 d46c9fd6 Dato Simó
{-# ANN module "HLint: ignore Use camelCase" #-}
56 d46c9fd6 Dato Simó
57 e1ee7d5a Iustin Pop
-- * Helpers
58 e1ee7d5a Iustin Pop
59 e1ee7d5a Iustin Pop
-- * Arbitrary instance
60 e1ee7d5a Iustin Pop
61 7022db83 Iustin Pop
$(genArbitrary ''Types.FailMode)
62 e1ee7d5a Iustin Pop
63 7022db83 Iustin Pop
$(genArbitrary ''Types.EvacMode)
64 e1ee7d5a Iustin Pop
65 e1ee7d5a Iustin Pop
instance Arbitrary a => Arbitrary (Types.OpResult a) where
66 e1ee7d5a Iustin Pop
  arbitrary = arbitrary >>= \c ->
67 e1ee7d5a Iustin Pop
              if c
68 a8038349 Iustin Pop
                then Ok  <$> arbitrary
69 a8038349 Iustin Pop
                else Bad <$> arbitrary
70 e1ee7d5a Iustin Pop
71 e1ee7d5a Iustin Pop
instance Arbitrary Types.ISpec where
72 e1ee7d5a Iustin Pop
  arbitrary = do
73 e1ee7d5a Iustin Pop
    mem_s <- arbitrary::Gen (NonNegative Int)
74 e1ee7d5a Iustin Pop
    dsk_c <- arbitrary::Gen (NonNegative Int)
75 e1ee7d5a Iustin Pop
    dsk_s <- arbitrary::Gen (NonNegative Int)
76 e1ee7d5a Iustin Pop
    cpu_c <- arbitrary::Gen (NonNegative Int)
77 e1ee7d5a Iustin Pop
    nic_c <- arbitrary::Gen (NonNegative Int)
78 e1ee7d5a Iustin Pop
    su    <- arbitrary::Gen (NonNegative Int)
79 e1ee7d5a Iustin Pop
    return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
80 e1ee7d5a Iustin Pop
                       , Types.iSpecCpuCount   = fromIntegral cpu_c
81 e1ee7d5a Iustin Pop
                       , Types.iSpecDiskSize   = fromIntegral dsk_s
82 e1ee7d5a Iustin Pop
                       , Types.iSpecDiskCount  = fromIntegral dsk_c
83 e1ee7d5a Iustin Pop
                       , Types.iSpecNicCount   = fromIntegral nic_c
84 e1ee7d5a Iustin Pop
                       , Types.iSpecSpindleUse = fromIntegral su
85 e1ee7d5a Iustin Pop
                       }
86 e1ee7d5a Iustin Pop
87 e1ee7d5a Iustin Pop
-- | Generates an ispec bigger than the given one.
88 e1ee7d5a Iustin Pop
genBiggerISpec :: Types.ISpec -> Gen Types.ISpec
89 e1ee7d5a Iustin Pop
genBiggerISpec imin = do
90 e1ee7d5a Iustin Pop
  mem_s <- choose (Types.iSpecMemorySize imin, maxBound)
91 e1ee7d5a Iustin Pop
  dsk_c <- choose (Types.iSpecDiskCount imin, maxBound)
92 e1ee7d5a Iustin Pop
  dsk_s <- choose (Types.iSpecDiskSize imin, maxBound)
93 e1ee7d5a Iustin Pop
  cpu_c <- choose (Types.iSpecCpuCount imin, maxBound)
94 e1ee7d5a Iustin Pop
  nic_c <- choose (Types.iSpecNicCount imin, maxBound)
95 e1ee7d5a Iustin Pop
  su    <- choose (Types.iSpecSpindleUse imin, maxBound)
96 e1ee7d5a Iustin Pop
  return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
97 e1ee7d5a Iustin Pop
                     , Types.iSpecCpuCount   = fromIntegral cpu_c
98 e1ee7d5a Iustin Pop
                     , Types.iSpecDiskSize   = fromIntegral dsk_s
99 e1ee7d5a Iustin Pop
                     , Types.iSpecDiskCount  = fromIntegral dsk_c
100 e1ee7d5a Iustin Pop
                     , Types.iSpecNicCount   = fromIntegral nic_c
101 e1ee7d5a Iustin Pop
                     , Types.iSpecSpindleUse = fromIntegral su
102 e1ee7d5a Iustin Pop
                     }
103 e1ee7d5a Iustin Pop
104 e1ee7d5a Iustin Pop
instance Arbitrary Types.IPolicy where
105 e1ee7d5a Iustin Pop
  arbitrary = do
106 e1ee7d5a Iustin Pop
    imin <- arbitrary
107 e1ee7d5a Iustin Pop
    istd <- genBiggerISpec imin
108 e1ee7d5a Iustin Pop
    imax <- genBiggerISpec istd
109 e1ee7d5a Iustin Pop
    num_tmpl <- choose (0, length allDiskTemplates)
110 df8578fb Iustin Pop
    dts  <- genUniquesList num_tmpl arbitrary
111 e1ee7d5a Iustin Pop
    vcpu_ratio <- choose (1.0, maxVcpuRatio)
112 e1ee7d5a Iustin Pop
    spindle_ratio <- choose (1.0, maxSpindleRatio)
113 da5f09ef Bernardo Dal Seno
    return Types.IPolicy { Types.iPolicyMinMaxISpecs = Types.MinMaxISpecs
114 da5f09ef Bernardo Dal Seno
                           { Types.minMaxISpecsMinSpec = imin
115 da5f09ef Bernardo Dal Seno
                           , Types.minMaxISpecsMaxSpec = imax
116 da5f09ef Bernardo Dal Seno
                           }
117 e1ee7d5a Iustin Pop
                         , Types.iPolicyStdSpec = istd
118 e1ee7d5a Iustin Pop
                         , Types.iPolicyDiskTemplates = dts
119 e1ee7d5a Iustin Pop
                         , Types.iPolicyVcpuRatio = vcpu_ratio
120 e1ee7d5a Iustin Pop
                         , Types.iPolicySpindleRatio = spindle_ratio
121 e1ee7d5a Iustin Pop
                         }
122 e1ee7d5a Iustin Pop
123 e1ee7d5a Iustin Pop
-- * Test cases
124 e1ee7d5a Iustin Pop
125 20bc5360 Iustin Pop
prop_ISpec_serialisation :: Types.ISpec -> Property
126 63b068c1 Iustin Pop
prop_ISpec_serialisation = testSerialisation
127 e1ee7d5a Iustin Pop
128 20bc5360 Iustin Pop
prop_IPolicy_serialisation :: Types.IPolicy -> Property
129 63b068c1 Iustin Pop
prop_IPolicy_serialisation = testSerialisation
130 e1ee7d5a Iustin Pop
131 20bc5360 Iustin Pop
prop_EvacMode_serialisation :: Types.EvacMode -> Property
132 63b068c1 Iustin Pop
prop_EvacMode_serialisation = testSerialisation
133 e1ee7d5a Iustin Pop
134 a8038349 Iustin Pop
prop_opToResult :: Types.OpResult Int -> Property
135 20bc5360 Iustin Pop
prop_opToResult op =
136 e1ee7d5a Iustin Pop
  case op of
137 a8038349 Iustin Pop
    Bad _ -> printTestCase ("expected bad but got " ++ show r) $ isBad r
138 a8038349 Iustin Pop
    Ok v  -> case r of
139 a8038349 Iustin Pop
               Bad msg -> failTest ("expected Ok but got Bad " ++ msg)
140 a8038349 Iustin Pop
               Ok v' -> v ==? v'
141 e1ee7d5a Iustin Pop
  where r = Types.opToResult op
142 e1ee7d5a Iustin Pop
143 20bc5360 Iustin Pop
prop_eitherToResult :: Either String Int -> Bool
144 20bc5360 Iustin Pop
prop_eitherToResult ei =
145 e1ee7d5a Iustin Pop
  case ei of
146 01e52493 Iustin Pop
    Left _ -> isBad r
147 e1ee7d5a Iustin Pop
    Right v -> case r of
148 01e52493 Iustin Pop
                 Bad _ -> False
149 01e52493 Iustin Pop
                 Ok v' -> v == v'
150 01e52493 Iustin Pop
    where r = eitherToResult ei
151 e1ee7d5a Iustin Pop
152 3e77a36c Dato Simó
-- | Test 'AutoRepairType' ordering is as expected and consistent with Python
153 3e77a36c Dato Simó
-- codebase.
154 3e77a36c Dato Simó
case_AutoRepairType_sort :: Assertion
155 3e77a36c Dato Simó
case_AutoRepairType_sort = do
156 3e77a36c Dato Simó
  let expected = [ Types.ArFixStorage
157 3e77a36c Dato Simó
                 , Types.ArMigrate
158 3e77a36c Dato Simó
                 , Types.ArFailover
159 3e77a36c Dato Simó
                 , Types.ArReinstall
160 3e77a36c Dato Simó
                 ]
161 3e77a36c Dato Simó
      all_hs_raw = map Types.autoRepairTypeToRaw [minBound..maxBound]
162 3e77a36c Dato Simó
  assertEqual "Haskell order" expected [minBound..maxBound]
163 3e77a36c Dato Simó
  assertEqual "consistent with Python" C.autoRepairAllTypes all_hs_raw
164 3e77a36c Dato Simó
165 3e77a36c Dato Simó
-- | Test 'AutoRepairResult' type is equivalent with Python codebase.
166 3e77a36c Dato Simó
case_AutoRepairResult_pyequiv :: Assertion
167 3e77a36c Dato Simó
case_AutoRepairResult_pyequiv = do
168 3e77a36c Dato Simó
  let all_py_results = sort C.autoRepairAllResults
169 3e77a36c Dato Simó
      all_hs_results = sort $
170 3e77a36c Dato Simó
                       map Types.autoRepairResultToRaw [minBound..maxBound]
171 3e77a36c Dato Simó
  assertEqual "for AutoRepairResult equivalence" all_py_results all_hs_results
172 3e77a36c Dato Simó
173 e09c1fa0 Iustin Pop
testSuite "HTools/Types"
174 5e9deac0 Iustin Pop
            [ 'prop_ISpec_serialisation
175 20bc5360 Iustin Pop
            , 'prop_IPolicy_serialisation
176 20bc5360 Iustin Pop
            , 'prop_EvacMode_serialisation
177 20bc5360 Iustin Pop
            , 'prop_opToResult
178 20bc5360 Iustin Pop
            , 'prop_eitherToResult
179 3e77a36c Dato Simó
            , 'case_AutoRepairType_sort
180 3e77a36c Dato Simó
            , 'case_AutoRepairResult_pyequiv
181 e1ee7d5a Iustin Pop
            ]