Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Confd / Types.hs @ 560ef132

History | View | Annotate | Download (3.2 kB)

1 fef919b7 Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 fef919b7 Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 fef919b7 Iustin Pop
4 fef919b7 Iustin Pop
{-| Unittests for ganeti-htools.
5 fef919b7 Iustin Pop
6 fef919b7 Iustin Pop
-}
7 fef919b7 Iustin Pop
8 fef919b7 Iustin Pop
{-
9 fef919b7 Iustin Pop
10 fef919b7 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11 fef919b7 Iustin Pop
12 fef919b7 Iustin Pop
This program is free software; you can redistribute it and/or modify
13 fef919b7 Iustin Pop
it under the terms of the GNU General Public License as published by
14 fef919b7 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 fef919b7 Iustin Pop
(at your option) any later version.
16 fef919b7 Iustin Pop
17 fef919b7 Iustin Pop
This program is distributed in the hope that it will be useful, but
18 fef919b7 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 fef919b7 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 fef919b7 Iustin Pop
General Public License for more details.
21 fef919b7 Iustin Pop
22 fef919b7 Iustin Pop
You should have received a copy of the GNU General Public License
23 fef919b7 Iustin Pop
along with this program; if not, write to the Free Software
24 fef919b7 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 fef919b7 Iustin Pop
02110-1301, USA.
26 fef919b7 Iustin Pop
27 fef919b7 Iustin Pop
-}
28 fef919b7 Iustin Pop
29 fef919b7 Iustin Pop
module Test.Ganeti.Confd.Types
30 fef919b7 Iustin Pop
  ( testConfd_Types
31 fef919b7 Iustin Pop
  , ConfdRequestType(..)
32 fef919b7 Iustin Pop
  , ConfdReqField(..)
33 fef919b7 Iustin Pop
  , ConfdReqQ(..)
34 fef919b7 Iustin Pop
  ) where
35 fef919b7 Iustin Pop
36 fef919b7 Iustin Pop
import Control.Applicative
37 fef919b7 Iustin Pop
import Test.QuickCheck
38 fef919b7 Iustin Pop
import Test.HUnit
39 fef919b7 Iustin Pop
import qualified Text.JSON as J
40 fef919b7 Iustin Pop
41 fef919b7 Iustin Pop
import Test.Ganeti.TestHelper
42 fef919b7 Iustin Pop
import Test.Ganeti.TestCommon
43 fef919b7 Iustin Pop
44 fef919b7 Iustin Pop
import Ganeti.Confd.Types as Confd
45 fef919b7 Iustin Pop
46 fef919b7 Iustin Pop
{-# ANN module "HLint: ignore Use camelCase" #-}
47 fef919b7 Iustin Pop
48 fef919b7 Iustin Pop
-- * Arbitrary instances
49 fef919b7 Iustin Pop
50 fef919b7 Iustin Pop
$(genArbitrary ''ConfdRequestType)
51 fef919b7 Iustin Pop
52 fef919b7 Iustin Pop
$(genArbitrary ''ConfdReqField)
53 fef919b7 Iustin Pop
54 fef919b7 Iustin Pop
$(genArbitrary ''ConfdReqQ)
55 fef919b7 Iustin Pop
56 fef919b7 Iustin Pop
instance Arbitrary ConfdQuery where
57 fef919b7 Iustin Pop
  arbitrary = oneof [ pure EmptyQuery
58 fef919b7 Iustin Pop
                    , PlainQuery <$> genName
59 fef919b7 Iustin Pop
                    , DictQuery <$> arbitrary
60 fef919b7 Iustin Pop
                    ]
61 fef919b7 Iustin Pop
62 fef919b7 Iustin Pop
$(genArbitrary ''ConfdRequest)
63 fef919b7 Iustin Pop
64 fef919b7 Iustin Pop
$(genArbitrary ''ConfdReplyStatus)
65 fef919b7 Iustin Pop
66 fef919b7 Iustin Pop
instance Arbitrary ConfdReply where
67 fef919b7 Iustin Pop
  arbitrary = ConfdReply <$> arbitrary <*> arbitrary <*>
68 fef919b7 Iustin Pop
                pure J.JSNull <*> arbitrary
69 fef919b7 Iustin Pop
70 fef919b7 Iustin Pop
$(genArbitrary ''ConfdErrorType)
71 fef919b7 Iustin Pop
72 fef919b7 Iustin Pop
$(genArbitrary ''ConfdNodeRole)
73 fef919b7 Iustin Pop
74 fef919b7 Iustin Pop
-- * Test cases
75 fef919b7 Iustin Pop
76 fef919b7 Iustin Pop
-- | Test 'ConfdQuery' serialisation.
77 fef919b7 Iustin Pop
prop_ConfdQuery_serialisation :: ConfdQuery -> Property
78 fef919b7 Iustin Pop
prop_ConfdQuery_serialisation = testSerialisation
79 fef919b7 Iustin Pop
80 fef919b7 Iustin Pop
-- | Test bad types deserialisation for 'ConfdQuery'.
81 fef919b7 Iustin Pop
case_ConfdQuery_BadTypes :: Assertion
82 fef919b7 Iustin Pop
case_ConfdQuery_BadTypes = do
83 fef919b7 Iustin Pop
  let helper jsval = case J.readJSON jsval of
84 fef919b7 Iustin Pop
                       J.Error _ -> return ()
85 fef919b7 Iustin Pop
                       J.Ok cq -> assertFailure $ "Parsed " ++ show jsval
86 fef919b7 Iustin Pop
                                   ++ " as query " ++ show (cq::ConfdQuery)
87 fef919b7 Iustin Pop
  helper $ J.showJSON (1::Int)
88 fef919b7 Iustin Pop
  helper $ J.JSBool True
89 fef919b7 Iustin Pop
  helper $ J.JSBool False
90 fef919b7 Iustin Pop
  helper $ J.JSArray []
91 fef919b7 Iustin Pop
92 fef919b7 Iustin Pop
93 fef919b7 Iustin Pop
-- | Test 'ConfdReplyStatus' serialisation.
94 fef919b7 Iustin Pop
prop_ConfdReplyStatus_serialisation :: ConfdReplyStatus -> Property
95 fef919b7 Iustin Pop
prop_ConfdReplyStatus_serialisation = testSerialisation
96 fef919b7 Iustin Pop
97 fef919b7 Iustin Pop
-- | Test 'ConfdReply' serialisation.
98 fef919b7 Iustin Pop
prop_ConfdReply_serialisation :: ConfdReply -> Property
99 fef919b7 Iustin Pop
prop_ConfdReply_serialisation = testSerialisation
100 fef919b7 Iustin Pop
101 fef919b7 Iustin Pop
-- | Test 'ConfdErrorType' serialisation.
102 fef919b7 Iustin Pop
prop_ConfdErrorType_serialisation :: ConfdErrorType -> Property
103 fef919b7 Iustin Pop
prop_ConfdErrorType_serialisation = testSerialisation
104 fef919b7 Iustin Pop
105 fef919b7 Iustin Pop
-- | Test 'ConfdNodeRole' serialisation.
106 fef919b7 Iustin Pop
prop_ConfdNodeRole_serialisation :: ConfdNodeRole -> Property
107 fef919b7 Iustin Pop
prop_ConfdNodeRole_serialisation = testSerialisation
108 fef919b7 Iustin Pop
109 fef919b7 Iustin Pop
testSuite "Confd/Types"
110 fef919b7 Iustin Pop
  [ 'prop_ConfdQuery_serialisation
111 fef919b7 Iustin Pop
  , 'case_ConfdQuery_BadTypes
112 fef919b7 Iustin Pop
  , 'prop_ConfdReplyStatus_serialisation
113 fef919b7 Iustin Pop
  , 'prop_ConfdReply_serialisation
114 fef919b7 Iustin Pop
  , 'prop_ConfdErrorType_serialisation
115 fef919b7 Iustin Pop
  , 'prop_ConfdNodeRole_serialisation
116 fef919b7 Iustin Pop
  ]