Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Rpc.hs @ c14ba680

History | View | Annotate | Download (3.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, 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
import Ganeti.Types
46

    
47
genStorageUnit :: Gen StorageUnit
48
genStorageUnit = do
49
  storage_type <- arbitrary
50
  storage_key <- genName
51
  storage_es <- arbitrary
52
  return $ addParamsToStorageUnit storage_es (SURaw storage_type storage_key)
53

    
54
genStorageUnits :: Gen [StorageUnit]
55
genStorageUnits = do
56
  num_storage_units <- choose (0, 5)
57
  vectorOf num_storage_units genStorageUnit
58

    
59
genStorageUnitMap :: Gen (Map.Map String [StorageUnit])
60
genStorageUnitMap = do
61
  num_nodes <- choose (0,5)
62
  node_uuids <- vectorOf num_nodes genName
63
  storage_units_list <- vectorOf num_nodes genStorageUnits
64
  return $ Map.fromList (zip node_uuids storage_units_list)
65

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

    
71
-- | Generate hypervisor specifications to be used for the NodeInfo call
72
genHvSpecs :: Gen [(Types.Hypervisor, Objects.HvParams)]
73
genHvSpecs = do
74
  numhv <- choose (0, 5)
75
  hvs <- vectorOf numhv arbitrary
76
  hvparams <- vectorOf numhv genHvParams
77
  let specs = zip hvs hvparams
78
  return specs
79

    
80
instance Arbitrary Rpc.RpcCallAllInstancesInfo where
81
  arbitrary = Rpc.RpcCallAllInstancesInfo <$> genHvSpecs
82

    
83
instance Arbitrary Rpc.RpcCallInstanceList where
84
  arbitrary = Rpc.RpcCallInstanceList <$> arbitrary
85

    
86
instance Arbitrary Rpc.RpcCallNodeInfo where
87
  arbitrary = Rpc.RpcCallNodeInfo <$> genStorageUnitMap <*> genHvSpecs
88

    
89
-- | Monadic check that, for an offline node and a call that does not
90
-- offline nodes, we get a OfflineNodeError response.
91
-- FIXME: We need a way of generalizing this, running it for
92
-- every call manually will soon get problematic
93
prop_noffl_request_allinstinfo :: Rpc.RpcCallAllInstancesInfo -> Property
94
prop_noffl_request_allinstinfo call =
95
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
96
      res <- run $ Rpc.executeRpcCall [node] call
97
      stop $ res ==? [(node, Left Rpc.OfflineNodeError)]
98

    
99
prop_noffl_request_instlist :: Rpc.RpcCallInstanceList -> Property
100
prop_noffl_request_instlist call =
101
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
102
      res <- run $ Rpc.executeRpcCall [node] call
103
      stop $ res ==? [(node, Left Rpc.OfflineNodeError)]
104

    
105
prop_noffl_request_nodeinfo :: Rpc.RpcCallNodeInfo -> Property
106
prop_noffl_request_nodeinfo call =
107
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
108
      res <- run $ Rpc.executeRpcCall [node] call
109
      stop $ res ==? [(node, Left Rpc.OfflineNodeError)]
110

    
111
testSuite "Rpc"
112
  [ 'prop_noffl_request_allinstinfo
113
  , 'prop_noffl_request_instlist
114
  , 'prop_noffl_request_nodeinfo
115
  ]