Statistics
| Branch: | Tag: | Revision:

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

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 qualified Text.JSON as J
40

    
41
import Test.Ganeti.TestHelper
42
import Test.Ganeti.TestCommon
43
import Test.Ganeti.Query.Language (genFilter)
44
import Test.Ganeti.OpCodes ()
45

    
46
import Ganeti.BasicTypes
47
import qualified Ganeti.Luxi as Luxi
48
import qualified Ganeti.UDSServer as US
49

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

    
52
-- * Luxi tests
53

    
54
$(genArbitrary ''Luxi.LuxiReq)
55

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

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

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

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

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

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

    
154

    
155
testSuite "Luxi"
156
          [ 'prop_CallEncoding
157
          , 'prop_ClientServer
158
          , 'case_AllDefined
159
          ]