Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Query / Instance.hs @ efa0d4fd

History | View | Annotate | Download (4.9 kB)

1
{-# LANGUAGE TupleSections, TemplateHaskell #-}
2

    
3
{-| Unittests for Instance Queries.
4

    
5
-}
6

    
7
{-
8

    
9
Copyright (C) 2013 Google Inc.
10

    
11
This program is free software; you can redistribute it and/or modify
12
it under the terms of the GNU General Public License as published by
13
the Free Software Foundation; either version 2 of the License, or
14
(at your option) any later version.
15

    
16
This program is distributed in the hope that it will be useful, but
17
WITHOUT ANY WARRANTY; without even the implied warranty of
18
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19
General Public License for more details.
20

    
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.Query.Instance
30
  ( testQuery_Instance
31
  ) where
32

    
33
import qualified Data.Map as Map
34
import qualified Data.Set as Set
35

    
36
import Ganeti.JSON
37
import Ganeti.Objects
38
import Ganeti.Query.Instance
39
import Ganeti.Rpc
40
import Ganeti.Types
41

    
42
import Test.Ganeti.TestHelper
43
import Test.HUnit
44

    
45
{-# ANN module "HLint: ignore Use camelCase" #-}
46

    
47
-- | Creates an instance with the desired name, pnode uuid, and AdminState.
48
-- All other fields are placeholders.
49
createInstance :: String -> String -> AdminState -> Instance
50
createInstance name pnodeUuid adminState =
51
  Instance name pnodeUuid "" Kvm
52
    (GenericContainer Map.empty)
53
    (PartialBeParams Nothing Nothing Nothing Nothing Nothing Nothing)
54
    (GenericContainer Map.empty)
55
    adminState [] [] DTDrbd8 False Nothing 0.0 0.0 "" 0 Set.empty
56

    
57
-- | A fake InstanceInfo to be used to check values.
58
fakeInstanceInfo :: InstanceInfo
59
fakeInstanceInfo = InstanceInfo 0 "" 0 0
60

    
61
-- | Erroneous node response - the exact error does not matter.
62
responseError :: String -> (String, ERpcError a)
63
responseError name = (name, Left . RpcResultError $ "Insignificant error")
64

    
65
-- | Successful response - the error does not really matter.
66
responseSuccess :: String
67
                -> [String]
68
                -> (String, ERpcError RpcResultAllInstancesInfo)
69
responseSuccess name instNames = (name, Right .
70
  RpcResultAllInstancesInfo . map (, fakeInstanceInfo) $ instNames)
71

    
72
-- | The instance used for testing. Called Waldo as test cases involve trouble
73
-- finding information related to it.
74
waldoInstance :: Instance
75
waldoInstance = createInstance "Waldo" "prim" AdminUp
76

    
77
-- | Check that an error is thrown when the node is offline
78
case_nodeOffline :: Assertion
79
case_nodeOffline =
80
  let responses = [ responseError   "prim"
81
                  , responseError   "second"
82
                  , responseSuccess "node" ["NotWaldo", "DefinitelyNotWaldo"]
83
                  ]
84
  in case getInstanceInfo responses waldoInstance of
85
       Left _   -> return ()
86
       Right _  -> assertFailure
87
         "Error occurred when instance info is missing and node is offline"
88

    
89
-- | Check that a Right Nothing is returned when the node is online, yet no info
90
-- is present anywhere in the system.
91
case_nodeOnlineNoInfo :: Assertion
92
case_nodeOnlineNoInfo =
93
  let responses = [ responseSuccess "prim"   ["NotWaldo1"]
94
                  , responseSuccess "second" ["NotWaldo2"]
95
                  , responseError   "node"
96
                  ]
97
  in case getInstanceInfo responses waldoInstance of
98
       Left _         -> assertFailure
99
         "Error occurred when instance info could be found on primary"
100
       Right Nothing  -> return ()
101
       Right _        -> assertFailure
102
         "Some instance info found when none should be"
103

    
104
-- | Check the case when the info is on the primary node
105
case_infoOnPrimary :: Assertion
106
case_infoOnPrimary =
107
  let responses = [ responseSuccess "prim"   ["NotWaldo1", "Waldo"]
108
                  , responseSuccess "second" ["NotWaldo2"]
109
                  , responseSuccess "node"   ["NotWaldo3"]
110
                  ]
111
  in case getInstanceInfo responses waldoInstance of
112
       Left _                  -> assertFailure
113
         "Cannot retrieve instance info when present on primary node"
114
       Right (Just (_, True))  -> return ()
115
       Right _                 -> assertFailure
116
         "Instance info not found on primary node, despite being there"
117

    
118
-- | Check the case when the info is on the primary node
119
case_infoOnSecondary :: Assertion
120
case_infoOnSecondary =
121
  let responses = [ responseSuccess "prim"   ["NotWaldo1"]
122
                  , responseSuccess "second" ["Waldo", "NotWaldo2"]
123
                  , responseError   "node"
124
                  ]
125
  in case getInstanceInfo responses waldoInstance of
126
       Left _                   -> assertFailure
127
         "Cannot retrieve instance info when present on secondary node"
128
       Right (Just (_, False))  -> return ()
129
       Right _                  -> assertFailure
130
         "Instance info not found on secondary node, despite being there"
131

    
132
testSuite "Query_Instance"
133
  [ 'case_nodeOffline
134
  , 'case_nodeOnlineNoInfo
135
  , 'case_infoOnPrimary
136
  , 'case_infoOnSecondary
137
  ]