Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / Types.hs @ 6903fea0

History | View | Annotate | Download (9.8 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, Ord a, Num a, Show a) =>
60
  Arbitrary (Types.NonNegative a) where
61
  arbitrary = do
62
    (QuickCheck.NonNegative i) <- arbitrary
63
    Types.mkNonNegative i
64

    
65
instance (Arbitrary a) => Arbitrary (Types.NonEmpty a) where
66
  arbitrary = do
67
    QuickCheck.NonEmpty lst <- arbitrary
68
    Types.mkNonEmpty lst
69

    
70
$(genArbitrary ''AllocPolicy)
71

    
72
$(genArbitrary ''DiskTemplate)
73

    
74
$(genArbitrary ''InstanceStatus)
75

    
76
$(genArbitrary ''MigrationMode)
77

    
78
$(genArbitrary ''VerifyOptionalChecks)
79

    
80
$(genArbitrary ''DdmSimple)
81

    
82
$(genArbitrary ''DdmFull)
83

    
84
$(genArbitrary ''CVErrorCode)
85

    
86
$(genArbitrary ''Hypervisor)
87

    
88
$(genArbitrary ''OobCommand)
89

    
90
$(genArbitrary ''StorageType)
91

    
92
$(genArbitrary ''NodeEvacMode)
93

    
94
$(genArbitrary ''FileDriver)
95

    
96
$(genArbitrary ''InstCreateMode)
97

    
98
$(genArbitrary ''RebootType)
99

    
100
$(genArbitrary ''ExportMode)
101

    
102
$(genArbitrary ''IAllocatorTestDir)
103

    
104
$(genArbitrary ''IAllocatorMode)
105

    
106
$(genArbitrary ''NetworkType)
107

    
108
$(genArbitrary ''NICMode)
109

    
110
$(genArbitrary ''FinalizedJobStatus)
111

    
112
-- * Properties
113

    
114
prop_AllocPolicy_serialisation :: AllocPolicy -> Property
115
prop_AllocPolicy_serialisation = testSerialisation
116

    
117
prop_DiskTemplate_serialisation :: DiskTemplate -> Property
118
prop_DiskTemplate_serialisation = testSerialisation
119

    
120
prop_InstanceStatus_serialisation :: InstanceStatus -> Property
121
prop_InstanceStatus_serialisation = testSerialisation
122

    
123
-- | Tests building non-negative numbers.
124
prop_NonNeg_pass :: QuickCheck.NonNegative Int -> Property
125
prop_NonNeg_pass (QuickCheck.NonNegative i) =
126
  case mkNonNegative i of
127
    Bad msg -> failTest $ "Fail to build non-negative: " ++ msg
128
    Ok nn -> fromNonNegative nn ==? i
129

    
130
-- | Tests building non-negative numbers.
131
prop_NonNeg_fail :: QuickCheck.Positive Int -> Property
132
prop_NonNeg_fail (QuickCheck.Positive i) =
133
  case mkNonNegative (negate i)::Result (Types.NonNegative Int) of
134
    Bad _ -> passTest
135
    Ok nn -> failTest $ "Built non-negative number '" ++ show nn ++
136
             "' from negative value " ++ show i
137

    
138
-- | Tests building positive numbers.
139
prop_Positive_pass :: QuickCheck.Positive Int -> Property
140
prop_Positive_pass (QuickCheck.Positive i) =
141
  case mkPositive i of
142
    Bad msg -> failTest $ "Fail to build positive: " ++ msg
143
    Ok nn -> fromPositive nn ==? i
144

    
145
-- | Tests building positive numbers.
146
prop_Positive_fail :: QuickCheck.NonNegative Int -> Property
147
prop_Positive_fail (QuickCheck.NonNegative i) =
148
  case mkPositive (negate i)::Result (Types.Positive Int) of
149
    Bad _ -> passTest
150
    Ok nn -> failTest $ "Built positive number '" ++ show nn ++
151
             "' from negative or zero value " ++ show i
152

    
153
-- | Tests building non-empty lists.
154
prop_NonEmpty_pass :: QuickCheck.NonEmptyList String -> Property
155
prop_NonEmpty_pass (QuickCheck.NonEmpty xs) =
156
  case mkNonEmpty xs of
157
    Bad msg -> failTest $ "Fail to build non-empty list: " ++ msg
158
    Ok nn -> fromNonEmpty nn ==? xs
159

    
160
-- | Tests building positive numbers.
161
case_NonEmpty_fail :: Assertion
162
case_NonEmpty_fail =
163
  assertEqual "building non-empty list from an empty list"
164
    (Bad "Received empty value for non-empty list") (mkNonEmpty ([]::[Int]))
165

    
166
-- | Tests migration mode serialisation.
167
prop_MigrationMode_serialisation :: MigrationMode -> Property
168
prop_MigrationMode_serialisation = testSerialisation
169

    
170
-- | Tests verify optional checks serialisation.
171
prop_VerifyOptionalChecks_serialisation :: VerifyOptionalChecks -> Property
172
prop_VerifyOptionalChecks_serialisation = testSerialisation
173

    
174
-- | Tests 'DdmSimple' serialisation.
175
prop_DdmSimple_serialisation :: DdmSimple -> Property
176
prop_DdmSimple_serialisation = testSerialisation
177

    
178
-- | Tests 'DdmFull' serialisation.
179
prop_DdmFull_serialisation :: DdmFull -> Property
180
prop_DdmFull_serialisation = testSerialisation
181

    
182
-- | Tests 'CVErrorCode' serialisation.
183
prop_CVErrorCode_serialisation :: CVErrorCode -> Property
184
prop_CVErrorCode_serialisation = testSerialisation
185

    
186
-- | Tests equivalence with Python, based on Constants.hs code.
187
case_CVErrorCode_pyequiv :: Assertion
188
case_CVErrorCode_pyequiv = do
189
  let all_py_codes = sort C.cvAllEcodesStrings
190
      all_hs_codes = sort $ map Types.cVErrorCodeToRaw [minBound..maxBound]
191
  assertEqual "for CVErrorCode equivalence" all_py_codes all_hs_codes
192

    
193
-- | Test 'Hypervisor' serialisation.
194
prop_Hypervisor_serialisation :: Hypervisor -> Property
195
prop_Hypervisor_serialisation = testSerialisation
196

    
197
-- | Test 'OobCommand' serialisation.
198
prop_OobCommand_serialisation :: OobCommand -> Property
199
prop_OobCommand_serialisation = testSerialisation
200

    
201
-- | Test 'StorageType' serialisation.
202
prop_StorageType_serialisation :: StorageType -> Property
203
prop_StorageType_serialisation = testSerialisation
204

    
205
-- | Test 'NodeEvacMode' serialisation.
206
prop_NodeEvacMode_serialisation :: NodeEvacMode -> Property
207
prop_NodeEvacMode_serialisation = testSerialisation
208

    
209
-- | Test 'FileDriver' serialisation.
210
prop_FileDriver_serialisation :: FileDriver -> Property
211
prop_FileDriver_serialisation = testSerialisation
212

    
213
-- | Test 'InstCreate' serialisation.
214
prop_InstCreateMode_serialisation :: InstCreateMode -> Property
215
prop_InstCreateMode_serialisation = testSerialisation
216

    
217
-- | Test 'RebootType' serialisation.
218
prop_RebootType_serialisation :: RebootType -> Property
219
prop_RebootType_serialisation = testSerialisation
220

    
221
-- | Test 'ExportMode' serialisation.
222
prop_ExportMode_serialisation :: ExportMode -> Property
223
prop_ExportMode_serialisation = testSerialisation
224

    
225
-- | Test 'IAllocatorTestDir' serialisation.
226
prop_IAllocatorTestDir_serialisation :: IAllocatorTestDir -> Property
227
prop_IAllocatorTestDir_serialisation = testSerialisation
228

    
229
-- | Test 'IAllocatorMode' serialisation.
230
prop_IAllocatorMode_serialisation :: IAllocatorMode -> Property
231
prop_IAllocatorMode_serialisation = testSerialisation
232

    
233
-- | Tests equivalence with Python, based on Constants.hs code.
234
case_IAllocatorMode_pyequiv :: Assertion
235
case_IAllocatorMode_pyequiv = do
236
  let all_py_codes = sort C.validIallocatorModes
237
      all_hs_codes = sort $ map Types.iAllocatorModeToRaw [minBound..maxBound]
238
  assertEqual "for IAllocatorMode equivalence" all_py_codes all_hs_codes
239

    
240
-- | Test 'NetworkType' serialisation.
241
prop_NetworkType_serialisation :: NetworkType -> Property
242
prop_NetworkType_serialisation = testSerialisation
243

    
244
-- | Tests equivalence with Python, based on Constants.hs code.
245
case_NetworkType_pyequiv :: Assertion
246
case_NetworkType_pyequiv = do
247
  let all_py_codes = sort C.networkValidTypes
248
      all_hs_codes = sort $ map Types.networkTypeToRaw [minBound..maxBound]
249
  assertEqual "for NetworkType equivalence" all_py_codes all_hs_codes
250

    
251
-- | Test 'NICMode' serialisation.
252
prop_NICMode_serialisation :: NICMode -> Property
253
prop_NICMode_serialisation = testSerialisation
254

    
255
-- | Tests equivalence with Python, based on Constants.hs code.
256
case_NICMode_pyequiv :: Assertion
257
case_NICMode_pyequiv = do
258
  let all_py_codes = sort C.nicValidModes
259
      all_hs_codes = sort $ map Types.nICModeToRaw [minBound..maxBound]
260
  assertEqual "for NICMode equivalence" all_py_codes all_hs_codes
261

    
262
-- | Test 'FinalizedJobStatus' serialisation.
263
prop_FinalizedJobStatus_serialisation :: FinalizedJobStatus -> Property
264
prop_FinalizedJobStatus_serialisation = testSerialisation
265

    
266
-- | Tests equivalence with Python, based on Constants.hs code.
267
case_FinalizedJobStatus_pyequiv :: Assertion
268
case_FinalizedJobStatus_pyequiv = do
269
  let all_py_codes = sort C.jobsFinalized
270
      all_hs_codes = sort $ map Types.finalizedJobStatusToRaw
271
                            [minBound..maxBound]
272
  assertEqual "for FinalizedJobStatus equivalence" all_py_codes all_hs_codes
273

    
274
testSuite "Types"
275
  [ 'prop_AllocPolicy_serialisation
276
  , 'prop_DiskTemplate_serialisation
277
  , 'prop_InstanceStatus_serialisation
278
  , 'prop_NonNeg_pass
279
  , 'prop_NonNeg_fail
280
  , 'prop_Positive_pass
281
  , 'prop_Positive_fail
282
  , 'prop_NonEmpty_pass
283
  , 'case_NonEmpty_fail
284
  , 'prop_MigrationMode_serialisation
285
  , 'prop_VerifyOptionalChecks_serialisation
286
  , 'prop_DdmSimple_serialisation
287
  , 'prop_DdmFull_serialisation
288
  , 'prop_CVErrorCode_serialisation
289
  , 'case_CVErrorCode_pyequiv
290
  , 'prop_Hypervisor_serialisation
291
  , 'prop_OobCommand_serialisation
292
  , 'prop_StorageType_serialisation
293
  , 'prop_NodeEvacMode_serialisation
294
  , 'prop_FileDriver_serialisation
295
  , 'prop_InstCreateMode_serialisation
296
  , 'prop_RebootType_serialisation
297
  , 'prop_ExportMode_serialisation
298
  , 'prop_IAllocatorTestDir_serialisation
299
  , 'prop_IAllocatorMode_serialisation
300
  , 'case_IAllocatorMode_pyequiv
301
  , 'prop_NetworkType_serialisation
302
  , 'case_NetworkType_pyequiv
303
  , 'prop_NICMode_serialisation
304
  , 'case_NICMode_pyequiv
305
  , 'prop_FinalizedJobStatus_serialisation
306
  , 'case_FinalizedJobStatus_pyequiv
307
  ]