Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / Luxi.hs @ da1dcce1

History | View | Annotate | Download (5.7 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2
{-# OPTIONS_GHC -fno-warn-orphans #-}
3

    
4
{-| Unittests for ganeti-htools.
5

    
6
-}
7

    
8
{-
9

    
10
Copyright (C) 2009, 2010, 2011, 2012 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.Luxi (testLuxi) where
30

    
31
import Test.HUnit
32
import Test.QuickCheck
33
import Test.QuickCheck.Monadic (monadicIO, run, stop)
34

    
35
import Data.List
36
import Control.Applicative
37
import Control.Concurrent (forkIO)
38
import Control.Exception (bracket)
39
import System.Directory (getTemporaryDirectory, removeFile)
40
import System.IO (hClose, openTempFile)
41
import qualified Text.JSON as J
42

    
43
import Test.Ganeti.TestHelper
44
import Test.Ganeti.TestCommon
45
import Test.Ganeti.Query.Language (genFilter)
46
import Test.Ganeti.OpCodes ()
47

    
48
import Ganeti.BasicTypes
49
import qualified Ganeti.Luxi as Luxi
50

    
51
{-# ANN module "HLint: ignore Use camelCase" #-}
52

    
53
-- * Luxi tests
54

    
55
$(genArbitrary ''Luxi.LuxiReq)
56

    
57
instance Arbitrary Luxi.LuxiOp where
58
  arbitrary = do
59
    lreq <- arbitrary
60
    case lreq of
61
      Luxi.ReqQuery -> Luxi.Query <$> arbitrary <*> genFields <*> genFilter
62
      Luxi.ReqQueryFields -> Luxi.QueryFields <$> arbitrary <*> genFields
63
      Luxi.ReqQueryNodes -> Luxi.QueryNodes <$> listOf genFQDN <*>
64
                            genFields <*> arbitrary
65
      Luxi.ReqQueryGroups -> Luxi.QueryGroups <$> arbitrary <*>
66
                             arbitrary <*> arbitrary
67
      Luxi.ReqQueryInstances -> Luxi.QueryInstances <$> listOf genFQDN <*>
68
                                genFields <*> arbitrary
69
      Luxi.ReqQueryJobs -> Luxi.QueryJobs <$> arbitrary <*> genFields
70
      Luxi.ReqQueryExports -> Luxi.QueryExports <$>
71
                              listOf genFQDN <*> arbitrary
72
      Luxi.ReqQueryConfigValues -> Luxi.QueryConfigValues <$> genFields
73
      Luxi.ReqQueryClusterInfo -> pure Luxi.QueryClusterInfo
74
      Luxi.ReqQueryTags -> Luxi.QueryTags <$> arbitrary
75
      Luxi.ReqSubmitJob -> Luxi.SubmitJob <$> resize maxOpCodes arbitrary
76
      Luxi.ReqSubmitManyJobs -> Luxi.SubmitManyJobs <$>
77
                                resize maxOpCodes arbitrary
78
      Luxi.ReqWaitForJobChange -> Luxi.WaitForJobChange <$> arbitrary <*>
79
                                  genFields <*> pure J.JSNull <*>
80
                                  pure J.JSNull <*> arbitrary
81
      Luxi.ReqArchiveJob -> Luxi.ArchiveJob <$> arbitrary
82
      Luxi.ReqAutoArchiveJobs -> Luxi.AutoArchiveJobs <$> arbitrary <*>
83
                                 arbitrary
84
      Luxi.ReqCancelJob -> Luxi.CancelJob <$> arbitrary
85
      Luxi.ReqChangeJobPriority -> Luxi.ChangeJobPriority <$> arbitrary <*>
86
                                   arbitrary
87
      Luxi.ReqSetDrainFlag -> Luxi.SetDrainFlag <$> arbitrary
88
      Luxi.ReqSetWatcherPause -> Luxi.SetWatcherPause <$> arbitrary
89

    
90
-- | Simple check that encoding/decoding of LuxiOp works.
91
prop_CallEncoding :: Luxi.LuxiOp -> Property
92
prop_CallEncoding op =
93
  (Luxi.validateCall (Luxi.buildCall op) >>= Luxi.decodeCall) ==? Ok op
94

    
95
-- | Helper to a get a temporary file name.
96
getTempFileName :: IO FilePath
97
getTempFileName = do
98
  tempdir <- getTemporaryDirectory
99
  (fpath, handle) <- openTempFile tempdir "luxitest"
100
  _ <- hClose handle
101
  removeFile fpath
102
  return fpath
103

    
104
-- | Server ping-pong helper.
105
luxiServerPong :: Luxi.Client -> IO ()
106
luxiServerPong c = do
107
  msg <- Luxi.recvMsgExt c
108
  case msg of
109
    Luxi.RecvOk m -> Luxi.sendMsg c m >> luxiServerPong c
110
    _ -> return ()
111

    
112
-- | Client ping-pong helper.
113
luxiClientPong :: Luxi.Client -> [String] -> IO [String]
114
luxiClientPong c =
115
  mapM (\m -> Luxi.sendMsg c m >> Luxi.recvMsg c)
116

    
117
-- | Monadic check that, given a server socket, we can connect via a
118
-- client to it, and that we can send a list of arbitrary messages and
119
-- get back what we sent.
120
prop_ClientServer :: [[DNSChar]] -> Property
121
prop_ClientServer dnschars = monadicIO $ do
122
  let msgs = map (map dnsGetChar) dnschars
123
  fpath <- run getTempFileName
124
  -- we need to create the server first, otherwise (if we do it in the
125
  -- forked thread) the client could try to connect to it before it's
126
  -- ready
127
  server <- run $ Luxi.getServer fpath
128
  -- fork the server responder
129
  _ <- run . forkIO $
130
    bracket
131
      (Luxi.acceptClient server)
132
      (\c -> Luxi.closeClient c >> Luxi.closeServer fpath server)
133
      luxiServerPong
134
  replies <- run $
135
    bracket
136
      (Luxi.getClient fpath)
137
      Luxi.closeClient
138
      (`luxiClientPong` msgs)
139
  stop $ replies ==? msgs
140

    
141
-- | Check that Python and Haskell define the same Luxi requests list.
142
case_AllDefined :: Assertion
143
case_AllDefined = do
144
  py_stdout <- runPython "from ganeti import luxi\n\
145
                         \print '\\n'.join(luxi.REQ_ALL)" "" >>=
146
               checkPythonResult
147
  let py_ops = sort $ lines py_stdout
148
      hs_ops = Luxi.allLuxiCalls
149
      extra_py = py_ops \\ hs_ops
150
      extra_hs = hs_ops \\ py_ops
151
  assertBool ("Luxi calls missing from Haskell code:\n" ++
152
              unlines extra_py) (null extra_py)
153
  assertBool ("Extra Luxi calls in the Haskell code code:\n" ++
154
              unlines extra_hs) (null extra_hs)
155

    
156

    
157
testSuite "Luxi"
158
          [ 'prop_CallEncoding
159
          , 'prop_ClientServer
160
          , 'case_AllDefined
161
          ]