Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / Query / Language.hs @ 76a0266e

History | View | Annotate | Download (5.5 kB)

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.Query.Language
30
  ( testQuery_Language
31
  , genFilter
32
  , genJSValue
33
  ) where
34

    
35
import Test.QuickCheck
36

    
37
import Control.Applicative
38
import Control.Arrow (second)
39
import Text.JSON
40

    
41
import Test.Ganeti.TestHelper
42
import Test.Ganeti.TestCommon
43

    
44
import Ganeti.Query.Language
45

    
46
-- | Custom 'Filter' generator (top-level), which enforces a
47
-- (sane) limit on the depth of the generated filters.
48
genFilter :: Gen (Filter FilterField)
49
genFilter = choose (0, 10) >>= genFilter'
50

    
51
-- | Custom generator for filters that correctly halves the state of
52
-- the generators at each recursive step, per the QuickCheck
53
-- documentation, in order not to run out of memory.
54
genFilter' :: Int -> Gen (Filter FilterField)
55
genFilter' 0 =
56
  oneof [ pure EmptyFilter
57
        , TrueFilter     <$> genName
58
        , EQFilter       <$> genName <*> value
59
        , LTFilter       <$> genName <*> value
60
        , GTFilter       <$> genName <*> value
61
        , LEFilter       <$> genName <*> value
62
        , GEFilter       <$> genName <*> value
63
        , RegexpFilter   <$> genName <*> arbitrary
64
        , ContainsFilter <$> genName <*> value
65
        ]
66
    where value = oneof [ QuotedString <$> genName
67
                        , NumericValue <$> arbitrary
68
                        ]
69
genFilter' n =
70
  oneof [ AndFilter  <$> vectorOf n'' (genFilter' n')
71
        , OrFilter   <$> vectorOf n'' (genFilter' n')
72
        , NotFilter  <$> genFilter' n'
73
        ]
74
  where n' = n `div` 2 -- sub-filter generator size
75
        n'' = max n' 2 -- but we don't want empty or 1-element lists,
76
                       -- so use this for and/or filter list length
77

    
78
$(genArbitrary ''QueryTypeOp)
79

    
80
$(genArbitrary ''QueryTypeLuxi)
81

    
82
$(genArbitrary ''ItemType)
83

    
84
instance Arbitrary FilterRegex where
85
  arbitrary = genName >>= mkRegex -- a name should be a good regex
86

    
87
$(genArbitrary ''ResultStatus)
88

    
89
$(genArbitrary ''FieldType)
90

    
91
$(genArbitrary ''FieldDefinition)
92

    
93
-- | Generates an arbitrary JSValue. We do this via a function a not
94
-- via arbitrary instance since that would require us to define an
95
-- arbitrary for JSValue, which can be recursive, entering the usual
96
-- problems with that; so we only generate the base types, not the
97
-- recursive ones, and not 'JSNull', which we can't use in a
98
-- 'RSNormal' 'ResultEntry'.
99
genJSValue :: Gen JSValue
100
genJSValue =
101
  oneof [ JSBool <$> arbitrary
102
        , JSRational <$> pure False <*> arbitrary
103
        , JSString <$> (toJSString <$> arbitrary)
104
        , (JSArray . map showJSON) <$> (arbitrary::Gen [Int])
105
        , JSObject . toJSObject . map (second showJSON) <$>
106
          (arbitrary::Gen [(String, Int)])
107
        ]
108

    
109
-- | Generates a 'ResultEntry' value.
110
genResultEntry :: Gen ResultEntry
111
genResultEntry = do
112
  rs <- arbitrary
113
  rv <- case rs of
114
          RSNormal -> Just <$> genJSValue
115
          _ -> pure Nothing
116
  return $ ResultEntry rs rv
117

    
118
$(genArbitrary ''QueryFieldsResult)
119

    
120
-- | Tests that serialisation/deserialisation of filters is
121
-- idempotent.
122
prop_filter_serialisation :: Property
123
prop_filter_serialisation = forAll genFilter testSerialisation
124

    
125
-- | Tests that filter regexes are serialised correctly.
126
prop_filterregex_instances :: FilterRegex -> Property
127
prop_filterregex_instances rex =
128
  printTestCase "failed JSON encoding" (testSerialisation rex)
129

    
130
-- | Tests 'ResultStatus' serialisation.
131
prop_resultstatus_serialisation :: ResultStatus -> Property
132
prop_resultstatus_serialisation = testSerialisation
133

    
134
-- | Tests 'FieldType' serialisation.
135
prop_fieldtype_serialisation :: FieldType -> Property
136
prop_fieldtype_serialisation = testSerialisation
137

    
138
-- | Tests 'FieldDef' serialisation.
139
prop_fielddef_serialisation :: FieldDefinition -> Property
140
prop_fielddef_serialisation = testSerialisation
141

    
142
-- | Tests 'ResultEntry' serialisation. Needed especially as this is
143
-- done manually, and not via buildObject (different serialisation
144
-- format).
145
prop_resultentry_serialisation :: Property
146
prop_resultentry_serialisation = forAll genResultEntry testSerialisation
147

    
148
-- | Tests 'FieldDef' serialisation. We use a made-up maximum limit of
149
-- 20 for the generator, since otherwise the lists become too long and
150
-- we don't care so much about list length but rather structure.
151
prop_fieldsresult_serialisation :: Property
152
prop_fieldsresult_serialisation =
153
  forAll (resize 20 arbitrary::Gen QueryFieldsResult) testSerialisation
154

    
155
-- | Tests 'ItemType' serialisation.
156
prop_itemtype_serialisation :: ItemType -> Property
157
prop_itemtype_serialisation = testSerialisation
158

    
159
testSuite "Query/Language"
160
  [ 'prop_filter_serialisation
161
  , 'prop_filterregex_instances
162
  , 'prop_resultstatus_serialisation
163
  , 'prop_fieldtype_serialisation
164
  , 'prop_fielddef_serialisation
165
  , 'prop_resultentry_serialisation
166
  , 'prop_fieldsresult_serialisation
167
  , 'prop_itemtype_serialisation
168
  ]