Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Rpc.hs @ 030ab01a

History | View | Annotate | Download (3.2 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, 2013 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
import qualified Data.Map as Map
36

    
37
import Test.Ganeti.TestHelper
38
import Test.Ganeti.TestCommon
39
import Test.Ganeti.Objects ()
40

    
41
import qualified Ganeti.Rpc as Rpc
42
import qualified Ganeti.Objects as Objects
43
import qualified Ganeti.Types as Types
44
import qualified Ganeti.JSON as JSON
45

    
46
instance Arbitrary Rpc.RpcCallAllInstancesInfo where
47
  arbitrary = Rpc.RpcCallAllInstancesInfo <$> arbitrary
48

    
49
instance Arbitrary Rpc.RpcCallInstanceList where
50
  arbitrary = Rpc.RpcCallInstanceList <$> arbitrary
51

    
52
instance Arbitrary Rpc.RpcCallNodeInfo where
53
  arbitrary = Rpc.RpcCallNodeInfo <$> arbitrary <*> genHvSpecs <*>
54
                pure Map.empty
55

    
56
-- | Generate hypervisor specifications to be used for the NodeInfo call
57
genHvSpecs :: Gen [ (Types.Hypervisor, Objects.HvParams) ]
58
genHvSpecs = do
59
  numhv <- choose (0, 5)
60
  hvs <- vectorOf numhv arbitrary
61
  hvparams <- vectorOf numhv genHvParams
62
  let specs = zip hvs hvparams
63
  return specs
64

    
65
-- FIXME: Generate more interesting hvparams
66
-- | Generate Hvparams
67
genHvParams :: Gen Objects.HvParams
68
genHvParams = return $ JSON.GenericContainer Map.empty
69

    
70
-- | Monadic check that, for an offline node and a call that does not
71
-- offline nodes, we get a OfflineNodeError response.
72
-- FIXME: We need a way of generalizing this, running it for
73
-- every call manually will soon get problematic
74
prop_noffl_request_allinstinfo :: Rpc.RpcCallAllInstancesInfo -> Property
75
prop_noffl_request_allinstinfo call =
76
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
77
      res <- run $ Rpc.executeRpcCall [node] call
78
      stop $ res ==? [(node, Left Rpc.OfflineNodeError)]
79

    
80
prop_noffl_request_instlist :: Rpc.RpcCallInstanceList -> Property
81
prop_noffl_request_instlist call =
82
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
83
      res <- run $ Rpc.executeRpcCall [node] call
84
      stop $ res ==? [(node, Left Rpc.OfflineNodeError)]
85

    
86
prop_noffl_request_nodeinfo :: Rpc.RpcCallNodeInfo -> Property
87
prop_noffl_request_nodeinfo call =
88
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
89
      res <- run $ Rpc.executeRpcCall [node] call
90
      stop $ res ==? [(node, Left Rpc.OfflineNodeError)]
91

    
92
testSuite "Rpc"
93
  [ 'prop_noffl_request_allinstinfo
94
  , 'prop_noffl_request_instlist
95
  , 'prop_noffl_request_nodeinfo
96
  ]