diff --git a/Makefile.am b/Makefile.am index 8b3e539c90d929ce67de164aa946453249ea1326..14ec43ffdb7c41d6650e9712e43884196460fca7 100644 --- a/Makefile.am +++ b/Makefile.am @@ -457,6 +457,7 @@ HS_TEST_SRCS = \ htest/Test/Ganeti/Objects.hs \ htest/Test/Ganeti/OpCodes.hs \ htest/Test/Ganeti/Query/Language.hs \ + htest/Test/Ganeti/Query/Query.hs \ htest/Test/Ganeti/Rpc.hs \ htest/Test/Ganeti/Ssconf.hs \ htest/Test/Ganeti/TestCommon.hs \ diff --git a/htest/Test/Ganeti/Objects.hs b/htest/Test/Ganeti/Objects.hs index c6d8e89d7d68295b08e2511f6efa1348761e0b64..6b2c345e43688ae8dd156575b25d887957361918 100644 --- a/htest/Test/Ganeti/Objects.hs +++ b/htest/Test/Ganeti/Objects.hs @@ -177,7 +177,9 @@ genEmptyCluster ncount = do nodes <- vector ncount version <- arbitrary let guuid = "00" - nodes' = map (\n -> n { nodeGroup = guuid }) nodes + nodes' = zipWith (\n idx -> n { nodeGroup = guuid, + nodeName = nodeName n ++ show idx }) + nodes [(1::Int)..] contnodes = Container . Map.fromList $ map (\n -> (nodeName n, n)) nodes' continsts = Container $ Map.empty grp <- arbitrary diff --git a/htest/Test/Ganeti/Query/Query.hs b/htest/Test/Ganeti/Query/Query.hs new file mode 100644 index 0000000000000000000000000000000000000000..1e20cc3d5643b4d9cafa5e8214ad0d64f0f7def8 --- /dev/null +++ b/htest/Test/Ganeti/Query/Query.hs @@ -0,0 +1,153 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# OPTIONS_GHC -fno-warn-orphans #-} + +{-| Unittests for ganeti-htools. + +-} + +{- + +Copyright (C) 2009, 2010, 2011, 2012 Google Inc. + +This program is free software; you can redistribute it and/or modify +it under the terms of the GNU General Public License as published by +the Free Software Foundation; either version 2 of the License, or +(at your option) any later version. + +This program is distributed in the hope that it will be useful, but +WITHOUT ANY WARRANTY; without even the implied warranty of +MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU +General Public License for more details. + +You should have received a copy of the GNU General Public License +along with this program; if not, write to the Free Software +Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA +02110-1301, USA. + +-} + +module Test.Ganeti.Query.Query (testQuery_Query) where + +import Test.HUnit (Assertion, assertEqual) +import Test.QuickCheck hiding (Result) +import Test.QuickCheck.Monadic + +import Data.Function (on) +import Data.List +import qualified Data.Map as Map +import Data.Maybe +import Text.JSON (JSValue(..)) + +import Test.Ganeti.TestHelper +import Test.Ganeti.TestCommon +import Test.Ganeti.Objects (genEmptyCluster) + +import Ganeti.BasicTypes +import Ganeti.Query.Language +import Ganeti.Query.Node +import Ganeti.Query.Query + +-- * Helpers + +-- | Checks if a list of field definitions contains unknown fields. +hasUnknownFields :: [FieldDefinition] -> Bool +hasUnknownFields = (QFTUnknown `notElem`) . map fdefKind + +-- * Test cases + +-- | Tests that querying any existing fields, via either query or +-- queryFields, will not return unknown fields. +prop_queryNode_noUnknown :: Property +prop_queryNode_noUnknown = + forAll (choose (0, maxNodes) >>= genEmptyCluster) $ \cluster -> + forAll (elements (Map.keys nodeFieldsMap)) $ \field -> monadicIO $ do + QueryResult fdefs fdata <- + run (query cluster (Query QRNode [field] EmptyFilter)) >>= resultProp + QueryFieldsResult fdefs' <- + resultProp $ queryFields (QueryFields QRNode [field]) + stop $ printTestCase ("Got unknown fields via query (" ++ show fdefs ++ ")") + (hasUnknownFields fdefs) .&&. + printTestCase ("Got unknown result status via query (" ++ + show fdata ++ ")") + (all (all ((/= RSUnknown) . rentryStatus)) fdata) .&&. + printTestCase ("Got unknown fields via query fields (" ++ show fdefs' + ++ ")") (hasUnknownFields fdefs') + +-- | Tests that an unknown field is returned as such. +prop_queryNode_Unknown :: Property +prop_queryNode_Unknown = + forAll (choose (0, maxNodes) >>= genEmptyCluster) $ \cluster -> + forAll (arbitrary `suchThat` (`notElem` (Map.keys nodeFieldsMap))) + $ \field -> monadicIO $ do + QueryResult fdefs fdata <- + run (query cluster (Query QRNode [field] EmptyFilter)) >>= resultProp + QueryFieldsResult fdefs' <- + resultProp $ queryFields (QueryFields QRNode [field]) + stop $ printTestCase ("Got known fields via query (" ++ show fdefs ++ ")") + (not $ hasUnknownFields fdefs) .&&. + printTestCase ("Got /= ResultUnknown result status via query (" ++ + show fdata ++ ")") + (all (all ((== RSUnknown) . rentryStatus)) fdata) .&&. + printTestCase ("Got a Just in a result value (" ++ + show fdata ++ ")") + (all (all (isNothing . rentryValue)) fdata) .&&. + printTestCase ("Got known fields via query fields (" ++ show fdefs' + ++ ")") (not $ hasUnknownFields fdefs') + +-- | Checks that a result type is conforming to a field definition. +checkResultType :: FieldDefinition -> ResultEntry -> Property +checkResultType _ (ResultEntry RSNormal Nothing) = + failTest "Nothing result in RSNormal field" +checkResultType _ (ResultEntry _ Nothing) = passTest +checkResultType fdef (ResultEntry RSNormal (Just v)) = + case (fdefKind fdef, v) of + (QFTText , JSString {}) -> passTest + (QFTBool , JSBool {}) -> passTest + (QFTNumber , JSRational {}) -> passTest + (QFTTimestamp , JSRational {}) -> passTest + (QFTUnit , JSRational {}) -> passTest + (QFTOther , _) -> passTest -- meh, QFT not precise... + (kind, _) -> failTest $ "Type mismatch, field definition says " ++ + show kind ++ " but returned value is " ++ show v ++ + " for field '" ++ fdefName fdef ++ "'" +checkResultType _ (ResultEntry r (Just _)) = + failTest $ "Just result in " ++ show r ++ " field" + +-- | Tests that querying any existing fields, the following three +-- properties hold: RSNormal corresponds to a Just value, any other +-- value corresponds to Nothing, and for a RSNormal and value field, +-- the type of the value corresponds to the type of the field as +-- declared in the FieldDefinition. +prop_queryNode_types :: Property +prop_queryNode_types = + forAll (choose (0, maxNodes)) $ \numnodes -> + forAll (genEmptyCluster numnodes) $ \cfg -> + forAll (elements (Map.keys nodeFieldsMap)) $ \field -> monadicIO $ do + QueryResult fdefs fdata <- + run (query cfg (Query QRNode [field] EmptyFilter)) >>= resultProp + stop $ printTestCase ("Inconsistent result entries (" ++ show fdata ++ ")") + (conjoin $ map (conjoin . zipWith checkResultType fdefs) fdata) .&&. + printTestCase "Wrong field definitions length" + (length fdefs ==? 1) .&&. + printTestCase "Wrong field result rows length" + (all ((== 1) . length) fdata) .&&. + printTestCase "Wrong number of result rows" + (length fdata ==? numnodes) + +-- | Test that queryFields with empty fields list returns all node fields. +case_queryNode_allfields :: Assertion +case_queryNode_allfields = do + fdefs <- case queryFields (QueryFields QRNode []) of + Bad msg -> fail $ "Error in query all fields: " ++ msg + Ok (QueryFieldsResult v) -> return v + let field_sort = compare `on` fdefName + assertEqual "Mismatch in all fields list" + (sortBy field_sort . map fst $ Map.elems nodeFieldsMap) + (sortBy field_sort fdefs) + +testSuite "Query/Query" + [ 'prop_queryNode_noUnknown + , 'prop_queryNode_Unknown + , 'prop_queryNode_types + , 'case_queryNode_allfields + ] diff --git a/htest/Test/Ganeti/TestCommon.hs b/htest/Test/Ganeti/TestCommon.hs index 5a244e1120d42f9f3a74535c901e2941315c648b..4861a46749c58c0fc15cd166af5b4661852fd755 100644 --- a/htest/Test/Ganeti/TestCommon.hs +++ b/htest/Test/Ganeti/TestCommon.hs @@ -31,12 +31,15 @@ import Control.Monad import Data.List import qualified Test.HUnit as HUnit import Test.QuickCheck +import Test.QuickCheck.Monadic import qualified Text.JSON as J import System.Environment (getEnv) import System.Exit (ExitCode(..)) import System.IO.Error (isDoesNotExistError) import System.Process (readProcessWithExitCode) +import qualified Ganeti.BasicTypes as BasicTypes + -- * Constants -- | Maximum memory (1TiB, somewhat random value). @@ -199,3 +202,8 @@ testSerialisation a = case J.readJSON (J.showJSON a) of J.Error msg -> failTest $ "Failed to deserialise: " ++ msg J.Ok a' -> a ==? a' + +-- | Result to PropertyM IO. +resultProp :: BasicTypes.Result a -> PropertyM IO a +resultProp (BasicTypes.Bad msg) = stop $ failTest msg +resultProp (BasicTypes.Ok val) = return val diff --git a/htest/test.hs b/htest/test.hs index c9f62f315b8140c90329dd86d48c0e2eae2b01c3..c3f22d18c5b2d9288b1673d152137e796b37e9bf 100644 --- a/htest/test.hs +++ b/htest/test.hs @@ -49,6 +49,7 @@ import Test.Ganeti.Luxi import Test.Ganeti.Objects import Test.Ganeti.OpCodes import Test.Ganeti.Query.Language +import Test.Ganeti.Query.Query import Test.Ganeti.Rpc import Test.Ganeti.Ssconf @@ -92,6 +93,7 @@ allTests = , (True, testObjects) , (True, testOpCodes) , (True, testQuery_Language) + , (True, testQuery_Query) , (True, testRpc) , (True, testSsconf) , (False, testHTools_Cluster) diff --git a/htools/Ganeti/Query/Language.hs b/htools/Ganeti/Query/Language.hs index 20dc3948c59ee7b6006d51468024448f4fb288bf..31b0a1b184679c07cc49dd1ec212b39569164e71 100644 --- a/htools/Ganeti/Query/Language.hs +++ b/htools/Ganeti/Query/Language.hs @@ -336,8 +336,10 @@ $(buildObject "FieldDefinition" "fdef" ]) --- | Single field entry result. -data ResultEntry = ResultEntry ResultStatus (Maybe ResultValue) - deriving (Show, Read, Eq) +data ResultEntry = ResultEntry + { rentryStatus :: ResultStatus -- ^ The result status + , rentryValue :: Maybe ResultValue -- ^ The (optional) result value + } deriving (Show, Read, Eq) instance JSON ResultEntry where showJSON (ResultEntry rs rv) = diff --git a/htools/Ganeti/Query/Node.hs b/htools/Ganeti/Query/Node.hs index 824df05c0b48518c09028f5e539aa3b2b40dc24d..8fbcee423d0ca64f30a9168d8f97174d22e05ebf 100644 --- a/htools/Ganeti/Query/Node.hs +++ b/htools/Ganeti/Query/Node.hs @@ -128,11 +128,11 @@ nodeFields = "Number of instances with this node as secondary", FieldConfig (\cfg -> rsNormal . length . snd . getNodeInstances cfg . nodeName)) - , (FieldDefinition "pinst_list" "PriInstances" QFTNumber + , (FieldDefinition "pinst_list" "PriInstances" QFTOther "List of instances with this node as primary", FieldConfig (\cfg -> rsNormal . map instName . fst . getNodeInstances cfg . nodeName)) - , (FieldDefinition "sinst_list" "SecInstances" QFTNumber + , (FieldDefinition "sinst_list" "SecInstances" QFTOther "List of instances with this node as secondary", FieldConfig (\cfg -> rsNormal . map instName . snd . getNodeInstances cfg . nodeName))