Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / Query / Query.hs @ 942a9a6a

History | View | Annotate | Download (10.2 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.Query.Group
47
import Ganeti.Query.Language
48
import Ganeti.Query.Node
49
import Ganeti.Query.Query
50

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

    
53
-- * Helpers
54

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

    
59
-- * Test cases
60

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

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

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

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

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

    
157
-- * Same as above, but for group
158

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

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

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

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

    
225

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

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