Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Types.hs @ 2fe1e043

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