Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / Query / Query.hs @ b9bdc10e

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

    
50
-- * Helpers
51

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

    
56
-- * Test cases
57

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

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

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

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

    
137
-- | Test that queryFields with empty fields list returns all node fields.
138
case_queryNode_allfields :: Assertion
139
case_queryNode_allfields = do
140
   fdefs <- case queryFields (QueryFields QRNode []) of
141
              Bad msg -> fail $ "Error in query all fields: " ++ msg
142
              Ok (QueryFieldsResult v) -> return v
143
   let field_sort = compare `on` fdefName
144
   assertEqual "Mismatch in all fields list"
145
     (sortBy field_sort . map fst $ Map.elems nodeFieldsMap)
146
     (sortBy field_sort fdefs)
147

    
148
testSuite "Query/Query"
149
  [ 'prop_queryNode_noUnknown
150
  , 'prop_queryNode_Unknown
151
  , 'prop_queryNode_types
152
  , 'case_queryNode_allfields
153
  ]