Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / Backend / Text.hs @ cce30754

History | View | Annotate | Download (8 kB)

1 e1ee7d5a Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 e1ee7d5a Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 e1ee7d5a Iustin Pop
4 e1ee7d5a Iustin Pop
{-| Unittests for ganeti-htools.
5 e1ee7d5a Iustin Pop
6 e1ee7d5a Iustin Pop
-}
7 e1ee7d5a Iustin Pop
8 e1ee7d5a Iustin Pop
{-
9 e1ee7d5a Iustin Pop
10 e1ee7d5a Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11 e1ee7d5a Iustin Pop
12 e1ee7d5a Iustin Pop
This program is free software; you can redistribute it and/or modify
13 e1ee7d5a Iustin Pop
it under the terms of the GNU General Public License as published by
14 e1ee7d5a Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 e1ee7d5a Iustin Pop
(at your option) any later version.
16 e1ee7d5a Iustin Pop
17 e1ee7d5a Iustin Pop
This program is distributed in the hope that it will be useful, but
18 e1ee7d5a Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 e1ee7d5a Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 e1ee7d5a Iustin Pop
General Public License for more details.
21 e1ee7d5a Iustin Pop
22 e1ee7d5a Iustin Pop
You should have received a copy of the GNU General Public License
23 e1ee7d5a Iustin Pop
along with this program; if not, write to the Free Software
24 e1ee7d5a Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 e1ee7d5a Iustin Pop
02110-1301, USA.
26 e1ee7d5a Iustin Pop
27 e1ee7d5a Iustin Pop
-}
28 e1ee7d5a Iustin Pop
29 879d9290 Iustin Pop
module Test.Ganeti.HTools.Backend.Text (testHTools_Backend_Text) where
30 e1ee7d5a Iustin Pop
31 e1ee7d5a Iustin Pop
import Test.QuickCheck
32 e1ee7d5a Iustin Pop
33 e1ee7d5a Iustin Pop
import qualified Data.Map as Map
34 e1ee7d5a Iustin Pop
import Data.List
35 e1ee7d5a Iustin Pop
import Data.Maybe
36 e1ee7d5a Iustin Pop
37 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHelper
38 e1ee7d5a Iustin Pop
import Test.Ganeti.TestCommon
39 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHTools
40 e1ee7d5a Iustin Pop
import Test.Ganeti.HTools.Instance (genInstanceSmallerThanNode)
41 e1ee7d5a Iustin Pop
import Test.Ganeti.HTools.Node (genNode, genOnlineNode)
42 e1ee7d5a Iustin Pop
43 01e52493 Iustin Pop
import Ganeti.BasicTypes
44 879d9290 Iustin Pop
import qualified Ganeti.HTools.Backend.Text as Text
45 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
46 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Container as Container
47 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Group as Group
48 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
49 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Loader as Loader
50 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Node as Node
51 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Types as Types
52 26d62e4c Iustin Pop
import qualified Ganeti.Utils as Utils
53 e1ee7d5a Iustin Pop
54 e1ee7d5a Iustin Pop
-- * Instance text loader tests
55 e1ee7d5a Iustin Pop
56 20bc5360 Iustin Pop
prop_Load_Instance :: String -> Int -> Int -> Int -> Types.InstanceStatus
57 5b11f8db Iustin Pop
                   -> NonEmptyList Char -> String
58 20bc5360 Iustin Pop
                   -> NonNegative Int -> NonNegative Int -> Bool
59 20bc5360 Iustin Pop
                   -> Types.DiskTemplate -> Int -> Property
60 20bc5360 Iustin Pop
prop_Load_Instance name mem dsk vcpus status
61 20bc5360 Iustin Pop
                   (NonEmpty pnode) snode
62 20bc5360 Iustin Pop
                   (NonNegative pdx) (NonNegative sdx) autobal dt su =
63 e1ee7d5a Iustin Pop
  pnode /= snode && pdx /= sdx ==>
64 e1ee7d5a Iustin Pop
  let vcpus_s = show vcpus
65 e1ee7d5a Iustin Pop
      dsk_s = show dsk
66 e1ee7d5a Iustin Pop
      mem_s = show mem
67 e1ee7d5a Iustin Pop
      su_s = show su
68 e1ee7d5a Iustin Pop
      status_s = Types.instanceStatusToRaw status
69 e1ee7d5a Iustin Pop
      ndx = if null snode
70 e1ee7d5a Iustin Pop
              then [(pnode, pdx)]
71 e1ee7d5a Iustin Pop
              else [(pnode, pdx), (snode, sdx)]
72 e1ee7d5a Iustin Pop
      nl = Map.fromList ndx
73 e1ee7d5a Iustin Pop
      tags = ""
74 e1ee7d5a Iustin Pop
      sbal = if autobal then "Y" else "N"
75 e1ee7d5a Iustin Pop
      sdt = Types.diskTemplateToRaw dt
76 e1ee7d5a Iustin Pop
      inst = Text.loadInst nl
77 e1ee7d5a Iustin Pop
             [name, mem_s, dsk_s, vcpus_s, status_s,
78 e1ee7d5a Iustin Pop
              sbal, pnode, snode, sdt, tags, su_s]
79 e1ee7d5a Iustin Pop
      fail1 = Text.loadInst nl
80 e1ee7d5a Iustin Pop
              [name, mem_s, dsk_s, vcpus_s, status_s,
81 e1ee7d5a Iustin Pop
               sbal, pnode, pnode, tags]
82 e1ee7d5a Iustin Pop
  in case inst of
83 01e52493 Iustin Pop
       Bad msg -> failTest $ "Failed to load instance: " ++ msg
84 01e52493 Iustin Pop
       Ok (_, i) -> printTestCase "Mismatch in some field while\
85 01e52493 Iustin Pop
                                  \ loading the instance" $
86 e1ee7d5a Iustin Pop
               Instance.name i == name &&
87 e1ee7d5a Iustin Pop
               Instance.vcpus i == vcpus &&
88 e1ee7d5a Iustin Pop
               Instance.mem i == mem &&
89 e1ee7d5a Iustin Pop
               Instance.pNode i == pdx &&
90 e1ee7d5a Iustin Pop
               Instance.sNode i == (if null snode
91 e1ee7d5a Iustin Pop
                                      then Node.noSecondary
92 e1ee7d5a Iustin Pop
                                      else sdx) &&
93 e1ee7d5a Iustin Pop
               Instance.autoBalance i == autobal &&
94 e1ee7d5a Iustin Pop
               Instance.spindleUse i == su &&
95 01e52493 Iustin Pop
               isBad fail1
96 e1ee7d5a Iustin Pop
97 20bc5360 Iustin Pop
prop_Load_InstanceFail :: [(String, Int)] -> [String] -> Property
98 20bc5360 Iustin Pop
prop_Load_InstanceFail ktn fields =
99 e1ee7d5a Iustin Pop
  length fields /= 10 && length fields /= 11 ==>
100 e1ee7d5a Iustin Pop
    case Text.loadInst nl fields of
101 01e52493 Iustin Pop
      Ok _ -> failTest "Managed to load instance from invalid data"
102 01e52493 Iustin Pop
      Bad msg -> printTestCase ("Unrecognised error message: " ++ msg) $
103 01e52493 Iustin Pop
                 "Invalid/incomplete instance data: '" `isPrefixOf` msg
104 e1ee7d5a Iustin Pop
    where nl = Map.fromList ktn
105 e1ee7d5a Iustin Pop
106 20bc5360 Iustin Pop
prop_Load_Node :: String -> Int -> Int -> Int -> Int -> Int
107 20bc5360 Iustin Pop
               -> Int -> Bool -> Bool
108 20bc5360 Iustin Pop
prop_Load_Node name tm nm fm td fd tc fo =
109 e1ee7d5a Iustin Pop
  let conv v = if v < 0
110 e1ee7d5a Iustin Pop
                 then "?"
111 e1ee7d5a Iustin Pop
                 else show v
112 e1ee7d5a Iustin Pop
      tm_s = conv tm
113 e1ee7d5a Iustin Pop
      nm_s = conv nm
114 e1ee7d5a Iustin Pop
      fm_s = conv fm
115 e1ee7d5a Iustin Pop
      td_s = conv td
116 e1ee7d5a Iustin Pop
      fd_s = conv fd
117 e1ee7d5a Iustin Pop
      tc_s = conv tc
118 e1ee7d5a Iustin Pop
      fo_s = if fo
119 e1ee7d5a Iustin Pop
               then "Y"
120 e1ee7d5a Iustin Pop
               else "N"
121 e1ee7d5a Iustin Pop
      any_broken = any (< 0) [tm, nm, fm, td, fd, tc]
122 e1ee7d5a Iustin Pop
      gid = Group.uuid defGroup
123 e1ee7d5a Iustin Pop
  in case Text.loadNode defGroupAssoc
124 e1ee7d5a Iustin Pop
       [name, tm_s, nm_s, fm_s, td_s, fd_s, tc_s, fo_s, gid] of
125 e1ee7d5a Iustin Pop
       Nothing -> False
126 e1ee7d5a Iustin Pop
       Just (name', node) ->
127 e1ee7d5a Iustin Pop
         if fo || any_broken
128 e1ee7d5a Iustin Pop
           then Node.offline node
129 e1ee7d5a Iustin Pop
           else Node.name node == name' && name' == name &&
130 e1ee7d5a Iustin Pop
                Node.alias node == name &&
131 e1ee7d5a Iustin Pop
                Node.tMem node == fromIntegral tm &&
132 e1ee7d5a Iustin Pop
                Node.nMem node == nm &&
133 e1ee7d5a Iustin Pop
                Node.fMem node == fm &&
134 e1ee7d5a Iustin Pop
                Node.tDsk node == fromIntegral td &&
135 e1ee7d5a Iustin Pop
                Node.fDsk node == fd &&
136 e1ee7d5a Iustin Pop
                Node.tCpu node == fromIntegral tc
137 e1ee7d5a Iustin Pop
138 20bc5360 Iustin Pop
prop_Load_NodeFail :: [String] -> Property
139 20bc5360 Iustin Pop
prop_Load_NodeFail fields =
140 e1ee7d5a Iustin Pop
  length fields /= 8 ==> isNothing $ Text.loadNode Map.empty fields
141 e1ee7d5a Iustin Pop
142 20bc5360 Iustin Pop
prop_NodeLSIdempotent :: Property
143 20bc5360 Iustin Pop
prop_NodeLSIdempotent =
144 e1ee7d5a Iustin Pop
  forAll (genNode (Just 1) Nothing) $ \node ->
145 e1ee7d5a Iustin Pop
  -- override failN1 to what loadNode returns by default
146 e1ee7d5a Iustin Pop
  let n = Node.setPolicy Types.defIPolicy $
147 e1ee7d5a Iustin Pop
          node { Node.failN1 = True, Node.offline = False }
148 e1ee7d5a Iustin Pop
  in
149 e1ee7d5a Iustin Pop
    (Text.loadNode defGroupAssoc.
150 e1ee7d5a Iustin Pop
         Utils.sepSplit '|' . Text.serializeNode defGroupList) n ==?
151 e1ee7d5a Iustin Pop
    Just (Node.name n, n)
152 e1ee7d5a Iustin Pop
153 20bc5360 Iustin Pop
prop_ISpecIdempotent :: Types.ISpec -> Property
154 20bc5360 Iustin Pop
prop_ISpecIdempotent ispec =
155 e1ee7d5a Iustin Pop
  case Text.loadISpec "dummy" . Utils.sepSplit ',' .
156 e1ee7d5a Iustin Pop
       Text.serializeISpec $ ispec of
157 01e52493 Iustin Pop
    Bad msg -> failTest $ "Failed to load ispec: " ++ msg
158 01e52493 Iustin Pop
    Ok ispec' -> ispec ==? ispec'
159 e1ee7d5a Iustin Pop
160 20bc5360 Iustin Pop
prop_IPolicyIdempotent :: Types.IPolicy -> Property
161 20bc5360 Iustin Pop
prop_IPolicyIdempotent ipol =
162 e1ee7d5a Iustin Pop
  case Text.loadIPolicy . Utils.sepSplit '|' $
163 e1ee7d5a Iustin Pop
       Text.serializeIPolicy owner ipol of
164 01e52493 Iustin Pop
    Bad msg -> failTest $ "Failed to load ispec: " ++ msg
165 01e52493 Iustin Pop
    Ok res -> (owner, ipol) ==? res
166 e1ee7d5a Iustin Pop
  where owner = "dummy"
167 e1ee7d5a Iustin Pop
168 e1ee7d5a Iustin Pop
-- | This property, while being in the text tests, does more than just
169 e1ee7d5a Iustin Pop
-- test end-to-end the serialisation and loading back workflow; it
170 235a0fa5 Dato Simó
-- also tests the Loader.mergeData and the actual
171 e1ee7d5a Iustin Pop
-- Cluster.iterateAlloc (for well-behaving w.r.t. instance
172 e1ee7d5a Iustin Pop
-- allocations, not for the business logic). As such, it's a quite
173 e1ee7d5a Iustin Pop
-- complex and slow test, and that's the reason we restrict it to
174 e1ee7d5a Iustin Pop
-- small cluster sizes.
175 20bc5360 Iustin Pop
prop_CreateSerialise :: Property
176 20bc5360 Iustin Pop
prop_CreateSerialise =
177 e1ee7d5a Iustin Pop
  forAll genTags $ \ctags ->
178 e1ee7d5a Iustin Pop
  forAll (choose (1, 20)) $ \maxiter ->
179 e1ee7d5a Iustin Pop
  forAll (choose (2, 10)) $ \count ->
180 e1ee7d5a Iustin Pop
  forAll genOnlineNode $ \node ->
181 e1ee7d5a Iustin Pop
  forAll (genInstanceSmallerThanNode node) $ \inst ->
182 e1ee7d5a Iustin Pop
  let nl = makeSmallCluster node count
183 e1ee7d5a Iustin Pop
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
184 e1ee7d5a Iustin Pop
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>= \allocn ->
185 e1ee7d5a Iustin Pop
     Cluster.iterateAlloc nl Container.empty (Just maxiter) inst allocn [] []
186 e1ee7d5a Iustin Pop
     of
187 01e52493 Iustin Pop
       Bad msg -> failTest $ "Failed to allocate: " ++ msg
188 01e52493 Iustin Pop
       Ok (_, _, _, [], _) -> printTestCase
189 01e52493 Iustin Pop
                              "Failed to allocate: no allocations" False
190 01e52493 Iustin Pop
       Ok (_, nl', il', _, _) ->
191 e1ee7d5a Iustin Pop
         let cdata = Loader.ClusterData defGroupList nl' il' ctags
192 e1ee7d5a Iustin Pop
                     Types.defIPolicy
193 e1ee7d5a Iustin Pop
             saved = Text.serializeCluster cdata
194 e1ee7d5a Iustin Pop
         in case Text.parseData saved >>= Loader.mergeData [] [] [] [] of
195 01e52493 Iustin Pop
              Bad msg -> failTest $ "Failed to load/merge: " ++ msg
196 01e52493 Iustin Pop
              Ok (Loader.ClusterData gl2 nl2 il2 ctags2 cpol2) ->
197 942a9a6a Iustin Pop
                conjoin [ ctags ==? ctags2
198 942a9a6a Iustin Pop
                        , Types.defIPolicy ==? cpol2
199 942a9a6a Iustin Pop
                        , il' ==? il2
200 942a9a6a Iustin Pop
                        , defGroupList ==? gl2
201 942a9a6a Iustin Pop
                        , nl' ==? nl2
202 942a9a6a Iustin Pop
                        ]
203 e1ee7d5a Iustin Pop
204 879d9290 Iustin Pop
testSuite "HTools/Backend/Text"
205 20bc5360 Iustin Pop
            [ 'prop_Load_Instance
206 20bc5360 Iustin Pop
            , 'prop_Load_InstanceFail
207 20bc5360 Iustin Pop
            , 'prop_Load_Node
208 20bc5360 Iustin Pop
            , 'prop_Load_NodeFail
209 20bc5360 Iustin Pop
            , 'prop_NodeLSIdempotent
210 20bc5360 Iustin Pop
            , 'prop_ISpecIdempotent
211 20bc5360 Iustin Pop
            , 'prop_IPolicyIdempotent
212 20bc5360 Iustin Pop
            , 'prop_CreateSerialise
213 e1ee7d5a Iustin Pop
            ]