Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Luxi.hs @ 4e4433e8

History | View | Annotate | Download (5.7 kB)

1 aed2325f Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 aed2325f Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 aed2325f Iustin Pop
4 aed2325f Iustin Pop
{-| Unittests for ganeti-htools.
5 aed2325f Iustin Pop
6 aed2325f Iustin Pop
-}
7 aed2325f Iustin Pop
8 aed2325f Iustin Pop
{-
9 aed2325f Iustin Pop
10 aed2325f Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11 aed2325f Iustin Pop
12 aed2325f Iustin Pop
This program is free software; you can redistribute it and/or modify
13 aed2325f Iustin Pop
it under the terms of the GNU General Public License as published by
14 aed2325f Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 aed2325f Iustin Pop
(at your option) any later version.
16 aed2325f Iustin Pop
17 aed2325f Iustin Pop
This program is distributed in the hope that it will be useful, but
18 aed2325f Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 aed2325f Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 aed2325f Iustin Pop
General Public License for more details.
21 aed2325f Iustin Pop
22 aed2325f Iustin Pop
You should have received a copy of the GNU General Public License
23 aed2325f Iustin Pop
along with this program; if not, write to the Free Software
24 aed2325f Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 aed2325f Iustin Pop
02110-1301, USA.
26 aed2325f Iustin Pop
27 aed2325f Iustin Pop
-}
28 aed2325f Iustin Pop
29 aed2325f Iustin Pop
module Test.Ganeti.Luxi (testLuxi) where
30 aed2325f Iustin Pop
31 471b6c46 Iustin Pop
import Test.HUnit
32 aed2325f Iustin Pop
import Test.QuickCheck
33 aed2325f Iustin Pop
import Test.QuickCheck.Monadic (monadicIO, run, stop)
34 aed2325f Iustin Pop
35 471b6c46 Iustin Pop
import Data.List
36 aed2325f Iustin Pop
import Control.Applicative
37 aed2325f Iustin Pop
import Control.Concurrent (forkIO)
38 aed2325f Iustin Pop
import Control.Exception (bracket)
39 aed2325f Iustin Pop
import System.Directory (getTemporaryDirectory, removeFile)
40 aed2325f Iustin Pop
import System.IO (hClose, openTempFile)
41 aed2325f Iustin Pop
import qualified Text.JSON as J
42 aed2325f Iustin Pop
43 aed2325f Iustin Pop
import Test.Ganeti.TestHelper
44 aed2325f Iustin Pop
import Test.Ganeti.TestCommon
45 aed2325f Iustin Pop
import Test.Ganeti.Query.Language (genFilter)
46 aed2325f Iustin Pop
import Test.Ganeti.OpCodes ()
47 aed2325f Iustin Pop
48 aed2325f Iustin Pop
import Ganeti.BasicTypes
49 aed2325f Iustin Pop
import qualified Ganeti.Luxi as Luxi
50 aed2325f Iustin Pop
51 67e4fcf4 Iustin Pop
{-# ANN module "HLint: ignore Use camelCase" #-}
52 67e4fcf4 Iustin Pop
53 aed2325f Iustin Pop
-- * Luxi tests
54 aed2325f Iustin Pop
55 7022db83 Iustin Pop
$(genArbitrary ''Luxi.LuxiReq)
56 aed2325f Iustin Pop
57 aed2325f Iustin Pop
instance Arbitrary Luxi.LuxiOp where
58 aed2325f Iustin Pop
  arbitrary = do
59 aed2325f Iustin Pop
    lreq <- arbitrary
60 aed2325f Iustin Pop
    case lreq of
61 5006418e Iustin Pop
      Luxi.ReqQuery -> Luxi.Query <$> arbitrary <*> genFields <*> genFilter
62 5006418e Iustin Pop
      Luxi.ReqQueryFields -> Luxi.QueryFields <$> arbitrary <*> genFields
63 5006418e Iustin Pop
      Luxi.ReqQueryNodes -> Luxi.QueryNodes <$> listOf genFQDN <*>
64 5006418e Iustin Pop
                            genFields <*> arbitrary
65 aed2325f Iustin Pop
      Luxi.ReqQueryGroups -> Luxi.QueryGroups <$> arbitrary <*>
66 aed2325f Iustin Pop
                             arbitrary <*> arbitrary
67 5006418e Iustin Pop
      Luxi.ReqQueryInstances -> Luxi.QueryInstances <$> listOf genFQDN <*>
68 5006418e Iustin Pop
                                genFields <*> arbitrary
69 5006418e Iustin Pop
      Luxi.ReqQueryJobs -> Luxi.QueryJobs <$> arbitrary <*> genFields
70 aed2325f Iustin Pop
      Luxi.ReqQueryExports -> Luxi.QueryExports <$>
71 5006418e Iustin Pop
                              listOf genFQDN <*> arbitrary
72 5006418e Iustin Pop
      Luxi.ReqQueryConfigValues -> Luxi.QueryConfigValues <$> genFields
73 aed2325f Iustin Pop
      Luxi.ReqQueryClusterInfo -> pure Luxi.QueryClusterInfo
74 d8e7c45e Iustin Pop
      Luxi.ReqQueryTags -> Luxi.QueryTags <$> arbitrary
75 5b11f8db Iustin Pop
      Luxi.ReqSubmitJob -> Luxi.SubmitJob <$> resize maxOpCodes arbitrary
76 aed2325f Iustin Pop
      Luxi.ReqSubmitManyJobs -> Luxi.SubmitManyJobs <$>
77 5b11f8db Iustin Pop
                                resize maxOpCodes arbitrary
78 aed2325f Iustin Pop
      Luxi.ReqWaitForJobChange -> Luxi.WaitForJobChange <$> arbitrary <*>
79 5006418e Iustin Pop
                                  genFields <*> pure J.JSNull <*>
80 aed2325f Iustin Pop
                                  pure J.JSNull <*> arbitrary
81 aed2325f Iustin Pop
      Luxi.ReqArchiveJob -> Luxi.ArchiveJob <$> arbitrary
82 aed2325f Iustin Pop
      Luxi.ReqAutoArchiveJobs -> Luxi.AutoArchiveJobs <$> arbitrary <*>
83 aed2325f Iustin Pop
                                 arbitrary
84 aed2325f Iustin Pop
      Luxi.ReqCancelJob -> Luxi.CancelJob <$> arbitrary
85 f63ffb37 Michael Hanselmann
      Luxi.ReqChangeJobPriority -> Luxi.ChangeJobPriority <$> arbitrary <*>
86 f63ffb37 Michael Hanselmann
                                   arbitrary
87 aed2325f Iustin Pop
      Luxi.ReqSetDrainFlag -> Luxi.SetDrainFlag <$> arbitrary
88 aed2325f Iustin Pop
      Luxi.ReqSetWatcherPause -> Luxi.SetWatcherPause <$> arbitrary
89 aed2325f Iustin Pop
90 aed2325f Iustin Pop
-- | Simple check that encoding/decoding of LuxiOp works.
91 20bc5360 Iustin Pop
prop_CallEncoding :: Luxi.LuxiOp -> Property
92 20bc5360 Iustin Pop
prop_CallEncoding op =
93 aed2325f Iustin Pop
  (Luxi.validateCall (Luxi.buildCall op) >>= Luxi.decodeCall) ==? Ok op
94 aed2325f Iustin Pop
95 aed2325f Iustin Pop
-- | Helper to a get a temporary file name.
96 aed2325f Iustin Pop
getTempFileName :: IO FilePath
97 aed2325f Iustin Pop
getTempFileName = do
98 aed2325f Iustin Pop
  tempdir <- getTemporaryDirectory
99 aed2325f Iustin Pop
  (fpath, handle) <- openTempFile tempdir "luxitest"
100 aed2325f Iustin Pop
  _ <- hClose handle
101 aed2325f Iustin Pop
  removeFile fpath
102 aed2325f Iustin Pop
  return fpath
103 aed2325f Iustin Pop
104 aed2325f Iustin Pop
-- | Server ping-pong helper.
105 aed2325f Iustin Pop
luxiServerPong :: Luxi.Client -> IO ()
106 aed2325f Iustin Pop
luxiServerPong c = do
107 aed2325f Iustin Pop
  msg <- Luxi.recvMsgExt c
108 aed2325f Iustin Pop
  case msg of
109 aed2325f Iustin Pop
    Luxi.RecvOk m -> Luxi.sendMsg c m >> luxiServerPong c
110 aed2325f Iustin Pop
    _ -> return ()
111 aed2325f Iustin Pop
112 aed2325f Iustin Pop
-- | Client ping-pong helper.
113 aed2325f Iustin Pop
luxiClientPong :: Luxi.Client -> [String] -> IO [String]
114 aed2325f Iustin Pop
luxiClientPong c =
115 aed2325f Iustin Pop
  mapM (\m -> Luxi.sendMsg c m >> Luxi.recvMsg c)
116 aed2325f Iustin Pop
117 aed2325f Iustin Pop
-- | Monadic check that, given a server socket, we can connect via a
118 aed2325f Iustin Pop
-- client to it, and that we can send a list of arbitrary messages and
119 aed2325f Iustin Pop
-- get back what we sent.
120 20bc5360 Iustin Pop
prop_ClientServer :: [[DNSChar]] -> Property
121 20bc5360 Iustin Pop
prop_ClientServer dnschars = monadicIO $ do
122 aed2325f Iustin Pop
  let msgs = map (map dnsGetChar) dnschars
123 5b11f8db Iustin Pop
  fpath <- run getTempFileName
124 aed2325f Iustin Pop
  -- we need to create the server first, otherwise (if we do it in the
125 aed2325f Iustin Pop
  -- forked thread) the client could try to connect to it before it's
126 aed2325f Iustin Pop
  -- ready
127 aed2325f Iustin Pop
  server <- run $ Luxi.getServer fpath
128 aed2325f Iustin Pop
  -- fork the server responder
129 aed2325f Iustin Pop
  _ <- run . forkIO $
130 aed2325f Iustin Pop
    bracket
131 aed2325f Iustin Pop
      (Luxi.acceptClient server)
132 aed2325f Iustin Pop
      (\c -> Luxi.closeClient c >> Luxi.closeServer fpath server)
133 aed2325f Iustin Pop
      luxiServerPong
134 aed2325f Iustin Pop
  replies <- run $
135 aed2325f Iustin Pop
    bracket
136 aed2325f Iustin Pop
      (Luxi.getClient fpath)
137 aed2325f Iustin Pop
      Luxi.closeClient
138 5b11f8db Iustin Pop
      (`luxiClientPong` msgs)
139 aed2325f Iustin Pop
  stop $ replies ==? msgs
140 aed2325f Iustin Pop
141 471b6c46 Iustin Pop
-- | Check that Python and Haskell define the same Luxi requests list.
142 471b6c46 Iustin Pop
case_AllDefined :: Assertion
143 471b6c46 Iustin Pop
case_AllDefined = do
144 471b6c46 Iustin Pop
  py_stdout <- runPython "from ganeti import luxi\n\
145 471b6c46 Iustin Pop
                         \print '\\n'.join(luxi.REQ_ALL)" "" >>=
146 471b6c46 Iustin Pop
               checkPythonResult
147 471b6c46 Iustin Pop
  let py_ops = sort $ lines py_stdout
148 471b6c46 Iustin Pop
      hs_ops = Luxi.allLuxiCalls
149 471b6c46 Iustin Pop
      extra_py = py_ops \\ hs_ops
150 471b6c46 Iustin Pop
      extra_hs = hs_ops \\ py_ops
151 471b6c46 Iustin Pop
  assertBool ("Luxi calls missing from Haskell code:\n" ++
152 471b6c46 Iustin Pop
              unlines extra_py) (null extra_py)
153 471b6c46 Iustin Pop
  assertBool ("Extra Luxi calls in the Haskell code code:\n" ++
154 471b6c46 Iustin Pop
              unlines extra_hs) (null extra_hs)
155 471b6c46 Iustin Pop
156 471b6c46 Iustin Pop
157 aed2325f Iustin Pop
testSuite "Luxi"
158 20bc5360 Iustin Pop
          [ 'prop_CallEncoding
159 20bc5360 Iustin Pop
          , 'prop_ClientServer
160 471b6c46 Iustin Pop
          , 'case_AllDefined
161 aed2325f Iustin Pop
          ]