Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Runtime.hs @ fb0fa957

History | View | Annotate | Download (4.8 kB)

1 ca7b4f48 Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 ca7b4f48 Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 ca7b4f48 Iustin Pop
4 ca7b4f48 Iustin Pop
{-| Unittests for "Ganeti.Runtime".
5 ca7b4f48 Iustin Pop
6 ca7b4f48 Iustin Pop
-}
7 ca7b4f48 Iustin Pop
8 ca7b4f48 Iustin Pop
{-
9 ca7b4f48 Iustin Pop
10 ca7b4f48 Iustin Pop
Copyright (C) 2013 Google Inc.
11 ca7b4f48 Iustin Pop
12 ca7b4f48 Iustin Pop
This program is free software; you can redistribute it and/or modify
13 ca7b4f48 Iustin Pop
it under the terms of the GNU General Public License as published by
14 ca7b4f48 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 ca7b4f48 Iustin Pop
(at your option) any later version.
16 ca7b4f48 Iustin Pop
17 ca7b4f48 Iustin Pop
This program is distributed in the hope that it will be useful, but
18 ca7b4f48 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 ca7b4f48 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 ca7b4f48 Iustin Pop
General Public License for more details.
21 ca7b4f48 Iustin Pop
22 ca7b4f48 Iustin Pop
You should have received a copy of the GNU General Public License
23 ca7b4f48 Iustin Pop
along with this program; if not, write to the Free Software
24 ca7b4f48 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 ca7b4f48 Iustin Pop
02110-1301, USA.
26 ca7b4f48 Iustin Pop
27 ca7b4f48 Iustin Pop
-}
28 ca7b4f48 Iustin Pop
29 ca7b4f48 Iustin Pop
module Test.Ganeti.Runtime (testRuntime) where
30 ca7b4f48 Iustin Pop
31 ca7b4f48 Iustin Pop
import Test.HUnit
32 ca7b4f48 Iustin Pop
import qualified Text.JSON as J
33 ca7b4f48 Iustin Pop
34 ca7b4f48 Iustin Pop
import Test.Ganeti.TestHelper
35 ca7b4f48 Iustin Pop
import Test.Ganeti.TestCommon
36 ca7b4f48 Iustin Pop
37 ca7b4f48 Iustin Pop
import Ganeti.Runtime
38 ca7b4f48 Iustin Pop
39 ca7b4f48 Iustin Pop
{-# ANN module "HLint: ignore Use camelCase" #-}
40 ca7b4f48 Iustin Pop
41 ca7b4f48 Iustin Pop
-- | Tests the compatibility between Haskell and Python log files.
42 ca7b4f48 Iustin Pop
case_LogFiles :: Assertion
43 ca7b4f48 Iustin Pop
case_LogFiles = do
44 ca7b4f48 Iustin Pop
  let daemons = [minBound..maxBound]::[GanetiDaemon]
45 ca7b4f48 Iustin Pop
      dnames = map daemonName daemons
46 ca7b4f48 Iustin Pop
  dfiles <- mapM daemonLogFile daemons
47 ca7b4f48 Iustin Pop
  let serialized = J.encode dnames
48 ca7b4f48 Iustin Pop
  py_stdout <-
49 ca7b4f48 Iustin Pop
    runPython "from ganeti import constants\n\
50 ca7b4f48 Iustin Pop
              \from ganeti import serializer\n\
51 ca7b4f48 Iustin Pop
              \import sys\n\
52 ca7b4f48 Iustin Pop
              \daemons = serializer.Load(sys.stdin.read())\n\
53 ca7b4f48 Iustin Pop
              \logfiles = [constants.DAEMONS_LOGFILES[d] for d in daemons]\n\
54 ca7b4f48 Iustin Pop
              \print serializer.Dump(logfiles)" serialized
55 ca7b4f48 Iustin Pop
    >>= checkPythonResult
56 ca7b4f48 Iustin Pop
  let deserialised = J.decode py_stdout::J.Result [String]
57 ca7b4f48 Iustin Pop
  decoded <- case deserialised of
58 ca7b4f48 Iustin Pop
               J.Ok ops -> return ops
59 ca7b4f48 Iustin Pop
               J.Error msg ->
60 ca7b4f48 Iustin Pop
                 assertFailure ("Unable to decode log files: " ++ msg)
61 ca7b4f48 Iustin Pop
                 -- this already raised an expection, but we need it
62 ca7b4f48 Iustin Pop
                 -- for proper types
63 ca7b4f48 Iustin Pop
                 >> fail "Unable to decode log files"
64 ca7b4f48 Iustin Pop
  assertEqual "Mismatch in number of returned log files"
65 ca7b4f48 Iustin Pop
    (length decoded) (length daemons)
66 ca7b4f48 Iustin Pop
  mapM_ (uncurry (assertEqual "Different result after encoding/decoding")
67 9d929656 Santi Raffa
        ) $ zip dfiles decoded
68 ca7b4f48 Iustin Pop
69 ca7b4f48 Iustin Pop
-- | Tests the compatibility between Haskell and Python users.
70 ca7b4f48 Iustin Pop
case_UsersGroups :: Assertion
71 ca7b4f48 Iustin Pop
case_UsersGroups = do
72 ca7b4f48 Iustin Pop
  -- note: we don't have here a programatic way to list all users, so
73 ca7b4f48 Iustin Pop
  -- we harcode some parts of the two (hs/py) lists
74 ca7b4f48 Iustin Pop
  let daemons = [minBound..maxBound]::[GanetiDaemon]
75 ca7b4f48 Iustin Pop
      users = map daemonUser daemons
76 ca7b4f48 Iustin Pop
      groups = map daemonGroup $
77 ca7b4f48 Iustin Pop
               map DaemonGroup daemons ++ map ExtraGroup [minBound..maxBound]
78 ca7b4f48 Iustin Pop
  py_stdout <-
79 ca7b4f48 Iustin Pop
    runPython "from ganeti import constants\n\
80 ca7b4f48 Iustin Pop
              \from ganeti import serializer\n\
81 ca7b4f48 Iustin Pop
              \import sys\n\
82 a29fcf38 Michele Tartara
              \users = [constants.MASTERD_USER,\n\
83 ca7b4f48 Iustin Pop
              \         constants.NODED_USER,\n\
84 ca7b4f48 Iustin Pop
              \         constants.RAPI_USER,\n\
85 ca7b4f48 Iustin Pop
              \         constants.CONFD_USER,\n\
86 fb0fa957 Petr Pudlak
              \         constants.WCONFD_USER,\n\
87 4084d18f Jose A. Lopes
              \         constants.KVMD_USER,\n\
88 3695a4e0 Thomas Thrainer
              \         constants.LUXID_USER,\n\
89 3af1359f Jose A. Lopes
              \         constants.METAD_USER,\n\
90 f511082f Michele Tartara
              \         constants.MOND_USER,\n\
91 ca7b4f48 Iustin Pop
              \        ]\n\
92 ca7b4f48 Iustin Pop
              \groups = [constants.MASTERD_GROUP,\n\
93 ca7b4f48 Iustin Pop
              \          constants.NODED_GROUP,\n\
94 ca7b4f48 Iustin Pop
              \          constants.RAPI_GROUP,\n\
95 ca7b4f48 Iustin Pop
              \          constants.CONFD_GROUP,\n\
96 fb0fa957 Petr Pudlak
              \          constants.WCONFD_GROUP,\n\
97 4084d18f Jose A. Lopes
              \          constants.KVMD_GROUP,\n\
98 3695a4e0 Thomas Thrainer
              \          constants.LUXID_GROUP,\n\
99 3af1359f Jose A. Lopes
              \          constants.METAD_GROUP,\n\
100 f511082f Michele Tartara
              \          constants.MOND_GROUP,\n\
101 ca7b4f48 Iustin Pop
              \          constants.DAEMONS_GROUP,\n\
102 f511082f Michele Tartara
              \          constants.ADMIN_GROUP,\n\
103 f511082f Michele Tartara
              \         ]\n\
104 ca7b4f48 Iustin Pop
              \encoded = (users, groups)\n\
105 ca7b4f48 Iustin Pop
              \print serializer.Dump(encoded)" ""
106 ca7b4f48 Iustin Pop
    >>= checkPythonResult
107 ca7b4f48 Iustin Pop
  let deserialised = J.decode py_stdout::J.Result ([String], [String])
108 ca7b4f48 Iustin Pop
  (py_users, py_groups) <-
109 ca7b4f48 Iustin Pop
    case deserialised of
110 ca7b4f48 Iustin Pop
      J.Ok ops -> return ops
111 ca7b4f48 Iustin Pop
      J.Error msg ->
112 ca7b4f48 Iustin Pop
        assertFailure ("Unable to decode users/groups: " ++ msg)
113 ca7b4f48 Iustin Pop
        -- this already raised an expection, but we need it for proper
114 ca7b4f48 Iustin Pop
        -- types
115 ca7b4f48 Iustin Pop
         >> fail "Unable to decode users/groups"
116 ca7b4f48 Iustin Pop
  assertEqual "Mismatch in number of returned users"
117 ca7b4f48 Iustin Pop
    (length py_users) (length users)
118 ca7b4f48 Iustin Pop
  assertEqual "Mismatch in number of returned users"
119 ca7b4f48 Iustin Pop
    (length py_groups) (length groups)
120 ca7b4f48 Iustin Pop
  mapM_ (uncurry (assertEqual "Different result for users")
121 9d929656 Santi Raffa
        ) $ zip users py_users
122 ca7b4f48 Iustin Pop
  mapM_ (uncurry (assertEqual "Different result for groups")
123 9d929656 Santi Raffa
        ) $ zip groups py_groups
124 ca7b4f48 Iustin Pop
125 ca7b4f48 Iustin Pop
testSuite "Runtime"
126 ca7b4f48 Iustin Pop
          [ 'case_LogFiles
127 ca7b4f48 Iustin Pop
          , 'case_UsersGroups
128 ca7b4f48 Iustin Pop
          ]