Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / Query / Query.hs @ 5183e8be

History | View | Annotate | Download (10.3 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.Query (testQuery_Query) where
30

    
31
import Test.HUnit (Assertion, assertEqual)
32
import Test.QuickCheck hiding (Result)
33
import Test.QuickCheck.Monadic
34

    
35
import Data.Function (on)
36
import Data.List
37
import qualified Data.Map as Map
38
import Data.Maybe
39
import Text.JSON (JSValue(..))
40

    
41
import Test.Ganeti.TestHelper
42
import Test.Ganeti.TestCommon
43
import Test.Ganeti.Objects (genEmptyCluster)
44

    
45
import Ganeti.BasicTypes
46
import Ganeti.Errors
47
import Ganeti.Query.Group
48
import Ganeti.Query.Language
49
import Ganeti.Query.Node
50
import Ganeti.Query.Query
51

    
52
{-# ANN module "HLint: ignore Use camelCase" #-}
53

    
54
-- * Helpers
55

    
56
-- | Checks if a list of field definitions contains unknown fields.
57
hasUnknownFields :: [FieldDefinition] -> Bool
58
hasUnknownFields = (QFTUnknown `notElem`) . map fdefKind
59

    
60
-- * Test cases
61

    
62
-- | Tests that querying any existing fields, via either query or
63
-- queryFields, will not return unknown fields.
64
prop_queryNode_noUnknown :: Property
65
prop_queryNode_noUnknown =
66
  forAll (choose (0, maxNodes) >>= genEmptyCluster) $ \cluster ->
67
  forAll (elements (Map.keys nodeFieldsMap)) $ \field -> monadicIO $ do
68
  QueryResult fdefs fdata <-
69
    run (query cluster False (Query QRNode [field] EmptyFilter)) >>= resultProp
70
  QueryFieldsResult fdefs' <-
71
    resultProp $ queryFields (QueryFields QRNode [field])
72
  stop $ conjoin
73
         [ printTestCase ("Got unknown fields via query (" ++
74
                          show fdefs ++ ")") (hasUnknownFields fdefs)
75
         , printTestCase ("Got unknown result status via query (" ++
76
                          show fdata ++ ")")
77
           (all (all ((/= RSUnknown) . rentryStatus)) fdata)
78
         , printTestCase ("Got unknown fields via query fields (" ++
79
                          show fdefs'++ ")") (hasUnknownFields fdefs')
80
         ]
81

    
82
-- | Tests that an unknown field is returned as such.
83
prop_queryNode_Unknown :: Property
84
prop_queryNode_Unknown =
85
  forAll (choose (0, maxNodes) >>= genEmptyCluster) $ \cluster ->
86
  forAll (arbitrary `suchThat` (`notElem` Map.keys nodeFieldsMap))
87
    $ \field -> monadicIO $ do
88
  QueryResult fdefs fdata <-
89
    run (query cluster False (Query QRNode [field] EmptyFilter)) >>= resultProp
90
  QueryFieldsResult fdefs' <-
91
    resultProp $ queryFields (QueryFields QRNode [field])
92
  stop $ conjoin
93
         [ printTestCase ("Got known fields via query (" ++ show fdefs ++ ")")
94
           (not $ hasUnknownFields fdefs)
95
         , printTestCase ("Got /= ResultUnknown result status via query (" ++
96
                          show fdata ++ ")")
97
           (all (all ((== RSUnknown) . rentryStatus)) fdata)
98
         , printTestCase ("Got a Just in a result value (" ++
99
                          show fdata ++ ")")
100
           (all (all (isNothing . rentryValue)) fdata)
101
         , printTestCase ("Got known fields via query fields (" ++ show fdefs'
102
                          ++ ")") (not $ hasUnknownFields fdefs')
103
         ]
104

    
105
-- | Checks that a result type is conforming to a field definition.
106
checkResultType :: FieldDefinition -> ResultEntry -> Property
107
checkResultType _ (ResultEntry RSNormal Nothing) =
108
  failTest "Nothing result in RSNormal field"
109
checkResultType _ (ResultEntry _ Nothing) = passTest
110
checkResultType fdef (ResultEntry RSNormal (Just v)) =
111
  case (fdefKind fdef, v) of
112
    (QFTText      , JSString {})   -> passTest
113
    (QFTBool      , JSBool {})     -> passTest
114
    (QFTNumber    , JSRational {}) -> passTest
115
    (QFTTimestamp , JSRational {}) -> passTest
116
    (QFTUnit      , JSRational {}) -> passTest
117
    (QFTOther     , _)             -> passTest -- meh, QFT not precise...
118
    (kind, _) -> failTest $ "Type mismatch, field definition says " ++
119
                  show kind ++ " but returned value is " ++ show v ++
120
                  " for field '" ++ fdefName fdef ++ "'"
121
checkResultType _ (ResultEntry r (Just _)) =
122
  failTest $ "Just result in " ++ show r ++ " field"
123

    
124
-- | Tests that querying any existing fields, the following three
125
-- properties hold: RSNormal corresponds to a Just value, any other
126
-- value corresponds to Nothing, and for a RSNormal and value field,
127
-- the type of the value corresponds to the type of the field as
128
-- declared in the FieldDefinition.
129
prop_queryNode_types :: Property
130
prop_queryNode_types =
131
  forAll (choose (0, maxNodes)) $ \numnodes ->
132
  forAll (genEmptyCluster numnodes) $ \cfg ->
133
  forAll (elements (Map.keys nodeFieldsMap)) $ \field -> monadicIO $ do
134
  QueryResult fdefs fdata <-
135
    run (query cfg False (Query QRNode [field] EmptyFilter)) >>= resultProp
136
  stop $ conjoin
137
         [ printTestCase ("Inconsistent result entries (" ++ show fdata ++ ")")
138
           (conjoin $ map (conjoin . zipWith checkResultType fdefs) fdata)
139
         , printTestCase "Wrong field definitions length"
140
           (length fdefs ==? 1)
141
         , printTestCase "Wrong field result rows length"
142
           (all ((== 1) . length) fdata)
143
         , printTestCase "Wrong number of result rows"
144
           (length fdata ==? numnodes)
145
         ]
146

    
147
-- | Test that queryFields with empty fields list returns all node fields.
148
case_queryNode_allfields :: Assertion
149
case_queryNode_allfields = do
150
   fdefs <- case queryFields (QueryFields QRNode []) of
151
              Bad msg -> fail $ "Error in query all fields: " ++
152
                         formatError msg
153
              Ok (QueryFieldsResult v) -> return v
154
   let field_sort = compare `on` fdefName
155
   assertEqual "Mismatch in all fields list"
156
     (sortBy field_sort . map fst $ Map.elems nodeFieldsMap)
157
     (sortBy field_sort fdefs)
158

    
159
-- * Same as above, but for group
160

    
161
prop_queryGroup_noUnknown :: Property
162
prop_queryGroup_noUnknown =
163
  forAll (choose (0, maxNodes) >>= genEmptyCluster) $ \cluster ->
164
   forAll (elements (Map.keys groupFieldsMap)) $ \field -> monadicIO $ do
165
   QueryResult fdefs fdata <-
166
     run (query cluster False (Query QRGroup [field] EmptyFilter)) >>=
167
         resultProp
168
   QueryFieldsResult fdefs' <-
169
     resultProp $ queryFields (QueryFields QRGroup [field])
170
   stop $ conjoin
171
    [ printTestCase ("Got unknown fields via query (" ++ show fdefs ++ ")")
172
         (hasUnknownFields fdefs)
173
    , printTestCase ("Got unknown result status via query (" ++
174
                     show fdata ++ ")")
175
      (all (all ((/= RSUnknown) . rentryStatus)) fdata)
176
    , printTestCase ("Got unknown fields via query fields (" ++ show fdefs'
177
                     ++ ")") (hasUnknownFields fdefs')
178
    ]
179

    
180
prop_queryGroup_Unknown :: Property
181
prop_queryGroup_Unknown =
182
  forAll (choose (0, maxNodes) >>= genEmptyCluster) $ \cluster ->
183
  forAll (arbitrary `suchThat` (`notElem` Map.keys groupFieldsMap))
184
    $ \field -> monadicIO $ do
185
  QueryResult fdefs fdata <-
186
    run (query cluster False (Query QRGroup [field] EmptyFilter)) >>= resultProp
187
  QueryFieldsResult fdefs' <-
188
    resultProp $ queryFields (QueryFields QRGroup [field])
189
  stop $ conjoin
190
         [ printTestCase ("Got known fields via query (" ++ show fdefs ++ ")")
191
           (not $ hasUnknownFields fdefs)
192
         , printTestCase ("Got /= ResultUnknown result status via query (" ++
193
                          show fdata ++ ")")
194
           (all (all ((== RSUnknown) . rentryStatus)) fdata)
195
         , printTestCase ("Got a Just in a result value (" ++
196
                          show fdata ++ ")")
197
           (all (all (isNothing . rentryValue)) fdata)
198
         , printTestCase ("Got known fields via query fields (" ++ show fdefs'
199
                          ++ ")") (not $ hasUnknownFields fdefs')
200
         ]
201

    
202
prop_queryGroup_types :: Property
203
prop_queryGroup_types =
204
  forAll (choose (0, maxNodes)) $ \numnodes ->
205
  forAll (genEmptyCluster numnodes) $ \cfg ->
206
  forAll (elements (Map.keys groupFieldsMap)) $ \field -> monadicIO $ do
207
  QueryResult fdefs fdata <-
208
    run (query cfg False (Query QRGroup [field] EmptyFilter)) >>= resultProp
209
  stop $ conjoin
210
         [ printTestCase ("Inconsistent result entries (" ++ show fdata ++ ")")
211
           (conjoin $ map (conjoin . zipWith checkResultType fdefs) fdata)
212
         , printTestCase "Wrong field definitions length" (length fdefs ==? 1)
213
         , printTestCase "Wrong field result rows length"
214
           (all ((== 1) . length) fdata)
215
         ]
216

    
217
case_queryGroup_allfields :: Assertion
218
case_queryGroup_allfields = do
219
   fdefs <- case queryFields (QueryFields QRGroup []) of
220
              Bad msg -> fail $ "Error in query all fields: " ++
221
                         formatError msg
222
              Ok (QueryFieldsResult v) -> return v
223
   let field_sort = compare `on` fdefName
224
   assertEqual "Mismatch in all fields list"
225
     (sortBy field_sort . map fst $ Map.elems groupFieldsMap)
226
     (sortBy field_sort fdefs)
227

    
228

    
229
-- | Tests that requested names checking behaves as expected.
230
prop_getRequestedNames :: Property
231
prop_getRequestedNames =
232
  forAll getName $ \node1 ->
233
  let chk = getRequestedNames . Query QRNode []
234
      q_node1 = QuotedString node1
235
      eq_name = EQFilter "name"
236
      eq_node1 = eq_name q_node1
237
  in conjoin [ printTestCase "empty filter" $ chk EmptyFilter ==? []
238
             , printTestCase "and filter" $ chk (AndFilter [eq_node1]) ==? []
239
             , printTestCase "simple equality" $ chk eq_node1 ==? [node1]
240
             , printTestCase "non-name field" $
241
               chk (EQFilter "foo" q_node1) ==? []
242
             , printTestCase "non-simple filter" $
243
               chk (OrFilter [ eq_node1 , LTFilter "foo" q_node1]) ==? []
244
             ]
245

    
246
testSuite "Query/Query"
247
  [ 'prop_queryNode_noUnknown
248
  , 'prop_queryNode_Unknown
249
  , 'prop_queryNode_types
250
  , 'case_queryNode_allfields
251
  , 'prop_queryGroup_noUnknown
252
  , 'prop_queryGroup_Unknown
253
  , 'prop_queryGroup_types
254
  , 'case_queryGroup_allfields
255
  , 'prop_getRequestedNames
256
  ]