Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / Query / Language.hs @ 139c0683

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
  ) where
33

    
34
import Test.QuickCheck
35

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

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

    
43
import Ganeti.Query.Language
44

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

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

    
77
$(genArbitrary ''QueryTypeOp)
78

    
79
$(genArbitrary ''QueryTypeLuxi)
80

    
81
$(genArbitrary ''ItemType)
82

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

    
86
$(genArbitrary ''ResultStatus)
87

    
88
$(genArbitrary ''FieldType)
89

    
90
$(genArbitrary ''FieldDefinition)
91

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

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

    
117
$(genArbitrary ''QueryFieldsResult)
118

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

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

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

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

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

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

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

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

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