Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Luxi.hs @ e455a3e8

History | View | Annotate | Download (5.8 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.ReqQueryNetworks -> Luxi.QueryNetworks <$> arbitrary <*>
68
                             arbitrary <*> arbitrary
69
      Luxi.ReqQueryInstances -> Luxi.QueryInstances <$> listOf genFQDN <*>
70
                                genFields <*> arbitrary
71
      Luxi.ReqQueryJobs -> Luxi.QueryJobs <$> arbitrary <*> genFields
72
      Luxi.ReqQueryExports -> Luxi.QueryExports <$>
73
                              listOf genFQDN <*> arbitrary
74
      Luxi.ReqQueryConfigValues -> Luxi.QueryConfigValues <$> genFields
75
      Luxi.ReqQueryClusterInfo -> pure Luxi.QueryClusterInfo
76
      Luxi.ReqQueryTags -> Luxi.QueryTags <$> arbitrary
77
      Luxi.ReqSubmitJob -> Luxi.SubmitJob <$> resize maxOpCodes arbitrary
78
      Luxi.ReqSubmitManyJobs -> Luxi.SubmitManyJobs <$>
79
                                resize maxOpCodes arbitrary
80
      Luxi.ReqWaitForJobChange -> Luxi.WaitForJobChange <$> arbitrary <*>
81
                                  genFields <*> pure J.JSNull <*>
82
                                  pure J.JSNull <*> arbitrary
83
      Luxi.ReqArchiveJob -> Luxi.ArchiveJob <$> arbitrary
84
      Luxi.ReqAutoArchiveJobs -> Luxi.AutoArchiveJobs <$> arbitrary <*>
85
                                 arbitrary
86
      Luxi.ReqCancelJob -> Luxi.CancelJob <$> arbitrary
87
      Luxi.ReqChangeJobPriority -> Luxi.ChangeJobPriority <$> arbitrary <*>
88
                                   arbitrary
89
      Luxi.ReqSetDrainFlag -> Luxi.SetDrainFlag <$> arbitrary
90
      Luxi.ReqSetWatcherPause -> Luxi.SetWatcherPause <$> arbitrary
91

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

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

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

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

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

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

    
158

    
159
testSuite "Luxi"
160
          [ 'prop_CallEncoding
161
          , 'prop_ClientServer
162
          , 'case_AllDefined
163
          ]