Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / Text.hs @ 26d62e4c

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 e09c1fa0 Iustin Pop
module Test.Ganeti.HTools.Text (testHTools_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 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
44 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Container as Container
45 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Group as Group
46 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
47 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Loader as Loader
48 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Node as Node
49 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Text as Text
50 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Types as Types
51 26d62e4c Iustin Pop
import qualified Ganeti.Utils as Utils
52 e1ee7d5a Iustin Pop
53 e1ee7d5a Iustin Pop
-- * Instance text loader tests
54 e1ee7d5a Iustin Pop
55 20bc5360 Iustin Pop
prop_Load_Instance :: String -> Int -> Int -> Int -> Types.InstanceStatus
56 5b11f8db Iustin Pop
                   -> NonEmptyList Char -> String
57 20bc5360 Iustin Pop
                   -> NonNegative Int -> NonNegative Int -> Bool
58 20bc5360 Iustin Pop
                   -> Types.DiskTemplate -> Int -> Property
59 20bc5360 Iustin Pop
prop_Load_Instance name mem dsk vcpus status
60 20bc5360 Iustin Pop
                   (NonEmpty pnode) snode
61 20bc5360 Iustin Pop
                   (NonNegative pdx) (NonNegative sdx) autobal dt su =
62 e1ee7d5a Iustin Pop
  pnode /= snode && pdx /= sdx ==>
63 e1ee7d5a Iustin Pop
  let vcpus_s = show vcpus
64 e1ee7d5a Iustin Pop
      dsk_s = show dsk
65 e1ee7d5a Iustin Pop
      mem_s = show mem
66 e1ee7d5a Iustin Pop
      su_s = show su
67 e1ee7d5a Iustin Pop
      status_s = Types.instanceStatusToRaw status
68 e1ee7d5a Iustin Pop
      ndx = if null snode
69 e1ee7d5a Iustin Pop
              then [(pnode, pdx)]
70 e1ee7d5a Iustin Pop
              else [(pnode, pdx), (snode, sdx)]
71 e1ee7d5a Iustin Pop
      nl = Map.fromList ndx
72 e1ee7d5a Iustin Pop
      tags = ""
73 e1ee7d5a Iustin Pop
      sbal = if autobal then "Y" else "N"
74 e1ee7d5a Iustin Pop
      sdt = Types.diskTemplateToRaw dt
75 e1ee7d5a Iustin Pop
      inst = Text.loadInst nl
76 e1ee7d5a Iustin Pop
             [name, mem_s, dsk_s, vcpus_s, status_s,
77 e1ee7d5a Iustin Pop
              sbal, pnode, snode, sdt, tags, su_s]
78 e1ee7d5a Iustin Pop
      fail1 = Text.loadInst nl
79 e1ee7d5a Iustin Pop
              [name, mem_s, dsk_s, vcpus_s, status_s,
80 e1ee7d5a Iustin Pop
               sbal, pnode, pnode, tags]
81 e1ee7d5a Iustin Pop
  in case inst of
82 e1ee7d5a Iustin Pop
       Types.Bad msg -> failTest $ "Failed to load instance: " ++ msg
83 e1ee7d5a Iustin Pop
       Types.Ok (_, i) -> printTestCase "Mismatch in some field while\
84 e1ee7d5a Iustin Pop
                                        \ loading the instance" $
85 e1ee7d5a Iustin Pop
               Instance.name i == name &&
86 e1ee7d5a Iustin Pop
               Instance.vcpus i == vcpus &&
87 e1ee7d5a Iustin Pop
               Instance.mem i == mem &&
88 e1ee7d5a Iustin Pop
               Instance.pNode i == pdx &&
89 e1ee7d5a Iustin Pop
               Instance.sNode i == (if null snode
90 e1ee7d5a Iustin Pop
                                      then Node.noSecondary
91 e1ee7d5a Iustin Pop
                                      else sdx) &&
92 e1ee7d5a Iustin Pop
               Instance.autoBalance i == autobal &&
93 e1ee7d5a Iustin Pop
               Instance.spindleUse i == su &&
94 e1ee7d5a Iustin Pop
               Types.isBad fail1
95 e1ee7d5a Iustin Pop
96 20bc5360 Iustin Pop
prop_Load_InstanceFail :: [(String, Int)] -> [String] -> Property
97 20bc5360 Iustin Pop
prop_Load_InstanceFail ktn fields =
98 e1ee7d5a Iustin Pop
  length fields /= 10 && length fields /= 11 ==>
99 e1ee7d5a Iustin Pop
    case Text.loadInst nl fields of
100 e1ee7d5a Iustin Pop
      Types.Ok _ -> failTest "Managed to load instance from invalid data"
101 e1ee7d5a Iustin Pop
      Types.Bad msg -> printTestCase ("Unrecognised error message: " ++ msg) $
102 e1ee7d5a Iustin Pop
                       "Invalid/incomplete instance data: '" `isPrefixOf` msg
103 e1ee7d5a Iustin Pop
    where nl = Map.fromList ktn
104 e1ee7d5a Iustin Pop
105 20bc5360 Iustin Pop
prop_Load_Node :: String -> Int -> Int -> Int -> Int -> Int
106 20bc5360 Iustin Pop
               -> Int -> Bool -> Bool
107 20bc5360 Iustin Pop
prop_Load_Node name tm nm fm td fd tc fo =
108 e1ee7d5a Iustin Pop
  let conv v = if v < 0
109 e1ee7d5a Iustin Pop
                 then "?"
110 e1ee7d5a Iustin Pop
                 else show v
111 e1ee7d5a Iustin Pop
      tm_s = conv tm
112 e1ee7d5a Iustin Pop
      nm_s = conv nm
113 e1ee7d5a Iustin Pop
      fm_s = conv fm
114 e1ee7d5a Iustin Pop
      td_s = conv td
115 e1ee7d5a Iustin Pop
      fd_s = conv fd
116 e1ee7d5a Iustin Pop
      tc_s = conv tc
117 e1ee7d5a Iustin Pop
      fo_s = if fo
118 e1ee7d5a Iustin Pop
               then "Y"
119 e1ee7d5a Iustin Pop
               else "N"
120 e1ee7d5a Iustin Pop
      any_broken = any (< 0) [tm, nm, fm, td, fd, tc]
121 e1ee7d5a Iustin Pop
      gid = Group.uuid defGroup
122 e1ee7d5a Iustin Pop
  in case Text.loadNode defGroupAssoc
123 e1ee7d5a Iustin Pop
       [name, tm_s, nm_s, fm_s, td_s, fd_s, tc_s, fo_s, gid] of
124 e1ee7d5a Iustin Pop
       Nothing -> False
125 e1ee7d5a Iustin Pop
       Just (name', node) ->
126 e1ee7d5a Iustin Pop
         if fo || any_broken
127 e1ee7d5a Iustin Pop
           then Node.offline node
128 e1ee7d5a Iustin Pop
           else Node.name node == name' && name' == name &&
129 e1ee7d5a Iustin Pop
                Node.alias node == name &&
130 e1ee7d5a Iustin Pop
                Node.tMem node == fromIntegral tm &&
131 e1ee7d5a Iustin Pop
                Node.nMem node == nm &&
132 e1ee7d5a Iustin Pop
                Node.fMem node == fm &&
133 e1ee7d5a Iustin Pop
                Node.tDsk node == fromIntegral td &&
134 e1ee7d5a Iustin Pop
                Node.fDsk node == fd &&
135 e1ee7d5a Iustin Pop
                Node.tCpu node == fromIntegral tc
136 e1ee7d5a Iustin Pop
137 20bc5360 Iustin Pop
prop_Load_NodeFail :: [String] -> Property
138 20bc5360 Iustin Pop
prop_Load_NodeFail fields =
139 e1ee7d5a Iustin Pop
  length fields /= 8 ==> isNothing $ Text.loadNode Map.empty fields
140 e1ee7d5a Iustin Pop
141 20bc5360 Iustin Pop
prop_NodeLSIdempotent :: Property
142 20bc5360 Iustin Pop
prop_NodeLSIdempotent =
143 e1ee7d5a Iustin Pop
  forAll (genNode (Just 1) Nothing) $ \node ->
144 e1ee7d5a Iustin Pop
  -- override failN1 to what loadNode returns by default
145 e1ee7d5a Iustin Pop
  let n = Node.setPolicy Types.defIPolicy $
146 e1ee7d5a Iustin Pop
          node { Node.failN1 = True, Node.offline = False }
147 e1ee7d5a Iustin Pop
  in
148 e1ee7d5a Iustin Pop
    (Text.loadNode defGroupAssoc.
149 e1ee7d5a Iustin Pop
         Utils.sepSplit '|' . Text.serializeNode defGroupList) n ==?
150 e1ee7d5a Iustin Pop
    Just (Node.name n, n)
151 e1ee7d5a Iustin Pop
152 20bc5360 Iustin Pop
prop_ISpecIdempotent :: Types.ISpec -> Property
153 20bc5360 Iustin Pop
prop_ISpecIdempotent ispec =
154 e1ee7d5a Iustin Pop
  case Text.loadISpec "dummy" . Utils.sepSplit ',' .
155 e1ee7d5a Iustin Pop
       Text.serializeISpec $ ispec of
156 e1ee7d5a Iustin Pop
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
157 e1ee7d5a Iustin Pop
    Types.Ok ispec' -> ispec ==? ispec'
158 e1ee7d5a Iustin Pop
159 20bc5360 Iustin Pop
prop_IPolicyIdempotent :: Types.IPolicy -> Property
160 20bc5360 Iustin Pop
prop_IPolicyIdempotent ipol =
161 e1ee7d5a Iustin Pop
  case Text.loadIPolicy . Utils.sepSplit '|' $
162 e1ee7d5a Iustin Pop
       Text.serializeIPolicy owner ipol of
163 e1ee7d5a Iustin Pop
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
164 e1ee7d5a Iustin Pop
    Types.Ok res -> (owner, ipol) ==? res
165 e1ee7d5a Iustin Pop
  where owner = "dummy"
166 e1ee7d5a Iustin Pop
167 e1ee7d5a Iustin Pop
-- | This property, while being in the text tests, does more than just
168 e1ee7d5a Iustin Pop
-- test end-to-end the serialisation and loading back workflow; it
169 e1ee7d5a Iustin Pop
-- also tests the Loader.mergeData and the actuall
170 e1ee7d5a Iustin Pop
-- Cluster.iterateAlloc (for well-behaving w.r.t. instance
171 e1ee7d5a Iustin Pop
-- allocations, not for the business logic). As such, it's a quite
172 e1ee7d5a Iustin Pop
-- complex and slow test, and that's the reason we restrict it to
173 e1ee7d5a Iustin Pop
-- small cluster sizes.
174 20bc5360 Iustin Pop
prop_CreateSerialise :: Property
175 20bc5360 Iustin Pop
prop_CreateSerialise =
176 e1ee7d5a Iustin Pop
  forAll genTags $ \ctags ->
177 e1ee7d5a Iustin Pop
  forAll (choose (1, 20)) $ \maxiter ->
178 e1ee7d5a Iustin Pop
  forAll (choose (2, 10)) $ \count ->
179 e1ee7d5a Iustin Pop
  forAll genOnlineNode $ \node ->
180 e1ee7d5a Iustin Pop
  forAll (genInstanceSmallerThanNode node) $ \inst ->
181 e1ee7d5a Iustin Pop
  let nl = makeSmallCluster node count
182 e1ee7d5a Iustin Pop
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
183 e1ee7d5a Iustin Pop
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>= \allocn ->
184 e1ee7d5a Iustin Pop
     Cluster.iterateAlloc nl Container.empty (Just maxiter) inst allocn [] []
185 e1ee7d5a Iustin Pop
     of
186 e1ee7d5a Iustin Pop
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
187 e1ee7d5a Iustin Pop
       Types.Ok (_, _, _, [], _) -> printTestCase
188 e1ee7d5a Iustin Pop
                                    "Failed to allocate: no allocations" False
189 e1ee7d5a Iustin Pop
       Types.Ok (_, nl', il', _, _) ->
190 e1ee7d5a Iustin Pop
         let cdata = Loader.ClusterData defGroupList nl' il' ctags
191 e1ee7d5a Iustin Pop
                     Types.defIPolicy
192 e1ee7d5a Iustin Pop
             saved = Text.serializeCluster cdata
193 e1ee7d5a Iustin Pop
         in case Text.parseData saved >>= Loader.mergeData [] [] [] [] of
194 e1ee7d5a Iustin Pop
              Types.Bad msg -> failTest $ "Failed to load/merge: " ++ msg
195 e1ee7d5a Iustin Pop
              Types.Ok (Loader.ClusterData gl2 nl2 il2 ctags2 cpol2) ->
196 e1ee7d5a Iustin Pop
                ctags ==? ctags2 .&&.
197 e1ee7d5a Iustin Pop
                Types.defIPolicy ==? cpol2 .&&.
198 e1ee7d5a Iustin Pop
                il' ==? il2 .&&.
199 e1ee7d5a Iustin Pop
                defGroupList ==? gl2 .&&.
200 e1ee7d5a Iustin Pop
                nl' ==? nl2
201 e1ee7d5a Iustin Pop
202 e09c1fa0 Iustin Pop
testSuite "HTools/Text"
203 20bc5360 Iustin Pop
            [ 'prop_Load_Instance
204 20bc5360 Iustin Pop
            , 'prop_Load_InstanceFail
205 20bc5360 Iustin Pop
            , 'prop_Load_Node
206 20bc5360 Iustin Pop
            , 'prop_Load_NodeFail
207 20bc5360 Iustin Pop
            , 'prop_NodeLSIdempotent
208 20bc5360 Iustin Pop
            , 'prop_ISpecIdempotent
209 20bc5360 Iustin Pop
            , 'prop_IPolicyIdempotent
210 20bc5360 Iustin Pop
            , 'prop_CreateSerialise
211 e1ee7d5a Iustin Pop
            ]