Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / Rpc.hs @ 61899e64

History | View | Annotate | Download (2.7 kB)

1 305e174c Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 305e174c Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 305e174c Iustin Pop
4 305e174c Iustin Pop
{-| Unittests for ganeti-htools.
5 305e174c Iustin Pop
6 305e174c Iustin Pop
-}
7 305e174c Iustin Pop
8 305e174c Iustin Pop
{-
9 305e174c Iustin Pop
10 305e174c Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11 305e174c Iustin Pop
12 305e174c Iustin Pop
This program is free software; you can redistribute it and/or modify
13 305e174c Iustin Pop
it under the terms of the GNU General Public License as published by
14 305e174c Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 305e174c Iustin Pop
(at your option) any later version.
16 305e174c Iustin Pop
17 305e174c Iustin Pop
This program is distributed in the hope that it will be useful, but
18 305e174c Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 305e174c Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 305e174c Iustin Pop
General Public License for more details.
21 305e174c Iustin Pop
22 305e174c Iustin Pop
You should have received a copy of the GNU General Public License
23 305e174c Iustin Pop
along with this program; if not, write to the Free Software
24 305e174c Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 305e174c Iustin Pop
02110-1301, USA.
26 305e174c Iustin Pop
27 305e174c Iustin Pop
-}
28 305e174c Iustin Pop
29 305e174c Iustin Pop
module Test.Ganeti.Rpc (testRpc) where
30 305e174c Iustin Pop
31 305e174c Iustin Pop
import Test.QuickCheck
32 305e174c Iustin Pop
import Test.QuickCheck.Monadic (monadicIO, run, stop)
33 305e174c Iustin Pop
34 305e174c Iustin Pop
import Control.Applicative
35 305e174c Iustin Pop
36 305e174c Iustin Pop
import Test.Ganeti.TestHelper
37 305e174c Iustin Pop
import Test.Ganeti.TestCommon
38 305e174c Iustin Pop
import Test.Ganeti.Objects ()
39 305e174c Iustin Pop
40 305e174c Iustin Pop
import qualified Ganeti.Rpc as Rpc
41 305e174c Iustin Pop
import qualified Ganeti.Objects as Objects
42 305e174c Iustin Pop
43 305e174c Iustin Pop
instance Arbitrary Rpc.RpcCallAllInstancesInfo where
44 305e174c Iustin Pop
  arbitrary = Rpc.RpcCallAllInstancesInfo <$> arbitrary
45 305e174c Iustin Pop
46 305e174c Iustin Pop
instance Arbitrary Rpc.RpcCallInstanceList where
47 305e174c Iustin Pop
  arbitrary = Rpc.RpcCallInstanceList <$> arbitrary
48 305e174c Iustin Pop
49 305e174c Iustin Pop
instance Arbitrary Rpc.RpcCallNodeInfo where
50 305e174c Iustin Pop
  arbitrary = Rpc.RpcCallNodeInfo <$> arbitrary <*> arbitrary
51 305e174c Iustin Pop
52 305e174c Iustin Pop
-- | Monadic check that, for an offline node and a call that does not
53 305e174c Iustin Pop
-- offline nodes, we get a OfflineNodeError response.
54 305e174c Iustin Pop
-- FIXME: We need a way of generalizing this, running it for
55 305e174c Iustin Pop
-- every call manually will soon get problematic
56 20bc5360 Iustin Pop
prop_noffl_request_allinstinfo :: Rpc.RpcCallAllInstancesInfo -> Property
57 20bc5360 Iustin Pop
prop_noffl_request_allinstinfo call =
58 305e174c Iustin Pop
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
59 305e174c Iustin Pop
      res <- run $ Rpc.executeRpcCall [node] call
60 305e174c Iustin Pop
      stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
61 305e174c Iustin Pop
62 20bc5360 Iustin Pop
prop_noffl_request_instlist :: Rpc.RpcCallInstanceList -> Property
63 20bc5360 Iustin Pop
prop_noffl_request_instlist call =
64 305e174c Iustin Pop
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
65 305e174c Iustin Pop
      res <- run $ Rpc.executeRpcCall [node] call
66 305e174c Iustin Pop
      stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
67 305e174c Iustin Pop
68 20bc5360 Iustin Pop
prop_noffl_request_nodeinfo :: Rpc.RpcCallNodeInfo -> Property
69 20bc5360 Iustin Pop
prop_noffl_request_nodeinfo call =
70 305e174c Iustin Pop
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
71 305e174c Iustin Pop
      res <- run $ Rpc.executeRpcCall [node] call
72 305e174c Iustin Pop
      stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
73 305e174c Iustin Pop
74 305e174c Iustin Pop
testSuite "Rpc"
75 20bc5360 Iustin Pop
  [ 'prop_noffl_request_allinstinfo
76 20bc5360 Iustin Pop
  , 'prop_noffl_request_instlist
77 20bc5360 Iustin Pop
  , 'prop_noffl_request_nodeinfo
78 305e174c Iustin Pop
  ]