Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Query / Language.hs @ b54ecf12

History | View | Annotate | Download (5.5 kB)

1 aed2325f Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 aed2325f Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 aed2325f Iustin Pop
4 aed2325f Iustin Pop
{-| Unittests for ganeti-htools.
5 aed2325f Iustin Pop
6 aed2325f Iustin Pop
-}
7 aed2325f Iustin Pop
8 aed2325f Iustin Pop
{-
9 aed2325f Iustin Pop
10 aed2325f Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11 aed2325f Iustin Pop
12 aed2325f Iustin Pop
This program is free software; you can redistribute it and/or modify
13 aed2325f Iustin Pop
it under the terms of the GNU General Public License as published by
14 aed2325f Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 aed2325f Iustin Pop
(at your option) any later version.
16 aed2325f Iustin Pop
17 aed2325f Iustin Pop
This program is distributed in the hope that it will be useful, but
18 aed2325f Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 aed2325f Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 aed2325f Iustin Pop
General Public License for more details.
21 aed2325f Iustin Pop
22 aed2325f Iustin Pop
You should have received a copy of the GNU General Public License
23 aed2325f Iustin Pop
along with this program; if not, write to the Free Software
24 aed2325f Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 aed2325f Iustin Pop
02110-1301, USA.
26 aed2325f Iustin Pop
27 aed2325f Iustin Pop
-}
28 aed2325f Iustin Pop
29 aed2325f Iustin Pop
module Test.Ganeti.Query.Language
30 e09c1fa0 Iustin Pop
  ( testQuery_Language
31 aed2325f Iustin Pop
  , genFilter
32 76a0266e Helga Velroyen
  , genJSValue
33 aed2325f Iustin Pop
  ) where
34 aed2325f Iustin Pop
35 aed2325f Iustin Pop
import Test.QuickCheck
36 aed2325f Iustin Pop
37 aed2325f Iustin Pop
import Control.Applicative
38 3ce788db Iustin Pop
import Control.Arrow (second)
39 3ce788db Iustin Pop
import Text.JSON
40 aed2325f Iustin Pop
41 aed2325f Iustin Pop
import Test.Ganeti.TestHelper
42 aed2325f Iustin Pop
import Test.Ganeti.TestCommon
43 aed2325f Iustin Pop
44 3ce788db Iustin Pop
import Ganeti.Query.Language
45 aed2325f Iustin Pop
46 3ce788db Iustin Pop
-- | Custom 'Filter' generator (top-level), which enforces a
47 aed2325f Iustin Pop
-- (sane) limit on the depth of the generated filters.
48 3ce788db Iustin Pop
genFilter :: Gen (Filter FilterField)
49 aed2325f Iustin Pop
genFilter = choose (0, 10) >>= genFilter'
50 aed2325f Iustin Pop
51 aed2325f Iustin Pop
-- | Custom generator for filters that correctly halves the state of
52 aed2325f Iustin Pop
-- the generators at each recursive step, per the QuickCheck
53 aed2325f Iustin Pop
-- documentation, in order not to run out of memory.
54 3ce788db Iustin Pop
genFilter' :: Int -> Gen (Filter FilterField)
55 aed2325f Iustin Pop
genFilter' 0 =
56 3ce788db Iustin Pop
  oneof [ pure EmptyFilter
57 5006418e Iustin Pop
        , TrueFilter     <$> genName
58 5006418e Iustin Pop
        , EQFilter       <$> genName <*> value
59 5006418e Iustin Pop
        , LTFilter       <$> genName <*> value
60 5006418e Iustin Pop
        , GTFilter       <$> genName <*> value
61 5006418e Iustin Pop
        , LEFilter       <$> genName <*> value
62 5006418e Iustin Pop
        , GEFilter       <$> genName <*> value
63 5006418e Iustin Pop
        , RegexpFilter   <$> genName <*> arbitrary
64 5006418e Iustin Pop
        , ContainsFilter <$> genName <*> value
65 aed2325f Iustin Pop
        ]
66 5006418e Iustin Pop
    where value = oneof [ QuotedString <$> genName
67 3ce788db Iustin Pop
                        , NumericValue <$> arbitrary
68 aed2325f Iustin Pop
                        ]
69 5b11f8db Iustin Pop
genFilter' n =
70 3ce788db Iustin Pop
  oneof [ AndFilter  <$> vectorOf n'' (genFilter' n')
71 3ce788db Iustin Pop
        , OrFilter   <$> vectorOf n'' (genFilter' n')
72 3ce788db Iustin Pop
        , NotFilter  <$> genFilter' n'
73 aed2325f Iustin Pop
        ]
74 aed2325f Iustin Pop
  where n' = n `div` 2 -- sub-filter generator size
75 aed2325f Iustin Pop
        n'' = max n' 2 -- but we don't want empty or 1-element lists,
76 aed2325f Iustin Pop
                       -- so use this for and/or filter list length
77 aed2325f Iustin Pop
78 1283cc38 Iustin Pop
$(genArbitrary ''QueryTypeOp)
79 1283cc38 Iustin Pop
80 1283cc38 Iustin Pop
$(genArbitrary ''QueryTypeLuxi)
81 1283cc38 Iustin Pop
82 3ce788db Iustin Pop
$(genArbitrary ''ItemType)
83 aed2325f Iustin Pop
84 3ce788db Iustin Pop
instance Arbitrary FilterRegex where
85 5006418e Iustin Pop
  arbitrary = genName >>= mkRegex -- a name should be a good regex
86 3ce788db Iustin Pop
87 3ce788db Iustin Pop
$(genArbitrary ''ResultStatus)
88 3ce788db Iustin Pop
89 3ce788db Iustin Pop
$(genArbitrary ''FieldType)
90 3ce788db Iustin Pop
91 3ce788db Iustin Pop
$(genArbitrary ''FieldDefinition)
92 3ce788db Iustin Pop
93 3ce788db Iustin Pop
-- | Generates an arbitrary JSValue. We do this via a function a not
94 3ce788db Iustin Pop
-- via arbitrary instance since that would require us to define an
95 3ce788db Iustin Pop
-- arbitrary for JSValue, which can be recursive, entering the usual
96 3ce788db Iustin Pop
-- problems with that; so we only generate the base types, not the
97 3ce788db Iustin Pop
-- recursive ones, and not 'JSNull', which we can't use in a
98 3ce788db Iustin Pop
-- 'RSNormal' 'ResultEntry'.
99 3ce788db Iustin Pop
genJSValue :: Gen JSValue
100 5b11f8db Iustin Pop
genJSValue =
101 3ce788db Iustin Pop
  oneof [ JSBool <$> arbitrary
102 3ce788db Iustin Pop
        , JSRational <$> pure False <*> arbitrary
103 3ce788db Iustin Pop
        , JSString <$> (toJSString <$> arbitrary)
104 3ce788db Iustin Pop
        , (JSArray . map showJSON) <$> (arbitrary::Gen [Int])
105 3ce788db Iustin Pop
        , JSObject . toJSObject . map (second showJSON) <$>
106 3ce788db Iustin Pop
          (arbitrary::Gen [(String, Int)])
107 3ce788db Iustin Pop
        ]
108 3ce788db Iustin Pop
109 3ce788db Iustin Pop
-- | Generates a 'ResultEntry' value.
110 3ce788db Iustin Pop
genResultEntry :: Gen ResultEntry
111 3ce788db Iustin Pop
genResultEntry = do
112 3ce788db Iustin Pop
  rs <- arbitrary
113 3ce788db Iustin Pop
  rv <- case rs of
114 3ce788db Iustin Pop
          RSNormal -> Just <$> genJSValue
115 3ce788db Iustin Pop
          _ -> pure Nothing
116 3ce788db Iustin Pop
  return $ ResultEntry rs rv
117 3ce788db Iustin Pop
118 3ce788db Iustin Pop
$(genArbitrary ''QueryFieldsResult)
119 aed2325f Iustin Pop
120 aed2325f Iustin Pop
-- | Tests that serialisation/deserialisation of filters is
121 aed2325f Iustin Pop
-- idempotent.
122 3ce788db Iustin Pop
prop_filter_serialisation :: Property
123 3ce788db Iustin Pop
prop_filter_serialisation = forAll genFilter testSerialisation
124 aed2325f Iustin Pop
125 3ce788db Iustin Pop
-- | Tests that filter regexes are serialised correctly.
126 3ce788db Iustin Pop
prop_filterregex_instances :: FilterRegex -> Property
127 3ce788db Iustin Pop
prop_filterregex_instances rex =
128 139c0683 Iustin Pop
  printTestCase "failed JSON encoding" (testSerialisation rex)
129 aed2325f Iustin Pop
130 3ce788db Iustin Pop
-- | Tests 'ResultStatus' serialisation.
131 3ce788db Iustin Pop
prop_resultstatus_serialisation :: ResultStatus -> Property
132 3ce788db Iustin Pop
prop_resultstatus_serialisation = testSerialisation
133 3ce788db Iustin Pop
134 3ce788db Iustin Pop
-- | Tests 'FieldType' serialisation.
135 3ce788db Iustin Pop
prop_fieldtype_serialisation :: FieldType -> Property
136 3ce788db Iustin Pop
prop_fieldtype_serialisation = testSerialisation
137 3ce788db Iustin Pop
138 3ce788db Iustin Pop
-- | Tests 'FieldDef' serialisation.
139 3ce788db Iustin Pop
prop_fielddef_serialisation :: FieldDefinition -> Property
140 3ce788db Iustin Pop
prop_fielddef_serialisation = testSerialisation
141 3ce788db Iustin Pop
142 3ce788db Iustin Pop
-- | Tests 'ResultEntry' serialisation. Needed especially as this is
143 3ce788db Iustin Pop
-- done manually, and not via buildObject (different serialisation
144 3ce788db Iustin Pop
-- format).
145 3ce788db Iustin Pop
prop_resultentry_serialisation :: Property
146 3ce788db Iustin Pop
prop_resultentry_serialisation = forAll genResultEntry testSerialisation
147 3ce788db Iustin Pop
148 3ce788db Iustin Pop
-- | Tests 'FieldDef' serialisation. We use a made-up maximum limit of
149 3ce788db Iustin Pop
-- 20 for the generator, since otherwise the lists become too long and
150 3ce788db Iustin Pop
-- we don't care so much about list length but rather structure.
151 3ce788db Iustin Pop
prop_fieldsresult_serialisation :: Property
152 3ce788db Iustin Pop
prop_fieldsresult_serialisation =
153 3ce788db Iustin Pop
  forAll (resize 20 arbitrary::Gen QueryFieldsResult) testSerialisation
154 3ce788db Iustin Pop
155 1283cc38 Iustin Pop
-- | Tests 'ItemType' serialisation.
156 1283cc38 Iustin Pop
prop_itemtype_serialisation :: ItemType -> Property
157 1283cc38 Iustin Pop
prop_itemtype_serialisation = testSerialisation
158 1283cc38 Iustin Pop
159 e09c1fa0 Iustin Pop
testSuite "Query/Language"
160 3ce788db Iustin Pop
  [ 'prop_filter_serialisation
161 3ce788db Iustin Pop
  , 'prop_filterregex_instances
162 3ce788db Iustin Pop
  , 'prop_resultstatus_serialisation
163 3ce788db Iustin Pop
  , 'prop_fieldtype_serialisation
164 3ce788db Iustin Pop
  , 'prop_fielddef_serialisation
165 3ce788db Iustin Pop
  , 'prop_resultentry_serialisation
166 3ce788db Iustin Pop
  , 'prop_fieldsresult_serialisation
167 1283cc38 Iustin Pop
  , 'prop_itemtype_serialisation
168 aed2325f Iustin Pop
  ]