Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / Types.hs @ 90634d95

History | View | Annotate | Download (14.2 kB)

1 5e9deac0 Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 5e9deac0 Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 5e9deac0 Iustin Pop
4 5e9deac0 Iustin Pop
{-| Unittests for 'Ganeti.Types'.
5 5e9deac0 Iustin Pop
6 5e9deac0 Iustin Pop
-}
7 5e9deac0 Iustin Pop
8 5e9deac0 Iustin Pop
{-
9 5e9deac0 Iustin Pop
10 5e9deac0 Iustin Pop
Copyright (C) 2012 Google Inc.
11 5e9deac0 Iustin Pop
12 5e9deac0 Iustin Pop
This program is free software; you can redistribute it and/or modify
13 5e9deac0 Iustin Pop
it under the terms of the GNU General Public License as published by
14 5e9deac0 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 5e9deac0 Iustin Pop
(at your option) any later version.
16 5e9deac0 Iustin Pop
17 5e9deac0 Iustin Pop
This program is distributed in the hope that it will be useful, but
18 5e9deac0 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 5e9deac0 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 5e9deac0 Iustin Pop
General Public License for more details.
21 5e9deac0 Iustin Pop
22 5e9deac0 Iustin Pop
You should have received a copy of the GNU General Public License
23 5e9deac0 Iustin Pop
along with this program; if not, write to the Free Software
24 5e9deac0 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 5e9deac0 Iustin Pop
02110-1301, USA.
26 5e9deac0 Iustin Pop
27 5e9deac0 Iustin Pop
-}
28 5e9deac0 Iustin Pop
29 5e9deac0 Iustin Pop
module Test.Ganeti.Types
30 5e9deac0 Iustin Pop
  ( testTypes
31 5e9deac0 Iustin Pop
  , AllocPolicy(..)
32 5e9deac0 Iustin Pop
  , DiskTemplate(..)
33 5e9deac0 Iustin Pop
  , InstanceStatus(..)
34 edb5a1c8 Iustin Pop
  , NonEmpty(..)
35 22381768 Iustin Pop
  , Hypervisor(..)
36 c48711d5 Iustin Pop
  , JobId(..)
37 5e9deac0 Iustin Pop
  ) where
38 5e9deac0 Iustin Pop
39 d696bbef Iustin Pop
import Data.List (sort)
40 edb5a1c8 Iustin Pop
import Test.QuickCheck as QuickCheck hiding (Result)
41 edb5a1c8 Iustin Pop
import Test.HUnit
42 c48711d5 Iustin Pop
import qualified Text.JSON as J
43 5e9deac0 Iustin Pop
44 5e9deac0 Iustin Pop
import Test.Ganeti.TestHelper
45 5e9deac0 Iustin Pop
import Test.Ganeti.TestCommon
46 5e9deac0 Iustin Pop
47 edb5a1c8 Iustin Pop
import Ganeti.BasicTypes
48 d696bbef Iustin Pop
import qualified Ganeti.Constants as C
49 edb5a1c8 Iustin Pop
import Ganeti.Types as Types
50 90634d95 Iustin Pop
import Ganeti.JSON
51 5e9deac0 Iustin Pop
52 39573352 Iustin Pop
{-# ANN module "HLint: ignore Use camelCase" #-}
53 39573352 Iustin Pop
54 5e9deac0 Iustin Pop
-- * Arbitrary instance
55 5e9deac0 Iustin Pop
56 edb5a1c8 Iustin Pop
instance (Arbitrary a, Ord a, Num a, Show a) =>
57 edb5a1c8 Iustin Pop
  Arbitrary (Types.Positive a) where
58 edb5a1c8 Iustin Pop
  arbitrary = do
59 edb5a1c8 Iustin Pop
    (QuickCheck.Positive i) <- arbitrary
60 edb5a1c8 Iustin Pop
    Types.mkPositive i
61 edb5a1c8 Iustin Pop
62 6d558717 Iustin Pop
instance (Arbitrary a, Ord a, Num a, Show a) =>
63 6d558717 Iustin Pop
  Arbitrary (Types.NonNegative a) where
64 6d558717 Iustin Pop
  arbitrary = do
65 6d558717 Iustin Pop
    (QuickCheck.NonNegative i) <- arbitrary
66 6d558717 Iustin Pop
    Types.mkNonNegative i
67 6d558717 Iustin Pop
68 c67b908a Iustin Pop
instance (Arbitrary a, Ord a, Num a, Show a) =>
69 c67b908a Iustin Pop
  Arbitrary (Types.Negative a) where
70 c67b908a Iustin Pop
  arbitrary = do
71 c67b908a Iustin Pop
    (QuickCheck.Positive i) <- arbitrary
72 c67b908a Iustin Pop
    Types.mkNegative $ negate i
73 c67b908a Iustin Pop
74 c65621d7 Iustin Pop
instance (Arbitrary a) => Arbitrary (Types.NonEmpty a) where
75 c65621d7 Iustin Pop
  arbitrary = do
76 c65621d7 Iustin Pop
    QuickCheck.NonEmpty lst <- arbitrary
77 c65621d7 Iustin Pop
    Types.mkNonEmpty lst
78 c65621d7 Iustin Pop
79 5e9deac0 Iustin Pop
$(genArbitrary ''AllocPolicy)
80 5e9deac0 Iustin Pop
81 5e9deac0 Iustin Pop
$(genArbitrary ''DiskTemplate)
82 5e9deac0 Iustin Pop
83 5e9deac0 Iustin Pop
$(genArbitrary ''InstanceStatus)
84 5e9deac0 Iustin Pop
85 d696bbef Iustin Pop
$(genArbitrary ''MigrationMode)
86 d696bbef Iustin Pop
87 d696bbef Iustin Pop
$(genArbitrary ''VerifyOptionalChecks)
88 d696bbef Iustin Pop
89 d696bbef Iustin Pop
$(genArbitrary ''DdmSimple)
90 d696bbef Iustin Pop
91 c2d3219b Iustin Pop
$(genArbitrary ''DdmFull)
92 c2d3219b Iustin Pop
93 d696bbef Iustin Pop
$(genArbitrary ''CVErrorCode)
94 d696bbef Iustin Pop
95 22381768 Iustin Pop
$(genArbitrary ''Hypervisor)
96 22381768 Iustin Pop
97 6a28e02c Iustin Pop
$(genArbitrary ''OobCommand)
98 6a28e02c Iustin Pop
99 48755fac Iustin Pop
$(genArbitrary ''StorageType)
100 48755fac Iustin Pop
101 6a28e02c Iustin Pop
$(genArbitrary ''NodeEvacMode)
102 6a28e02c Iustin Pop
103 c65621d7 Iustin Pop
$(genArbitrary ''FileDriver)
104 edb5a1c8 Iustin Pop
105 6d558717 Iustin Pop
$(genArbitrary ''InstCreateMode)
106 6d558717 Iustin Pop
107 c2d3219b Iustin Pop
$(genArbitrary ''RebootType)
108 c2d3219b Iustin Pop
109 398e9066 Iustin Pop
$(genArbitrary ''ExportMode)
110 398e9066 Iustin Pop
111 a3f02317 Iustin Pop
$(genArbitrary ''IAllocatorTestDir)
112 a3f02317 Iustin Pop
113 a3f02317 Iustin Pop
$(genArbitrary ''IAllocatorMode)
114 a3f02317 Iustin Pop
115 8d239fa4 Iustin Pop
$(genArbitrary ''NetworkType)
116 8d239fa4 Iustin Pop
117 497beee2 Iustin Pop
$(genArbitrary ''NICMode)
118 497beee2 Iustin Pop
119 3bdbe4b3 Dato Simó
$(genArbitrary ''JobStatus)
120 3bdbe4b3 Dato Simó
121 6903fea0 Iustin Pop
$(genArbitrary ''FinalizedJobStatus)
122 6903fea0 Iustin Pop
123 b46ba79c Iustin Pop
instance Arbitrary JobId where
124 c48711d5 Iustin Pop
  arbitrary = do
125 c48711d5 Iustin Pop
    (Positive i) <- arbitrary
126 b46ba79c Iustin Pop
    makeJobId i
127 b46ba79c Iustin Pop
128 b46ba79c Iustin Pop
$(genArbitrary ''JobIdDep)
129 b46ba79c Iustin Pop
130 b46ba79c Iustin Pop
$(genArbitrary ''JobDependency)
131 b46ba79c Iustin Pop
132 b46ba79c Iustin Pop
$(genArbitrary ''OpSubmitPriority)
133 c48711d5 Iustin Pop
134 3bdbe4b3 Dato Simó
$(genArbitrary ''OpStatus)
135 3bdbe4b3 Dato Simó
136 5cd95d46 Iustin Pop
$(genArbitrary ''ELogType)
137 5cd95d46 Iustin Pop
138 d696bbef Iustin Pop
-- * Properties
139 d696bbef Iustin Pop
140 5e9deac0 Iustin Pop
prop_AllocPolicy_serialisation :: AllocPolicy -> Property
141 5e9deac0 Iustin Pop
prop_AllocPolicy_serialisation = testSerialisation
142 5e9deac0 Iustin Pop
143 bccb8d20 Dato Simó
-- | Test 'AllocPolicy' ordering is as expected.
144 bccb8d20 Dato Simó
case_AllocPolicy_order :: Assertion
145 bccb8d20 Dato Simó
case_AllocPolicy_order =
146 bccb8d20 Dato Simó
  assertEqual "sort order" [ Types.AllocPreferred
147 bccb8d20 Dato Simó
                           , Types.AllocLastResort
148 bccb8d20 Dato Simó
                           , Types.AllocUnallocable
149 bccb8d20 Dato Simó
                           ] [minBound..maxBound]
150 bccb8d20 Dato Simó
151 5e9deac0 Iustin Pop
prop_DiskTemplate_serialisation :: DiskTemplate -> Property
152 5e9deac0 Iustin Pop
prop_DiskTemplate_serialisation = testSerialisation
153 5e9deac0 Iustin Pop
154 5e9deac0 Iustin Pop
prop_InstanceStatus_serialisation :: InstanceStatus -> Property
155 5e9deac0 Iustin Pop
prop_InstanceStatus_serialisation = testSerialisation
156 5e9deac0 Iustin Pop
157 edb5a1c8 Iustin Pop
-- | Tests building non-negative numbers.
158 edb5a1c8 Iustin Pop
prop_NonNeg_pass :: QuickCheck.NonNegative Int -> Property
159 edb5a1c8 Iustin Pop
prop_NonNeg_pass (QuickCheck.NonNegative i) =
160 edb5a1c8 Iustin Pop
  case mkNonNegative i of
161 edb5a1c8 Iustin Pop
    Bad msg -> failTest $ "Fail to build non-negative: " ++ msg
162 edb5a1c8 Iustin Pop
    Ok nn -> fromNonNegative nn ==? i
163 edb5a1c8 Iustin Pop
164 edb5a1c8 Iustin Pop
-- | Tests building non-negative numbers.
165 edb5a1c8 Iustin Pop
prop_NonNeg_fail :: QuickCheck.Positive Int -> Property
166 edb5a1c8 Iustin Pop
prop_NonNeg_fail (QuickCheck.Positive i) =
167 edb5a1c8 Iustin Pop
  case mkNonNegative (negate i)::Result (Types.NonNegative Int) of
168 edb5a1c8 Iustin Pop
    Bad _ -> passTest
169 edb5a1c8 Iustin Pop
    Ok nn -> failTest $ "Built non-negative number '" ++ show nn ++
170 edb5a1c8 Iustin Pop
             "' from negative value " ++ show i
171 edb5a1c8 Iustin Pop
172 edb5a1c8 Iustin Pop
-- | Tests building positive numbers.
173 edb5a1c8 Iustin Pop
prop_Positive_pass :: QuickCheck.Positive Int -> Property
174 edb5a1c8 Iustin Pop
prop_Positive_pass (QuickCheck.Positive i) =
175 edb5a1c8 Iustin Pop
  case mkPositive i of
176 edb5a1c8 Iustin Pop
    Bad msg -> failTest $ "Fail to build positive: " ++ msg
177 edb5a1c8 Iustin Pop
    Ok nn -> fromPositive nn ==? i
178 edb5a1c8 Iustin Pop
179 edb5a1c8 Iustin Pop
-- | Tests building positive numbers.
180 edb5a1c8 Iustin Pop
prop_Positive_fail :: QuickCheck.NonNegative Int -> Property
181 edb5a1c8 Iustin Pop
prop_Positive_fail (QuickCheck.NonNegative i) =
182 edb5a1c8 Iustin Pop
  case mkPositive (negate i)::Result (Types.Positive Int) of
183 edb5a1c8 Iustin Pop
    Bad _ -> passTest
184 edb5a1c8 Iustin Pop
    Ok nn -> failTest $ "Built positive number '" ++ show nn ++
185 edb5a1c8 Iustin Pop
             "' from negative or zero value " ++ show i
186 edb5a1c8 Iustin Pop
187 c67b908a Iustin Pop
-- | Tests building negative numbers.
188 c67b908a Iustin Pop
prop_Neg_pass :: QuickCheck.Positive Int -> Property
189 c67b908a Iustin Pop
prop_Neg_pass (QuickCheck.Positive i) =
190 c67b908a Iustin Pop
  case mkNegative i' of
191 c67b908a Iustin Pop
    Bad msg -> failTest $ "Fail to build negative: " ++ msg
192 c67b908a Iustin Pop
    Ok nn -> fromNegative nn ==? i'
193 c67b908a Iustin Pop
  where i' = negate i
194 c67b908a Iustin Pop
195 c67b908a Iustin Pop
-- | Tests building negative numbers.
196 c67b908a Iustin Pop
prop_Neg_fail :: QuickCheck.NonNegative Int -> Property
197 c67b908a Iustin Pop
prop_Neg_fail (QuickCheck.NonNegative i) =
198 c67b908a Iustin Pop
  case mkNegative i::Result (Types.Negative Int) of
199 c67b908a Iustin Pop
    Bad _ -> passTest
200 c67b908a Iustin Pop
    Ok nn -> failTest $ "Built negative number '" ++ show nn ++
201 c67b908a Iustin Pop
             "' from non-negative value " ++ show i
202 c67b908a Iustin Pop
203 edb5a1c8 Iustin Pop
-- | Tests building non-empty lists.
204 39573352 Iustin Pop
prop_NonEmpty_pass :: QuickCheck.NonEmptyList String -> Property
205 edb5a1c8 Iustin Pop
prop_NonEmpty_pass (QuickCheck.NonEmpty xs) =
206 edb5a1c8 Iustin Pop
  case mkNonEmpty xs of
207 edb5a1c8 Iustin Pop
    Bad msg -> failTest $ "Fail to build non-empty list: " ++ msg
208 edb5a1c8 Iustin Pop
    Ok nn -> fromNonEmpty nn ==? xs
209 edb5a1c8 Iustin Pop
210 edb5a1c8 Iustin Pop
-- | Tests building positive numbers.
211 edb5a1c8 Iustin Pop
case_NonEmpty_fail :: Assertion
212 39573352 Iustin Pop
case_NonEmpty_fail =
213 edb5a1c8 Iustin Pop
  assertEqual "building non-empty list from an empty list"
214 edb5a1c8 Iustin Pop
    (Bad "Received empty value for non-empty list") (mkNonEmpty ([]::[Int]))
215 edb5a1c8 Iustin Pop
216 d696bbef Iustin Pop
-- | Tests migration mode serialisation.
217 d696bbef Iustin Pop
prop_MigrationMode_serialisation :: MigrationMode -> Property
218 d696bbef Iustin Pop
prop_MigrationMode_serialisation = testSerialisation
219 d696bbef Iustin Pop
220 d696bbef Iustin Pop
-- | Tests verify optional checks serialisation.
221 d696bbef Iustin Pop
prop_VerifyOptionalChecks_serialisation :: VerifyOptionalChecks -> Property
222 d696bbef Iustin Pop
prop_VerifyOptionalChecks_serialisation = testSerialisation
223 d696bbef Iustin Pop
224 d696bbef Iustin Pop
-- | Tests 'DdmSimple' serialisation.
225 d696bbef Iustin Pop
prop_DdmSimple_serialisation :: DdmSimple -> Property
226 d696bbef Iustin Pop
prop_DdmSimple_serialisation = testSerialisation
227 d696bbef Iustin Pop
228 c2d3219b Iustin Pop
-- | Tests 'DdmFull' serialisation.
229 c2d3219b Iustin Pop
prop_DdmFull_serialisation :: DdmFull -> Property
230 c2d3219b Iustin Pop
prop_DdmFull_serialisation = testSerialisation
231 c2d3219b Iustin Pop
232 d696bbef Iustin Pop
-- | Tests 'CVErrorCode' serialisation.
233 d696bbef Iustin Pop
prop_CVErrorCode_serialisation :: CVErrorCode -> Property
234 d696bbef Iustin Pop
prop_CVErrorCode_serialisation = testSerialisation
235 d696bbef Iustin Pop
236 d696bbef Iustin Pop
-- | Tests equivalence with Python, based on Constants.hs code.
237 d696bbef Iustin Pop
case_CVErrorCode_pyequiv :: Assertion
238 d696bbef Iustin Pop
case_CVErrorCode_pyequiv = do
239 d696bbef Iustin Pop
  let all_py_codes = sort C.cvAllEcodesStrings
240 d696bbef Iustin Pop
      all_hs_codes = sort $ map Types.cVErrorCodeToRaw [minBound..maxBound]
241 d696bbef Iustin Pop
  assertEqual "for CVErrorCode equivalence" all_py_codes all_hs_codes
242 d696bbef Iustin Pop
243 22381768 Iustin Pop
-- | Test 'Hypervisor' serialisation.
244 22381768 Iustin Pop
prop_Hypervisor_serialisation :: Hypervisor -> Property
245 22381768 Iustin Pop
prop_Hypervisor_serialisation = testSerialisation
246 22381768 Iustin Pop
247 6a28e02c Iustin Pop
-- | Test 'OobCommand' serialisation.
248 6a28e02c Iustin Pop
prop_OobCommand_serialisation :: OobCommand -> Property
249 6a28e02c Iustin Pop
prop_OobCommand_serialisation = testSerialisation
250 6a28e02c Iustin Pop
251 48755fac Iustin Pop
-- | Test 'StorageType' serialisation.
252 48755fac Iustin Pop
prop_StorageType_serialisation :: StorageType -> Property
253 48755fac Iustin Pop
prop_StorageType_serialisation = testSerialisation
254 48755fac Iustin Pop
255 6a28e02c Iustin Pop
-- | Test 'NodeEvacMode' serialisation.
256 6a28e02c Iustin Pop
prop_NodeEvacMode_serialisation :: NodeEvacMode -> Property
257 6a28e02c Iustin Pop
prop_NodeEvacMode_serialisation = testSerialisation
258 6a28e02c Iustin Pop
259 c65621d7 Iustin Pop
-- | Test 'FileDriver' serialisation.
260 c65621d7 Iustin Pop
prop_FileDriver_serialisation :: FileDriver -> Property
261 c65621d7 Iustin Pop
prop_FileDriver_serialisation = testSerialisation
262 c65621d7 Iustin Pop
263 6d558717 Iustin Pop
-- | Test 'InstCreate' serialisation.
264 6d558717 Iustin Pop
prop_InstCreateMode_serialisation :: InstCreateMode -> Property
265 6d558717 Iustin Pop
prop_InstCreateMode_serialisation = testSerialisation
266 6d558717 Iustin Pop
267 c2d3219b Iustin Pop
-- | Test 'RebootType' serialisation.
268 c2d3219b Iustin Pop
prop_RebootType_serialisation :: RebootType -> Property
269 c2d3219b Iustin Pop
prop_RebootType_serialisation = testSerialisation
270 c2d3219b Iustin Pop
271 398e9066 Iustin Pop
-- | Test 'ExportMode' serialisation.
272 398e9066 Iustin Pop
prop_ExportMode_serialisation :: ExportMode -> Property
273 398e9066 Iustin Pop
prop_ExportMode_serialisation = testSerialisation
274 398e9066 Iustin Pop
275 a3f02317 Iustin Pop
-- | Test 'IAllocatorTestDir' serialisation.
276 a3f02317 Iustin Pop
prop_IAllocatorTestDir_serialisation :: IAllocatorTestDir -> Property
277 a3f02317 Iustin Pop
prop_IAllocatorTestDir_serialisation = testSerialisation
278 a3f02317 Iustin Pop
279 a3f02317 Iustin Pop
-- | Test 'IAllocatorMode' serialisation.
280 a3f02317 Iustin Pop
prop_IAllocatorMode_serialisation :: IAllocatorMode -> Property
281 a3f02317 Iustin Pop
prop_IAllocatorMode_serialisation = testSerialisation
282 a3f02317 Iustin Pop
283 a3f02317 Iustin Pop
-- | Tests equivalence with Python, based on Constants.hs code.
284 a3f02317 Iustin Pop
case_IAllocatorMode_pyequiv :: Assertion
285 a3f02317 Iustin Pop
case_IAllocatorMode_pyequiv = do
286 a3f02317 Iustin Pop
  let all_py_codes = sort C.validIallocatorModes
287 a3f02317 Iustin Pop
      all_hs_codes = sort $ map Types.iAllocatorModeToRaw [minBound..maxBound]
288 a3f02317 Iustin Pop
  assertEqual "for IAllocatorMode equivalence" all_py_codes all_hs_codes
289 a3f02317 Iustin Pop
290 8d239fa4 Iustin Pop
-- | Test 'NetworkType' serialisation.
291 8d239fa4 Iustin Pop
prop_NetworkType_serialisation :: NetworkType -> Property
292 8d239fa4 Iustin Pop
prop_NetworkType_serialisation = testSerialisation
293 8d239fa4 Iustin Pop
294 8d239fa4 Iustin Pop
-- | Tests equivalence with Python, based on Constants.hs code.
295 8d239fa4 Iustin Pop
case_NetworkType_pyequiv :: Assertion
296 8d239fa4 Iustin Pop
case_NetworkType_pyequiv = do
297 8d239fa4 Iustin Pop
  let all_py_codes = sort C.networkValidTypes
298 8d239fa4 Iustin Pop
      all_hs_codes = sort $ map Types.networkTypeToRaw [minBound..maxBound]
299 8d239fa4 Iustin Pop
  assertEqual "for NetworkType equivalence" all_py_codes all_hs_codes
300 8d239fa4 Iustin Pop
301 497beee2 Iustin Pop
-- | Test 'NICMode' serialisation.
302 497beee2 Iustin Pop
prop_NICMode_serialisation :: NICMode -> Property
303 497beee2 Iustin Pop
prop_NICMode_serialisation = testSerialisation
304 497beee2 Iustin Pop
305 3bdbe4b3 Dato Simó
-- | Test 'OpStatus' serialisation.
306 3bdbe4b3 Dato Simó
prop_OpStatus_serialization :: OpStatus -> Property
307 3bdbe4b3 Dato Simó
prop_OpStatus_serialization = testSerialisation
308 3bdbe4b3 Dato Simó
309 3bdbe4b3 Dato Simó
-- | Test 'JobStatus' serialisation.
310 3bdbe4b3 Dato Simó
prop_JobStatus_serialization :: JobStatus -> Property
311 3bdbe4b3 Dato Simó
prop_JobStatus_serialization = testSerialisation
312 3bdbe4b3 Dato Simó
313 bccb8d20 Dato Simó
-- | Test 'JobStatus' ordering is as expected.
314 bccb8d20 Dato Simó
case_JobStatus_order :: Assertion
315 bccb8d20 Dato Simó
case_JobStatus_order =
316 bccb8d20 Dato Simó
  assertEqual "sort order" [ Types.JOB_STATUS_QUEUED
317 bccb8d20 Dato Simó
                           , Types.JOB_STATUS_WAITING
318 bccb8d20 Dato Simó
                           , Types.JOB_STATUS_CANCELING
319 bccb8d20 Dato Simó
                           , Types.JOB_STATUS_RUNNING
320 bccb8d20 Dato Simó
                           , Types.JOB_STATUS_CANCELED
321 bccb8d20 Dato Simó
                           , Types.JOB_STATUS_SUCCESS
322 bccb8d20 Dato Simó
                           , Types.JOB_STATUS_ERROR
323 bccb8d20 Dato Simó
                           ] [minBound..maxBound]
324 bccb8d20 Dato Simó
325 497beee2 Iustin Pop
-- | Tests equivalence with Python, based on Constants.hs code.
326 497beee2 Iustin Pop
case_NICMode_pyequiv :: Assertion
327 497beee2 Iustin Pop
case_NICMode_pyequiv = do
328 497beee2 Iustin Pop
  let all_py_codes = sort C.nicValidModes
329 497beee2 Iustin Pop
      all_hs_codes = sort $ map Types.nICModeToRaw [minBound..maxBound]
330 497beee2 Iustin Pop
  assertEqual "for NICMode equivalence" all_py_codes all_hs_codes
331 497beee2 Iustin Pop
332 6903fea0 Iustin Pop
-- | Test 'FinalizedJobStatus' serialisation.
333 6903fea0 Iustin Pop
prop_FinalizedJobStatus_serialisation :: FinalizedJobStatus -> Property
334 6903fea0 Iustin Pop
prop_FinalizedJobStatus_serialisation = testSerialisation
335 6903fea0 Iustin Pop
336 6903fea0 Iustin Pop
-- | Tests equivalence with Python, based on Constants.hs code.
337 6903fea0 Iustin Pop
case_FinalizedJobStatus_pyequiv :: Assertion
338 6903fea0 Iustin Pop
case_FinalizedJobStatus_pyequiv = do
339 6903fea0 Iustin Pop
  let all_py_codes = sort C.jobsFinalized
340 6903fea0 Iustin Pop
      all_hs_codes = sort $ map Types.finalizedJobStatusToRaw
341 6903fea0 Iustin Pop
                            [minBound..maxBound]
342 6903fea0 Iustin Pop
  assertEqual "for FinalizedJobStatus equivalence" all_py_codes all_hs_codes
343 6903fea0 Iustin Pop
344 c48711d5 Iustin Pop
-- | Tests JobId serialisation (both from string and ints).
345 c48711d5 Iustin Pop
prop_JobId_serialisation :: JobId -> Property
346 c48711d5 Iustin Pop
prop_JobId_serialisation jid =
347 90634d95 Iustin Pop
  conjoin [ testSerialisation jid
348 90634d95 Iustin Pop
          , (J.readJSON . J.showJSON . show $ fromJobId jid) ==? J.Ok jid
349 90634d95 Iustin Pop
          , case (fromJVal . J.showJSON . negate $
350 90634d95 Iustin Pop
                  fromJobId jid)::Result JobId of
351 90634d95 Iustin Pop
              Bad _ -> passTest
352 90634d95 Iustin Pop
              Ok jid' -> failTest $ "Parsed negative job id as id " ++
353 90634d95 Iustin Pop
                         show (fromJobId jid')
354 90634d95 Iustin Pop
          ]
355 90634d95 Iustin Pop
356 90634d95 Iustin Pop
-- | Tests that fractional job IDs are not accepted.
357 90634d95 Iustin Pop
prop_JobId_fractional :: Property
358 90634d95 Iustin Pop
prop_JobId_fractional =
359 90634d95 Iustin Pop
  forAll (arbitrary `suchThat`
360 90634d95 Iustin Pop
          (\d -> fromIntegral (truncate d::Int) /= d)) $ \d ->
361 90634d95 Iustin Pop
  case J.readJSON (J.showJSON (d::Double)) of
362 90634d95 Iustin Pop
    J.Error _ -> passTest
363 90634d95 Iustin Pop
    J.Ok jid -> failTest $ "Parsed fractional value " ++ show d ++
364 90634d95 Iustin Pop
                " as job id " ++ show (fromJobId jid)
365 90634d95 Iustin Pop
366 90634d95 Iustin Pop
-- | Tests that a job ID is not parseable from \"bad\" JSON values.
367 90634d95 Iustin Pop
case_JobId_BadTypes :: Assertion
368 90634d95 Iustin Pop
case_JobId_BadTypes = do
369 90634d95 Iustin Pop
  let helper jsval = case J.readJSON jsval of
370 90634d95 Iustin Pop
                       J.Error _ -> return ()
371 90634d95 Iustin Pop
                       J.Ok jid -> assertFailure $ "Parsed " ++ show jsval
372 90634d95 Iustin Pop
                                   ++ " as job id " ++ show (fromJobId jid)
373 90634d95 Iustin Pop
  helper J.JSNull
374 90634d95 Iustin Pop
  helper (J.JSBool True)
375 90634d95 Iustin Pop
  helper (J.JSBool False)
376 90634d95 Iustin Pop
  helper (J.JSArray [])
377 c48711d5 Iustin Pop
378 b46ba79c Iustin Pop
-- | Test 'JobDependency' serialisation.
379 b46ba79c Iustin Pop
prop_JobDependency_serialisation :: JobDependency -> Property
380 b46ba79c Iustin Pop
prop_JobDependency_serialisation = testSerialisation
381 b46ba79c Iustin Pop
382 b46ba79c Iustin Pop
-- | Test 'OpSubmitPriority' serialisation.
383 b46ba79c Iustin Pop
prop_OpSubmitPriority_serialisation :: OpSubmitPriority -> Property
384 b46ba79c Iustin Pop
prop_OpSubmitPriority_serialisation = testSerialisation
385 b46ba79c Iustin Pop
386 5cd95d46 Iustin Pop
-- | Test 'ELogType' serialisation.
387 5cd95d46 Iustin Pop
prop_ELogType_serialisation :: ELogType -> Property
388 5cd95d46 Iustin Pop
prop_ELogType_serialisation = testSerialisation
389 5cd95d46 Iustin Pop
390 5e9deac0 Iustin Pop
testSuite "Types"
391 5e9deac0 Iustin Pop
  [ 'prop_AllocPolicy_serialisation
392 bccb8d20 Dato Simó
  , 'case_AllocPolicy_order
393 5e9deac0 Iustin Pop
  , 'prop_DiskTemplate_serialisation
394 5e9deac0 Iustin Pop
  , 'prop_InstanceStatus_serialisation
395 edb5a1c8 Iustin Pop
  , 'prop_NonNeg_pass
396 edb5a1c8 Iustin Pop
  , 'prop_NonNeg_fail
397 edb5a1c8 Iustin Pop
  , 'prop_Positive_pass
398 edb5a1c8 Iustin Pop
  , 'prop_Positive_fail
399 c67b908a Iustin Pop
  , 'prop_Neg_pass
400 c67b908a Iustin Pop
  , 'prop_Neg_fail
401 edb5a1c8 Iustin Pop
  , 'prop_NonEmpty_pass
402 edb5a1c8 Iustin Pop
  , 'case_NonEmpty_fail
403 d696bbef Iustin Pop
  , 'prop_MigrationMode_serialisation
404 d696bbef Iustin Pop
  , 'prop_VerifyOptionalChecks_serialisation
405 d696bbef Iustin Pop
  , 'prop_DdmSimple_serialisation
406 c2d3219b Iustin Pop
  , 'prop_DdmFull_serialisation
407 d696bbef Iustin Pop
  , 'prop_CVErrorCode_serialisation
408 d696bbef Iustin Pop
  , 'case_CVErrorCode_pyequiv
409 22381768 Iustin Pop
  , 'prop_Hypervisor_serialisation
410 6a28e02c Iustin Pop
  , 'prop_OobCommand_serialisation
411 48755fac Iustin Pop
  , 'prop_StorageType_serialisation
412 6a28e02c Iustin Pop
  , 'prop_NodeEvacMode_serialisation
413 c65621d7 Iustin Pop
  , 'prop_FileDriver_serialisation
414 6d558717 Iustin Pop
  , 'prop_InstCreateMode_serialisation
415 c2d3219b Iustin Pop
  , 'prop_RebootType_serialisation
416 398e9066 Iustin Pop
  , 'prop_ExportMode_serialisation
417 a3f02317 Iustin Pop
  , 'prop_IAllocatorTestDir_serialisation
418 a3f02317 Iustin Pop
  , 'prop_IAllocatorMode_serialisation
419 a3f02317 Iustin Pop
  , 'case_IAllocatorMode_pyequiv
420 8d239fa4 Iustin Pop
  , 'prop_NetworkType_serialisation
421 8d239fa4 Iustin Pop
  , 'case_NetworkType_pyequiv
422 497beee2 Iustin Pop
  , 'prop_NICMode_serialisation
423 3bdbe4b3 Dato Simó
  , 'prop_OpStatus_serialization
424 3bdbe4b3 Dato Simó
  , 'prop_JobStatus_serialization
425 bccb8d20 Dato Simó
  , 'case_JobStatus_order
426 497beee2 Iustin Pop
  , 'case_NICMode_pyequiv
427 6903fea0 Iustin Pop
  , 'prop_FinalizedJobStatus_serialisation
428 6903fea0 Iustin Pop
  , 'case_FinalizedJobStatus_pyequiv
429 c48711d5 Iustin Pop
  , 'prop_JobId_serialisation
430 90634d95 Iustin Pop
  , 'prop_JobId_fractional
431 90634d95 Iustin Pop
  , 'case_JobId_BadTypes
432 b46ba79c Iustin Pop
  , 'prop_JobDependency_serialisation
433 b46ba79c Iustin Pop
  , 'prop_OpSubmitPriority_serialisation
434 5cd95d46 Iustin Pop
  , 'prop_ELogType_serialisation
435 5e9deac0 Iustin Pop
  ]