Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / HTools / Backend / Text.hs @ ef947a42

History | View | Annotate | Download (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 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.HTools.Backend.Text (testHTools_Backend_Text) where
30

    
31
import Test.QuickCheck
32

    
33
import qualified Data.Map as Map
34
import Data.List
35
import Data.Maybe
36
import System.Time (ClockTime(..))
37

    
38
import Test.Ganeti.TestHelper
39
import Test.Ganeti.TestCommon
40
import Test.Ganeti.TestHTools
41
import Test.Ganeti.HTools.Instance (genInstanceSmallerThanNode)
42
import Test.Ganeti.HTools.Node (genNode, genOnlineNode)
43

    
44
import Ganeti.BasicTypes
45
import qualified Ganeti.HTools.Backend.Text as Text
46
import qualified Ganeti.HTools.Cluster as Cluster
47
import qualified Ganeti.HTools.Container as Container
48
import qualified Ganeti.HTools.Group as Group
49
import qualified Ganeti.HTools.Instance as Instance
50
import qualified Ganeti.HTools.Loader as Loader
51
import qualified Ganeti.HTools.Node as Node
52
import qualified Ganeti.HTools.Types as Types
53
import qualified Ganeti.Utils as Utils
54

    
55
-- * Instance text loader tests
56

    
57
prop_Load_Instance :: String -> Int -> Int -> Int -> Types.InstanceStatus
58
                   -> NonEmptyList Char -> String
59
                   -> NonNegative Int -> NonNegative Int -> Bool
60
                   -> Types.DiskTemplate -> Int -> Property
61
prop_Load_Instance name mem dsk vcpus status
62
                   (NonEmpty pnode) snode
63
                   (NonNegative pdx) (NonNegative sdx) autobal dt su =
64
  pnode /= snode && pdx /= sdx ==>
65
  let vcpus_s = show vcpus
66
      dsk_s = show dsk
67
      mem_s = show mem
68
      su_s = show su
69
      status_s = Types.instanceStatusToRaw status
70
      ndx = if null snode
71
              then [(pnode, pdx)]
72
              else [(pnode, pdx), (snode, sdx)]
73
      nl = Map.fromList ndx
74
      tags = ""
75
      sbal = if autobal then "Y" else "N"
76
      sdt = Types.diskTemplateToRaw dt
77
      inst = Text.loadInst nl
78
             [name, mem_s, dsk_s, vcpus_s, status_s,
79
              sbal, pnode, snode, sdt, tags, su_s]
80
      fail1 = Text.loadInst nl
81
              [name, mem_s, dsk_s, vcpus_s, status_s,
82
               sbal, pnode, pnode, tags]
83
  in case inst of
84
       Bad msg -> failTest $ "Failed to load instance: " ++ msg
85
       Ok (_, i) -> printTestCase "Mismatch in some field while\
86
                                  \ loading the instance" $
87
               Instance.name i == name &&
88
               Instance.vcpus i == vcpus &&
89
               Instance.mem i == mem &&
90
               Instance.pNode i == pdx &&
91
               Instance.sNode i == (if null snode
92
                                      then Node.noSecondary
93
                                      else sdx) &&
94
               Instance.autoBalance i == autobal &&
95
               Instance.spindleUse i == su &&
96
               isBad fail1
97

    
98
prop_Load_InstanceFail :: [(String, Int)] -> [String] -> Property
99
prop_Load_InstanceFail ktn fields =
100
  length fields /= 10 && length fields /= 11 ==>
101
    case Text.loadInst nl fields of
102
      Ok _ -> failTest "Managed to load instance from invalid data"
103
      Bad msg -> printTestCase ("Unrecognised error message: " ++ msg) $
104
                 "Invalid/incomplete instance data: '" `isPrefixOf` msg
105
    where nl = Map.fromList ktn
106

    
107
prop_Load_Node :: String -> Int -> Int -> Int -> Int -> Int
108
               -> Int -> Bool -> Bool
109
prop_Load_Node name tm nm fm td fd tc fo =
110
  let conv v = if v < 0
111
                 then "?"
112
                 else show v
113
      tm_s = conv tm
114
      nm_s = conv nm
115
      fm_s = conv fm
116
      td_s = conv td
117
      fd_s = conv fd
118
      tc_s = conv tc
119
      fo_s = if fo
120
               then "Y"
121
               else "N"
122
      any_broken = any (< 0) [tm, nm, fm, td, fd, tc]
123
      gid = Group.uuid defGroup
124
  in case Text.loadNode defGroupAssoc
125
       [name, tm_s, nm_s, fm_s, td_s, fd_s, tc_s, fo_s, gid] of
126
       Nothing -> False
127
       Just (name', node) ->
128
         if fo || any_broken
129
           then Node.offline node
130
           else Node.name node == name' && name' == name &&
131
                Node.alias node == name &&
132
                Node.tMem node == fromIntegral tm &&
133
                Node.nMem node == nm &&
134
                Node.fMem node == fm &&
135
                Node.tDsk node == fromIntegral td &&
136
                Node.fDsk node == fd &&
137
                Node.tCpu node == fromIntegral tc
138

    
139
prop_Load_NodeFail :: [String] -> Property
140
prop_Load_NodeFail fields =
141
  length fields /= 8 ==> isNothing $ Text.loadNode Map.empty fields
142

    
143
prop_NodeLSIdempotent :: Property
144
prop_NodeLSIdempotent =
145
  forAll (genNode (Just 1) Nothing) $ \node ->
146
  -- override failN1 to what loadNode returns by default
147
  let n = Node.setPolicy Types.defIPolicy $
148
          node { Node.failN1 = True, Node.offline = False }
149
  in
150
    (Text.loadNode defGroupAssoc.
151
         Utils.sepSplit '|' . Text.serializeNode defGroupList) n ==?
152
    Just (Node.name n, n)
153

    
154
prop_ISpecIdempotent :: Types.ISpec -> Property
155
prop_ISpecIdempotent ispec =
156
  case Text.loadISpec "dummy" . Utils.sepSplit ',' .
157
       Text.serializeISpec $ ispec of
158
    Bad msg -> failTest $ "Failed to load ispec: " ++ msg
159
    Ok ispec' -> ispec ==? ispec'
160

    
161
prop_IPolicyIdempotent :: Types.IPolicy -> Property
162
prop_IPolicyIdempotent ipol =
163
  case Text.loadIPolicy . Utils.sepSplit '|' $
164
       Text.serializeIPolicy owner ipol of
165
    Bad msg -> failTest $ "Failed to load ispec: " ++ msg
166
    Ok res -> (owner, ipol) ==? res
167
  where owner = "dummy"
168

    
169
-- | This property, while being in the text tests, does more than just
170
-- test end-to-end the serialisation and loading back workflow; it
171
-- also tests the Loader.mergeData and the actual
172
-- Cluster.iterateAlloc (for well-behaving w.r.t. instance
173
-- allocations, not for the business logic). As such, it's a quite
174
-- complex and slow test, and that's the reason we restrict it to
175
-- small cluster sizes.
176
prop_CreateSerialise :: Property
177
prop_CreateSerialise =
178
  forAll genTags $ \ctags ->
179
  forAll (choose (1, 20)) $ \maxiter ->
180
  forAll (choose (2, 10)) $ \count ->
181
  forAll genOnlineNode $ \node ->
182
  forAll (genInstanceSmallerThanNode node) $ \inst ->
183
  let nl = makeSmallCluster node count
184
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
185
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>= \allocn ->
186
     Cluster.iterateAlloc nl Container.empty (Just maxiter) inst allocn [] []
187
     of
188
       Bad msg -> failTest $ "Failed to allocate: " ++ msg
189
       Ok (_, _, _, [], _) -> printTestCase
190
                              "Failed to allocate: no allocations" False
191
       Ok (_, nl', il', _, _) ->
192
         let cdata = Loader.ClusterData defGroupList nl' il' ctags
193
                     Types.defIPolicy
194
             saved = Text.serializeCluster cdata
195
         in case Text.parseData saved >>= Loader.mergeData [] [] [] [] (TOD 0 0)
196
            of
197
              Bad msg -> failTest $ "Failed to load/merge: " ++ msg
198
              Ok (Loader.ClusterData gl2 nl2 il2 ctags2 cpol2) ->
199
                conjoin [ ctags ==? ctags2
200
                        , Types.defIPolicy ==? cpol2
201
                        , il' ==? il2
202
                        , defGroupList ==? gl2
203
                        , nl' ==? nl2
204
                        ]
205

    
206
testSuite "HTools/Backend/Text"
207
            [ 'prop_Load_Instance
208
            , 'prop_Load_InstanceFail
209
            , 'prop_Load_Node
210
            , 'prop_Load_NodeFail
211
            , 'prop_NodeLSIdempotent
212
            , 'prop_ISpecIdempotent
213
            , 'prop_IPolicyIdempotent
214
            , 'prop_CreateSerialise
215
            ]