Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (5.4 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 5e9deac0 Iustin Pop
  ) where
37 5e9deac0 Iustin Pop
38 d696bbef Iustin Pop
import Data.List (sort)
39 edb5a1c8 Iustin Pop
import Test.QuickCheck as QuickCheck hiding (Result)
40 edb5a1c8 Iustin Pop
import Test.HUnit
41 5e9deac0 Iustin Pop
42 5e9deac0 Iustin Pop
import Test.Ganeti.TestHelper
43 5e9deac0 Iustin Pop
import Test.Ganeti.TestCommon
44 5e9deac0 Iustin Pop
45 edb5a1c8 Iustin Pop
import Ganeti.BasicTypes
46 d696bbef Iustin Pop
import qualified Ganeti.Constants as C
47 edb5a1c8 Iustin Pop
import Ganeti.Types as Types
48 5e9deac0 Iustin Pop
49 39573352 Iustin Pop
{-# ANN module "HLint: ignore Use camelCase" #-}
50 39573352 Iustin Pop
51 5e9deac0 Iustin Pop
-- * Arbitrary instance
52 5e9deac0 Iustin Pop
53 edb5a1c8 Iustin Pop
instance (Arbitrary a, Ord a, Num a, Show a) =>
54 edb5a1c8 Iustin Pop
  Arbitrary (Types.Positive a) where
55 edb5a1c8 Iustin Pop
  arbitrary = do
56 edb5a1c8 Iustin Pop
    (QuickCheck.Positive i) <- arbitrary
57 edb5a1c8 Iustin Pop
    Types.mkPositive i
58 edb5a1c8 Iustin Pop
59 5e9deac0 Iustin Pop
$(genArbitrary ''AllocPolicy)
60 5e9deac0 Iustin Pop
61 5e9deac0 Iustin Pop
$(genArbitrary ''DiskTemplate)
62 5e9deac0 Iustin Pop
63 5e9deac0 Iustin Pop
$(genArbitrary ''InstanceStatus)
64 5e9deac0 Iustin Pop
65 d696bbef Iustin Pop
$(genArbitrary ''MigrationMode)
66 d696bbef Iustin Pop
67 d696bbef Iustin Pop
$(genArbitrary ''VerifyOptionalChecks)
68 d696bbef Iustin Pop
69 d696bbef Iustin Pop
$(genArbitrary ''DdmSimple)
70 d696bbef Iustin Pop
71 d696bbef Iustin Pop
$(genArbitrary ''CVErrorCode)
72 d696bbef Iustin Pop
73 22381768 Iustin Pop
$(genArbitrary ''Hypervisor)
74 22381768 Iustin Pop
75 edb5a1c8 Iustin Pop
instance (Arbitrary a) => Arbitrary (Types.NonEmpty a) where
76 edb5a1c8 Iustin Pop
  arbitrary = do
77 edb5a1c8 Iustin Pop
    QuickCheck.NonEmpty lst <- arbitrary
78 edb5a1c8 Iustin Pop
    Types.mkNonEmpty lst
79 edb5a1c8 Iustin Pop
80 d696bbef Iustin Pop
-- * Properties
81 d696bbef Iustin Pop
82 5e9deac0 Iustin Pop
prop_AllocPolicy_serialisation :: AllocPolicy -> Property
83 5e9deac0 Iustin Pop
prop_AllocPolicy_serialisation = testSerialisation
84 5e9deac0 Iustin Pop
85 5e9deac0 Iustin Pop
prop_DiskTemplate_serialisation :: DiskTemplate -> Property
86 5e9deac0 Iustin Pop
prop_DiskTemplate_serialisation = testSerialisation
87 5e9deac0 Iustin Pop
88 5e9deac0 Iustin Pop
prop_InstanceStatus_serialisation :: InstanceStatus -> Property
89 5e9deac0 Iustin Pop
prop_InstanceStatus_serialisation = testSerialisation
90 5e9deac0 Iustin Pop
91 edb5a1c8 Iustin Pop
-- | Tests building non-negative numbers.
92 edb5a1c8 Iustin Pop
prop_NonNeg_pass :: QuickCheck.NonNegative Int -> Property
93 edb5a1c8 Iustin Pop
prop_NonNeg_pass (QuickCheck.NonNegative i) =
94 edb5a1c8 Iustin Pop
  case mkNonNegative i of
95 edb5a1c8 Iustin Pop
    Bad msg -> failTest $ "Fail to build non-negative: " ++ msg
96 edb5a1c8 Iustin Pop
    Ok nn -> fromNonNegative nn ==? i
97 edb5a1c8 Iustin Pop
98 edb5a1c8 Iustin Pop
-- | Tests building non-negative numbers.
99 edb5a1c8 Iustin Pop
prop_NonNeg_fail :: QuickCheck.Positive Int -> Property
100 edb5a1c8 Iustin Pop
prop_NonNeg_fail (QuickCheck.Positive i) =
101 edb5a1c8 Iustin Pop
  case mkNonNegative (negate i)::Result (Types.NonNegative Int) of
102 edb5a1c8 Iustin Pop
    Bad _ -> passTest
103 edb5a1c8 Iustin Pop
    Ok nn -> failTest $ "Built non-negative number '" ++ show nn ++
104 edb5a1c8 Iustin Pop
             "' from negative value " ++ show i
105 edb5a1c8 Iustin Pop
106 edb5a1c8 Iustin Pop
-- | Tests building positive numbers.
107 edb5a1c8 Iustin Pop
prop_Positive_pass :: QuickCheck.Positive Int -> Property
108 edb5a1c8 Iustin Pop
prop_Positive_pass (QuickCheck.Positive i) =
109 edb5a1c8 Iustin Pop
  case mkPositive i of
110 edb5a1c8 Iustin Pop
    Bad msg -> failTest $ "Fail to build positive: " ++ msg
111 edb5a1c8 Iustin Pop
    Ok nn -> fromPositive nn ==? i
112 edb5a1c8 Iustin Pop
113 edb5a1c8 Iustin Pop
-- | Tests building positive numbers.
114 edb5a1c8 Iustin Pop
prop_Positive_fail :: QuickCheck.NonNegative Int -> Property
115 edb5a1c8 Iustin Pop
prop_Positive_fail (QuickCheck.NonNegative i) =
116 edb5a1c8 Iustin Pop
  case mkPositive (negate i)::Result (Types.Positive Int) of
117 edb5a1c8 Iustin Pop
    Bad _ -> passTest
118 edb5a1c8 Iustin Pop
    Ok nn -> failTest $ "Built positive number '" ++ show nn ++
119 edb5a1c8 Iustin Pop
             "' from negative or zero value " ++ show i
120 edb5a1c8 Iustin Pop
121 edb5a1c8 Iustin Pop
-- | Tests building non-empty lists.
122 39573352 Iustin Pop
prop_NonEmpty_pass :: QuickCheck.NonEmptyList String -> Property
123 edb5a1c8 Iustin Pop
prop_NonEmpty_pass (QuickCheck.NonEmpty xs) =
124 edb5a1c8 Iustin Pop
  case mkNonEmpty xs of
125 edb5a1c8 Iustin Pop
    Bad msg -> failTest $ "Fail to build non-empty list: " ++ msg
126 edb5a1c8 Iustin Pop
    Ok nn -> fromNonEmpty nn ==? xs
127 edb5a1c8 Iustin Pop
128 edb5a1c8 Iustin Pop
-- | Tests building positive numbers.
129 edb5a1c8 Iustin Pop
case_NonEmpty_fail :: Assertion
130 39573352 Iustin Pop
case_NonEmpty_fail =
131 edb5a1c8 Iustin Pop
  assertEqual "building non-empty list from an empty list"
132 edb5a1c8 Iustin Pop
    (Bad "Received empty value for non-empty list") (mkNonEmpty ([]::[Int]))
133 edb5a1c8 Iustin Pop
134 d696bbef Iustin Pop
-- | Tests migration mode serialisation.
135 d696bbef Iustin Pop
prop_MigrationMode_serialisation :: MigrationMode -> Property
136 d696bbef Iustin Pop
prop_MigrationMode_serialisation = testSerialisation
137 d696bbef Iustin Pop
138 d696bbef Iustin Pop
-- | Tests verify optional checks serialisation.
139 d696bbef Iustin Pop
prop_VerifyOptionalChecks_serialisation :: VerifyOptionalChecks -> Property
140 d696bbef Iustin Pop
prop_VerifyOptionalChecks_serialisation = testSerialisation
141 d696bbef Iustin Pop
142 d696bbef Iustin Pop
-- | Tests 'DdmSimple' serialisation.
143 d696bbef Iustin Pop
prop_DdmSimple_serialisation :: DdmSimple -> Property
144 d696bbef Iustin Pop
prop_DdmSimple_serialisation = testSerialisation
145 d696bbef Iustin Pop
146 d696bbef Iustin Pop
-- | Tests 'CVErrorCode' serialisation.
147 d696bbef Iustin Pop
prop_CVErrorCode_serialisation :: CVErrorCode -> Property
148 d696bbef Iustin Pop
prop_CVErrorCode_serialisation = testSerialisation
149 d696bbef Iustin Pop
150 d696bbef Iustin Pop
-- | Tests equivalence with Python, based on Constants.hs code.
151 d696bbef Iustin Pop
case_CVErrorCode_pyequiv :: Assertion
152 d696bbef Iustin Pop
case_CVErrorCode_pyequiv = do
153 d696bbef Iustin Pop
  let all_py_codes = sort C.cvAllEcodesStrings
154 d696bbef Iustin Pop
      all_hs_codes = sort $ map Types.cVErrorCodeToRaw [minBound..maxBound]
155 d696bbef Iustin Pop
  assertEqual "for CVErrorCode equivalence" all_py_codes all_hs_codes
156 d696bbef Iustin Pop
157 22381768 Iustin Pop
-- | Test 'Hypervisor' serialisation.
158 22381768 Iustin Pop
prop_Hypervisor_serialisation :: Hypervisor -> Property
159 22381768 Iustin Pop
prop_Hypervisor_serialisation = testSerialisation
160 22381768 Iustin Pop
161 5e9deac0 Iustin Pop
testSuite "Types"
162 5e9deac0 Iustin Pop
  [ 'prop_AllocPolicy_serialisation
163 5e9deac0 Iustin Pop
  , 'prop_DiskTemplate_serialisation
164 5e9deac0 Iustin Pop
  , 'prop_InstanceStatus_serialisation
165 edb5a1c8 Iustin Pop
  , 'prop_NonNeg_pass
166 edb5a1c8 Iustin Pop
  , 'prop_NonNeg_fail
167 edb5a1c8 Iustin Pop
  , 'prop_Positive_pass
168 edb5a1c8 Iustin Pop
  , 'prop_Positive_fail
169 edb5a1c8 Iustin Pop
  , 'prop_NonEmpty_pass
170 edb5a1c8 Iustin Pop
  , 'case_NonEmpty_fail
171 d696bbef Iustin Pop
  , 'prop_MigrationMode_serialisation
172 d696bbef Iustin Pop
  , 'prop_VerifyOptionalChecks_serialisation
173 d696bbef Iustin Pop
  , 'prop_DdmSimple_serialisation
174 d696bbef Iustin Pop
  , 'prop_CVErrorCode_serialisation
175 d696bbef Iustin Pop
  , 'case_CVErrorCode_pyequiv
176 22381768 Iustin Pop
  , 'prop_Hypervisor_serialisation
177 5e9deac0 Iustin Pop
  ]