Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / Types.hs @ 6a28e02c

History | View | Annotate | Download (6.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
$(genArbitrary ''AllocPolicy)
60

    
61
$(genArbitrary ''DiskTemplate)
62

    
63
$(genArbitrary ''InstanceStatus)
64

    
65
$(genArbitrary ''MigrationMode)
66

    
67
$(genArbitrary ''VerifyOptionalChecks)
68

    
69
$(genArbitrary ''DdmSimple)
70

    
71
$(genArbitrary ''CVErrorCode)
72

    
73
$(genArbitrary ''Hypervisor)
74

    
75
$(genArbitrary ''OobCommand)
76

    
77
$(genArbitrary ''StorageType)
78

    
79
$(genArbitrary ''NodeEvacMode)
80

    
81
instance (Arbitrary a) => Arbitrary (Types.NonEmpty a) where
82
  arbitrary = do
83
    QuickCheck.NonEmpty lst <- arbitrary
84
    Types.mkNonEmpty lst
85

    
86
-- * Properties
87

    
88
prop_AllocPolicy_serialisation :: AllocPolicy -> Property
89
prop_AllocPolicy_serialisation = testSerialisation
90

    
91
prop_DiskTemplate_serialisation :: DiskTemplate -> Property
92
prop_DiskTemplate_serialisation = testSerialisation
93

    
94
prop_InstanceStatus_serialisation :: InstanceStatus -> Property
95
prop_InstanceStatus_serialisation = testSerialisation
96

    
97
-- | Tests building non-negative numbers.
98
prop_NonNeg_pass :: QuickCheck.NonNegative Int -> Property
99
prop_NonNeg_pass (QuickCheck.NonNegative i) =
100
  case mkNonNegative i of
101
    Bad msg -> failTest $ "Fail to build non-negative: " ++ msg
102
    Ok nn -> fromNonNegative nn ==? i
103

    
104
-- | Tests building non-negative numbers.
105
prop_NonNeg_fail :: QuickCheck.Positive Int -> Property
106
prop_NonNeg_fail (QuickCheck.Positive i) =
107
  case mkNonNegative (negate i)::Result (Types.NonNegative Int) of
108
    Bad _ -> passTest
109
    Ok nn -> failTest $ "Built non-negative number '" ++ show nn ++
110
             "' from negative value " ++ show i
111

    
112
-- | Tests building positive numbers.
113
prop_Positive_pass :: QuickCheck.Positive Int -> Property
114
prop_Positive_pass (QuickCheck.Positive i) =
115
  case mkPositive i of
116
    Bad msg -> failTest $ "Fail to build positive: " ++ msg
117
    Ok nn -> fromPositive nn ==? i
118

    
119
-- | Tests building positive numbers.
120
prop_Positive_fail :: QuickCheck.NonNegative Int -> Property
121
prop_Positive_fail (QuickCheck.NonNegative i) =
122
  case mkPositive (negate i)::Result (Types.Positive Int) of
123
    Bad _ -> passTest
124
    Ok nn -> failTest $ "Built positive number '" ++ show nn ++
125
             "' from negative or zero value " ++ show i
126

    
127
-- | Tests building non-empty lists.
128
prop_NonEmpty_pass :: QuickCheck.NonEmptyList String -> Property
129
prop_NonEmpty_pass (QuickCheck.NonEmpty xs) =
130
  case mkNonEmpty xs of
131
    Bad msg -> failTest $ "Fail to build non-empty list: " ++ msg
132
    Ok nn -> fromNonEmpty nn ==? xs
133

    
134
-- | Tests building positive numbers.
135
case_NonEmpty_fail :: Assertion
136
case_NonEmpty_fail =
137
  assertEqual "building non-empty list from an empty list"
138
    (Bad "Received empty value for non-empty list") (mkNonEmpty ([]::[Int]))
139

    
140
-- | Tests migration mode serialisation.
141
prop_MigrationMode_serialisation :: MigrationMode -> Property
142
prop_MigrationMode_serialisation = testSerialisation
143

    
144
-- | Tests verify optional checks serialisation.
145
prop_VerifyOptionalChecks_serialisation :: VerifyOptionalChecks -> Property
146
prop_VerifyOptionalChecks_serialisation = testSerialisation
147

    
148
-- | Tests 'DdmSimple' serialisation.
149
prop_DdmSimple_serialisation :: DdmSimple -> Property
150
prop_DdmSimple_serialisation = testSerialisation
151

    
152
-- | Tests 'CVErrorCode' serialisation.
153
prop_CVErrorCode_serialisation :: CVErrorCode -> Property
154
prop_CVErrorCode_serialisation = testSerialisation
155

    
156
-- | Tests equivalence with Python, based on Constants.hs code.
157
case_CVErrorCode_pyequiv :: Assertion
158
case_CVErrorCode_pyequiv = do
159
  let all_py_codes = sort C.cvAllEcodesStrings
160
      all_hs_codes = sort $ map Types.cVErrorCodeToRaw [minBound..maxBound]
161
  assertEqual "for CVErrorCode equivalence" all_py_codes all_hs_codes
162

    
163
-- | Test 'Hypervisor' serialisation.
164
prop_Hypervisor_serialisation :: Hypervisor -> Property
165
prop_Hypervisor_serialisation = testSerialisation
166

    
167
-- | Test 'OobCommand' serialisation.
168
prop_OobCommand_serialisation :: OobCommand -> Property
169
prop_OobCommand_serialisation = testSerialisation
170

    
171
-- | Test 'StorageType' serialisation.
172
prop_StorageType_serialisation :: StorageType -> Property
173
prop_StorageType_serialisation = testSerialisation
174

    
175
-- | Test 'NodeEvacMode' serialisation.
176
prop_NodeEvacMode_serialisation :: NodeEvacMode -> Property
177
prop_NodeEvacMode_serialisation = testSerialisation
178

    
179
testSuite "Types"
180
  [ 'prop_AllocPolicy_serialisation
181
  , 'prop_DiskTemplate_serialisation
182
  , 'prop_InstanceStatus_serialisation
183
  , 'prop_NonNeg_pass
184
  , 'prop_NonNeg_fail
185
  , 'prop_Positive_pass
186
  , 'prop_Positive_fail
187
  , 'prop_NonEmpty_pass
188
  , 'case_NonEmpty_fail
189
  , 'prop_MigrationMode_serialisation
190
  , 'prop_VerifyOptionalChecks_serialisation
191
  , 'prop_DdmSimple_serialisation
192
  , 'prop_CVErrorCode_serialisation
193
  , 'case_CVErrorCode_pyequiv
194
  , 'prop_Hypervisor_serialisation
195
  , 'prop_OobCommand_serialisation
196
  , 'prop_StorageType_serialisation
197
  , 'prop_NodeEvacMode_serialisation
198
  ]