Revision 2d87bd0a

b/Makefile.am
446 446
	htest/Test/Ganeti/HTools/Text.hs \
447 447
	htest/Test/Ganeti/HTools/Types.hs \
448 448
	htest/Test/Ganeti/HTools/Utils.hs \
449
	htest/Test/Ganeti/JSON.hs \
450
	htest/Test/Ganeti/Jobs.hs \
449 451
	htest/Test/Ganeti/Luxi.hs \
450 452
	htest/Test/Ganeti/Objects.hs \
451 453
	htest/Test/Ganeti/OpCodes.hs \
b/htest/Test/Ganeti/JSON.hs
1
{-# LANGUAGE TemplateHaskell #-}
2
{-# OPTIONS_GHC -fno-warn-orphans #-}
3

  
4
{-| Unittests for ganeti-htools.
5

  
6
-}
7

  
8
{-
9

  
10
Copyright (C) 2009, 2010, 2011, 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.JSON (testJSON) where
30

  
31
import Test.QuickCheck
32

  
33
import qualified Text.JSON as J
34

  
35
import Test.Ganeti.TestHelper
36
import Test.Ganeti.TestCommon
37

  
38
import qualified Ganeti.BasicTypes as BasicTypes
39
import qualified Ganeti.JSON as JSON
40

  
41
prop_JSON_toArray :: [Int] -> Property
42
prop_JSON_toArray intarr =
43
  let arr = map J.showJSON intarr in
44
  case JSON.toArray (J.JSArray arr) of
45
    BasicTypes.Ok arr' -> arr ==? arr'
46
    BasicTypes.Bad err -> failTest $ "Failed to parse array: " ++ err
47

  
48
prop_JSON_toArrayFail :: Int -> String -> Bool -> Property
49
prop_JSON_toArrayFail i s b =
50
  -- poor man's instance Arbitrary JSValue
51
  forAll (elements [J.showJSON i, J.showJSON s, J.showJSON b]) $ \item ->
52
  case JSON.toArray item of
53
    BasicTypes.Bad _ -> property True
54
    BasicTypes.Ok result -> failTest $ "Unexpected parse, got " ++ show result
55

  
56
testSuite "JSON"
57
          [ 'prop_JSON_toArray
58
          , 'prop_JSON_toArrayFail
59
          ]
b/htest/Test/Ganeti/Jobs.hs
1
{-# LANGUAGE TemplateHaskell #-}
2
{-# OPTIONS_GHC -fno-warn-orphans #-}
3

  
4
{-| Unittests for ganeti-htools.
5

  
6
-}
7

  
8
{-
9

  
10
Copyright (C) 2009, 2010, 2011, 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.Jobs (testJobs) where
30

  
31
import Test.QuickCheck
32

  
33
import qualified Text.JSON as J
34

  
35
import Test.Ganeti.TestHelper
36
import Test.Ganeti.TestCommon
37

  
38
import qualified Ganeti.Jobs as Jobs
39

  
40
-- * Arbitrary instances
41

  
42
instance Arbitrary Jobs.OpStatus where
43
  arbitrary = elements [minBound..maxBound]
44

  
45
instance Arbitrary Jobs.JobStatus where
46
  arbitrary = elements [minBound..maxBound]
47

  
48
-- * Test cases
49

  
50
-- | Check that (queued) job\/opcode status serialization is idempotent.
51
prop_Jobs_OpStatus_serialization :: Jobs.OpStatus -> Property
52
prop_Jobs_OpStatus_serialization os =
53
  case J.readJSON (J.showJSON os) of
54
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
55
    J.Ok os' -> os ==? os'
56

  
57
prop_Jobs_JobStatus_serialization :: Jobs.JobStatus -> Property
58
prop_Jobs_JobStatus_serialization js =
59
  case J.readJSON (J.showJSON js) of
60
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
61
    J.Ok js' -> js ==? js'
62

  
63
testSuite "Jobs"
64
            [ 'prop_Jobs_OpStatus_serialization
65
            , 'prop_Jobs_JobStatus_serialization
66
            ]
b/htest/test.hs
29 29
import Test.Framework
30 30
import System.Environment (getArgs)
31 31

  
32
import Ganeti.HTools.QC
32
import Ganeti.HTools.QC ()
33 33
import Test.Ganeti.Confd.Utils
34 34
import Test.Ganeti.HTools.CLI
35 35
import Test.Ganeti.HTools.Cluster
......
42 42
import Test.Ganeti.HTools.Text
43 43
import Test.Ganeti.HTools.Types
44 44
import Test.Ganeti.HTools.Utils
45
import Test.Ganeti.Jobs
46
import Test.Ganeti.JSON
45 47
import Test.Ganeti.Luxi
46 48
import Test.Ganeti.Objects
47 49
import Test.Ganeti.OpCodes
b/htools/Ganeti/HTools/QC.hs
32 32
-}
33 33

  
34 34
module Ganeti.HTools.QC
35
  ( testJobs
36
  , testJSON
37
  ) where
35
  () where
38 36

  
39 37
import qualified Test.HUnit as HUnit
40 38
import Test.QuickCheck
......
100 98

  
101 99
import Test.Ganeti.TestHelper (testSuite)
102 100
import Test.Ganeti.TestCommon
103

  
104
-- * Helper functions
105

  
106

  
107
instance Arbitrary Jobs.OpStatus where
108
  arbitrary = elements [minBound..maxBound]
109

  
110
instance Arbitrary Jobs.JobStatus where
111
  arbitrary = elements [minBound..maxBound]
112

  
113
-- * Actual tests
114

  
115

  
116
-- ** Jobs tests
117

  
118
-- | Check that (queued) job\/opcode status serialization is idempotent.
119
prop_Jobs_OpStatus_serialization :: Jobs.OpStatus -> Property
120
prop_Jobs_OpStatus_serialization os =
121
  case J.readJSON (J.showJSON os) of
122
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
123
    J.Ok os' -> os ==? os'
124

  
125
prop_Jobs_JobStatus_serialization :: Jobs.JobStatus -> Property
126
prop_Jobs_JobStatus_serialization js =
127
  case J.readJSON (J.showJSON js) of
128
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
129
    J.Ok js' -> js ==? js'
130

  
131
testSuite "Jobs"
132
            [ 'prop_Jobs_OpStatus_serialization
133
            , 'prop_Jobs_JobStatus_serialization
134
            ]
135

  
136
-- * JSON tests
137

  
138
prop_JSON_toArray :: [Int] -> Property
139
prop_JSON_toArray intarr =
140
  let arr = map J.showJSON intarr in
141
  case JSON.toArray (J.JSArray arr) of
142
    Types.Ok arr' -> arr ==? arr'
143
    Types.Bad err -> failTest $ "Failed to parse array: " ++ err
144

  
145
prop_JSON_toArrayFail :: Int -> String -> Bool -> Property
146
prop_JSON_toArrayFail i s b =
147
  -- poor man's instance Arbitrary JSValue
148
  forAll (elements [J.showJSON i, J.showJSON s, J.showJSON b]) $ \item ->
149
  case JSON.toArray item of
150
    Types.Bad _ -> property True
151
    Types.Ok result -> failTest $ "Unexpected parse, got " ++ show result
152

  
153
testSuite "JSON"
154
          [ 'prop_JSON_toArray
155
          , 'prop_JSON_toArrayFail
156
          ]

Also available in: Unified diff