root / test / hs / Test / Ganeti / Runtime.hs @ 9d929656
History | View | Annotate | Download (4.7 kB)
1 |
{-# LANGUAGE TemplateHaskell #-} |
---|---|
2 |
{-# OPTIONS_GHC -fno-warn-orphans #-} |
3 |
|
4 |
{-| Unittests for "Ganeti.Runtime". |
5 |
|
6 |
-} |
7 |
|
8 |
{- |
9 |
|
10 |
Copyright (C) 2013 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.Runtime (testRuntime) where |
30 |
|
31 |
import Test.HUnit |
32 |
import qualified Text.JSON as J |
33 |
|
34 |
import Test.Ganeti.TestHelper |
35 |
import Test.Ganeti.TestCommon |
36 |
|
37 |
import Ganeti.Runtime |
38 |
|
39 |
{-# ANN module "HLint: ignore Use camelCase" #-} |
40 |
|
41 |
-- | Tests the compatibility between Haskell and Python log files. |
42 |
case_LogFiles :: Assertion |
43 |
case_LogFiles = do |
44 |
let daemons = [minBound..maxBound]::[GanetiDaemon] |
45 |
dnames = map daemonName daemons |
46 |
dfiles <- mapM daemonLogFile daemons |
47 |
let serialized = J.encode dnames |
48 |
py_stdout <- |
49 |
runPython "from ganeti import constants\n\ |
50 |
\from ganeti import serializer\n\ |
51 |
\import sys\n\ |
52 |
\daemons = serializer.Load(sys.stdin.read())\n\ |
53 |
\logfiles = [constants.DAEMONS_LOGFILES[d] for d in daemons]\n\ |
54 |
\print serializer.Dump(logfiles)" serialized |
55 |
>>= checkPythonResult |
56 |
let deserialised = J.decode py_stdout::J.Result [String] |
57 |
decoded <- case deserialised of |
58 |
J.Ok ops -> return ops |
59 |
J.Error msg -> |
60 |
assertFailure ("Unable to decode log files: " ++ msg) |
61 |
-- this already raised an expection, but we need it |
62 |
-- for proper types |
63 |
>> fail "Unable to decode log files" |
64 |
assertEqual "Mismatch in number of returned log files" |
65 |
(length decoded) (length daemons) |
66 |
mapM_ (uncurry (assertEqual "Different result after encoding/decoding") |
67 |
) $ zip dfiles decoded |
68 |
|
69 |
-- | Tests the compatibility between Haskell and Python users. |
70 |
case_UsersGroups :: Assertion |
71 |
case_UsersGroups = do |
72 |
-- note: we don't have here a programatic way to list all users, so |
73 |
-- we harcode some parts of the two (hs/py) lists |
74 |
let daemons = [minBound..maxBound]::[GanetiDaemon] |
75 |
users = map daemonUser daemons |
76 |
groups = map daemonGroup $ |
77 |
map DaemonGroup daemons ++ map ExtraGroup [minBound..maxBound] |
78 |
py_stdout <- |
79 |
runPython "from ganeti import constants\n\ |
80 |
\from ganeti import serializer\n\ |
81 |
\import sys\n\ |
82 |
\users = [constants.MASTERD_USER,\n\ |
83 |
\ constants.NODED_USER,\n\ |
84 |
\ constants.RAPI_USER,\n\ |
85 |
\ constants.CONFD_USER,\n\ |
86 |
\ constants.KVMD_USER,\n\ |
87 |
\ constants.LUXID_USER,\n\ |
88 |
\ constants.METAD_USER,\n\ |
89 |
\ constants.MOND_USER,\n\ |
90 |
\ ]\n\ |
91 |
\groups = [constants.MASTERD_GROUP,\n\ |
92 |
\ constants.NODED_GROUP,\n\ |
93 |
\ constants.RAPI_GROUP,\n\ |
94 |
\ constants.CONFD_GROUP,\n\ |
95 |
\ constants.KVMD_GROUP,\n\ |
96 |
\ constants.LUXID_GROUP,\n\ |
97 |
\ constants.METAD_GROUP,\n\ |
98 |
\ constants.MOND_GROUP,\n\ |
99 |
\ constants.DAEMONS_GROUP,\n\ |
100 |
\ constants.ADMIN_GROUP,\n\ |
101 |
\ ]\n\ |
102 |
\encoded = (users, groups)\n\ |
103 |
\print serializer.Dump(encoded)" "" |
104 |
>>= checkPythonResult |
105 |
let deserialised = J.decode py_stdout::J.Result ([String], [String]) |
106 |
(py_users, py_groups) <- |
107 |
case deserialised of |
108 |
J.Ok ops -> return ops |
109 |
J.Error msg -> |
110 |
assertFailure ("Unable to decode users/groups: " ++ msg) |
111 |
-- this already raised an expection, but we need it for proper |
112 |
-- types |
113 |
>> fail "Unable to decode users/groups" |
114 |
assertEqual "Mismatch in number of returned users" |
115 |
(length py_users) (length users) |
116 |
assertEqual "Mismatch in number of returned users" |
117 |
(length py_groups) (length groups) |
118 |
mapM_ (uncurry (assertEqual "Different result for users") |
119 |
) $ zip users py_users |
120 |
mapM_ (uncurry (assertEqual "Different result for groups") |
121 |
) $ zip groups py_groups |
122 |
|
123 |
testSuite "Runtime" |
124 |
[ 'case_LogFiles |
125 |
, 'case_UsersGroups |
126 |
] |