Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (6.1 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
import qualified Ganeti.UDSServer as US
51

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

    
54
-- * Luxi tests
55

    
56
$(genArbitrary ''Luxi.LuxiReq)
57

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

    
98
-- | Simple check that encoding/decoding of LuxiOp works.
99
prop_CallEncoding :: Luxi.LuxiOp -> Property
100
prop_CallEncoding op =
101
  (US.parseCall (Luxi.buildCall op) >>= uncurry Luxi.decodeLuxiCall) ==? Ok op
102

    
103
-- | Helper to a get a temporary file name.
104
getTempFileName :: IO FilePath
105
getTempFileName = do
106
  tempdir <- getTemporaryDirectory
107
  (fpath, handle) <- openTempFile tempdir "luxitest"
108
  _ <- hClose handle
109
  removeFile fpath
110
  return fpath
111

    
112
-- | Server ping-pong helper.
113
luxiServerPong :: Luxi.Client -> IO ()
114
luxiServerPong c = do
115
  msg <- Luxi.recvMsgExt c
116
  case msg of
117
    Luxi.RecvOk m -> Luxi.sendMsg c m >> luxiServerPong c
118
    _ -> return ()
119

    
120
-- | Client ping-pong helper.
121
luxiClientPong :: Luxi.Client -> [String] -> IO [String]
122
luxiClientPong c =
123
  mapM (\m -> Luxi.sendMsg c m >> Luxi.recvMsg c)
124

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

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

    
164

    
165
testSuite "Luxi"
166
          [ 'prop_CallEncoding
167
          , 'prop_ClientServer
168
          , 'case_AllDefined
169
          ]