Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / Types.hs @ 5cd95d46

History | View | Annotate | Download (13 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

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

    
53
-- * Arbitrary instance
54

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

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

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

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

    
78
$(genArbitrary ''AllocPolicy)
79

    
80
$(genArbitrary ''DiskTemplate)
81

    
82
$(genArbitrary ''InstanceStatus)
83

    
84
$(genArbitrary ''MigrationMode)
85

    
86
$(genArbitrary ''VerifyOptionalChecks)
87

    
88
$(genArbitrary ''DdmSimple)
89

    
90
$(genArbitrary ''DdmFull)
91

    
92
$(genArbitrary ''CVErrorCode)
93

    
94
$(genArbitrary ''Hypervisor)
95

    
96
$(genArbitrary ''OobCommand)
97

    
98
$(genArbitrary ''StorageType)
99

    
100
$(genArbitrary ''NodeEvacMode)
101

    
102
$(genArbitrary ''FileDriver)
103

    
104
$(genArbitrary ''InstCreateMode)
105

    
106
$(genArbitrary ''RebootType)
107

    
108
$(genArbitrary ''ExportMode)
109

    
110
$(genArbitrary ''IAllocatorTestDir)
111

    
112
$(genArbitrary ''IAllocatorMode)
113

    
114
$(genArbitrary ''NetworkType)
115

    
116
$(genArbitrary ''NICMode)
117

    
118
$(genArbitrary ''JobStatus)
119

    
120
$(genArbitrary ''FinalizedJobStatus)
121

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

    
127
$(genArbitrary ''JobIdDep)
128

    
129
$(genArbitrary ''JobDependency)
130

    
131
$(genArbitrary ''OpSubmitPriority)
132

    
133
$(genArbitrary ''OpStatus)
134

    
135
$(genArbitrary ''ELogType)
136

    
137
-- * Properties
138

    
139
prop_AllocPolicy_serialisation :: AllocPolicy -> Property
140
prop_AllocPolicy_serialisation = testSerialisation
141

    
142
-- | Test 'AllocPolicy' ordering is as expected.
143
case_AllocPolicy_order :: Assertion
144
case_AllocPolicy_order =
145
  assertEqual "sort order" [ Types.AllocPreferred
146
                           , Types.AllocLastResort
147
                           , Types.AllocUnallocable
148
                           ] [minBound..maxBound]
149

    
150
prop_DiskTemplate_serialisation :: DiskTemplate -> Property
151
prop_DiskTemplate_serialisation = testSerialisation
152

    
153
prop_InstanceStatus_serialisation :: InstanceStatus -> Property
154
prop_InstanceStatus_serialisation = testSerialisation
155

    
156
-- | Tests building non-negative numbers.
157
prop_NonNeg_pass :: QuickCheck.NonNegative Int -> Property
158
prop_NonNeg_pass (QuickCheck.NonNegative i) =
159
  case mkNonNegative i of
160
    Bad msg -> failTest $ "Fail to build non-negative: " ++ msg
161
    Ok nn -> fromNonNegative nn ==? i
162

    
163
-- | Tests building non-negative numbers.
164
prop_NonNeg_fail :: QuickCheck.Positive Int -> Property
165
prop_NonNeg_fail (QuickCheck.Positive i) =
166
  case mkNonNegative (negate i)::Result (Types.NonNegative Int) of
167
    Bad _ -> passTest
168
    Ok nn -> failTest $ "Built non-negative number '" ++ show nn ++
169
             "' from negative value " ++ show i
170

    
171
-- | Tests building positive numbers.
172
prop_Positive_pass :: QuickCheck.Positive Int -> Property
173
prop_Positive_pass (QuickCheck.Positive i) =
174
  case mkPositive i of
175
    Bad msg -> failTest $ "Fail to build positive: " ++ msg
176
    Ok nn -> fromPositive nn ==? i
177

    
178
-- | Tests building positive numbers.
179
prop_Positive_fail :: QuickCheck.NonNegative Int -> Property
180
prop_Positive_fail (QuickCheck.NonNegative i) =
181
  case mkPositive (negate i)::Result (Types.Positive Int) of
182
    Bad _ -> passTest
183
    Ok nn -> failTest $ "Built positive number '" ++ show nn ++
184
             "' from negative or zero value " ++ show i
185

    
186
-- | Tests building negative numbers.
187
prop_Neg_pass :: QuickCheck.Positive Int -> Property
188
prop_Neg_pass (QuickCheck.Positive i) =
189
  case mkNegative i' of
190
    Bad msg -> failTest $ "Fail to build negative: " ++ msg
191
    Ok nn -> fromNegative nn ==? i'
192
  where i' = negate i
193

    
194
-- | Tests building negative numbers.
195
prop_Neg_fail :: QuickCheck.NonNegative Int -> Property
196
prop_Neg_fail (QuickCheck.NonNegative i) =
197
  case mkNegative i::Result (Types.Negative Int) of
198
    Bad _ -> passTest
199
    Ok nn -> failTest $ "Built negative number '" ++ show nn ++
200
             "' from non-negative value " ++ show i
201

    
202
-- | Tests building non-empty lists.
203
prop_NonEmpty_pass :: QuickCheck.NonEmptyList String -> Property
204
prop_NonEmpty_pass (QuickCheck.NonEmpty xs) =
205
  case mkNonEmpty xs of
206
    Bad msg -> failTest $ "Fail to build non-empty list: " ++ msg
207
    Ok nn -> fromNonEmpty nn ==? xs
208

    
209
-- | Tests building positive numbers.
210
case_NonEmpty_fail :: Assertion
211
case_NonEmpty_fail =
212
  assertEqual "building non-empty list from an empty list"
213
    (Bad "Received empty value for non-empty list") (mkNonEmpty ([]::[Int]))
214

    
215
-- | Tests migration mode serialisation.
216
prop_MigrationMode_serialisation :: MigrationMode -> Property
217
prop_MigrationMode_serialisation = testSerialisation
218

    
219
-- | Tests verify optional checks serialisation.
220
prop_VerifyOptionalChecks_serialisation :: VerifyOptionalChecks -> Property
221
prop_VerifyOptionalChecks_serialisation = testSerialisation
222

    
223
-- | Tests 'DdmSimple' serialisation.
224
prop_DdmSimple_serialisation :: DdmSimple -> Property
225
prop_DdmSimple_serialisation = testSerialisation
226

    
227
-- | Tests 'DdmFull' serialisation.
228
prop_DdmFull_serialisation :: DdmFull -> Property
229
prop_DdmFull_serialisation = testSerialisation
230

    
231
-- | Tests 'CVErrorCode' serialisation.
232
prop_CVErrorCode_serialisation :: CVErrorCode -> Property
233
prop_CVErrorCode_serialisation = testSerialisation
234

    
235
-- | Tests equivalence with Python, based on Constants.hs code.
236
case_CVErrorCode_pyequiv :: Assertion
237
case_CVErrorCode_pyequiv = do
238
  let all_py_codes = sort C.cvAllEcodesStrings
239
      all_hs_codes = sort $ map Types.cVErrorCodeToRaw [minBound..maxBound]
240
  assertEqual "for CVErrorCode equivalence" all_py_codes all_hs_codes
241

    
242
-- | Test 'Hypervisor' serialisation.
243
prop_Hypervisor_serialisation :: Hypervisor -> Property
244
prop_Hypervisor_serialisation = testSerialisation
245

    
246
-- | Test 'OobCommand' serialisation.
247
prop_OobCommand_serialisation :: OobCommand -> Property
248
prop_OobCommand_serialisation = testSerialisation
249

    
250
-- | Test 'StorageType' serialisation.
251
prop_StorageType_serialisation :: StorageType -> Property
252
prop_StorageType_serialisation = testSerialisation
253

    
254
-- | Test 'NodeEvacMode' serialisation.
255
prop_NodeEvacMode_serialisation :: NodeEvacMode -> Property
256
prop_NodeEvacMode_serialisation = testSerialisation
257

    
258
-- | Test 'FileDriver' serialisation.
259
prop_FileDriver_serialisation :: FileDriver -> Property
260
prop_FileDriver_serialisation = testSerialisation
261

    
262
-- | Test 'InstCreate' serialisation.
263
prop_InstCreateMode_serialisation :: InstCreateMode -> Property
264
prop_InstCreateMode_serialisation = testSerialisation
265

    
266
-- | Test 'RebootType' serialisation.
267
prop_RebootType_serialisation :: RebootType -> Property
268
prop_RebootType_serialisation = testSerialisation
269

    
270
-- | Test 'ExportMode' serialisation.
271
prop_ExportMode_serialisation :: ExportMode -> Property
272
prop_ExportMode_serialisation = testSerialisation
273

    
274
-- | Test 'IAllocatorTestDir' serialisation.
275
prop_IAllocatorTestDir_serialisation :: IAllocatorTestDir -> Property
276
prop_IAllocatorTestDir_serialisation = testSerialisation
277

    
278
-- | Test 'IAllocatorMode' serialisation.
279
prop_IAllocatorMode_serialisation :: IAllocatorMode -> Property
280
prop_IAllocatorMode_serialisation = testSerialisation
281

    
282
-- | Tests equivalence with Python, based on Constants.hs code.
283
case_IAllocatorMode_pyequiv :: Assertion
284
case_IAllocatorMode_pyequiv = do
285
  let all_py_codes = sort C.validIallocatorModes
286
      all_hs_codes = sort $ map Types.iAllocatorModeToRaw [minBound..maxBound]
287
  assertEqual "for IAllocatorMode equivalence" all_py_codes all_hs_codes
288

    
289
-- | Test 'NetworkType' serialisation.
290
prop_NetworkType_serialisation :: NetworkType -> Property
291
prop_NetworkType_serialisation = testSerialisation
292

    
293
-- | Tests equivalence with Python, based on Constants.hs code.
294
case_NetworkType_pyequiv :: Assertion
295
case_NetworkType_pyequiv = do
296
  let all_py_codes = sort C.networkValidTypes
297
      all_hs_codes = sort $ map Types.networkTypeToRaw [minBound..maxBound]
298
  assertEqual "for NetworkType equivalence" all_py_codes all_hs_codes
299

    
300
-- | Test 'NICMode' serialisation.
301
prop_NICMode_serialisation :: NICMode -> Property
302
prop_NICMode_serialisation = testSerialisation
303

    
304
-- | Test 'OpStatus' serialisation.
305
prop_OpStatus_serialization :: OpStatus -> Property
306
prop_OpStatus_serialization = testSerialisation
307

    
308
-- | Test 'JobStatus' serialisation.
309
prop_JobStatus_serialization :: JobStatus -> Property
310
prop_JobStatus_serialization = testSerialisation
311

    
312
-- | Test 'JobStatus' ordering is as expected.
313
case_JobStatus_order :: Assertion
314
case_JobStatus_order =
315
  assertEqual "sort order" [ Types.JOB_STATUS_QUEUED
316
                           , Types.JOB_STATUS_WAITING
317
                           , Types.JOB_STATUS_CANCELING
318
                           , Types.JOB_STATUS_RUNNING
319
                           , Types.JOB_STATUS_CANCELED
320
                           , Types.JOB_STATUS_SUCCESS
321
                           , Types.JOB_STATUS_ERROR
322
                           ] [minBound..maxBound]
323

    
324
-- | Tests equivalence with Python, based on Constants.hs code.
325
case_NICMode_pyequiv :: Assertion
326
case_NICMode_pyequiv = do
327
  let all_py_codes = sort C.nicValidModes
328
      all_hs_codes = sort $ map Types.nICModeToRaw [minBound..maxBound]
329
  assertEqual "for NICMode equivalence" all_py_codes all_hs_codes
330

    
331
-- | Test 'FinalizedJobStatus' serialisation.
332
prop_FinalizedJobStatus_serialisation :: FinalizedJobStatus -> Property
333
prop_FinalizedJobStatus_serialisation = testSerialisation
334

    
335
-- | Tests equivalence with Python, based on Constants.hs code.
336
case_FinalizedJobStatus_pyequiv :: Assertion
337
case_FinalizedJobStatus_pyequiv = do
338
  let all_py_codes = sort C.jobsFinalized
339
      all_hs_codes = sort $ map Types.finalizedJobStatusToRaw
340
                            [minBound..maxBound]
341
  assertEqual "for FinalizedJobStatus equivalence" all_py_codes all_hs_codes
342

    
343
-- | Tests JobId serialisation (both from string and ints).
344
prop_JobId_serialisation :: JobId -> Property
345
prop_JobId_serialisation jid =
346
  testSerialisation jid .&&.
347
  (J.readJSON . J.showJSON . show $ fromJobId jid) ==? J.Ok jid
348

    
349
-- | Test 'JobDependency' serialisation.
350
prop_JobDependency_serialisation :: JobDependency -> Property
351
prop_JobDependency_serialisation = testSerialisation
352

    
353
-- | Test 'OpSubmitPriority' serialisation.
354
prop_OpSubmitPriority_serialisation :: OpSubmitPriority -> Property
355
prop_OpSubmitPriority_serialisation = testSerialisation
356

    
357
-- | Test 'ELogType' serialisation.
358
prop_ELogType_serialisation :: ELogType -> Property
359
prop_ELogType_serialisation = testSerialisation
360

    
361
testSuite "Types"
362
  [ 'prop_AllocPolicy_serialisation
363
  , 'case_AllocPolicy_order
364
  , 'prop_DiskTemplate_serialisation
365
  , 'prop_InstanceStatus_serialisation
366
  , 'prop_NonNeg_pass
367
  , 'prop_NonNeg_fail
368
  , 'prop_Positive_pass
369
  , 'prop_Positive_fail
370
  , 'prop_Neg_pass
371
  , 'prop_Neg_fail
372
  , 'prop_NonEmpty_pass
373
  , 'case_NonEmpty_fail
374
  , 'prop_MigrationMode_serialisation
375
  , 'prop_VerifyOptionalChecks_serialisation
376
  , 'prop_DdmSimple_serialisation
377
  , 'prop_DdmFull_serialisation
378
  , 'prop_CVErrorCode_serialisation
379
  , 'case_CVErrorCode_pyequiv
380
  , 'prop_Hypervisor_serialisation
381
  , 'prop_OobCommand_serialisation
382
  , 'prop_StorageType_serialisation
383
  , 'prop_NodeEvacMode_serialisation
384
  , 'prop_FileDriver_serialisation
385
  , 'prop_InstCreateMode_serialisation
386
  , 'prop_RebootType_serialisation
387
  , 'prop_ExportMode_serialisation
388
  , 'prop_IAllocatorTestDir_serialisation
389
  , 'prop_IAllocatorMode_serialisation
390
  , 'case_IAllocatorMode_pyequiv
391
  , 'prop_NetworkType_serialisation
392
  , 'case_NetworkType_pyequiv
393
  , 'prop_NICMode_serialisation
394
  , 'prop_OpStatus_serialization
395
  , 'prop_JobStatus_serialization
396
  , 'case_JobStatus_order
397
  , 'case_NICMode_pyequiv
398
  , 'prop_FinalizedJobStatus_serialisation
399
  , 'case_FinalizedJobStatus_pyequiv
400
  , 'prop_JobId_serialisation
401
  , 'prop_JobDependency_serialisation
402
  , 'prop_OpSubmitPriority_serialisation
403
  , 'prop_ELogType_serialisation
404
  ]