Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Query / Network.hs @ b54ecf12

History | View | Annotate | Download (2.9 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2
{-# OPTIONS_GHC -fno-warn-orphans #-}
3

    
4
{-| Unittests for Network Queries.
5

    
6
-}
7

    
8
{-
9

    
10
Copyright (C) 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.Query.Network
30
  ( testQuery_Network
31
  ) where
32

    
33
import Ganeti.JSON
34
import Ganeti.Objects
35
import Ganeti.Query.Network
36
import Ganeti.Types
37

    
38
import Test.Ganeti.Objects
39
import Test.Ganeti.TestCommon
40
import Test.Ganeti.TestHelper
41

    
42
import Test.QuickCheck
43

    
44
import qualified Data.Map as Map
45
import Data.Maybe
46

    
47
instance Arbitrary ConfigData where
48
  arbitrary = genEmptyCluster 0 >>= genConfigDataWithNetworks
49

    
50
-- | Check if looking up a valid network ID of a nodegroup yields
51
-- a non-Nothing result.
52
prop_getGroupConnection :: NodeGroup -> Property
53
prop_getGroupConnection group =
54
  let net_keys = (Map.keys . fromContainer . groupNetworks) group
55
  in True ==? all
56
    (\nk -> isJust (getGroupConnection nk group)) net_keys
57

    
58
-- | Checks if looking up an ID of a non-existing network in a node group
59
-- yields 'Nothing'.
60
prop_getGroupConnection_notFound :: NodeGroup -> String -> Property
61
prop_getGroupConnection_notFound group uuid =
62
  let net_keys = (Map.keys . fromContainer . groupNetworks) group
63
  in notElem uuid net_keys ==> isNothing (getGroupConnection uuid group)
64

    
65
-- | Checks whether actually connected instances are identified as such.
66
prop_instIsConnected :: ConfigData -> Property
67
prop_instIsConnected cfg =
68
  let nets = (fromContainer . configNetworks) cfg
69
      net_keys = Map.keys nets
70
      net_names = map (fromNonEmpty . networkName) (Map.elems nets)
71
  in  forAll (genInstWithNets net_names) $ \inst ->
72
      True ==? all (\nk -> instIsConnected cfg nk inst) net_keys
73

    
74
-- | Tests whether instances that are not connected to a network are
75
-- correctly classified as such.
76
prop_instIsConnected_notFound :: ConfigData -> String -> Property
77
prop_instIsConnected_notFound cfg network_uuid =
78
  let nets = (fromContainer . configNetworks) cfg
79
      net_keys = Map.keys nets
80
      net_names = map (fromNonEmpty . networkName) (Map.elems nets)
81
  in  notElem network_uuid net_keys ==>
82
      forAll (genInstWithNets net_names) $ \inst ->
83
        not (instIsConnected cfg network_uuid inst)
84

    
85
testSuite "Query_Network"
86
  [ 'prop_getGroupConnection
87
  , 'prop_getGroupConnection_notFound
88
  , 'prop_instIsConnected
89
  , 'prop_instIsConnected_notFound
90
  ]
91

    
92