Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / Types.hs @ c65621d7

History | View | Annotate | Download (6.3 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2
{-# OPTIONS_GHC -fno-warn-orphans #-}
3

    
4
{-| Unittests for 'Ganeti.Types'.
5

    
6
-}
7

    
8
{-
9

    
10
Copyright (C) 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.Types
30
  ( testTypes
31
  , AllocPolicy(..)
32
  , DiskTemplate(..)
33
  , InstanceStatus(..)
34
  , NonEmpty(..)
35
  , Hypervisor(..)
36
  ) where
37

    
38
import Data.List (sort)
39
import Test.QuickCheck as QuickCheck hiding (Result)
40
import Test.HUnit
41

    
42
import Test.Ganeti.TestHelper
43
import Test.Ganeti.TestCommon
44

    
45
import Ganeti.BasicTypes
46
import qualified Ganeti.Constants as C
47
import Ganeti.Types as Types
48

    
49
{-# ANN module "HLint: ignore Use camelCase" #-}
50

    
51
-- * Arbitrary instance
52

    
53
instance (Arbitrary a, Ord a, Num a, Show a) =>
54
  Arbitrary (Types.Positive a) where
55
  arbitrary = do
56
    (QuickCheck.Positive i) <- arbitrary
57
    Types.mkPositive i
58

    
59
instance (Arbitrary a) => Arbitrary (Types.NonEmpty a) where
60
  arbitrary = do
61
    QuickCheck.NonEmpty lst <- arbitrary
62
    Types.mkNonEmpty lst
63

    
64
$(genArbitrary ''AllocPolicy)
65

    
66
$(genArbitrary ''DiskTemplate)
67

    
68
$(genArbitrary ''InstanceStatus)
69

    
70
$(genArbitrary ''MigrationMode)
71

    
72
$(genArbitrary ''VerifyOptionalChecks)
73

    
74
$(genArbitrary ''DdmSimple)
75

    
76
$(genArbitrary ''CVErrorCode)
77

    
78
$(genArbitrary ''Hypervisor)
79

    
80
$(genArbitrary ''OobCommand)
81

    
82
$(genArbitrary ''StorageType)
83

    
84
$(genArbitrary ''NodeEvacMode)
85

    
86
$(genArbitrary ''FileDriver)
87

    
88
-- * Properties
89

    
90
prop_AllocPolicy_serialisation :: AllocPolicy -> Property
91
prop_AllocPolicy_serialisation = testSerialisation
92

    
93
prop_DiskTemplate_serialisation :: DiskTemplate -> Property
94
prop_DiskTemplate_serialisation = testSerialisation
95

    
96
prop_InstanceStatus_serialisation :: InstanceStatus -> Property
97
prop_InstanceStatus_serialisation = testSerialisation
98

    
99
-- | Tests building non-negative numbers.
100
prop_NonNeg_pass :: QuickCheck.NonNegative Int -> Property
101
prop_NonNeg_pass (QuickCheck.NonNegative i) =
102
  case mkNonNegative i of
103
    Bad msg -> failTest $ "Fail to build non-negative: " ++ msg
104
    Ok nn -> fromNonNegative nn ==? i
105

    
106
-- | Tests building non-negative numbers.
107
prop_NonNeg_fail :: QuickCheck.Positive Int -> Property
108
prop_NonNeg_fail (QuickCheck.Positive i) =
109
  case mkNonNegative (negate i)::Result (Types.NonNegative Int) of
110
    Bad _ -> passTest
111
    Ok nn -> failTest $ "Built non-negative number '" ++ show nn ++
112
             "' from negative value " ++ show i
113

    
114
-- | Tests building positive numbers.
115
prop_Positive_pass :: QuickCheck.Positive Int -> Property
116
prop_Positive_pass (QuickCheck.Positive i) =
117
  case mkPositive i of
118
    Bad msg -> failTest $ "Fail to build positive: " ++ msg
119
    Ok nn -> fromPositive nn ==? i
120

    
121
-- | Tests building positive numbers.
122
prop_Positive_fail :: QuickCheck.NonNegative Int -> Property
123
prop_Positive_fail (QuickCheck.NonNegative i) =
124
  case mkPositive (negate i)::Result (Types.Positive Int) of
125
    Bad _ -> passTest
126
    Ok nn -> failTest $ "Built positive number '" ++ show nn ++
127
             "' from negative or zero value " ++ show i
128

    
129
-- | Tests building non-empty lists.
130
prop_NonEmpty_pass :: QuickCheck.NonEmptyList String -> Property
131
prop_NonEmpty_pass (QuickCheck.NonEmpty xs) =
132
  case mkNonEmpty xs of
133
    Bad msg -> failTest $ "Fail to build non-empty list: " ++ msg
134
    Ok nn -> fromNonEmpty nn ==? xs
135

    
136
-- | Tests building positive numbers.
137
case_NonEmpty_fail :: Assertion
138
case_NonEmpty_fail =
139
  assertEqual "building non-empty list from an empty list"
140
    (Bad "Received empty value for non-empty list") (mkNonEmpty ([]::[Int]))
141

    
142
-- | Tests migration mode serialisation.
143
prop_MigrationMode_serialisation :: MigrationMode -> Property
144
prop_MigrationMode_serialisation = testSerialisation
145

    
146
-- | Tests verify optional checks serialisation.
147
prop_VerifyOptionalChecks_serialisation :: VerifyOptionalChecks -> Property
148
prop_VerifyOptionalChecks_serialisation = testSerialisation
149

    
150
-- | Tests 'DdmSimple' serialisation.
151
prop_DdmSimple_serialisation :: DdmSimple -> Property
152
prop_DdmSimple_serialisation = testSerialisation
153

    
154
-- | Tests 'CVErrorCode' serialisation.
155
prop_CVErrorCode_serialisation :: CVErrorCode -> Property
156
prop_CVErrorCode_serialisation = testSerialisation
157

    
158
-- | Tests equivalence with Python, based on Constants.hs code.
159
case_CVErrorCode_pyequiv :: Assertion
160
case_CVErrorCode_pyequiv = do
161
  let all_py_codes = sort C.cvAllEcodesStrings
162
      all_hs_codes = sort $ map Types.cVErrorCodeToRaw [minBound..maxBound]
163
  assertEqual "for CVErrorCode equivalence" all_py_codes all_hs_codes
164

    
165
-- | Test 'Hypervisor' serialisation.
166
prop_Hypervisor_serialisation :: Hypervisor -> Property
167
prop_Hypervisor_serialisation = testSerialisation
168

    
169
-- | Test 'OobCommand' serialisation.
170
prop_OobCommand_serialisation :: OobCommand -> Property
171
prop_OobCommand_serialisation = testSerialisation
172

    
173
-- | Test 'StorageType' serialisation.
174
prop_StorageType_serialisation :: StorageType -> Property
175
prop_StorageType_serialisation = testSerialisation
176

    
177
-- | Test 'NodeEvacMode' serialisation.
178
prop_NodeEvacMode_serialisation :: NodeEvacMode -> Property
179
prop_NodeEvacMode_serialisation = testSerialisation
180

    
181
-- | Test 'FileDriver' serialisation.
182
prop_FileDriver_serialisation :: FileDriver -> Property
183
prop_FileDriver_serialisation = testSerialisation
184

    
185
testSuite "Types"
186
  [ 'prop_AllocPolicy_serialisation
187
  , 'prop_DiskTemplate_serialisation
188
  , 'prop_InstanceStatus_serialisation
189
  , 'prop_NonNeg_pass
190
  , 'prop_NonNeg_fail
191
  , 'prop_Positive_pass
192
  , 'prop_Positive_fail
193
  , 'prop_NonEmpty_pass
194
  , 'case_NonEmpty_fail
195
  , 'prop_MigrationMode_serialisation
196
  , 'prop_VerifyOptionalChecks_serialisation
197
  , 'prop_DdmSimple_serialisation
198
  , 'prop_CVErrorCode_serialisation
199
  , 'case_CVErrorCode_pyequiv
200
  , 'prop_Hypervisor_serialisation
201
  , 'prop_OobCommand_serialisation
202
  , 'prop_StorageType_serialisation
203
  , 'prop_NodeEvacMode_serialisation
204
  , 'prop_FileDriver_serialisation
205
  ]