Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (5.1 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 e1ee7d5a Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 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 e1ee7d5a Iustin Pop
42 e1ee7d5a Iustin Pop
import Control.Applicative
43 e1ee7d5a Iustin Pop
44 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHelper
45 e1ee7d5a Iustin Pop
import Test.Ganeti.TestCommon
46 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHTools
47 5e9deac0 Iustin Pop
import Test.Ganeti.Types ()
48 e1ee7d5a Iustin Pop
49 01e52493 Iustin Pop
import Ganeti.BasicTypes
50 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Types as Types
51 e1ee7d5a Iustin Pop
52 e1ee7d5a Iustin Pop
-- * Helpers
53 e1ee7d5a Iustin Pop
54 e1ee7d5a Iustin Pop
-- | All disk templates (used later)
55 e1ee7d5a Iustin Pop
allDiskTemplates :: [Types.DiskTemplate]
56 e1ee7d5a Iustin Pop
allDiskTemplates = [minBound..maxBound]
57 e1ee7d5a Iustin Pop
58 e1ee7d5a Iustin Pop
-- * Arbitrary instance
59 e1ee7d5a Iustin Pop
60 7022db83 Iustin Pop
$(genArbitrary ''Types.FailMode)
61 e1ee7d5a Iustin Pop
62 7022db83 Iustin Pop
$(genArbitrary ''Types.EvacMode)
63 e1ee7d5a Iustin Pop
64 e1ee7d5a Iustin Pop
instance Arbitrary a => Arbitrary (Types.OpResult a) where
65 e1ee7d5a Iustin Pop
  arbitrary = arbitrary >>= \c ->
66 e1ee7d5a Iustin Pop
              if c
67 a8038349 Iustin Pop
                then Ok  <$> arbitrary
68 a8038349 Iustin Pop
                else Bad <$> arbitrary
69 e1ee7d5a Iustin Pop
70 e1ee7d5a Iustin Pop
instance Arbitrary Types.ISpec where
71 e1ee7d5a Iustin Pop
  arbitrary = do
72 e1ee7d5a Iustin Pop
    mem_s <- arbitrary::Gen (NonNegative Int)
73 e1ee7d5a Iustin Pop
    dsk_c <- arbitrary::Gen (NonNegative Int)
74 e1ee7d5a Iustin Pop
    dsk_s <- arbitrary::Gen (NonNegative Int)
75 e1ee7d5a Iustin Pop
    cpu_c <- arbitrary::Gen (NonNegative Int)
76 e1ee7d5a Iustin Pop
    nic_c <- arbitrary::Gen (NonNegative Int)
77 e1ee7d5a Iustin Pop
    su    <- arbitrary::Gen (NonNegative Int)
78 e1ee7d5a Iustin Pop
    return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
79 e1ee7d5a Iustin Pop
                       , Types.iSpecCpuCount   = fromIntegral cpu_c
80 e1ee7d5a Iustin Pop
                       , Types.iSpecDiskSize   = fromIntegral dsk_s
81 e1ee7d5a Iustin Pop
                       , Types.iSpecDiskCount  = fromIntegral dsk_c
82 e1ee7d5a Iustin Pop
                       , Types.iSpecNicCount   = fromIntegral nic_c
83 e1ee7d5a Iustin Pop
                       , Types.iSpecSpindleUse = fromIntegral su
84 e1ee7d5a Iustin Pop
                       }
85 e1ee7d5a Iustin Pop
86 e1ee7d5a Iustin Pop
-- | Generates an ispec bigger than the given one.
87 e1ee7d5a Iustin Pop
genBiggerISpec :: Types.ISpec -> Gen Types.ISpec
88 e1ee7d5a Iustin Pop
genBiggerISpec imin = do
89 e1ee7d5a Iustin Pop
  mem_s <- choose (Types.iSpecMemorySize imin, maxBound)
90 e1ee7d5a Iustin Pop
  dsk_c <- choose (Types.iSpecDiskCount imin, maxBound)
91 e1ee7d5a Iustin Pop
  dsk_s <- choose (Types.iSpecDiskSize imin, maxBound)
92 e1ee7d5a Iustin Pop
  cpu_c <- choose (Types.iSpecCpuCount imin, maxBound)
93 e1ee7d5a Iustin Pop
  nic_c <- choose (Types.iSpecNicCount imin, maxBound)
94 e1ee7d5a Iustin Pop
  su    <- choose (Types.iSpecSpindleUse imin, maxBound)
95 e1ee7d5a Iustin Pop
  return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
96 e1ee7d5a Iustin Pop
                     , Types.iSpecCpuCount   = fromIntegral cpu_c
97 e1ee7d5a Iustin Pop
                     , Types.iSpecDiskSize   = fromIntegral dsk_s
98 e1ee7d5a Iustin Pop
                     , Types.iSpecDiskCount  = fromIntegral dsk_c
99 e1ee7d5a Iustin Pop
                     , Types.iSpecNicCount   = fromIntegral nic_c
100 e1ee7d5a Iustin Pop
                     , Types.iSpecSpindleUse = fromIntegral su
101 e1ee7d5a Iustin Pop
                     }
102 e1ee7d5a Iustin Pop
103 e1ee7d5a Iustin Pop
instance Arbitrary Types.IPolicy where
104 e1ee7d5a Iustin Pop
  arbitrary = do
105 e1ee7d5a Iustin Pop
    imin <- arbitrary
106 e1ee7d5a Iustin Pop
    istd <- genBiggerISpec imin
107 e1ee7d5a Iustin Pop
    imax <- genBiggerISpec istd
108 e1ee7d5a Iustin Pop
    num_tmpl <- choose (0, length allDiskTemplates)
109 e1ee7d5a Iustin Pop
    dts  <- genUniquesList num_tmpl
110 e1ee7d5a Iustin Pop
    vcpu_ratio <- choose (1.0, maxVcpuRatio)
111 e1ee7d5a Iustin Pop
    spindle_ratio <- choose (1.0, maxSpindleRatio)
112 e1ee7d5a Iustin Pop
    return Types.IPolicy { Types.iPolicyMinSpec = imin
113 e1ee7d5a Iustin Pop
                         , Types.iPolicyStdSpec = istd
114 e1ee7d5a Iustin Pop
                         , Types.iPolicyMaxSpec = imax
115 e1ee7d5a Iustin Pop
                         , Types.iPolicyDiskTemplates = dts
116 e1ee7d5a Iustin Pop
                         , Types.iPolicyVcpuRatio = vcpu_ratio
117 e1ee7d5a Iustin Pop
                         , Types.iPolicySpindleRatio = spindle_ratio
118 e1ee7d5a Iustin Pop
                         }
119 e1ee7d5a Iustin Pop
120 e1ee7d5a Iustin Pop
-- * Test cases
121 e1ee7d5a Iustin Pop
122 20bc5360 Iustin Pop
prop_ISpec_serialisation :: Types.ISpec -> Property
123 63b068c1 Iustin Pop
prop_ISpec_serialisation = testSerialisation
124 e1ee7d5a Iustin Pop
125 20bc5360 Iustin Pop
prop_IPolicy_serialisation :: Types.IPolicy -> Property
126 63b068c1 Iustin Pop
prop_IPolicy_serialisation = testSerialisation
127 e1ee7d5a Iustin Pop
128 20bc5360 Iustin Pop
prop_EvacMode_serialisation :: Types.EvacMode -> Property
129 63b068c1 Iustin Pop
prop_EvacMode_serialisation = testSerialisation
130 e1ee7d5a Iustin Pop
131 a8038349 Iustin Pop
prop_opToResult :: Types.OpResult Int -> Property
132 20bc5360 Iustin Pop
prop_opToResult op =
133 e1ee7d5a Iustin Pop
  case op of
134 a8038349 Iustin Pop
    Bad _ -> printTestCase ("expected bad but got " ++ show r) $ isBad r
135 a8038349 Iustin Pop
    Ok v  -> case r of
136 a8038349 Iustin Pop
               Bad msg -> failTest ("expected Ok but got Bad " ++ msg)
137 a8038349 Iustin Pop
               Ok v' -> v ==? v'
138 e1ee7d5a Iustin Pop
  where r = Types.opToResult op
139 e1ee7d5a Iustin Pop
140 20bc5360 Iustin Pop
prop_eitherToResult :: Either String Int -> Bool
141 20bc5360 Iustin Pop
prop_eitherToResult ei =
142 e1ee7d5a Iustin Pop
  case ei of
143 01e52493 Iustin Pop
    Left _ -> isBad r
144 e1ee7d5a Iustin Pop
    Right v -> case r of
145 01e52493 Iustin Pop
                 Bad _ -> False
146 01e52493 Iustin Pop
                 Ok v' -> v == v'
147 01e52493 Iustin Pop
    where r = eitherToResult ei
148 e1ee7d5a Iustin Pop
149 e09c1fa0 Iustin Pop
testSuite "HTools/Types"
150 5e9deac0 Iustin Pop
            [ 'prop_ISpec_serialisation
151 20bc5360 Iustin Pop
            , 'prop_IPolicy_serialisation
152 20bc5360 Iustin Pop
            , 'prop_EvacMode_serialisation
153 20bc5360 Iustin Pop
            , 'prop_opToResult
154 20bc5360 Iustin Pop
            , 'prop_eitherToResult
155 e1ee7d5a Iustin Pop
            ]