Split Luxi, Qlang, Ssconf and OpCodes tests
[ganeti-local] / htest / Test / Ganeti / Rpc.hs
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.Rpc (testRpc) where
30
31 import Test.QuickCheck
32 import Test.QuickCheck.Monadic (monadicIO, run, stop)
33
34 import Control.Applicative
35
36 import Test.Ganeti.TestHelper
37 import Test.Ganeti.TestCommon
38 import Test.Ganeti.Objects ()
39
40 import qualified Ganeti.Rpc as Rpc
41 import qualified Ganeti.Objects as Objects
42
43 instance Arbitrary Rpc.RpcCallAllInstancesInfo where
44   arbitrary = Rpc.RpcCallAllInstancesInfo <$> arbitrary
45
46 instance Arbitrary Rpc.RpcCallInstanceList where
47   arbitrary = Rpc.RpcCallInstanceList <$> arbitrary
48
49 instance Arbitrary Rpc.RpcCallNodeInfo where
50   arbitrary = Rpc.RpcCallNodeInfo <$> arbitrary <*> arbitrary
51
52 -- | Monadic check that, for an offline node and a call that does not
53 -- offline nodes, we get a OfflineNodeError response.
54 -- FIXME: We need a way of generalizing this, running it for
55 -- every call manually will soon get problematic
56 prop_Rpc_noffl_request_allinstinfo :: Rpc.RpcCallAllInstancesInfo -> Property
57 prop_Rpc_noffl_request_allinstinfo call =
58   forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
59       res <- run $ Rpc.executeRpcCall [node] call
60       stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
61
62 prop_Rpc_noffl_request_instlist :: Rpc.RpcCallInstanceList -> Property
63 prop_Rpc_noffl_request_instlist call =
64   forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
65       res <- run $ Rpc.executeRpcCall [node] call
66       stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
67
68 prop_Rpc_noffl_request_nodeinfo :: Rpc.RpcCallNodeInfo -> Property
69 prop_Rpc_noffl_request_nodeinfo call =
70   forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
71       res <- run $ Rpc.executeRpcCall [node] call
72       stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
73
74 testSuite "Rpc"
75   [ 'prop_Rpc_noffl_request_allinstinfo
76   , 'prop_Rpc_noffl_request_instlist
77   , 'prop_Rpc_noffl_request_nodeinfo
78   ]