Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / TestHTools.hs @ e1ee7d5a

History | View | Annotate | Download (4.8 kB)

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

    
4
{-| Common functionality for htools-related unittests.
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.TestHTools where
30

    
31
import Test.QuickCheck
32

    
33
import qualified Data.Map as Map
34

    
35
import Test.Ganeti.TestCommon
36

    
37
import qualified Ganeti.Constants as C
38
import qualified Ganeti.HTools.Container as Container
39
import qualified Ganeti.HTools.Group as Group
40
import qualified Ganeti.HTools.Instance as Instance
41
import qualified Ganeti.HTools.Loader as Loader
42
import qualified Ganeti.HTools.Node as Node
43
import qualified Ganeti.HTools.Types as Types
44

    
45
-- * Helpers
46

    
47
-- | Null iPolicy, and by null we mean very liberal.
48
nullIPolicy :: Types.IPolicy
49
nullIPolicy = Types.IPolicy
50
  { Types.iPolicyMinSpec = Types.ISpec { Types.iSpecMemorySize = 0
51
                                       , Types.iSpecCpuCount   = 0
52
                                       , Types.iSpecDiskSize   = 0
53
                                       , Types.iSpecDiskCount  = 0
54
                                       , Types.iSpecNicCount   = 0
55
                                       , Types.iSpecSpindleUse = 0
56
                                       }
57
  , Types.iPolicyMaxSpec = Types.ISpec { Types.iSpecMemorySize = maxBound
58
                                       , Types.iSpecCpuCount   = maxBound
59
                                       , Types.iSpecDiskSize   = maxBound
60
                                       , Types.iSpecDiskCount  = C.maxDisks
61
                                       , Types.iSpecNicCount   = C.maxNics
62
                                       , Types.iSpecSpindleUse = maxBound
63
                                       }
64
  , Types.iPolicyStdSpec = Types.ISpec { Types.iSpecMemorySize = Types.unitMem
65
                                       , Types.iSpecCpuCount   = Types.unitCpu
66
                                       , Types.iSpecDiskSize   = Types.unitDsk
67
                                       , Types.iSpecDiskCount  = 1
68
                                       , Types.iSpecNicCount   = 1
69
                                       , Types.iSpecSpindleUse = 1
70
                                       }
71
  , Types.iPolicyDiskTemplates = [minBound..maxBound]
72
  , Types.iPolicyVcpuRatio = maxVcpuRatio -- somewhat random value, high
73
                                          -- enough to not impact us
74
  , Types.iPolicySpindleRatio = maxSpindleRatio
75
  }
76

    
77
defGroup :: Group.Group
78
defGroup = flip Group.setIdx 0 $
79
             Group.create "default" Types.defaultGroupID Types.AllocPreferred
80
                  nullIPolicy
81

    
82
defGroupList :: Group.List
83
defGroupList = Container.fromList [(Group.idx defGroup, defGroup)]
84

    
85
defGroupAssoc :: Map.Map String Types.Gdx
86
defGroupAssoc = Map.singleton (Group.uuid defGroup) (Group.idx defGroup)
87

    
88
-- | Simple checker for whether OpResult is fail or pass.
89
isFailure :: Types.OpResult a -> Bool
90
isFailure (Types.OpFail _) = True
91
isFailure _ = False
92

    
93
-- | Create an instance given its spec.
94
createInstance :: Int -> Int -> Int -> Instance.Instance
95
createInstance mem dsk vcpus =
96
  Instance.create "inst-unnamed" mem dsk vcpus Types.Running [] True (-1) (-1)
97
    Types.DTDrbd8 1
98

    
99
-- | Create a small cluster by repeating a node spec.
100
makeSmallCluster :: Node.Node -> Int -> Node.List
101
makeSmallCluster node count =
102
  let origname = Node.name node
103
      origalias = Node.alias node
104
      nodes = map (\idx -> node { Node.name = origname ++ "-" ++ show idx
105
                                , Node.alias = origalias ++ "-" ++ show idx })
106
              [1..count]
107
      fn = flip Node.buildPeers Container.empty
108
      namelst = map (\n -> (Node.name n, fn n)) nodes
109
      (_, nlst) = Loader.assignIndices namelst
110
  in nlst
111

    
112
-- | Update an instance to be smaller than a node.
113
setInstanceSmallerThanNode :: Node.Node
114
                           -> Instance.Instance -> Instance.Instance
115
setInstanceSmallerThanNode node inst =
116
  inst { Instance.mem = Node.availMem node `div` 2
117
       , Instance.dsk = Node.availDisk node `div` 2
118
       , Instance.vcpus = Node.availCpu node `div` 2
119
       }
120

    
121
-- * Arbitrary instances
122

    
123
instance Arbitrary Types.InstanceStatus where
124
    arbitrary = elements [minBound..maxBound]