Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (11.1 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
  , JobId(..)
37
  ) where
38

    
39
import Data.List (sort)
40
import Test.QuickCheck as QuickCheck hiding (Result)
41
import Test.HUnit
42
import qualified Text.JSON as J
43

    
44
import Test.Ganeti.TestHelper
45
import Test.Ganeti.TestCommon
46

    
47
import Ganeti.BasicTypes
48
import qualified Ganeti.Constants as C
49
import Ganeti.Types as Types
50
import Ganeti.Luxi as Luxi
51

    
52
{-# ANN module "HLint: ignore Use camelCase" #-}
53

    
54
-- * Arbitrary instance
55

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

    
62
instance (Arbitrary a, Ord a, Num a, Show a) =>
63
  Arbitrary (Types.NonNegative a) where
64
  arbitrary = do
65
    (QuickCheck.NonNegative i) <- arbitrary
66
    Types.mkNonNegative i
67

    
68
instance (Arbitrary a, Ord a, Num a, Show a) =>
69
  Arbitrary (Types.Negative a) where
70
  arbitrary = do
71
    (QuickCheck.Positive i) <- arbitrary
72
    Types.mkNegative $ negate i
73

    
74
instance (Arbitrary a) => Arbitrary (Types.NonEmpty a) where
75
  arbitrary = do
76
    QuickCheck.NonEmpty lst <- arbitrary
77
    Types.mkNonEmpty lst
78

    
79
$(genArbitrary ''AllocPolicy)
80

    
81
$(genArbitrary ''DiskTemplate)
82

    
83
$(genArbitrary ''InstanceStatus)
84

    
85
$(genArbitrary ''MigrationMode)
86

    
87
$(genArbitrary ''VerifyOptionalChecks)
88

    
89
$(genArbitrary ''DdmSimple)
90

    
91
$(genArbitrary ''DdmFull)
92

    
93
$(genArbitrary ''CVErrorCode)
94

    
95
$(genArbitrary ''Hypervisor)
96

    
97
$(genArbitrary ''OobCommand)
98

    
99
$(genArbitrary ''StorageType)
100

    
101
$(genArbitrary ''NodeEvacMode)
102

    
103
$(genArbitrary ''FileDriver)
104

    
105
$(genArbitrary ''InstCreateMode)
106

    
107
$(genArbitrary ''RebootType)
108

    
109
$(genArbitrary ''ExportMode)
110

    
111
$(genArbitrary ''IAllocatorTestDir)
112

    
113
$(genArbitrary ''IAllocatorMode)
114

    
115
$(genArbitrary ''NetworkType)
116

    
117
$(genArbitrary ''NICMode)
118

    
119
$(genArbitrary ''FinalizedJobStatus)
120

    
121
instance Arbitrary Luxi.JobId where
122
  arbitrary = do
123
    (Positive i) <- arbitrary
124
    Luxi.makeJobId i
125

    
126
-- * Properties
127

    
128
prop_AllocPolicy_serialisation :: AllocPolicy -> Property
129
prop_AllocPolicy_serialisation = testSerialisation
130

    
131
prop_DiskTemplate_serialisation :: DiskTemplate -> Property
132
prop_DiskTemplate_serialisation = testSerialisation
133

    
134
prop_InstanceStatus_serialisation :: InstanceStatus -> Property
135
prop_InstanceStatus_serialisation = testSerialisation
136

    
137
-- | Tests building non-negative numbers.
138
prop_NonNeg_pass :: QuickCheck.NonNegative Int -> Property
139
prop_NonNeg_pass (QuickCheck.NonNegative i) =
140
  case mkNonNegative i of
141
    Bad msg -> failTest $ "Fail to build non-negative: " ++ msg
142
    Ok nn -> fromNonNegative nn ==? i
143

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

    
152
-- | Tests building positive numbers.
153
prop_Positive_pass :: QuickCheck.Positive Int -> Property
154
prop_Positive_pass (QuickCheck.Positive i) =
155
  case mkPositive i of
156
    Bad msg -> failTest $ "Fail to build positive: " ++ msg
157
    Ok nn -> fromPositive nn ==? i
158

    
159
-- | Tests building positive numbers.
160
prop_Positive_fail :: QuickCheck.NonNegative Int -> Property
161
prop_Positive_fail (QuickCheck.NonNegative i) =
162
  case mkPositive (negate i)::Result (Types.Positive Int) of
163
    Bad _ -> passTest
164
    Ok nn -> failTest $ "Built positive number '" ++ show nn ++
165
             "' from negative or zero value " ++ show i
166

    
167
-- | Tests building negative numbers.
168
prop_Neg_pass :: QuickCheck.Positive Int -> Property
169
prop_Neg_pass (QuickCheck.Positive i) =
170
  case mkNegative i' of
171
    Bad msg -> failTest $ "Fail to build negative: " ++ msg
172
    Ok nn -> fromNegative nn ==? i'
173
  where i' = negate i
174

    
175
-- | Tests building negative numbers.
176
prop_Neg_fail :: QuickCheck.NonNegative Int -> Property
177
prop_Neg_fail (QuickCheck.NonNegative i) =
178
  case mkNegative i::Result (Types.Negative Int) of
179
    Bad _ -> passTest
180
    Ok nn -> failTest $ "Built negative number '" ++ show nn ++
181
             "' from non-negative value " ++ show i
182

    
183
-- | Tests building non-empty lists.
184
prop_NonEmpty_pass :: QuickCheck.NonEmptyList String -> Property
185
prop_NonEmpty_pass (QuickCheck.NonEmpty xs) =
186
  case mkNonEmpty xs of
187
    Bad msg -> failTest $ "Fail to build non-empty list: " ++ msg
188
    Ok nn -> fromNonEmpty nn ==? xs
189

    
190
-- | Tests building positive numbers.
191
case_NonEmpty_fail :: Assertion
192
case_NonEmpty_fail =
193
  assertEqual "building non-empty list from an empty list"
194
    (Bad "Received empty value for non-empty list") (mkNonEmpty ([]::[Int]))
195

    
196
-- | Tests migration mode serialisation.
197
prop_MigrationMode_serialisation :: MigrationMode -> Property
198
prop_MigrationMode_serialisation = testSerialisation
199

    
200
-- | Tests verify optional checks serialisation.
201
prop_VerifyOptionalChecks_serialisation :: VerifyOptionalChecks -> Property
202
prop_VerifyOptionalChecks_serialisation = testSerialisation
203

    
204
-- | Tests 'DdmSimple' serialisation.
205
prop_DdmSimple_serialisation :: DdmSimple -> Property
206
prop_DdmSimple_serialisation = testSerialisation
207

    
208
-- | Tests 'DdmFull' serialisation.
209
prop_DdmFull_serialisation :: DdmFull -> Property
210
prop_DdmFull_serialisation = testSerialisation
211

    
212
-- | Tests 'CVErrorCode' serialisation.
213
prop_CVErrorCode_serialisation :: CVErrorCode -> Property
214
prop_CVErrorCode_serialisation = testSerialisation
215

    
216
-- | Tests equivalence with Python, based on Constants.hs code.
217
case_CVErrorCode_pyequiv :: Assertion
218
case_CVErrorCode_pyequiv = do
219
  let all_py_codes = sort C.cvAllEcodesStrings
220
      all_hs_codes = sort $ map Types.cVErrorCodeToRaw [minBound..maxBound]
221
  assertEqual "for CVErrorCode equivalence" all_py_codes all_hs_codes
222

    
223
-- | Test 'Hypervisor' serialisation.
224
prop_Hypervisor_serialisation :: Hypervisor -> Property
225
prop_Hypervisor_serialisation = testSerialisation
226

    
227
-- | Test 'OobCommand' serialisation.
228
prop_OobCommand_serialisation :: OobCommand -> Property
229
prop_OobCommand_serialisation = testSerialisation
230

    
231
-- | Test 'StorageType' serialisation.
232
prop_StorageType_serialisation :: StorageType -> Property
233
prop_StorageType_serialisation = testSerialisation
234

    
235
-- | Test 'NodeEvacMode' serialisation.
236
prop_NodeEvacMode_serialisation :: NodeEvacMode -> Property
237
prop_NodeEvacMode_serialisation = testSerialisation
238

    
239
-- | Test 'FileDriver' serialisation.
240
prop_FileDriver_serialisation :: FileDriver -> Property
241
prop_FileDriver_serialisation = testSerialisation
242

    
243
-- | Test 'InstCreate' serialisation.
244
prop_InstCreateMode_serialisation :: InstCreateMode -> Property
245
prop_InstCreateMode_serialisation = testSerialisation
246

    
247
-- | Test 'RebootType' serialisation.
248
prop_RebootType_serialisation :: RebootType -> Property
249
prop_RebootType_serialisation = testSerialisation
250

    
251
-- | Test 'ExportMode' serialisation.
252
prop_ExportMode_serialisation :: ExportMode -> Property
253
prop_ExportMode_serialisation = testSerialisation
254

    
255
-- | Test 'IAllocatorTestDir' serialisation.
256
prop_IAllocatorTestDir_serialisation :: IAllocatorTestDir -> Property
257
prop_IAllocatorTestDir_serialisation = testSerialisation
258

    
259
-- | Test 'IAllocatorMode' serialisation.
260
prop_IAllocatorMode_serialisation :: IAllocatorMode -> Property
261
prop_IAllocatorMode_serialisation = testSerialisation
262

    
263
-- | Tests equivalence with Python, based on Constants.hs code.
264
case_IAllocatorMode_pyequiv :: Assertion
265
case_IAllocatorMode_pyequiv = do
266
  let all_py_codes = sort C.validIallocatorModes
267
      all_hs_codes = sort $ map Types.iAllocatorModeToRaw [minBound..maxBound]
268
  assertEqual "for IAllocatorMode equivalence" all_py_codes all_hs_codes
269

    
270
-- | Test 'NetworkType' serialisation.
271
prop_NetworkType_serialisation :: NetworkType -> Property
272
prop_NetworkType_serialisation = testSerialisation
273

    
274
-- | Tests equivalence with Python, based on Constants.hs code.
275
case_NetworkType_pyequiv :: Assertion
276
case_NetworkType_pyequiv = do
277
  let all_py_codes = sort C.networkValidTypes
278
      all_hs_codes = sort $ map Types.networkTypeToRaw [minBound..maxBound]
279
  assertEqual "for NetworkType equivalence" all_py_codes all_hs_codes
280

    
281
-- | Test 'NICMode' serialisation.
282
prop_NICMode_serialisation :: NICMode -> Property
283
prop_NICMode_serialisation = testSerialisation
284

    
285
-- | Tests equivalence with Python, based on Constants.hs code.
286
case_NICMode_pyequiv :: Assertion
287
case_NICMode_pyequiv = do
288
  let all_py_codes = sort C.nicValidModes
289
      all_hs_codes = sort $ map Types.nICModeToRaw [minBound..maxBound]
290
  assertEqual "for NICMode equivalence" all_py_codes all_hs_codes
291

    
292
-- | Test 'FinalizedJobStatus' serialisation.
293
prop_FinalizedJobStatus_serialisation :: FinalizedJobStatus -> Property
294
prop_FinalizedJobStatus_serialisation = testSerialisation
295

    
296
-- | Tests equivalence with Python, based on Constants.hs code.
297
case_FinalizedJobStatus_pyequiv :: Assertion
298
case_FinalizedJobStatus_pyequiv = do
299
  let all_py_codes = sort C.jobsFinalized
300
      all_hs_codes = sort $ map Types.finalizedJobStatusToRaw
301
                            [minBound..maxBound]
302
  assertEqual "for FinalizedJobStatus equivalence" all_py_codes all_hs_codes
303

    
304
-- | Tests JobId serialisation (both from string and ints).
305
prop_JobId_serialisation :: JobId -> Property
306
prop_JobId_serialisation jid =
307
  testSerialisation jid .&&.
308
  (J.readJSON . J.showJSON . show $ fromJobId jid) ==? J.Ok jid
309

    
310
testSuite "Types"
311
  [ 'prop_AllocPolicy_serialisation
312
  , 'prop_DiskTemplate_serialisation
313
  , 'prop_InstanceStatus_serialisation
314
  , 'prop_NonNeg_pass
315
  , 'prop_NonNeg_fail
316
  , 'prop_Positive_pass
317
  , 'prop_Positive_fail
318
  , 'prop_Neg_pass
319
  , 'prop_Neg_fail
320
  , 'prop_NonEmpty_pass
321
  , 'case_NonEmpty_fail
322
  , 'prop_MigrationMode_serialisation
323
  , 'prop_VerifyOptionalChecks_serialisation
324
  , 'prop_DdmSimple_serialisation
325
  , 'prop_DdmFull_serialisation
326
  , 'prop_CVErrorCode_serialisation
327
  , 'case_CVErrorCode_pyequiv
328
  , 'prop_Hypervisor_serialisation
329
  , 'prop_OobCommand_serialisation
330
  , 'prop_StorageType_serialisation
331
  , 'prop_NodeEvacMode_serialisation
332
  , 'prop_FileDriver_serialisation
333
  , 'prop_InstCreateMode_serialisation
334
  , 'prop_RebootType_serialisation
335
  , 'prop_ExportMode_serialisation
336
  , 'prop_IAllocatorTestDir_serialisation
337
  , 'prop_IAllocatorMode_serialisation
338
  , 'case_IAllocatorMode_pyequiv
339
  , 'prop_NetworkType_serialisation
340
  , 'case_NetworkType_pyequiv
341
  , 'prop_NICMode_serialisation
342
  , 'case_NICMode_pyequiv
343
  , 'prop_FinalizedJobStatus_serialisation
344
  , 'case_FinalizedJobStatus_pyequiv
345
  , 'prop_JobId_serialisation
346
  ]