Add some more Haskell/Python equivalence tests
authorIustin Pop <iustin@google.com>
Mon, 4 Feb 2013 13:52:43 +0000 (14:52 +0100)
committerIustin Pop <iustin@google.com>
Tue, 5 Feb 2013 08:36:41 +0000 (09:36 +0100)
This would have caught the log file problem fixed in the previous
patch (9411474b), for example. Also we test user/group equivalence,
name only.

Signed-off-by: Iustin Pop <iustin@google.com>
Reviewed-by: Guido Trotter <ultrotter@google.com>

Makefile.am
test/hs/Test/Ganeti/Runtime.hs [new file with mode: 0644]
test/hs/htest.hs

index 792c526..3657d7b 100644 (file)
@@ -572,6 +572,7 @@ HS_TEST_SRCS = \
        test/hs/Test/Ganeti/Query/Language.hs \
        test/hs/Test/Ganeti/Query/Query.hs \
        test/hs/Test/Ganeti/Rpc.hs \
+       test/hs/Test/Ganeti/Runtime.hs \
        test/hs/Test/Ganeti/Ssconf.hs \
        test/hs/Test/Ganeti/THH.hs \
        test/hs/Test/Ganeti/TestCommon.hs \
diff --git a/test/hs/Test/Ganeti/Runtime.hs b/test/hs/Test/Ganeti/Runtime.hs
new file mode 100644 (file)
index 0000000..310efcd
--- /dev/null
@@ -0,0 +1,117 @@
+{-# LANGUAGE TemplateHaskell #-}
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+
+{-| Unittests for "Ganeti.Runtime".
+
+-}
+
+{-
+
+Copyright (C) 2013 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.Runtime (testRuntime) where
+
+import Test.HUnit
+import qualified Text.JSON as J
+
+import Test.Ganeti.TestHelper
+import Test.Ganeti.TestCommon
+
+import Ganeti.Runtime
+
+{-# ANN module "HLint: ignore Use camelCase" #-}
+
+-- | Tests the compatibility between Haskell and Python log files.
+case_LogFiles :: Assertion
+case_LogFiles = do
+  let daemons = [minBound..maxBound]::[GanetiDaemon]
+      dnames = map daemonName daemons
+  dfiles <- mapM daemonLogFile daemons
+  let serialized = J.encode dnames
+  py_stdout <-
+    runPython "from ganeti import constants\n\
+              \from ganeti import serializer\n\
+              \import sys\n\
+              \daemons = serializer.Load(sys.stdin.read())\n\
+              \logfiles = [constants.DAEMONS_LOGFILES[d] for d in daemons]\n\
+              \print serializer.Dump(logfiles)" serialized
+    >>= checkPythonResult
+  let deserialised = J.decode py_stdout::J.Result [String]
+  decoded <- case deserialised of
+               J.Ok ops -> return ops
+               J.Error msg ->
+                 assertFailure ("Unable to decode log files: " ++ msg)
+                 -- this already raised an expection, but we need it
+                 -- for proper types
+                 >> fail "Unable to decode log files"
+  assertEqual "Mismatch in number of returned log files"
+    (length decoded) (length daemons)
+  mapM_ (uncurry (assertEqual "Different result after encoding/decoding")
+        ) $ zip decoded dfiles
+
+-- | Tests the compatibility between Haskell and Python users.
+case_UsersGroups :: Assertion
+case_UsersGroups = do
+  -- note: we don't have here a programatic way to list all users, so
+  -- we harcode some parts of the two (hs/py) lists
+  let daemons = [minBound..maxBound]::[GanetiDaemon]
+      users = map daemonUser daemons
+      groups = map daemonGroup $
+               map DaemonGroup daemons ++ map ExtraGroup [minBound..maxBound]
+  py_stdout <-
+    runPython "from ganeti import constants\n\
+              \from ganeti import serializer\n\
+              \import sys\n\
+              \users = [constants.MASTERD_GROUP,\n\
+              \         constants.NODED_USER,\n\
+              \         constants.RAPI_USER,\n\
+              \         constants.CONFD_USER,\n\
+              \        ]\n\
+              \groups = [constants.MASTERD_GROUP,\n\
+              \          constants.NODED_GROUP,\n\
+              \          constants.RAPI_GROUP,\n\
+              \          constants.CONFD_GROUP,\n\
+              \          constants.DAEMONS_GROUP,\n\
+              \          constants.ADMIN_GROUP]\n\
+              \encoded = (users, groups)\n\
+              \print serializer.Dump(encoded)" ""
+    >>= checkPythonResult
+  let deserialised = J.decode py_stdout::J.Result ([String], [String])
+  (py_users, py_groups) <-
+    case deserialised of
+      J.Ok ops -> return ops
+      J.Error msg ->
+        assertFailure ("Unable to decode users/groups: " ++ msg)
+        -- this already raised an expection, but we need it for proper
+        -- types
+         >> fail "Unable to decode users/groups"
+  assertEqual "Mismatch in number of returned users"
+    (length py_users) (length users)
+  assertEqual "Mismatch in number of returned users"
+    (length py_groups) (length groups)
+  mapM_ (uncurry (assertEqual "Different result for users")
+        ) $ zip py_users users
+  mapM_ (uncurry (assertEqual "Different result for groups")
+        ) $ zip py_groups groups
+
+testSuite "Runtime"
+          [ 'case_LogFiles
+          , 'case_UsersGroups
+          ]
index d7848aa..c2791f3 100644 (file)
@@ -4,7 +4,7 @@
 
 {-
 
-Copyright (C) 2009, 2011, 2012 Google Inc.
+Copyright (C) 2009, 2011, 2012, 2013 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
@@ -62,6 +62,7 @@ import Test.Ganeti.Query.Filter
 import Test.Ganeti.Query.Language
 import Test.Ganeti.Query.Query
 import Test.Ganeti.Rpc
+import Test.Ganeti.Runtime
 import Test.Ganeti.Ssconf
 import Test.Ganeti.THH
 import Test.Ganeti.Types
@@ -113,6 +114,7 @@ allTests =
   , testQuery_Language
   , testQuery_Query
   , testRpc
+  , testRuntime
   , testSsconf
   , testTHH
   , testTypes