Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Query / Query.hs @ 36162faf

History | View | Annotate | Download (13.4 kB)

1 b9bdc10e Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 b9bdc10e Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 b9bdc10e Iustin Pop
4 b9bdc10e Iustin Pop
{-| Unittests for ganeti-htools.
5 b9bdc10e Iustin Pop
6 b9bdc10e Iustin Pop
-}
7 b9bdc10e Iustin Pop
8 b9bdc10e Iustin Pop
{-
9 b9bdc10e Iustin Pop
10 36162faf Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
11 b9bdc10e Iustin Pop
12 b9bdc10e Iustin Pop
This program is free software; you can redistribute it and/or modify
13 b9bdc10e Iustin Pop
it under the terms of the GNU General Public License as published by
14 b9bdc10e Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 b9bdc10e Iustin Pop
(at your option) any later version.
16 b9bdc10e Iustin Pop
17 b9bdc10e Iustin Pop
This program is distributed in the hope that it will be useful, but
18 b9bdc10e Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 b9bdc10e Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 b9bdc10e Iustin Pop
General Public License for more details.
21 b9bdc10e Iustin Pop
22 b9bdc10e Iustin Pop
You should have received a copy of the GNU General Public License
23 b9bdc10e Iustin Pop
along with this program; if not, write to the Free Software
24 b9bdc10e Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 b9bdc10e Iustin Pop
02110-1301, USA.
26 b9bdc10e Iustin Pop
27 b9bdc10e Iustin Pop
-}
28 b9bdc10e Iustin Pop
29 b9bdc10e Iustin Pop
module Test.Ganeti.Query.Query (testQuery_Query) where
30 b9bdc10e Iustin Pop
31 b9bdc10e Iustin Pop
import Test.HUnit (Assertion, assertEqual)
32 b9bdc10e Iustin Pop
import Test.QuickCheck hiding (Result)
33 b9bdc10e Iustin Pop
import Test.QuickCheck.Monadic
34 b9bdc10e Iustin Pop
35 b9bdc10e Iustin Pop
import Data.Function (on)
36 b9bdc10e Iustin Pop
import Data.List
37 b9bdc10e Iustin Pop
import qualified Data.Map as Map
38 b9bdc10e Iustin Pop
import Data.Maybe
39 b9bdc10e Iustin Pop
import Text.JSON (JSValue(..))
40 b9bdc10e Iustin Pop
41 b9bdc10e Iustin Pop
import Test.Ganeti.TestHelper
42 b9bdc10e Iustin Pop
import Test.Ganeti.TestCommon
43 b9bdc10e Iustin Pop
import Test.Ganeti.Objects (genEmptyCluster)
44 b9bdc10e Iustin Pop
45 b9bdc10e Iustin Pop
import Ganeti.BasicTypes
46 5183e8be Iustin Pop
import Ganeti.Errors
47 a7e484c4 Iustin Pop
import Ganeti.Query.Filter
48 36162faf Iustin Pop
import qualified Ganeti.Query.Group as Group
49 b9bdc10e Iustin Pop
import Ganeti.Query.Language
50 36162faf Iustin Pop
import qualified Ganeti.Query.Node as Node
51 b9bdc10e Iustin Pop
import Ganeti.Query.Query
52 a7e484c4 Iustin Pop
import qualified Ganeti.Query.Job as Job
53 b9bdc10e Iustin Pop
54 5b11f8db Iustin Pop
{-# ANN module "HLint: ignore Use camelCase" #-}
55 5b11f8db Iustin Pop
56 b9bdc10e Iustin Pop
-- * Helpers
57 b9bdc10e Iustin Pop
58 b9bdc10e Iustin Pop
-- | Checks if a list of field definitions contains unknown fields.
59 b9bdc10e Iustin Pop
hasUnknownFields :: [FieldDefinition] -> Bool
60 b9bdc10e Iustin Pop
hasUnknownFields = (QFTUnknown `notElem`) . map fdefKind
61 b9bdc10e Iustin Pop
62 b9bdc10e Iustin Pop
-- * Test cases
63 b9bdc10e Iustin Pop
64 a7e484c4 Iustin Pop
-- ** Node queries
65 a7e484c4 Iustin Pop
66 b9bdc10e Iustin Pop
-- | Tests that querying any existing fields, via either query or
67 b9bdc10e Iustin Pop
-- queryFields, will not return unknown fields.
68 b9bdc10e Iustin Pop
prop_queryNode_noUnknown :: Property
69 b9bdc10e Iustin Pop
prop_queryNode_noUnknown =
70 b9bdc10e Iustin Pop
  forAll (choose (0, maxNodes) >>= genEmptyCluster) $ \cluster ->
71 36162faf Iustin Pop
  forAll (elements (Map.keys Node.fieldsMap)) $ \field -> monadicIO $ do
72 b9bdc10e Iustin Pop
  QueryResult fdefs fdata <-
73 1283cc38 Iustin Pop
    run (query cluster False (Query (ItemTypeOpCode QRNode)
74 1283cc38 Iustin Pop
                              [field] EmptyFilter)) >>= resultProp
75 b9bdc10e Iustin Pop
  QueryFieldsResult fdefs' <-
76 1283cc38 Iustin Pop
    resultProp $ queryFields (QueryFields (ItemTypeOpCode QRNode) [field])
77 942a9a6a Iustin Pop
  stop $ conjoin
78 942a9a6a Iustin Pop
         [ printTestCase ("Got unknown fields via query (" ++
79 942a9a6a Iustin Pop
                          show fdefs ++ ")") (hasUnknownFields fdefs)
80 942a9a6a Iustin Pop
         , printTestCase ("Got unknown result status via query (" ++
81 942a9a6a Iustin Pop
                          show fdata ++ ")")
82 942a9a6a Iustin Pop
           (all (all ((/= RSUnknown) . rentryStatus)) fdata)
83 942a9a6a Iustin Pop
         , printTestCase ("Got unknown fields via query fields (" ++
84 942a9a6a Iustin Pop
                          show fdefs'++ ")") (hasUnknownFields fdefs')
85 942a9a6a Iustin Pop
         ]
86 b9bdc10e Iustin Pop
87 b9bdc10e Iustin Pop
-- | Tests that an unknown field is returned as such.
88 b9bdc10e Iustin Pop
prop_queryNode_Unknown :: Property
89 b9bdc10e Iustin Pop
prop_queryNode_Unknown =
90 b9bdc10e Iustin Pop
  forAll (choose (0, maxNodes) >>= genEmptyCluster) $ \cluster ->
91 36162faf Iustin Pop
  forAll (arbitrary `suchThat` (`notElem` Map.keys Node.fieldsMap))
92 b9bdc10e Iustin Pop
    $ \field -> monadicIO $ do
93 b9bdc10e Iustin Pop
  QueryResult fdefs fdata <-
94 1283cc38 Iustin Pop
    run (query cluster False (Query (ItemTypeOpCode QRNode)
95 1283cc38 Iustin Pop
                              [field] EmptyFilter)) >>= resultProp
96 b9bdc10e Iustin Pop
  QueryFieldsResult fdefs' <-
97 1283cc38 Iustin Pop
    resultProp $ queryFields (QueryFields (ItemTypeOpCode QRNode) [field])
98 942a9a6a Iustin Pop
  stop $ conjoin
99 942a9a6a Iustin Pop
         [ printTestCase ("Got known fields via query (" ++ show fdefs ++ ")")
100 942a9a6a Iustin Pop
           (not $ hasUnknownFields fdefs)
101 942a9a6a Iustin Pop
         , printTestCase ("Got /= ResultUnknown result status via query (" ++
102 942a9a6a Iustin Pop
                          show fdata ++ ")")
103 942a9a6a Iustin Pop
           (all (all ((== RSUnknown) . rentryStatus)) fdata)
104 942a9a6a Iustin Pop
         , printTestCase ("Got a Just in a result value (" ++
105 942a9a6a Iustin Pop
                          show fdata ++ ")")
106 942a9a6a Iustin Pop
           (all (all (isNothing . rentryValue)) fdata)
107 942a9a6a Iustin Pop
         , printTestCase ("Got known fields via query fields (" ++ show fdefs'
108 942a9a6a Iustin Pop
                          ++ ")") (not $ hasUnknownFields fdefs')
109 942a9a6a Iustin Pop
         ]
110 b9bdc10e Iustin Pop
111 b9bdc10e Iustin Pop
-- | Checks that a result type is conforming to a field definition.
112 b9bdc10e Iustin Pop
checkResultType :: FieldDefinition -> ResultEntry -> Property
113 b9bdc10e Iustin Pop
checkResultType _ (ResultEntry RSNormal Nothing) =
114 b9bdc10e Iustin Pop
  failTest "Nothing result in RSNormal field"
115 b9bdc10e Iustin Pop
checkResultType _ (ResultEntry _ Nothing) = passTest
116 b9bdc10e Iustin Pop
checkResultType fdef (ResultEntry RSNormal (Just v)) =
117 b9bdc10e Iustin Pop
  case (fdefKind fdef, v) of
118 b9bdc10e Iustin Pop
    (QFTText      , JSString {})   -> passTest
119 b9bdc10e Iustin Pop
    (QFTBool      , JSBool {})     -> passTest
120 b9bdc10e Iustin Pop
    (QFTNumber    , JSRational {}) -> passTest
121 b9bdc10e Iustin Pop
    (QFTTimestamp , JSRational {}) -> passTest
122 b9bdc10e Iustin Pop
    (QFTUnit      , JSRational {}) -> passTest
123 b9bdc10e Iustin Pop
    (QFTOther     , _)             -> passTest -- meh, QFT not precise...
124 b9bdc10e Iustin Pop
    (kind, _) -> failTest $ "Type mismatch, field definition says " ++
125 b9bdc10e Iustin Pop
                  show kind ++ " but returned value is " ++ show v ++
126 b9bdc10e Iustin Pop
                  " for field '" ++ fdefName fdef ++ "'"
127 b9bdc10e Iustin Pop
checkResultType _ (ResultEntry r (Just _)) =
128 b9bdc10e Iustin Pop
  failTest $ "Just result in " ++ show r ++ " field"
129 b9bdc10e Iustin Pop
130 b9bdc10e Iustin Pop
-- | Tests that querying any existing fields, the following three
131 b9bdc10e Iustin Pop
-- properties hold: RSNormal corresponds to a Just value, any other
132 b9bdc10e Iustin Pop
-- value corresponds to Nothing, and for a RSNormal and value field,
133 b9bdc10e Iustin Pop
-- the type of the value corresponds to the type of the field as
134 b9bdc10e Iustin Pop
-- declared in the FieldDefinition.
135 b9bdc10e Iustin Pop
prop_queryNode_types :: Property
136 b9bdc10e Iustin Pop
prop_queryNode_types =
137 b9bdc10e Iustin Pop
  forAll (choose (0, maxNodes)) $ \numnodes ->
138 b9bdc10e Iustin Pop
  forAll (genEmptyCluster numnodes) $ \cfg ->
139 36162faf Iustin Pop
  forAll (elements (Map.keys Node.fieldsMap)) $ \field -> monadicIO $ do
140 b9bdc10e Iustin Pop
  QueryResult fdefs fdata <-
141 1283cc38 Iustin Pop
    run (query cfg False (Query (ItemTypeOpCode QRNode)
142 1283cc38 Iustin Pop
                          [field] EmptyFilter)) >>= resultProp
143 942a9a6a Iustin Pop
  stop $ conjoin
144 942a9a6a Iustin Pop
         [ printTestCase ("Inconsistent result entries (" ++ show fdata ++ ")")
145 942a9a6a Iustin Pop
           (conjoin $ map (conjoin . zipWith checkResultType fdefs) fdata)
146 942a9a6a Iustin Pop
         , printTestCase "Wrong field definitions length"
147 942a9a6a Iustin Pop
           (length fdefs ==? 1)
148 942a9a6a Iustin Pop
         , printTestCase "Wrong field result rows length"
149 942a9a6a Iustin Pop
           (all ((== 1) . length) fdata)
150 942a9a6a Iustin Pop
         , printTestCase "Wrong number of result rows"
151 b9bdc10e Iustin Pop
           (length fdata ==? numnodes)
152 942a9a6a Iustin Pop
         ]
153 b9bdc10e Iustin Pop
154 b9bdc10e Iustin Pop
-- | Test that queryFields with empty fields list returns all node fields.
155 b9bdc10e Iustin Pop
case_queryNode_allfields :: Assertion
156 b9bdc10e Iustin Pop
case_queryNode_allfields = do
157 1283cc38 Iustin Pop
   fdefs <- case queryFields (QueryFields (ItemTypeOpCode QRNode) []) of
158 5183e8be Iustin Pop
              Bad msg -> fail $ "Error in query all fields: " ++
159 5183e8be Iustin Pop
                         formatError msg
160 b9bdc10e Iustin Pop
              Ok (QueryFieldsResult v) -> return v
161 b9bdc10e Iustin Pop
   let field_sort = compare `on` fdefName
162 b9bdc10e Iustin Pop
   assertEqual "Mismatch in all fields list"
163 36162faf Iustin Pop
     (sortBy field_sort . map (\(f, _, _) -> f) $ Map.elems Node.fieldsMap)
164 b9bdc10e Iustin Pop
     (sortBy field_sort fdefs)
165 b9bdc10e Iustin Pop
166 a7e484c4 Iustin Pop
-- ** Group queries
167 a9d6f4e0 Agata Murawska
168 a9d6f4e0 Agata Murawska
prop_queryGroup_noUnknown :: Property
169 a9d6f4e0 Agata Murawska
prop_queryGroup_noUnknown =
170 a9d6f4e0 Agata Murawska
  forAll (choose (0, maxNodes) >>= genEmptyCluster) $ \cluster ->
171 36162faf Iustin Pop
   forAll (elements (Map.keys Group.fieldsMap)) $ \field -> monadicIO $ do
172 a9d6f4e0 Agata Murawska
   QueryResult fdefs fdata <-
173 1283cc38 Iustin Pop
     run (query cluster False (Query (ItemTypeOpCode QRGroup)
174 1283cc38 Iustin Pop
                               [field] EmptyFilter)) >>=
175 942a9a6a Iustin Pop
         resultProp
176 a9d6f4e0 Agata Murawska
   QueryFieldsResult fdefs' <-
177 1283cc38 Iustin Pop
     resultProp $ queryFields (QueryFields (ItemTypeOpCode QRGroup) [field])
178 942a9a6a Iustin Pop
   stop $ conjoin
179 942a9a6a Iustin Pop
    [ printTestCase ("Got unknown fields via query (" ++ show fdefs ++ ")")
180 942a9a6a Iustin Pop
         (hasUnknownFields fdefs)
181 942a9a6a Iustin Pop
    , printTestCase ("Got unknown result status via query (" ++
182 942a9a6a Iustin Pop
                     show fdata ++ ")")
183 942a9a6a Iustin Pop
      (all (all ((/= RSUnknown) . rentryStatus)) fdata)
184 942a9a6a Iustin Pop
    , printTestCase ("Got unknown fields via query fields (" ++ show fdefs'
185 942a9a6a Iustin Pop
                     ++ ")") (hasUnknownFields fdefs')
186 942a9a6a Iustin Pop
    ]
187 a9d6f4e0 Agata Murawska
188 a9d6f4e0 Agata Murawska
prop_queryGroup_Unknown :: Property
189 a9d6f4e0 Agata Murawska
prop_queryGroup_Unknown =
190 a9d6f4e0 Agata Murawska
  forAll (choose (0, maxNodes) >>= genEmptyCluster) $ \cluster ->
191 36162faf Iustin Pop
  forAll (arbitrary `suchThat` (`notElem` Map.keys Group.fieldsMap))
192 a9d6f4e0 Agata Murawska
    $ \field -> monadicIO $ do
193 a9d6f4e0 Agata Murawska
  QueryResult fdefs fdata <-
194 1283cc38 Iustin Pop
    run (query cluster False (Query (ItemTypeOpCode QRGroup)
195 1283cc38 Iustin Pop
                              [field] EmptyFilter)) >>= resultProp
196 a9d6f4e0 Agata Murawska
  QueryFieldsResult fdefs' <-
197 1283cc38 Iustin Pop
    resultProp $ queryFields (QueryFields (ItemTypeOpCode QRGroup) [field])
198 942a9a6a Iustin Pop
  stop $ conjoin
199 942a9a6a Iustin Pop
         [ printTestCase ("Got known fields via query (" ++ show fdefs ++ ")")
200 942a9a6a Iustin Pop
           (not $ hasUnknownFields fdefs)
201 942a9a6a Iustin Pop
         , printTestCase ("Got /= ResultUnknown result status via query (" ++
202 942a9a6a Iustin Pop
                          show fdata ++ ")")
203 942a9a6a Iustin Pop
           (all (all ((== RSUnknown) . rentryStatus)) fdata)
204 942a9a6a Iustin Pop
         , printTestCase ("Got a Just in a result value (" ++
205 942a9a6a Iustin Pop
                          show fdata ++ ")")
206 942a9a6a Iustin Pop
           (all (all (isNothing . rentryValue)) fdata)
207 942a9a6a Iustin Pop
         , printTestCase ("Got known fields via query fields (" ++ show fdefs'
208 942a9a6a Iustin Pop
                          ++ ")") (not $ hasUnknownFields fdefs')
209 942a9a6a Iustin Pop
         ]
210 a9d6f4e0 Agata Murawska
211 a9d6f4e0 Agata Murawska
prop_queryGroup_types :: Property
212 a9d6f4e0 Agata Murawska
prop_queryGroup_types =
213 a9d6f4e0 Agata Murawska
  forAll (choose (0, maxNodes)) $ \numnodes ->
214 a9d6f4e0 Agata Murawska
  forAll (genEmptyCluster numnodes) $ \cfg ->
215 36162faf Iustin Pop
  forAll (elements (Map.keys Group.fieldsMap)) $ \field -> monadicIO $ do
216 a9d6f4e0 Agata Murawska
  QueryResult fdefs fdata <-
217 1283cc38 Iustin Pop
    run (query cfg False (Query (ItemTypeOpCode QRGroup)
218 1283cc38 Iustin Pop
                          [field] EmptyFilter)) >>= resultProp
219 942a9a6a Iustin Pop
  stop $ conjoin
220 942a9a6a Iustin Pop
         [ printTestCase ("Inconsistent result entries (" ++ show fdata ++ ")")
221 942a9a6a Iustin Pop
           (conjoin $ map (conjoin . zipWith checkResultType fdefs) fdata)
222 942a9a6a Iustin Pop
         , printTestCase "Wrong field definitions length" (length fdefs ==? 1)
223 942a9a6a Iustin Pop
         , printTestCase "Wrong field result rows length"
224 a9d6f4e0 Agata Murawska
           (all ((== 1) . length) fdata)
225 942a9a6a Iustin Pop
         ]
226 a9d6f4e0 Agata Murawska
227 a9d6f4e0 Agata Murawska
case_queryGroup_allfields :: Assertion
228 a9d6f4e0 Agata Murawska
case_queryGroup_allfields = do
229 1283cc38 Iustin Pop
   fdefs <- case queryFields (QueryFields (ItemTypeOpCode QRGroup) []) of
230 5183e8be Iustin Pop
              Bad msg -> fail $ "Error in query all fields: " ++
231 5183e8be Iustin Pop
                         formatError msg
232 a9d6f4e0 Agata Murawska
              Ok (QueryFieldsResult v) -> return v
233 a9d6f4e0 Agata Murawska
   let field_sort = compare `on` fdefName
234 a9d6f4e0 Agata Murawska
   assertEqual "Mismatch in all fields list"
235 36162faf Iustin Pop
     (sortBy field_sort . map (\(f, _, _) -> f) $ Map.elems Group.fieldsMap)
236 a9d6f4e0 Agata Murawska
     (sortBy field_sort fdefs)
237 a9d6f4e0 Agata Murawska
238 a7e484c4 Iustin Pop
-- ** Job queries
239 a7e484c4 Iustin Pop
240 a7e484c4 Iustin Pop
-- | Tests that querying any existing fields, via either query or
241 a7e484c4 Iustin Pop
-- queryFields, will not return unknown fields. This uses 'undefined'
242 a7e484c4 Iustin Pop
-- for config, as job queries shouldn't use the configuration, and an
243 a7e484c4 Iustin Pop
-- explicit filter as otherwise non-live queries wouldn't return any
244 a7e484c4 Iustin Pop
-- result rows.
245 a7e484c4 Iustin Pop
prop_queryJob_noUnknown :: Property
246 a7e484c4 Iustin Pop
prop_queryJob_noUnknown =
247 a7e484c4 Iustin Pop
  forAll (listOf (arbitrary::Gen (Positive Integer))) $ \ids ->
248 a7e484c4 Iustin Pop
  forAll (elements (Map.keys Job.fieldsMap)) $ \field -> monadicIO $ do
249 a7e484c4 Iustin Pop
  let qtype = ItemTypeLuxi QRJob
250 a7e484c4 Iustin Pop
      flt = makeSimpleFilter (nameField qtype) $
251 a7e484c4 Iustin Pop
            map (\(Positive i) -> Right i) ids
252 a7e484c4 Iustin Pop
  QueryResult fdefs fdata <-
253 a7e484c4 Iustin Pop
    run (query undefined False (Query qtype [field] flt)) >>= resultProp
254 a7e484c4 Iustin Pop
  QueryFieldsResult fdefs' <-
255 a7e484c4 Iustin Pop
    resultProp $ queryFields (QueryFields qtype [field])
256 a7e484c4 Iustin Pop
  stop $ conjoin
257 a7e484c4 Iustin Pop
         [ printTestCase ("Got unknown fields via query (" ++
258 a7e484c4 Iustin Pop
                          show fdefs ++ ")") (hasUnknownFields fdefs)
259 a7e484c4 Iustin Pop
         , printTestCase ("Got unknown result status via query (" ++
260 a7e484c4 Iustin Pop
                          show fdata ++ ")")
261 a7e484c4 Iustin Pop
           (all (all ((/= RSUnknown) . rentryStatus)) fdata)
262 a7e484c4 Iustin Pop
         , printTestCase ("Got unknown fields via query fields (" ++
263 a7e484c4 Iustin Pop
                          show fdefs'++ ")") (hasUnknownFields fdefs')
264 a7e484c4 Iustin Pop
         ]
265 a7e484c4 Iustin Pop
266 a7e484c4 Iustin Pop
-- | Tests that an unknown field is returned as such.
267 a7e484c4 Iustin Pop
prop_queryJob_Unknown :: Property
268 a7e484c4 Iustin Pop
prop_queryJob_Unknown =
269 a7e484c4 Iustin Pop
  forAll (listOf (arbitrary::Gen (Positive Integer))) $ \ids ->
270 a7e484c4 Iustin Pop
  forAll (arbitrary `suchThat` (`notElem` Map.keys Job.fieldsMap))
271 a7e484c4 Iustin Pop
    $ \field -> monadicIO $ do
272 a7e484c4 Iustin Pop
  let qtype = ItemTypeLuxi QRJob
273 a7e484c4 Iustin Pop
      flt = makeSimpleFilter (nameField qtype) $
274 a7e484c4 Iustin Pop
            map (\(Positive i) -> Right i) ids
275 a7e484c4 Iustin Pop
  QueryResult fdefs fdata <-
276 a7e484c4 Iustin Pop
    run (query undefined False (Query qtype [field] flt)) >>= resultProp
277 a7e484c4 Iustin Pop
  QueryFieldsResult fdefs' <-
278 a7e484c4 Iustin Pop
    resultProp $ queryFields (QueryFields qtype [field])
279 a7e484c4 Iustin Pop
  stop $ conjoin
280 a7e484c4 Iustin Pop
         [ printTestCase ("Got known fields via query (" ++ show fdefs ++ ")")
281 a7e484c4 Iustin Pop
           (not $ hasUnknownFields fdefs)
282 a7e484c4 Iustin Pop
         , printTestCase ("Got /= ResultUnknown result status via query (" ++
283 a7e484c4 Iustin Pop
                          show fdata ++ ")")
284 a7e484c4 Iustin Pop
           (all (all ((== RSUnknown) . rentryStatus)) fdata)
285 a7e484c4 Iustin Pop
         , printTestCase ("Got a Just in a result value (" ++
286 a7e484c4 Iustin Pop
                          show fdata ++ ")")
287 a7e484c4 Iustin Pop
           (all (all (isNothing . rentryValue)) fdata)
288 a7e484c4 Iustin Pop
         , printTestCase ("Got known fields via query fields (" ++ show fdefs'
289 a7e484c4 Iustin Pop
                          ++ ")") (not $ hasUnknownFields fdefs')
290 a7e484c4 Iustin Pop
         ]
291 a7e484c4 Iustin Pop
292 a7e484c4 Iustin Pop
-- ** Misc other tests
293 bc4cdeef Iustin Pop
294 bc4cdeef Iustin Pop
-- | Tests that requested names checking behaves as expected.
295 bc4cdeef Iustin Pop
prop_getRequestedNames :: Property
296 bc4cdeef Iustin Pop
prop_getRequestedNames =
297 5006418e Iustin Pop
  forAll genName $ \node1 ->
298 1283cc38 Iustin Pop
  let chk = getRequestedNames . Query (ItemTypeOpCode QRNode) []
299 bc4cdeef Iustin Pop
      q_node1 = QuotedString node1
300 bc4cdeef Iustin Pop
      eq_name = EQFilter "name"
301 bc4cdeef Iustin Pop
      eq_node1 = eq_name q_node1
302 bc4cdeef Iustin Pop
  in conjoin [ printTestCase "empty filter" $ chk EmptyFilter ==? []
303 bc4cdeef Iustin Pop
             , printTestCase "and filter" $ chk (AndFilter [eq_node1]) ==? []
304 bc4cdeef Iustin Pop
             , printTestCase "simple equality" $ chk eq_node1 ==? [node1]
305 bc4cdeef Iustin Pop
             , printTestCase "non-name field" $
306 bc4cdeef Iustin Pop
               chk (EQFilter "foo" q_node1) ==? []
307 bc4cdeef Iustin Pop
             , printTestCase "non-simple filter" $
308 bc4cdeef Iustin Pop
               chk (OrFilter [ eq_node1 , LTFilter "foo" q_node1]) ==? []
309 bc4cdeef Iustin Pop
             ]
310 bc4cdeef Iustin Pop
311 b9bdc10e Iustin Pop
testSuite "Query/Query"
312 b9bdc10e Iustin Pop
  [ 'prop_queryNode_noUnknown
313 b9bdc10e Iustin Pop
  , 'prop_queryNode_Unknown
314 b9bdc10e Iustin Pop
  , 'prop_queryNode_types
315 b9bdc10e Iustin Pop
  , 'case_queryNode_allfields
316 a9d6f4e0 Agata Murawska
  , 'prop_queryGroup_noUnknown
317 a9d6f4e0 Agata Murawska
  , 'prop_queryGroup_Unknown
318 a9d6f4e0 Agata Murawska
  , 'prop_queryGroup_types
319 a9d6f4e0 Agata Murawska
  , 'case_queryGroup_allfields
320 a7e484c4 Iustin Pop
  , 'prop_queryJob_noUnknown
321 a7e484c4 Iustin Pop
  , 'prop_queryJob_Unknown
322 bc4cdeef Iustin Pop
  , 'prop_getRequestedNames
323 b9bdc10e Iustin Pop
  ]