Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (8.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
  ) 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
-- * Properties
107

    
108
prop_AllocPolicy_serialisation :: AllocPolicy -> Property
109
prop_AllocPolicy_serialisation = testSerialisation
110

    
111
prop_DiskTemplate_serialisation :: DiskTemplate -> Property
112
prop_DiskTemplate_serialisation = testSerialisation
113

    
114
prop_InstanceStatus_serialisation :: InstanceStatus -> Property
115
prop_InstanceStatus_serialisation = testSerialisation
116

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

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

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

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

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

    
154
-- | Tests building positive numbers.
155
case_NonEmpty_fail :: Assertion
156
case_NonEmpty_fail =
157
  assertEqual "building non-empty list from an empty list"
158
    (Bad "Received empty value for non-empty list") (mkNonEmpty ([]::[Int]))
159

    
160
-- | Tests migration mode serialisation.
161
prop_MigrationMode_serialisation :: MigrationMode -> Property
162
prop_MigrationMode_serialisation = testSerialisation
163

    
164
-- | Tests verify optional checks serialisation.
165
prop_VerifyOptionalChecks_serialisation :: VerifyOptionalChecks -> Property
166
prop_VerifyOptionalChecks_serialisation = testSerialisation
167

    
168
-- | Tests 'DdmSimple' serialisation.
169
prop_DdmSimple_serialisation :: DdmSimple -> Property
170
prop_DdmSimple_serialisation = testSerialisation
171

    
172
-- | Tests 'DdmFull' serialisation.
173
prop_DdmFull_serialisation :: DdmFull -> Property
174
prop_DdmFull_serialisation = testSerialisation
175

    
176
-- | Tests 'CVErrorCode' serialisation.
177
prop_CVErrorCode_serialisation :: CVErrorCode -> Property
178
prop_CVErrorCode_serialisation = testSerialisation
179

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

    
187
-- | Test 'Hypervisor' serialisation.
188
prop_Hypervisor_serialisation :: Hypervisor -> Property
189
prop_Hypervisor_serialisation = testSerialisation
190

    
191
-- | Test 'OobCommand' serialisation.
192
prop_OobCommand_serialisation :: OobCommand -> Property
193
prop_OobCommand_serialisation = testSerialisation
194

    
195
-- | Test 'StorageType' serialisation.
196
prop_StorageType_serialisation :: StorageType -> Property
197
prop_StorageType_serialisation = testSerialisation
198

    
199
-- | Test 'NodeEvacMode' serialisation.
200
prop_NodeEvacMode_serialisation :: NodeEvacMode -> Property
201
prop_NodeEvacMode_serialisation = testSerialisation
202

    
203
-- | Test 'FileDriver' serialisation.
204
prop_FileDriver_serialisation :: FileDriver -> Property
205
prop_FileDriver_serialisation = testSerialisation
206

    
207
-- | Test 'InstCreate' serialisation.
208
prop_InstCreateMode_serialisation :: InstCreateMode -> Property
209
prop_InstCreateMode_serialisation = testSerialisation
210

    
211
-- | Test 'RebootType' serialisation.
212
prop_RebootType_serialisation :: RebootType -> Property
213
prop_RebootType_serialisation = testSerialisation
214

    
215
-- | Test 'ExportMode' serialisation.
216
prop_ExportMode_serialisation :: ExportMode -> Property
217
prop_ExportMode_serialisation = testSerialisation
218

    
219
-- | Test 'IAllocatorTestDir' serialisation.
220
prop_IAllocatorTestDir_serialisation :: IAllocatorTestDir -> Property
221
prop_IAllocatorTestDir_serialisation = testSerialisation
222

    
223
-- | Test 'IAllocatorMode' serialisation.
224
prop_IAllocatorMode_serialisation :: IAllocatorMode -> Property
225
prop_IAllocatorMode_serialisation = testSerialisation
226

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

    
234
testSuite "Types"
235
  [ 'prop_AllocPolicy_serialisation
236
  , 'prop_DiskTemplate_serialisation
237
  , 'prop_InstanceStatus_serialisation
238
  , 'prop_NonNeg_pass
239
  , 'prop_NonNeg_fail
240
  , 'prop_Positive_pass
241
  , 'prop_Positive_fail
242
  , 'prop_NonEmpty_pass
243
  , 'case_NonEmpty_fail
244
  , 'prop_MigrationMode_serialisation
245
  , 'prop_VerifyOptionalChecks_serialisation
246
  , 'prop_DdmSimple_serialisation
247
  , 'prop_DdmFull_serialisation
248
  , 'prop_CVErrorCode_serialisation
249
  , 'case_CVErrorCode_pyequiv
250
  , 'prop_Hypervisor_serialisation
251
  , 'prop_OobCommand_serialisation
252
  , 'prop_StorageType_serialisation
253
  , 'prop_NodeEvacMode_serialisation
254
  , 'prop_FileDriver_serialisation
255
  , 'prop_InstCreateMode_serialisation
256
  , 'prop_RebootType_serialisation
257
  , 'prop_ExportMode_serialisation
258
  , 'prop_IAllocatorTestDir_serialisation
259
  , 'prop_IAllocatorMode_serialisation
260
  , 'case_IAllocatorMode_pyequiv
261
  ]