Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / Types.hs @ 8d239fa4

History | View | Annotate | Download (9.2 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
-- * Properties
111

    
112
prop_AllocPolicy_serialisation :: AllocPolicy -> Property
113
prop_AllocPolicy_serialisation = testSerialisation
114

    
115
prop_DiskTemplate_serialisation :: DiskTemplate -> Property
116
prop_DiskTemplate_serialisation = testSerialisation
117

    
118
prop_InstanceStatus_serialisation :: InstanceStatus -> Property
119
prop_InstanceStatus_serialisation = testSerialisation
120

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

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

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

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

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

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

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

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

    
172
-- | Tests 'DdmSimple' serialisation.
173
prop_DdmSimple_serialisation :: DdmSimple -> Property
174
prop_DdmSimple_serialisation = testSerialisation
175

    
176
-- | Tests 'DdmFull' serialisation.
177
prop_DdmFull_serialisation :: DdmFull -> Property
178
prop_DdmFull_serialisation = testSerialisation
179

    
180
-- | Tests 'CVErrorCode' serialisation.
181
prop_CVErrorCode_serialisation :: CVErrorCode -> Property
182
prop_CVErrorCode_serialisation = testSerialisation
183

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

    
191
-- | Test 'Hypervisor' serialisation.
192
prop_Hypervisor_serialisation :: Hypervisor -> Property
193
prop_Hypervisor_serialisation = testSerialisation
194

    
195
-- | Test 'OobCommand' serialisation.
196
prop_OobCommand_serialisation :: OobCommand -> Property
197
prop_OobCommand_serialisation = testSerialisation
198

    
199
-- | Test 'StorageType' serialisation.
200
prop_StorageType_serialisation :: StorageType -> Property
201
prop_StorageType_serialisation = testSerialisation
202

    
203
-- | Test 'NodeEvacMode' serialisation.
204
prop_NodeEvacMode_serialisation :: NodeEvacMode -> Property
205
prop_NodeEvacMode_serialisation = testSerialisation
206

    
207
-- | Test 'FileDriver' serialisation.
208
prop_FileDriver_serialisation :: FileDriver -> Property
209
prop_FileDriver_serialisation = testSerialisation
210

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

    
215
-- | Test 'RebootType' serialisation.
216
prop_RebootType_serialisation :: RebootType -> Property
217
prop_RebootType_serialisation = testSerialisation
218

    
219
-- | Test 'ExportMode' serialisation.
220
prop_ExportMode_serialisation :: ExportMode -> Property
221
prop_ExportMode_serialisation = testSerialisation
222

    
223
-- | Test 'IAllocatorTestDir' serialisation.
224
prop_IAllocatorTestDir_serialisation :: IAllocatorTestDir -> Property
225
prop_IAllocatorTestDir_serialisation = testSerialisation
226

    
227
-- | Test 'IAllocatorMode' serialisation.
228
prop_IAllocatorMode_serialisation :: IAllocatorMode -> Property
229
prop_IAllocatorMode_serialisation = testSerialisation
230

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

    
238
-- | Test 'NetworkType' serialisation.
239
prop_NetworkType_serialisation :: NetworkType -> Property
240
prop_NetworkType_serialisation = testSerialisation
241

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

    
249
-- | Test 'NICMode' serialisation.
250
prop_NICMode_serialisation :: NICMode -> Property
251
prop_NICMode_serialisation = testSerialisation
252

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

    
260
testSuite "Types"
261
  [ 'prop_AllocPolicy_serialisation
262
  , 'prop_DiskTemplate_serialisation
263
  , 'prop_InstanceStatus_serialisation
264
  , 'prop_NonNeg_pass
265
  , 'prop_NonNeg_fail
266
  , 'prop_Positive_pass
267
  , 'prop_Positive_fail
268
  , 'prop_NonEmpty_pass
269
  , 'case_NonEmpty_fail
270
  , 'prop_MigrationMode_serialisation
271
  , 'prop_VerifyOptionalChecks_serialisation
272
  , 'prop_DdmSimple_serialisation
273
  , 'prop_DdmFull_serialisation
274
  , 'prop_CVErrorCode_serialisation
275
  , 'case_CVErrorCode_pyequiv
276
  , 'prop_Hypervisor_serialisation
277
  , 'prop_OobCommand_serialisation
278
  , 'prop_StorageType_serialisation
279
  , 'prop_NodeEvacMode_serialisation
280
  , 'prop_FileDriver_serialisation
281
  , 'prop_InstCreateMode_serialisation
282
  , 'prop_RebootType_serialisation
283
  , 'prop_ExportMode_serialisation
284
  , 'prop_IAllocatorTestDir_serialisation
285
  , 'prop_IAllocatorMode_serialisation
286
  , 'case_IAllocatorMode_pyequiv
287
  , 'prop_NetworkType_serialisation
288
  , 'case_NetworkType_pyequiv
289
  , 'prop_NICMode_serialisation
290
  , 'case_NICMode_pyequiv
291
  ]