Revision b9bdc10e

b/Makefile.am
457 457
	htest/Test/Ganeti/Objects.hs \
458 458
	htest/Test/Ganeti/OpCodes.hs \
459 459
	htest/Test/Ganeti/Query/Language.hs \
460
	htest/Test/Ganeti/Query/Query.hs \
460 461
	htest/Test/Ganeti/Rpc.hs \
461 462
	htest/Test/Ganeti/Ssconf.hs \
462 463
	htest/Test/Ganeti/TestCommon.hs \
b/htest/Test/Ganeti/Objects.hs
177 177
  nodes <- vector ncount
178 178
  version <- arbitrary
179 179
  let guuid = "00"
180
      nodes' = map (\n -> n { nodeGroup = guuid }) nodes
180
      nodes' = zipWith (\n idx -> n { nodeGroup = guuid,
181
                                      nodeName = nodeName n ++ show idx })
182
               nodes [(1::Int)..]
181 183
      contnodes = Container . Map.fromList $ map (\n -> (nodeName n, n)) nodes'
182 184
      continsts = Container $ Map.empty
183 185
  grp <- arbitrary
b/htest/Test/Ganeti/Query/Query.hs
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
  ]
b/htest/Test/Ganeti/TestCommon.hs
31 31
import Data.List
32 32
import qualified Test.HUnit as HUnit
33 33
import Test.QuickCheck
34
import Test.QuickCheck.Monadic
34 35
import qualified Text.JSON as J
35 36
import System.Environment (getEnv)
36 37
import System.Exit (ExitCode(..))
37 38
import System.IO.Error (isDoesNotExistError)
38 39
import System.Process (readProcessWithExitCode)
39 40

  
41
import qualified Ganeti.BasicTypes as BasicTypes
42

  
40 43
-- * Constants
41 44

  
42 45
-- | Maximum memory (1TiB, somewhat random value).
......
199 202
  case J.readJSON (J.showJSON a) of
200 203
    J.Error msg -> failTest $ "Failed to deserialise: " ++ msg
201 204
    J.Ok a' -> a ==? a'
205

  
206
-- | Result to PropertyM IO.
207
resultProp :: BasicTypes.Result a -> PropertyM IO a
208
resultProp (BasicTypes.Bad msg) = stop $ failTest msg
209
resultProp (BasicTypes.Ok  val) = return val
b/htest/test.hs
49 49
import Test.Ganeti.Objects
50 50
import Test.Ganeti.OpCodes
51 51
import Test.Ganeti.Query.Language
52
import Test.Ganeti.Query.Query
52 53
import Test.Ganeti.Rpc
53 54
import Test.Ganeti.Ssconf
54 55

  
......
92 93
  , (True, testObjects)
93 94
  , (True, testOpCodes)
94 95
  , (True, testQuery_Language)
96
  , (True, testQuery_Query)
95 97
  , (True, testRpc)
96 98
  , (True, testSsconf)
97 99
  , (False, testHTools_Cluster)
b/htools/Ganeti/Query/Language.hs
336 336
  ])
337 337

  
338 338
--- | Single field entry result.
339
data ResultEntry = ResultEntry ResultStatus (Maybe ResultValue)
340
                   deriving (Show, Read, Eq)
339
data ResultEntry = ResultEntry
340
  { rentryStatus :: ResultStatus      -- ^ The result status
341
  , rentryValue  :: Maybe ResultValue -- ^ The (optional) result value
342
  } deriving (Show, Read, Eq)
341 343

  
342 344
instance JSON ResultEntry where
343 345
  showJSON (ResultEntry rs rv) =
b/htools/Ganeti/Query/Node.hs
128 128
       "Number of instances with this node as secondary",
129 129
     FieldConfig (\cfg ->
130 130
                    rsNormal . length . snd . getNodeInstances cfg . nodeName))
131
  , (FieldDefinition "pinst_list" "PriInstances" QFTNumber
131
  , (FieldDefinition "pinst_list" "PriInstances" QFTOther
132 132
       "List of instances with this node as primary",
133 133
     FieldConfig (\cfg -> rsNormal . map instName . fst .
134 134
                          getNodeInstances cfg . nodeName))
135
  , (FieldDefinition "sinst_list" "SecInstances" QFTNumber
135
  , (FieldDefinition "sinst_list" "SecInstances" QFTOther
136 136
       "List of instances with this node as secondary",
137 137
     FieldConfig (\cfg -> rsNormal . map instName . snd .
138 138
                          getNodeInstances cfg . nodeName))

Also available in: Unified diff