Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (4.9 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 aed2325f Iustin Pop
import Test.QuickCheck
32 aed2325f Iustin Pop
import Test.QuickCheck.Monadic (monadicIO, run, stop)
33 aed2325f Iustin Pop
34 aed2325f Iustin Pop
import Control.Applicative
35 aed2325f Iustin Pop
import Control.Concurrent (forkIO)
36 aed2325f Iustin Pop
import Control.Exception (bracket)
37 aed2325f Iustin Pop
import System.Directory (getTemporaryDirectory, removeFile)
38 aed2325f Iustin Pop
import System.IO (hClose, openTempFile)
39 aed2325f Iustin Pop
import qualified Text.JSON as J
40 aed2325f Iustin Pop
41 aed2325f Iustin Pop
import Test.Ganeti.TestHelper
42 aed2325f Iustin Pop
import Test.Ganeti.TestCommon
43 aed2325f Iustin Pop
import Test.Ganeti.Query.Language (genFilter)
44 aed2325f Iustin Pop
import Test.Ganeti.OpCodes ()
45 aed2325f Iustin Pop
46 aed2325f Iustin Pop
import Ganeti.BasicTypes
47 aed2325f Iustin Pop
import qualified Ganeti.Luxi as Luxi
48 aed2325f Iustin Pop
49 aed2325f Iustin Pop
-- * Luxi tests
50 aed2325f Iustin Pop
51 7022db83 Iustin Pop
$(genArbitrary ''Luxi.TagObject)
52 aed2325f Iustin Pop
53 7022db83 Iustin Pop
$(genArbitrary ''Luxi.LuxiReq)
54 aed2325f Iustin Pop
55 aed2325f Iustin Pop
instance Arbitrary Luxi.LuxiOp where
56 aed2325f Iustin Pop
  arbitrary = do
57 aed2325f Iustin Pop
    lreq <- arbitrary
58 aed2325f Iustin Pop
    case lreq of
59 aed2325f Iustin Pop
      Luxi.ReqQuery -> Luxi.Query <$> arbitrary <*> getFields <*> genFilter
60 aed2325f Iustin Pop
      Luxi.ReqQueryFields -> Luxi.QueryFields <$> arbitrary <*> getFields
61 5b11f8db Iustin Pop
      Luxi.ReqQueryNodes -> Luxi.QueryNodes <$> listOf getFQDN <*>
62 aed2325f Iustin Pop
                            getFields <*> arbitrary
63 aed2325f Iustin Pop
      Luxi.ReqQueryGroups -> Luxi.QueryGroups <$> arbitrary <*>
64 aed2325f Iustin Pop
                             arbitrary <*> arbitrary
65 5b11f8db Iustin Pop
      Luxi.ReqQueryInstances -> Luxi.QueryInstances <$> listOf getFQDN <*>
66 aed2325f Iustin Pop
                                getFields <*> arbitrary
67 aed2325f Iustin Pop
      Luxi.ReqQueryJobs -> Luxi.QueryJobs <$> arbitrary <*> getFields
68 aed2325f Iustin Pop
      Luxi.ReqQueryExports -> Luxi.QueryExports <$>
69 5b11f8db Iustin Pop
                              listOf getFQDN <*> arbitrary
70 aed2325f Iustin Pop
      Luxi.ReqQueryConfigValues -> Luxi.QueryConfigValues <$> getFields
71 aed2325f Iustin Pop
      Luxi.ReqQueryClusterInfo -> pure Luxi.QueryClusterInfo
72 aed2325f Iustin Pop
      Luxi.ReqQueryTags -> Luxi.QueryTags <$> arbitrary <*> getFQDN
73 5b11f8db Iustin Pop
      Luxi.ReqSubmitJob -> Luxi.SubmitJob <$> resize maxOpCodes arbitrary
74 aed2325f Iustin Pop
      Luxi.ReqSubmitManyJobs -> Luxi.SubmitManyJobs <$>
75 5b11f8db Iustin Pop
                                resize maxOpCodes arbitrary
76 aed2325f Iustin Pop
      Luxi.ReqWaitForJobChange -> Luxi.WaitForJobChange <$> arbitrary <*>
77 aed2325f Iustin Pop
                                  getFields <*> pure J.JSNull <*>
78 aed2325f Iustin Pop
                                  pure J.JSNull <*> arbitrary
79 aed2325f Iustin Pop
      Luxi.ReqArchiveJob -> Luxi.ArchiveJob <$> arbitrary
80 aed2325f Iustin Pop
      Luxi.ReqAutoArchiveJobs -> Luxi.AutoArchiveJobs <$> arbitrary <*>
81 aed2325f Iustin Pop
                                 arbitrary
82 aed2325f Iustin Pop
      Luxi.ReqCancelJob -> Luxi.CancelJob <$> arbitrary
83 aed2325f Iustin Pop
      Luxi.ReqSetDrainFlag -> Luxi.SetDrainFlag <$> arbitrary
84 aed2325f Iustin Pop
      Luxi.ReqSetWatcherPause -> Luxi.SetWatcherPause <$> arbitrary
85 aed2325f Iustin Pop
86 aed2325f Iustin Pop
-- | Simple check that encoding/decoding of LuxiOp works.
87 20bc5360 Iustin Pop
prop_CallEncoding :: Luxi.LuxiOp -> Property
88 20bc5360 Iustin Pop
prop_CallEncoding op =
89 aed2325f Iustin Pop
  (Luxi.validateCall (Luxi.buildCall op) >>= Luxi.decodeCall) ==? Ok op
90 aed2325f Iustin Pop
91 aed2325f Iustin Pop
-- | Helper to a get a temporary file name.
92 aed2325f Iustin Pop
getTempFileName :: IO FilePath
93 aed2325f Iustin Pop
getTempFileName = do
94 aed2325f Iustin Pop
  tempdir <- getTemporaryDirectory
95 aed2325f Iustin Pop
  (fpath, handle) <- openTempFile tempdir "luxitest"
96 aed2325f Iustin Pop
  _ <- hClose handle
97 aed2325f Iustin Pop
  removeFile fpath
98 aed2325f Iustin Pop
  return fpath
99 aed2325f Iustin Pop
100 aed2325f Iustin Pop
-- | Server ping-pong helper.
101 aed2325f Iustin Pop
luxiServerPong :: Luxi.Client -> IO ()
102 aed2325f Iustin Pop
luxiServerPong c = do
103 aed2325f Iustin Pop
  msg <- Luxi.recvMsgExt c
104 aed2325f Iustin Pop
  case msg of
105 aed2325f Iustin Pop
    Luxi.RecvOk m -> Luxi.sendMsg c m >> luxiServerPong c
106 aed2325f Iustin Pop
    _ -> return ()
107 aed2325f Iustin Pop
108 aed2325f Iustin Pop
-- | Client ping-pong helper.
109 aed2325f Iustin Pop
luxiClientPong :: Luxi.Client -> [String] -> IO [String]
110 aed2325f Iustin Pop
luxiClientPong c =
111 aed2325f Iustin Pop
  mapM (\m -> Luxi.sendMsg c m >> Luxi.recvMsg c)
112 aed2325f Iustin Pop
113 aed2325f Iustin Pop
-- | Monadic check that, given a server socket, we can connect via a
114 aed2325f Iustin Pop
-- client to it, and that we can send a list of arbitrary messages and
115 aed2325f Iustin Pop
-- get back what we sent.
116 20bc5360 Iustin Pop
prop_ClientServer :: [[DNSChar]] -> Property
117 20bc5360 Iustin Pop
prop_ClientServer dnschars = monadicIO $ do
118 aed2325f Iustin Pop
  let msgs = map (map dnsGetChar) dnschars
119 5b11f8db Iustin Pop
  fpath <- run getTempFileName
120 aed2325f Iustin Pop
  -- we need to create the server first, otherwise (if we do it in the
121 aed2325f Iustin Pop
  -- forked thread) the client could try to connect to it before it's
122 aed2325f Iustin Pop
  -- ready
123 aed2325f Iustin Pop
  server <- run $ Luxi.getServer fpath
124 aed2325f Iustin Pop
  -- fork the server responder
125 aed2325f Iustin Pop
  _ <- run . forkIO $
126 aed2325f Iustin Pop
    bracket
127 aed2325f Iustin Pop
      (Luxi.acceptClient server)
128 aed2325f Iustin Pop
      (\c -> Luxi.closeClient c >> Luxi.closeServer fpath server)
129 aed2325f Iustin Pop
      luxiServerPong
130 aed2325f Iustin Pop
  replies <- run $
131 aed2325f Iustin Pop
    bracket
132 aed2325f Iustin Pop
      (Luxi.getClient fpath)
133 aed2325f Iustin Pop
      Luxi.closeClient
134 5b11f8db Iustin Pop
      (`luxiClientPong` msgs)
135 aed2325f Iustin Pop
  stop $ replies ==? msgs
136 aed2325f Iustin Pop
137 aed2325f Iustin Pop
testSuite "Luxi"
138 20bc5360 Iustin Pop
          [ 'prop_CallEncoding
139 20bc5360 Iustin Pop
          , 'prop_ClientServer
140 aed2325f Iustin Pop
          ]