Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 72bb6b4e

History | View | Annotate | Download (40 kB)

1 23fe06c2 Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 23fe06c2 Iustin Pop
3 525bfb36 Iustin Pop
{-| Unittests for ganeti-htools.
4 e2fa2baf Iustin Pop
5 e2fa2baf Iustin Pop
-}
6 e2fa2baf Iustin Pop
7 e2fa2baf Iustin Pop
{-
8 e2fa2baf Iustin Pop
9 1bc47d38 Iustin Pop
Copyright (C) 2009, 2010, 2011 Google Inc.
10 e2fa2baf Iustin Pop
11 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
12 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
13 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
14 e2fa2baf Iustin Pop
(at your option) any later version.
15 e2fa2baf Iustin Pop
16 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
17 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
18 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 e2fa2baf Iustin Pop
General Public License for more details.
20 e2fa2baf Iustin Pop
21 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
22 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
23 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 e2fa2baf Iustin Pop
02110-1301, USA.
25 e2fa2baf Iustin Pop
26 e2fa2baf Iustin Pop
-}
27 e2fa2baf Iustin Pop
28 15f4c8ca Iustin Pop
module Ganeti.HTools.QC
29 691dcd2a Iustin Pop
    ( testUtils
30 691dcd2a Iustin Pop
    , testPeerMap
31 c15f7183 Iustin Pop
    , testContainer
32 c15f7183 Iustin Pop
    , testInstance
33 c15f7183 Iustin Pop
    , testNode
34 c15f7183 Iustin Pop
    , testText
35 88f25dd0 Iustin Pop
    , testOpCodes
36 db079755 Iustin Pop
    , testJobs
37 c15f7183 Iustin Pop
    , testCluster
38 c088674b Iustin Pop
    , testLoader
39 3c002a13 Iustin Pop
    , testTypes
40 7dd5ee6c Iustin Pop
    ) where
41 15f4c8ca Iustin Pop
42 15f4c8ca Iustin Pop
import Test.QuickCheck
43 bc782180 Iustin Pop
import Data.List (findIndex, intercalate, nub, isPrefixOf)
44 15f4c8ca Iustin Pop
import Data.Maybe
45 88f25dd0 Iustin Pop
import Control.Monad
46 88f25dd0 Iustin Pop
import qualified Text.JSON as J
47 8fcf251f Iustin Pop
import qualified Data.Map
48 3fea6959 Iustin Pop
import qualified Data.IntMap as IntMap
49 88f25dd0 Iustin Pop
import qualified Ganeti.OpCodes as OpCodes
50 db079755 Iustin Pop
import qualified Ganeti.Jobs as Jobs
51 223dbe53 Iustin Pop
import qualified Ganeti.Luxi
52 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.CLI as CLI
53 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
54 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Container as Container
55 223dbe53 Iustin Pop
import qualified Ganeti.HTools.ExtLoader
56 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.IAlloc as IAlloc
57 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
58 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Loader as Loader
59 223dbe53 Iustin Pop
import qualified Ganeti.HTools.Luxi
60 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Node as Node
61 10ef6b4e Iustin Pop
import qualified Ganeti.HTools.Group as Group
62 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.PeerMap as PeerMap
63 c478f837 Iustin Pop
import qualified Ganeti.HTools.Rapi
64 223dbe53 Iustin Pop
import qualified Ganeti.HTools.Simu
65 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Text as Text
66 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Types as Types
67 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Utils as Utils
68 223dbe53 Iustin Pop
import qualified Ganeti.HTools.Version
69 e82271f8 Iustin Pop
import qualified Ganeti.Constants as C
70 15f4c8ca Iustin Pop
71 33b9d92d Iustin Pop
import qualified Ganeti.HTools.Program.Hail
72 33b9d92d Iustin Pop
import qualified Ganeti.HTools.Program.Hbal
73 33b9d92d Iustin Pop
import qualified Ganeti.HTools.Program.Hscan
74 33b9d92d Iustin Pop
import qualified Ganeti.HTools.Program.Hspace
75 33b9d92d Iustin Pop
76 23fe06c2 Iustin Pop
import Ganeti.HTools.QCHelper (testSuite)
77 8e4f6d56 Iustin Pop
78 3fea6959 Iustin Pop
-- * Constants
79 3fea6959 Iustin Pop
80 525bfb36 Iustin Pop
-- | Maximum memory (1TiB, somewhat random value).
81 8fcf251f Iustin Pop
maxMem :: Int
82 8fcf251f Iustin Pop
maxMem = 1024 * 1024
83 8fcf251f Iustin Pop
84 525bfb36 Iustin Pop
-- | Maximum disk (8TiB, somewhat random value).
85 8fcf251f Iustin Pop
maxDsk :: Int
86 49f9627a Iustin Pop
maxDsk = 1024 * 1024 * 8
87 8fcf251f Iustin Pop
88 525bfb36 Iustin Pop
-- | Max CPUs (1024, somewhat random value).
89 8fcf251f Iustin Pop
maxCpu :: Int
90 8fcf251f Iustin Pop
maxCpu = 1024
91 8fcf251f Iustin Pop
92 10ef6b4e Iustin Pop
defGroup :: Group.Group
93 10ef6b4e Iustin Pop
defGroup = flip Group.setIdx 0 $
94 10ef6b4e Iustin Pop
               Group.create "default" Utils.defaultGroupID
95 10ef6b4e Iustin Pop
                    Types.AllocPreferred
96 10ef6b4e Iustin Pop
97 10ef6b4e Iustin Pop
defGroupList :: Group.List
98 cb0c77ff Iustin Pop
defGroupList = Container.fromList [(Group.idx defGroup, defGroup)]
99 10ef6b4e Iustin Pop
100 10ef6b4e Iustin Pop
defGroupAssoc :: Data.Map.Map String Types.Gdx
101 10ef6b4e Iustin Pop
defGroupAssoc = Data.Map.singleton (Group.uuid defGroup) (Group.idx defGroup)
102 10ef6b4e Iustin Pop
103 3fea6959 Iustin Pop
-- * Helper functions
104 3fea6959 Iustin Pop
105 525bfb36 Iustin Pop
-- | Simple checker for whether OpResult is fail or pass.
106 79a72ce7 Iustin Pop
isFailure :: Types.OpResult a -> Bool
107 79a72ce7 Iustin Pop
isFailure (Types.OpFail _) = True
108 79a72ce7 Iustin Pop
isFailure _ = False
109 79a72ce7 Iustin Pop
110 72bb6b4e Iustin Pop
-- | Checks for equality with proper annotation.
111 72bb6b4e Iustin Pop
(==?) :: (Show a, Eq a) => a -> a -> Property
112 72bb6b4e Iustin Pop
(==?) x y = printTestCase
113 72bb6b4e Iustin Pop
            ("Expected equality, but '" ++
114 72bb6b4e Iustin Pop
             show x ++ "' /= '" ++ show y ++ "'") (x == y)
115 72bb6b4e Iustin Pop
infix 3 ==?
116 72bb6b4e Iustin Pop
117 525bfb36 Iustin Pop
-- | Update an instance to be smaller than a node.
118 3fea6959 Iustin Pop
setInstanceSmallerThanNode node inst =
119 4a007641 Iustin Pop
    inst { Instance.mem = Node.availMem node `div` 2
120 4a007641 Iustin Pop
         , Instance.dsk = Node.availDisk node `div` 2
121 4a007641 Iustin Pop
         , Instance.vcpus = Node.availCpu node `div` 2
122 3fea6959 Iustin Pop
         }
123 3fea6959 Iustin Pop
124 525bfb36 Iustin Pop
-- | Create an instance given its spec.
125 3fea6959 Iustin Pop
createInstance mem dsk vcpus =
126 c352b0a9 Iustin Pop
    Instance.create "inst-unnamed" mem dsk vcpus "running" [] True (-1) (-1)
127 d25643d1 Iustin Pop
                    Types.DTDrbd8
128 3fea6959 Iustin Pop
129 525bfb36 Iustin Pop
-- | Create a small cluster by repeating a node spec.
130 3fea6959 Iustin Pop
makeSmallCluster :: Node.Node -> Int -> Node.List
131 3fea6959 Iustin Pop
makeSmallCluster node count =
132 3fea6959 Iustin Pop
    let fn = Node.buildPeers node Container.empty
133 3fea6959 Iustin Pop
        namelst = map (\n -> (Node.name n, n)) (replicate count fn)
134 3fea6959 Iustin Pop
        (_, nlst) = Loader.assignIndices namelst
135 99b63608 Iustin Pop
    in nlst
136 3fea6959 Iustin Pop
137 525bfb36 Iustin Pop
-- | Checks if a node is "big" enough.
138 3fea6959 Iustin Pop
isNodeBig :: Node.Node -> Int -> Bool
139 3fea6959 Iustin Pop
isNodeBig node size = Node.availDisk node > size * Types.unitDsk
140 3fea6959 Iustin Pop
                      && Node.availMem node > size * Types.unitMem
141 3fea6959 Iustin Pop
                      && Node.availCpu node > size * Types.unitCpu
142 3fea6959 Iustin Pop
143 e08424a8 Guido Trotter
canBalance :: Cluster.Table -> Bool -> Bool -> Bool -> Bool
144 e08424a8 Guido Trotter
canBalance tbl dm im evac = isJust $ Cluster.tryBalance tbl dm im evac 0 0
145 3fea6959 Iustin Pop
146 f4161783 Iustin Pop
-- | Assigns a new fresh instance to a cluster; this is not
147 525bfb36 Iustin Pop
-- allocation, so no resource checks are done.
148 f4161783 Iustin Pop
assignInstance :: Node.List -> Instance.List -> Instance.Instance ->
149 f4161783 Iustin Pop
                  Types.Idx -> Types.Idx ->
150 f4161783 Iustin Pop
                  (Node.List, Instance.List)
151 f4161783 Iustin Pop
assignInstance nl il inst pdx sdx =
152 f4161783 Iustin Pop
  let pnode = Container.find pdx nl
153 f4161783 Iustin Pop
      snode = Container.find sdx nl
154 f4161783 Iustin Pop
      maxiidx = if Container.null il
155 f4161783 Iustin Pop
                then 0
156 f4161783 Iustin Pop
                else fst (Container.findMax il) + 1
157 f4161783 Iustin Pop
      inst' = inst { Instance.idx = maxiidx,
158 f4161783 Iustin Pop
                     Instance.pNode = pdx, Instance.sNode = sdx }
159 f4161783 Iustin Pop
      pnode' = Node.setPri pnode inst'
160 f4161783 Iustin Pop
      snode' = Node.setSec snode inst'
161 f4161783 Iustin Pop
      nl' = Container.addTwo pdx pnode' sdx snode' nl
162 f4161783 Iustin Pop
      il' = Container.add maxiidx inst' il
163 f4161783 Iustin Pop
  in (nl', il')
164 f4161783 Iustin Pop
165 3fea6959 Iustin Pop
-- * Arbitrary instances
166 3fea6959 Iustin Pop
167 525bfb36 Iustin Pop
-- | Defines a DNS name.
168 a070c426 Iustin Pop
newtype DNSChar = DNSChar { dnsGetChar::Char }
169 525bfb36 Iustin Pop
170 a070c426 Iustin Pop
instance Arbitrary DNSChar where
171 a070c426 Iustin Pop
    arbitrary = do
172 a070c426 Iustin Pop
      x <- elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
173 a070c426 Iustin Pop
      return (DNSChar x)
174 a070c426 Iustin Pop
175 a070c426 Iustin Pop
getName :: Gen String
176 a070c426 Iustin Pop
getName = do
177 a070c426 Iustin Pop
  n <- choose (1, 64)
178 a070c426 Iustin Pop
  dn <- vector n::Gen [DNSChar]
179 a070c426 Iustin Pop
  return (map dnsGetChar dn)
180 a070c426 Iustin Pop
181 a070c426 Iustin Pop
182 a070c426 Iustin Pop
getFQDN :: Gen String
183 a070c426 Iustin Pop
getFQDN = do
184 a070c426 Iustin Pop
  felem <- getName
185 a070c426 Iustin Pop
  ncomps <- choose (1, 4)
186 a070c426 Iustin Pop
  frest <- vector ncomps::Gen [[DNSChar]]
187 a070c426 Iustin Pop
  let frest' = map (map dnsGetChar) frest
188 a070c426 Iustin Pop
  return (felem ++ "." ++ intercalate "." frest')
189 a070c426 Iustin Pop
190 15f4c8ca Iustin Pop
-- let's generate a random instance
191 15f4c8ca Iustin Pop
instance Arbitrary Instance.Instance where
192 15f4c8ca Iustin Pop
    arbitrary = do
193 a070c426 Iustin Pop
      name <- getFQDN
194 8fcf251f Iustin Pop
      mem <- choose (0, maxMem)
195 8fcf251f Iustin Pop
      dsk <- choose (0, maxDsk)
196 e82271f8 Iustin Pop
      run_st <- elements [ C.inststErrorup
197 e82271f8 Iustin Pop
                         , C.inststErrordown
198 e82271f8 Iustin Pop
                         , C.inststAdmindown
199 e82271f8 Iustin Pop
                         , C.inststNodedown
200 e82271f8 Iustin Pop
                         , C.inststNodeoffline
201 e82271f8 Iustin Pop
                         , C.inststRunning
202 e82271f8 Iustin Pop
                         , "no_such_status1"
203 e82271f8 Iustin Pop
                         , "no_such_status2"]
204 15f4c8ca Iustin Pop
      pn <- arbitrary
205 15f4c8ca Iustin Pop
      sn <- arbitrary
206 8fcf251f Iustin Pop
      vcpus <- choose (0, maxCpu)
207 c352b0a9 Iustin Pop
      return $ Instance.create name mem dsk vcpus run_st [] True pn sn
208 d25643d1 Iustin Pop
                               Types.DTDrbd8
209 15f4c8ca Iustin Pop
210 525bfb36 Iustin Pop
-- | Generas an arbitrary node based on sizing information.
211 525bfb36 Iustin Pop
genNode :: Maybe Int -- ^ Minimum node size in terms of units
212 525bfb36 Iustin Pop
        -> Maybe Int -- ^ Maximum node size (when Nothing, bounded
213 525bfb36 Iustin Pop
                     -- just by the max... constants)
214 525bfb36 Iustin Pop
        -> Gen Node.Node
215 00c75986 Iustin Pop
genNode min_multiplier max_multiplier = do
216 00c75986 Iustin Pop
  let (base_mem, base_dsk, base_cpu) =
217 00c75986 Iustin Pop
          case min_multiplier of
218 00c75986 Iustin Pop
            Just mm -> (mm * Types.unitMem,
219 00c75986 Iustin Pop
                        mm * Types.unitDsk,
220 00c75986 Iustin Pop
                        mm * Types.unitCpu)
221 00c75986 Iustin Pop
            Nothing -> (0, 0, 0)
222 00c75986 Iustin Pop
      (top_mem, top_dsk, top_cpu)  =
223 00c75986 Iustin Pop
          case max_multiplier of
224 00c75986 Iustin Pop
            Just mm -> (mm * Types.unitMem,
225 00c75986 Iustin Pop
                        mm * Types.unitDsk,
226 00c75986 Iustin Pop
                        mm * Types.unitCpu)
227 00c75986 Iustin Pop
            Nothing -> (maxMem, maxDsk, maxCpu)
228 00c75986 Iustin Pop
  name  <- getFQDN
229 00c75986 Iustin Pop
  mem_t <- choose (base_mem, top_mem)
230 00c75986 Iustin Pop
  mem_f <- choose (base_mem, mem_t)
231 00c75986 Iustin Pop
  mem_n <- choose (0, mem_t - mem_f)
232 00c75986 Iustin Pop
  dsk_t <- choose (base_dsk, top_dsk)
233 00c75986 Iustin Pop
  dsk_f <- choose (base_dsk, dsk_t)
234 00c75986 Iustin Pop
  cpu_t <- choose (base_cpu, top_cpu)
235 00c75986 Iustin Pop
  offl  <- arbitrary
236 00c75986 Iustin Pop
  let n = Node.create name (fromIntegral mem_t) mem_n mem_f
237 00c75986 Iustin Pop
          (fromIntegral dsk_t) dsk_f (fromIntegral cpu_t) offl 0
238 00c75986 Iustin Pop
  return $ Node.buildPeers n Container.empty
239 00c75986 Iustin Pop
240 15f4c8ca Iustin Pop
-- and a random node
241 15f4c8ca Iustin Pop
instance Arbitrary Node.Node where
242 00c75986 Iustin Pop
    arbitrary = genNode Nothing Nothing
243 15f4c8ca Iustin Pop
244 88f25dd0 Iustin Pop
-- replace disks
245 88f25dd0 Iustin Pop
instance Arbitrary OpCodes.ReplaceDisksMode where
246 88f25dd0 Iustin Pop
  arbitrary = elements [ OpCodes.ReplaceOnPrimary
247 88f25dd0 Iustin Pop
                       , OpCodes.ReplaceOnSecondary
248 88f25dd0 Iustin Pop
                       , OpCodes.ReplaceNewSecondary
249 88f25dd0 Iustin Pop
                       , OpCodes.ReplaceAuto
250 88f25dd0 Iustin Pop
                       ]
251 88f25dd0 Iustin Pop
252 88f25dd0 Iustin Pop
instance Arbitrary OpCodes.OpCode where
253 88f25dd0 Iustin Pop
  arbitrary = do
254 88f25dd0 Iustin Pop
    op_id <- elements [ "OP_TEST_DELAY"
255 88f25dd0 Iustin Pop
                      , "OP_INSTANCE_REPLACE_DISKS"
256 88f25dd0 Iustin Pop
                      , "OP_INSTANCE_FAILOVER"
257 88f25dd0 Iustin Pop
                      , "OP_INSTANCE_MIGRATE"
258 88f25dd0 Iustin Pop
                      ]
259 88f25dd0 Iustin Pop
    (case op_id of
260 88f25dd0 Iustin Pop
        "OP_TEST_DELAY" ->
261 88f25dd0 Iustin Pop
          liftM3 OpCodes.OpTestDelay arbitrary arbitrary arbitrary
262 88f25dd0 Iustin Pop
        "OP_INSTANCE_REPLACE_DISKS" ->
263 10028866 René Nussbaumer
          liftM5 OpCodes.OpInstanceReplaceDisks arbitrary arbitrary
264 88f25dd0 Iustin Pop
          arbitrary arbitrary arbitrary
265 88f25dd0 Iustin Pop
        "OP_INSTANCE_FAILOVER" ->
266 bbe9758d Iustin Pop
          liftM3 OpCodes.OpInstanceFailover arbitrary arbitrary
267 bbe9758d Iustin Pop
                 arbitrary
268 88f25dd0 Iustin Pop
        "OP_INSTANCE_MIGRATE" ->
269 bbe9758d Iustin Pop
          liftM5 OpCodes.OpInstanceMigrate arbitrary arbitrary
270 bbe9758d Iustin Pop
                 arbitrary arbitrary
271 8d66f58a René Nussbaumer
          arbitrary
272 88f25dd0 Iustin Pop
        _ -> fail "Wrong opcode")
273 88f25dd0 Iustin Pop
274 db079755 Iustin Pop
instance Arbitrary Jobs.OpStatus where
275 db079755 Iustin Pop
  arbitrary = elements [minBound..maxBound]
276 db079755 Iustin Pop
277 db079755 Iustin Pop
instance Arbitrary Jobs.JobStatus where
278 db079755 Iustin Pop
  arbitrary = elements [minBound..maxBound]
279 db079755 Iustin Pop
280 525bfb36 Iustin Pop
newtype SmallRatio = SmallRatio Double deriving Show
281 525bfb36 Iustin Pop
instance Arbitrary SmallRatio where
282 525bfb36 Iustin Pop
    arbitrary = do
283 525bfb36 Iustin Pop
      v <- choose (0, 1)
284 525bfb36 Iustin Pop
      return $ SmallRatio v
285 525bfb36 Iustin Pop
286 3c002a13 Iustin Pop
instance Arbitrary Types.AllocPolicy where
287 3c002a13 Iustin Pop
  arbitrary = elements [minBound..maxBound]
288 3c002a13 Iustin Pop
289 3c002a13 Iustin Pop
instance Arbitrary Types.DiskTemplate where
290 3c002a13 Iustin Pop
  arbitrary = elements [minBound..maxBound]
291 3c002a13 Iustin Pop
292 0047d4e2 Iustin Pop
instance Arbitrary Types.FailMode where
293 0047d4e2 Iustin Pop
    arbitrary = elements [minBound..maxBound]
294 0047d4e2 Iustin Pop
295 0047d4e2 Iustin Pop
instance Arbitrary a => Arbitrary (Types.OpResult a) where
296 0047d4e2 Iustin Pop
    arbitrary = arbitrary >>= \c ->
297 0047d4e2 Iustin Pop
                case c of
298 0047d4e2 Iustin Pop
                  False -> liftM Types.OpFail arbitrary
299 0047d4e2 Iustin Pop
                  True -> liftM Types.OpGood arbitrary
300 0047d4e2 Iustin Pop
301 3fea6959 Iustin Pop
-- * Actual tests
302 8fcf251f Iustin Pop
303 525bfb36 Iustin Pop
-- ** Utils tests
304 525bfb36 Iustin Pop
305 525bfb36 Iustin Pop
-- | If the list is not just an empty element, and if the elements do
306 525bfb36 Iustin Pop
-- not contain commas, then join+split should be idempotent.
307 a1cd7c1e Iustin Pop
prop_Utils_commaJoinSplit =
308 a1cd7c1e Iustin Pop
    forAll (arbitrary `suchThat`
309 a1cd7c1e Iustin Pop
            (\l -> l /= [""] && all (not . elem ',') l )) $ \lst ->
310 72bb6b4e Iustin Pop
    Utils.sepSplit ',' (Utils.commaJoin lst) ==? lst
311 a1cd7c1e Iustin Pop
312 525bfb36 Iustin Pop
-- | Split and join should always be idempotent.
313 72bb6b4e Iustin Pop
prop_Utils_commaSplitJoin s =
314 72bb6b4e Iustin Pop
    Utils.commaJoin (Utils.sepSplit ',' s) ==? s
315 691dcd2a Iustin Pop
316 a810ad21 Iustin Pop
-- | fromObjWithDefault, we test using the Maybe monad and an integer
317 525bfb36 Iustin Pop
-- value.
318 a810ad21 Iustin Pop
prop_Utils_fromObjWithDefault def_value random_key =
319 a810ad21 Iustin Pop
    -- a missing key will be returned with the default
320 a810ad21 Iustin Pop
    Utils.fromObjWithDefault [] random_key def_value == Just def_value &&
321 a810ad21 Iustin Pop
    -- a found key will be returned as is, not with default
322 a810ad21 Iustin Pop
    Utils.fromObjWithDefault [(random_key, J.showJSON def_value)]
323 a810ad21 Iustin Pop
         random_key (def_value+1) == Just def_value
324 cc532bdd Iustin Pop
        where _types = def_value :: Integer
325 a810ad21 Iustin Pop
326 bfe6c954 Guido Trotter
-- | Test that functional if' behaves like the syntactic sugar if.
327 72bb6b4e Iustin Pop
prop_Utils_if'if :: Bool -> Int -> Int -> Gen Prop
328 72bb6b4e Iustin Pop
prop_Utils_if'if cnd a b =
329 72bb6b4e Iustin Pop
    Utils.if' cnd a b ==? if cnd then a else b
330 bfe6c954 Guido Trotter
331 22fac87d Guido Trotter
-- | Test basic select functionality
332 72bb6b4e Iustin Pop
prop_Utils_select :: Int      -- ^ Default result
333 72bb6b4e Iustin Pop
                  -> [Int]    -- ^ List of False values
334 72bb6b4e Iustin Pop
                  -> [Int]    -- ^ List of True values
335 72bb6b4e Iustin Pop
                  -> Gen Prop -- ^ Test result
336 22fac87d Guido Trotter
prop_Utils_select def lst1 lst2 =
337 72bb6b4e Iustin Pop
  Utils.select def cndlist ==? expectedresult
338 22fac87d Guido Trotter
  where expectedresult = Utils.if' (null lst2) def (head lst2)
339 bfe6c954 Guido Trotter
        flist = map (\e -> (False, e)) lst1
340 bfe6c954 Guido Trotter
        tlist = map (\e -> (True, e)) lst2
341 22fac87d Guido Trotter
        cndlist = flist ++ tlist
342 22fac87d Guido Trotter
343 22fac87d Guido Trotter
-- | Test basic select functionality with undefined default
344 72bb6b4e Iustin Pop
prop_Utils_select_undefd :: [Int]            -- ^ List of False values
345 22fac87d Guido Trotter
                         -> NonEmptyList Int -- ^ List of True values
346 72bb6b4e Iustin Pop
                         -> Gen Prop         -- ^ Test result
347 22fac87d Guido Trotter
prop_Utils_select_undefd lst1 (NonEmpty lst2) =
348 72bb6b4e Iustin Pop
  Utils.select undefined cndlist ==? head lst2
349 22fac87d Guido Trotter
  where flist = map (\e -> (False, e)) lst1
350 22fac87d Guido Trotter
        tlist = map (\e -> (True, e)) lst2
351 22fac87d Guido Trotter
        cndlist = flist ++ tlist
352 22fac87d Guido Trotter
353 22fac87d Guido Trotter
-- | Test basic select functionality with undefined list values
354 72bb6b4e Iustin Pop
prop_Utils_select_undefv :: [Int]            -- ^ List of False values
355 22fac87d Guido Trotter
                         -> NonEmptyList Int -- ^ List of True values
356 72bb6b4e Iustin Pop
                         -> Gen Prop         -- ^ Test result
357 22fac87d Guido Trotter
prop_Utils_select_undefv lst1 (NonEmpty lst2) =
358 72bb6b4e Iustin Pop
  Utils.select undefined cndlist ==? head lst2
359 22fac87d Guido Trotter
  where flist = map (\e -> (False, e)) lst1
360 22fac87d Guido Trotter
        tlist = map (\e -> (True, e)) lst2
361 22fac87d Guido Trotter
        cndlist = flist ++ tlist ++ [undefined]
362 bfe6c954 Guido Trotter
363 1cb92fac Iustin Pop
prop_Utils_parseUnit (NonNegative n) =
364 1cb92fac Iustin Pop
    Utils.parseUnit (show n) == Types.Ok n &&
365 1cb92fac Iustin Pop
    Utils.parseUnit (show n ++ "m") == Types.Ok n &&
366 1cb92fac Iustin Pop
    (case Utils.parseUnit (show n ++ "M") of
367 1cb92fac Iustin Pop
      Types.Ok m -> if n > 0
368 1cb92fac Iustin Pop
                    then m < n  -- for positive values, X MB is less than X MiB
369 1cb92fac Iustin Pop
                    else m == 0 -- but for 0, 0 MB == 0 MiB
370 1cb92fac Iustin Pop
      Types.Bad _ -> False) &&
371 1cb92fac Iustin Pop
    Utils.parseUnit (show n ++ "g") == Types.Ok (n*1024) &&
372 1cb92fac Iustin Pop
    Utils.parseUnit (show n ++ "t") == Types.Ok (n*1048576) &&
373 1cb92fac Iustin Pop
    Types.isBad (Utils.parseUnit (show n ++ "x")::Types.Result Int)
374 1b0a6356 Iustin Pop
    where _types = n::Int
375 1cb92fac Iustin Pop
376 525bfb36 Iustin Pop
-- | Test list for the Utils module.
377 23fe06c2 Iustin Pop
testSuite "Utils"
378 23fe06c2 Iustin Pop
              [ 'prop_Utils_commaJoinSplit
379 23fe06c2 Iustin Pop
              , 'prop_Utils_commaSplitJoin
380 23fe06c2 Iustin Pop
              , 'prop_Utils_fromObjWithDefault
381 23fe06c2 Iustin Pop
              , 'prop_Utils_if'if
382 23fe06c2 Iustin Pop
              , 'prop_Utils_select
383 23fe06c2 Iustin Pop
              , 'prop_Utils_select_undefd
384 23fe06c2 Iustin Pop
              , 'prop_Utils_select_undefv
385 23fe06c2 Iustin Pop
              , 'prop_Utils_parseUnit
386 23fe06c2 Iustin Pop
              ]
387 691dcd2a Iustin Pop
388 525bfb36 Iustin Pop
-- ** PeerMap tests
389 525bfb36 Iustin Pop
390 525bfb36 Iustin Pop
-- | Make sure add is idempotent.
391 fbb95f28 Iustin Pop
prop_PeerMap_addIdempotent pmap key em =
392 72bb6b4e Iustin Pop
    fn puniq ==? fn (fn puniq)
393 7bc82927 Iustin Pop
    where _types = (pmap::PeerMap.PeerMap,
394 fbb95f28 Iustin Pop
                    key::PeerMap.Key, em::PeerMap.Elem)
395 fbb95f28 Iustin Pop
          fn = PeerMap.add key em
396 7bc82927 Iustin Pop
          puniq = PeerMap.accumArray const pmap
397 15f4c8ca Iustin Pop
398 525bfb36 Iustin Pop
-- | Make sure remove is idempotent.
399 15f4c8ca Iustin Pop
prop_PeerMap_removeIdempotent pmap key =
400 72bb6b4e Iustin Pop
    fn puniq ==? fn (fn puniq)
401 7bc82927 Iustin Pop
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
402 7bc82927 Iustin Pop
          fn = PeerMap.remove key
403 15f4c8ca Iustin Pop
          puniq = PeerMap.accumArray const pmap
404 15f4c8ca Iustin Pop
405 525bfb36 Iustin Pop
-- | Make sure a missing item returns 0.
406 15f4c8ca Iustin Pop
prop_PeerMap_findMissing pmap key =
407 72bb6b4e Iustin Pop
    PeerMap.find key (PeerMap.remove key puniq) ==? 0
408 7bc82927 Iustin Pop
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
409 15f4c8ca Iustin Pop
          puniq = PeerMap.accumArray const pmap
410 15f4c8ca Iustin Pop
411 525bfb36 Iustin Pop
-- | Make sure an added item is found.
412 fbb95f28 Iustin Pop
prop_PeerMap_addFind pmap key em =
413 72bb6b4e Iustin Pop
    PeerMap.find key (PeerMap.add key em puniq) ==? em
414 7bc82927 Iustin Pop
    where _types = (pmap::PeerMap.PeerMap,
415 fbb95f28 Iustin Pop
                    key::PeerMap.Key, em::PeerMap.Elem)
416 7bc82927 Iustin Pop
          puniq = PeerMap.accumArray const pmap
417 15f4c8ca Iustin Pop
418 525bfb36 Iustin Pop
-- | Manual check that maxElem returns the maximum indeed, or 0 for null.
419 15f4c8ca Iustin Pop
prop_PeerMap_maxElem pmap =
420 72bb6b4e Iustin Pop
    PeerMap.maxElem puniq ==? if null puniq then 0
421 72bb6b4e Iustin Pop
                              else (maximum . snd . unzip) puniq
422 7bc82927 Iustin Pop
    where _types = pmap::PeerMap.PeerMap
423 15f4c8ca Iustin Pop
          puniq = PeerMap.accumArray const pmap
424 15f4c8ca Iustin Pop
425 525bfb36 Iustin Pop
-- | List of tests for the PeerMap module.
426 23fe06c2 Iustin Pop
testSuite "PeerMap"
427 23fe06c2 Iustin Pop
              [ 'prop_PeerMap_addIdempotent
428 23fe06c2 Iustin Pop
              , 'prop_PeerMap_removeIdempotent
429 23fe06c2 Iustin Pop
              , 'prop_PeerMap_maxElem
430 23fe06c2 Iustin Pop
              , 'prop_PeerMap_addFind
431 23fe06c2 Iustin Pop
              , 'prop_PeerMap_findMissing
432 23fe06c2 Iustin Pop
              ]
433 7dd5ee6c Iustin Pop
434 525bfb36 Iustin Pop
-- ** Container tests
435 095d7ac0 Iustin Pop
436 095d7ac0 Iustin Pop
prop_Container_addTwo cdata i1 i2 =
437 095d7ac0 Iustin Pop
    fn i1 i2 cont == fn i2 i1 cont &&
438 095d7ac0 Iustin Pop
       fn i1 i2 cont == fn i1 i2 (fn i1 i2 cont)
439 095d7ac0 Iustin Pop
    where _types = (cdata::[Int],
440 095d7ac0 Iustin Pop
                    i1::Int, i2::Int)
441 095d7ac0 Iustin Pop
          cont = foldl (\c x -> Container.add x x c) Container.empty cdata
442 095d7ac0 Iustin Pop
          fn x1 x2 = Container.addTwo x1 x1 x2 x2
443 095d7ac0 Iustin Pop
444 5ef78537 Iustin Pop
prop_Container_nameOf node =
445 5ef78537 Iustin Pop
  let nl = makeSmallCluster node 1
446 5ef78537 Iustin Pop
      fnode = head (Container.elems nl)
447 72bb6b4e Iustin Pop
  in Container.nameOf nl (Node.idx fnode) ==? Node.name fnode
448 5ef78537 Iustin Pop
449 525bfb36 Iustin Pop
-- | We test that in a cluster, given a random node, we can find it by
450 5ef78537 Iustin Pop
-- its name and alias, as long as all names and aliases are unique,
451 525bfb36 Iustin Pop
-- and that we fail to find a non-existing name.
452 5ef78537 Iustin Pop
prop_Container_findByName node othername =
453 5ef78537 Iustin Pop
  forAll (choose (1, 20)) $ \ cnt ->
454 5ef78537 Iustin Pop
  forAll (choose (0, cnt - 1)) $ \ fidx ->
455 5ef78537 Iustin Pop
  forAll (vector cnt) $ \ names ->
456 5ef78537 Iustin Pop
  (length . nub) (map fst names ++ map snd names) ==
457 5ef78537 Iustin Pop
  length names * 2 &&
458 5ef78537 Iustin Pop
  not (othername `elem` (map fst names ++ map snd names)) ==>
459 5ef78537 Iustin Pop
  let nl = makeSmallCluster node cnt
460 5ef78537 Iustin Pop
      nodes = Container.elems nl
461 5ef78537 Iustin Pop
      nodes' = map (\((name, alias), nn) -> (Node.idx nn,
462 5ef78537 Iustin Pop
                                             nn { Node.name = name,
463 5ef78537 Iustin Pop
                                                  Node.alias = alias }))
464 5ef78537 Iustin Pop
               $ zip names nodes
465 cb0c77ff Iustin Pop
      nl' = Container.fromList nodes'
466 5ef78537 Iustin Pop
      target = snd (nodes' !! fidx)
467 5ef78537 Iustin Pop
  in Container.findByName nl' (Node.name target) == Just target &&
468 5ef78537 Iustin Pop
     Container.findByName nl' (Node.alias target) == Just target &&
469 5ef78537 Iustin Pop
     Container.findByName nl' othername == Nothing
470 5ef78537 Iustin Pop
471 23fe06c2 Iustin Pop
testSuite "Container"
472 23fe06c2 Iustin Pop
              [ 'prop_Container_addTwo
473 23fe06c2 Iustin Pop
              , 'prop_Container_nameOf
474 23fe06c2 Iustin Pop
              , 'prop_Container_findByName
475 23fe06c2 Iustin Pop
              ]
476 095d7ac0 Iustin Pop
477 525bfb36 Iustin Pop
-- ** Instance tests
478 525bfb36 Iustin Pop
479 7bc82927 Iustin Pop
-- Simple instance tests, we only have setter/getters
480 7bc82927 Iustin Pop
481 39d11971 Iustin Pop
prop_Instance_creat inst =
482 72bb6b4e Iustin Pop
    Instance.name inst ==? Instance.alias inst
483 39d11971 Iustin Pop
484 7bc82927 Iustin Pop
prop_Instance_setIdx inst idx =
485 72bb6b4e Iustin Pop
    Instance.idx (Instance.setIdx inst idx) ==? idx
486 7bc82927 Iustin Pop
    where _types = (inst::Instance.Instance, idx::Types.Idx)
487 7bc82927 Iustin Pop
488 7bc82927 Iustin Pop
prop_Instance_setName inst name =
489 39d11971 Iustin Pop
    Instance.name newinst == name &&
490 39d11971 Iustin Pop
    Instance.alias newinst == name
491 39d11971 Iustin Pop
    where _types = (inst::Instance.Instance, name::String)
492 39d11971 Iustin Pop
          newinst = Instance.setName inst name
493 39d11971 Iustin Pop
494 39d11971 Iustin Pop
prop_Instance_setAlias inst name =
495 39d11971 Iustin Pop
    Instance.name newinst == Instance.name inst &&
496 39d11971 Iustin Pop
    Instance.alias newinst == name
497 7bc82927 Iustin Pop
    where _types = (inst::Instance.Instance, name::String)
498 39d11971 Iustin Pop
          newinst = Instance.setAlias inst name
499 7bc82927 Iustin Pop
500 7bc82927 Iustin Pop
prop_Instance_setPri inst pdx =
501 72bb6b4e Iustin Pop
    Instance.pNode (Instance.setPri inst pdx) ==? pdx
502 7bc82927 Iustin Pop
    where _types = (inst::Instance.Instance, pdx::Types.Ndx)
503 7bc82927 Iustin Pop
504 7bc82927 Iustin Pop
prop_Instance_setSec inst sdx =
505 72bb6b4e Iustin Pop
    Instance.sNode (Instance.setSec inst sdx) ==? sdx
506 7bc82927 Iustin Pop
    where _types = (inst::Instance.Instance, sdx::Types.Ndx)
507 7bc82927 Iustin Pop
508 7bc82927 Iustin Pop
prop_Instance_setBoth inst pdx sdx =
509 2060348b Iustin Pop
    Instance.pNode si == pdx && Instance.sNode si == sdx
510 7bc82927 Iustin Pop
    where _types = (inst::Instance.Instance, pdx::Types.Ndx, sdx::Types.Ndx)
511 7bc82927 Iustin Pop
          si = Instance.setBoth inst pdx sdx
512 7bc82927 Iustin Pop
513 a1cd7c1e Iustin Pop
prop_Instance_runStatus_True =
514 a1cd7c1e Iustin Pop
    forAll (arbitrary `suchThat`
515 a1cd7c1e Iustin Pop
            ((`elem` Instance.runningStates) . Instance.runSt))
516 a1cd7c1e Iustin Pop
    Instance.running
517 1ae7a904 Iustin Pop
518 1ae7a904 Iustin Pop
prop_Instance_runStatus_False inst =
519 1ae7a904 Iustin Pop
    let run_st = Instance.running inst
520 2060348b Iustin Pop
        run_tx = Instance.runSt inst
521 1ae7a904 Iustin Pop
    in
522 a46f34d7 Iustin Pop
      run_tx `notElem` Instance.runningStates ==> not run_st
523 1ae7a904 Iustin Pop
524 8fcf251f Iustin Pop
prop_Instance_shrinkMG inst =
525 8fcf251f Iustin Pop
    Instance.mem inst >= 2 * Types.unitMem ==>
526 8fcf251f Iustin Pop
        case Instance.shrinkByType inst Types.FailMem of
527 8fcf251f Iustin Pop
          Types.Ok inst' ->
528 8fcf251f Iustin Pop
              Instance.mem inst' == Instance.mem inst - Types.unitMem
529 8fcf251f Iustin Pop
          _ -> False
530 8fcf251f Iustin Pop
531 8fcf251f Iustin Pop
prop_Instance_shrinkMF inst =
532 41085bd3 Iustin Pop
    forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
533 41085bd3 Iustin Pop
    let inst' = inst { Instance.mem = mem}
534 41085bd3 Iustin Pop
    in Types.isBad $ Instance.shrinkByType inst' Types.FailMem
535 8fcf251f Iustin Pop
536 8fcf251f Iustin Pop
prop_Instance_shrinkCG inst =
537 8fcf251f Iustin Pop
    Instance.vcpus inst >= 2 * Types.unitCpu ==>
538 8fcf251f Iustin Pop
        case Instance.shrinkByType inst Types.FailCPU of
539 8fcf251f Iustin Pop
          Types.Ok inst' ->
540 8fcf251f Iustin Pop
              Instance.vcpus inst' == Instance.vcpus inst - Types.unitCpu
541 8fcf251f Iustin Pop
          _ -> False
542 8fcf251f Iustin Pop
543 8fcf251f Iustin Pop
prop_Instance_shrinkCF inst =
544 41085bd3 Iustin Pop
    forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
545 41085bd3 Iustin Pop
    let inst' = inst { Instance.vcpus = vcpus }
546 41085bd3 Iustin Pop
    in Types.isBad $ Instance.shrinkByType inst' Types.FailCPU
547 8fcf251f Iustin Pop
548 8fcf251f Iustin Pop
prop_Instance_shrinkDG inst =
549 8fcf251f Iustin Pop
    Instance.dsk inst >= 2 * Types.unitDsk ==>
550 8fcf251f Iustin Pop
        case Instance.shrinkByType inst Types.FailDisk of
551 8fcf251f Iustin Pop
          Types.Ok inst' ->
552 8fcf251f Iustin Pop
              Instance.dsk inst' == Instance.dsk inst - Types.unitDsk
553 8fcf251f Iustin Pop
          _ -> False
554 8fcf251f Iustin Pop
555 8fcf251f Iustin Pop
prop_Instance_shrinkDF inst =
556 41085bd3 Iustin Pop
    forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
557 41085bd3 Iustin Pop
    let inst' = inst { Instance.dsk = dsk }
558 41085bd3 Iustin Pop
    in Types.isBad $ Instance.shrinkByType inst' Types.FailDisk
559 8fcf251f Iustin Pop
560 8fcf251f Iustin Pop
prop_Instance_setMovable inst m =
561 72bb6b4e Iustin Pop
    Instance.movable inst' ==? m
562 4a007641 Iustin Pop
    where inst' = Instance.setMovable inst m
563 8fcf251f Iustin Pop
564 23fe06c2 Iustin Pop
testSuite "Instance"
565 23fe06c2 Iustin Pop
              [ 'prop_Instance_creat
566 23fe06c2 Iustin Pop
              , 'prop_Instance_setIdx
567 23fe06c2 Iustin Pop
              , 'prop_Instance_setName
568 23fe06c2 Iustin Pop
              , 'prop_Instance_setAlias
569 23fe06c2 Iustin Pop
              , 'prop_Instance_setPri
570 23fe06c2 Iustin Pop
              , 'prop_Instance_setSec
571 23fe06c2 Iustin Pop
              , 'prop_Instance_setBoth
572 23fe06c2 Iustin Pop
              , 'prop_Instance_runStatus_True
573 23fe06c2 Iustin Pop
              , 'prop_Instance_runStatus_False
574 23fe06c2 Iustin Pop
              , 'prop_Instance_shrinkMG
575 23fe06c2 Iustin Pop
              , 'prop_Instance_shrinkMF
576 23fe06c2 Iustin Pop
              , 'prop_Instance_shrinkCG
577 23fe06c2 Iustin Pop
              , 'prop_Instance_shrinkCF
578 23fe06c2 Iustin Pop
              , 'prop_Instance_shrinkDG
579 23fe06c2 Iustin Pop
              , 'prop_Instance_shrinkDF
580 23fe06c2 Iustin Pop
              , 'prop_Instance_setMovable
581 23fe06c2 Iustin Pop
              ]
582 1ae7a904 Iustin Pop
583 525bfb36 Iustin Pop
-- ** Text backend tests
584 525bfb36 Iustin Pop
585 1ae7a904 Iustin Pop
-- Instance text loader tests
586 1ae7a904 Iustin Pop
587 a1cd7c1e Iustin Pop
prop_Text_Load_Instance name mem dsk vcpus status
588 a1cd7c1e Iustin Pop
                        (NonEmpty pnode) snode
589 6429e8d8 Iustin Pop
                        (NonNegative pdx) (NonNegative sdx) autobal dt =
590 309e7c9a Iustin Pop
    pnode /= snode && pdx /= sdx ==>
591 1ae7a904 Iustin Pop
    let vcpus_s = show vcpus
592 1ae7a904 Iustin Pop
        dsk_s = show dsk
593 1ae7a904 Iustin Pop
        mem_s = show mem
594 39d11971 Iustin Pop
        ndx = if null snode
595 39d11971 Iustin Pop
              then [(pnode, pdx)]
596 309e7c9a Iustin Pop
              else [(pnode, pdx), (snode, sdx)]
597 99b63608 Iustin Pop
        nl = Data.Map.fromList ndx
598 434c15d5 Iustin Pop
        tags = ""
599 bc782180 Iustin Pop
        sbal = if autobal then "Y" else "N"
600 2c9336a4 Iustin Pop
        sdt = Types.diskTemplateToString dt
601 99b63608 Iustin Pop
        inst = Text.loadInst nl
602 bc782180 Iustin Pop
               [name, mem_s, dsk_s, vcpus_s, status,
603 6429e8d8 Iustin Pop
                sbal, pnode, snode, sdt, tags]
604 99b63608 Iustin Pop
        fail1 = Text.loadInst nl
605 bc782180 Iustin Pop
               [name, mem_s, dsk_s, vcpus_s, status,
606 6429e8d8 Iustin Pop
                sbal, pnode, pnode, tags]
607 1ae7a904 Iustin Pop
        _types = ( name::String, mem::Int, dsk::Int
608 1ae7a904 Iustin Pop
                 , vcpus::Int, status::String
609 a1cd7c1e Iustin Pop
                 , snode::String
610 bc782180 Iustin Pop
                 , autobal::Bool)
611 1ae7a904 Iustin Pop
    in
612 1ae7a904 Iustin Pop
      case inst of
613 6429e8d8 Iustin Pop
        Types.Bad msg -> printTestCase ("Failed to load instance: " ++ msg)
614 6429e8d8 Iustin Pop
                         False
615 1b0a6356 Iustin Pop
        Types.Ok (_, i) -> printTestCase "Mismatch in some field while\
616 1b0a6356 Iustin Pop
                                         \ loading the instance" $
617 cc532bdd Iustin Pop
            Instance.name i == name &&
618 cc532bdd Iustin Pop
            Instance.vcpus i == vcpus &&
619 cc532bdd Iustin Pop
            Instance.mem i == mem &&
620 cc532bdd Iustin Pop
            Instance.pNode i == pdx &&
621 cc532bdd Iustin Pop
            Instance.sNode i == (if null snode
622 cc532bdd Iustin Pop
                                 then Node.noSecondary
623 309e7c9a Iustin Pop
                                 else sdx) &&
624 0e09422b Iustin Pop
            Instance.autoBalance i == autobal &&
625 6429e8d8 Iustin Pop
            Types.isBad fail1
626 39d11971 Iustin Pop
627 39d11971 Iustin Pop
prop_Text_Load_InstanceFail ktn fields =
628 6429e8d8 Iustin Pop
    length fields /= 10 ==>
629 bc782180 Iustin Pop
    case Text.loadInst nl fields of
630 6429e8d8 Iustin Pop
      Types.Ok _ -> printTestCase "Managed to load instance from invalid\
631 6429e8d8 Iustin Pop
                                  \ data" False
632 6429e8d8 Iustin Pop
      Types.Bad msg -> printTestCase ("Unrecognised error message: " ++ msg) $
633 6429e8d8 Iustin Pop
                       "Invalid/incomplete instance data: '" `isPrefixOf` msg
634 99b63608 Iustin Pop
    where nl = Data.Map.fromList ktn
635 39d11971 Iustin Pop
636 39d11971 Iustin Pop
prop_Text_Load_Node name tm nm fm td fd tc fo =
637 39d11971 Iustin Pop
    let conv v = if v < 0
638 39d11971 Iustin Pop
                    then "?"
639 39d11971 Iustin Pop
                    else show v
640 39d11971 Iustin Pop
        tm_s = conv tm
641 39d11971 Iustin Pop
        nm_s = conv nm
642 39d11971 Iustin Pop
        fm_s = conv fm
643 39d11971 Iustin Pop
        td_s = conv td
644 39d11971 Iustin Pop
        fd_s = conv fd
645 39d11971 Iustin Pop
        tc_s = conv tc
646 39d11971 Iustin Pop
        fo_s = if fo
647 39d11971 Iustin Pop
               then "Y"
648 39d11971 Iustin Pop
               else "N"
649 39d11971 Iustin Pop
        any_broken = any (< 0) [tm, nm, fm, td, fd, tc]
650 10ef6b4e Iustin Pop
        gid = Group.uuid defGroup
651 10ef6b4e Iustin Pop
    in case Text.loadNode defGroupAssoc
652 10ef6b4e Iustin Pop
           [name, tm_s, nm_s, fm_s, td_s, fd_s, tc_s, fo_s, gid] of
653 39d11971 Iustin Pop
         Nothing -> False
654 39d11971 Iustin Pop
         Just (name', node) ->
655 39d11971 Iustin Pop
             if fo || any_broken
656 39d11971 Iustin Pop
             then Node.offline node
657 4a007641 Iustin Pop
             else Node.name node == name' && name' == name &&
658 4a007641 Iustin Pop
                  Node.alias node == name &&
659 4a007641 Iustin Pop
                  Node.tMem node == fromIntegral tm &&
660 4a007641 Iustin Pop
                  Node.nMem node == nm &&
661 4a007641 Iustin Pop
                  Node.fMem node == fm &&
662 4a007641 Iustin Pop
                  Node.tDsk node == fromIntegral td &&
663 4a007641 Iustin Pop
                  Node.fDsk node == fd &&
664 4a007641 Iustin Pop
                  Node.tCpu node == fromIntegral tc
665 39d11971 Iustin Pop
666 39d11971 Iustin Pop
prop_Text_Load_NodeFail fields =
667 10ef6b4e Iustin Pop
    length fields /= 8 ==> isNothing $ Text.loadNode Data.Map.empty fields
668 1ae7a904 Iustin Pop
669 50811e2c Iustin Pop
prop_Text_NodeLSIdempotent node =
670 10ef6b4e Iustin Pop
    (Text.loadNode defGroupAssoc.
671 10ef6b4e Iustin Pop
         Utils.sepSplit '|' . Text.serializeNode defGroupList) n ==
672 50811e2c Iustin Pop
    Just (Node.name n, n)
673 50811e2c Iustin Pop
    -- override failN1 to what loadNode returns by default
674 50811e2c Iustin Pop
    where n = node { Node.failN1 = True, Node.offline = False }
675 50811e2c Iustin Pop
676 23fe06c2 Iustin Pop
testSuite "Text"
677 23fe06c2 Iustin Pop
              [ 'prop_Text_Load_Instance
678 23fe06c2 Iustin Pop
              , 'prop_Text_Load_InstanceFail
679 23fe06c2 Iustin Pop
              , 'prop_Text_Load_Node
680 23fe06c2 Iustin Pop
              , 'prop_Text_Load_NodeFail
681 23fe06c2 Iustin Pop
              , 'prop_Text_NodeLSIdempotent
682 23fe06c2 Iustin Pop
              ]
683 7dd5ee6c Iustin Pop
684 525bfb36 Iustin Pop
-- ** Node tests
685 7dd5ee6c Iustin Pop
686 82ea2874 Iustin Pop
prop_Node_setAlias node name =
687 82ea2874 Iustin Pop
    Node.name newnode == Node.name node &&
688 82ea2874 Iustin Pop
    Node.alias newnode == name
689 82ea2874 Iustin Pop
    where _types = (node::Node.Node, name::String)
690 82ea2874 Iustin Pop
          newnode = Node.setAlias node name
691 82ea2874 Iustin Pop
692 82ea2874 Iustin Pop
prop_Node_setOffline node status =
693 72bb6b4e Iustin Pop
    Node.offline newnode ==? status
694 82ea2874 Iustin Pop
    where newnode = Node.setOffline node status
695 82ea2874 Iustin Pop
696 82ea2874 Iustin Pop
prop_Node_setXmem node xm =
697 72bb6b4e Iustin Pop
    Node.xMem newnode ==? xm
698 82ea2874 Iustin Pop
    where newnode = Node.setXmem node xm
699 82ea2874 Iustin Pop
700 82ea2874 Iustin Pop
prop_Node_setMcpu node mc =
701 72bb6b4e Iustin Pop
    Node.mCpu newnode ==? mc
702 82ea2874 Iustin Pop
    where newnode = Node.setMcpu node mc
703 82ea2874 Iustin Pop
704 525bfb36 Iustin Pop
-- | Check that an instance add with too high memory or disk will be
705 525bfb36 Iustin Pop
-- rejected.
706 8fcf251f Iustin Pop
prop_Node_addPriFM node inst = Instance.mem inst >= Node.fMem node &&
707 8fcf251f Iustin Pop
                               not (Node.failN1 node)
708 8fcf251f Iustin Pop
                               ==>
709 8fcf251f Iustin Pop
                               case Node.addPri node inst'' of
710 8fcf251f Iustin Pop
                                 Types.OpFail Types.FailMem -> True
711 8fcf251f Iustin Pop
                                 _ -> False
712 15f4c8ca Iustin Pop
    where _types = (node::Node.Node, inst::Instance.Instance)
713 8fcf251f Iustin Pop
          inst' = setInstanceSmallerThanNode node inst
714 8fcf251f Iustin Pop
          inst'' = inst' { Instance.mem = Instance.mem inst }
715 8fcf251f Iustin Pop
716 8fcf251f Iustin Pop
prop_Node_addPriFD node inst = Instance.dsk inst >= Node.fDsk node &&
717 8fcf251f Iustin Pop
                               not (Node.failN1 node)
718 8fcf251f Iustin Pop
                               ==>
719 8fcf251f Iustin Pop
                               case Node.addPri node inst'' of
720 8fcf251f Iustin Pop
                                 Types.OpFail Types.FailDisk -> True
721 8fcf251f Iustin Pop
                                 _ -> False
722 8fcf251f Iustin Pop
    where _types = (node::Node.Node, inst::Instance.Instance)
723 8fcf251f Iustin Pop
          inst' = setInstanceSmallerThanNode node inst
724 8fcf251f Iustin Pop
          inst'' = inst' { Instance.dsk = Instance.dsk inst }
725 8fcf251f Iustin Pop
726 41085bd3 Iustin Pop
prop_Node_addPriFC node inst (Positive extra) =
727 41085bd3 Iustin Pop
    not (Node.failN1 node) ==>
728 41085bd3 Iustin Pop
        case Node.addPri node inst'' of
729 41085bd3 Iustin Pop
          Types.OpFail Types.FailCPU -> True
730 41085bd3 Iustin Pop
          _ -> False
731 8fcf251f Iustin Pop
    where _types = (node::Node.Node, inst::Instance.Instance)
732 8fcf251f Iustin Pop
          inst' = setInstanceSmallerThanNode node inst
733 41085bd3 Iustin Pop
          inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
734 7bc82927 Iustin Pop
735 525bfb36 Iustin Pop
-- | Check that an instance add with too high memory or disk will be
736 525bfb36 Iustin Pop
-- rejected.
737 15f4c8ca Iustin Pop
prop_Node_addSec node inst pdx =
738 2060348b Iustin Pop
    (Instance.mem inst >= (Node.fMem node - Node.rMem node) ||
739 2060348b Iustin Pop
     Instance.dsk inst >= Node.fDsk node) &&
740 9f6dcdea Iustin Pop
    not (Node.failN1 node)
741 79a72ce7 Iustin Pop
    ==> isFailure (Node.addSec node inst pdx)
742 15f4c8ca Iustin Pop
        where _types = (node::Node.Node, inst::Instance.Instance, pdx::Int)
743 7dd5ee6c Iustin Pop
744 525bfb36 Iustin Pop
-- | Checks for memory reservation changes.
745 752635d3 Iustin Pop
prop_Node_rMem inst =
746 3158250d Iustin Pop
    forAll (arbitrary `suchThat` ((> Types.unitMem) . Node.fMem)) $ \node ->
747 9cbc1edb Iustin Pop
    -- ab = auto_balance, nb = non-auto_balance
748 9cbc1edb Iustin Pop
    -- we use -1 as the primary node of the instance
749 0e09422b Iustin Pop
    let inst' = inst { Instance.pNode = -1, Instance.autoBalance = True }
750 9cbc1edb Iustin Pop
        inst_ab = setInstanceSmallerThanNode node inst'
751 0e09422b Iustin Pop
        inst_nb = inst_ab { Instance.autoBalance = False }
752 9cbc1edb Iustin Pop
        -- now we have the two instances, identical except the
753 0e09422b Iustin Pop
        -- autoBalance attribute
754 9cbc1edb Iustin Pop
        orig_rmem = Node.rMem node
755 9cbc1edb Iustin Pop
        inst_idx = Instance.idx inst_ab
756 9cbc1edb Iustin Pop
        node_add_ab = Node.addSec node inst_ab (-1)
757 9cbc1edb Iustin Pop
        node_add_nb = Node.addSec node inst_nb (-1)
758 1b0a6356 Iustin Pop
        node_del_ab = liftM (`Node.removeSec` inst_ab) node_add_ab
759 1b0a6356 Iustin Pop
        node_del_nb = liftM (`Node.removeSec` inst_nb) node_add_nb
760 9cbc1edb Iustin Pop
    in case (node_add_ab, node_add_nb, node_del_ab, node_del_nb) of
761 9cbc1edb Iustin Pop
         (Types.OpGood a_ab, Types.OpGood a_nb,
762 9cbc1edb Iustin Pop
          Types.OpGood d_ab, Types.OpGood d_nb) ->
763 752635d3 Iustin Pop
             printTestCase "Consistency checks failed" $
764 9cbc1edb Iustin Pop
             Node.rMem a_ab >  orig_rmem &&
765 9cbc1edb Iustin Pop
             Node.rMem a_ab - orig_rmem == Instance.mem inst_ab &&
766 9cbc1edb Iustin Pop
             Node.rMem a_nb == orig_rmem &&
767 9cbc1edb Iustin Pop
             Node.rMem d_ab == orig_rmem &&
768 9cbc1edb Iustin Pop
             Node.rMem d_nb == orig_rmem &&
769 9cbc1edb Iustin Pop
             -- this is not related to rMem, but as good a place to
770 9cbc1edb Iustin Pop
             -- test as any
771 9cbc1edb Iustin Pop
             inst_idx `elem` Node.sList a_ab &&
772 9cbc1edb Iustin Pop
             not (inst_idx `elem` Node.sList d_ab)
773 752635d3 Iustin Pop
         x -> printTestCase ("Failed to add/remove instances: " ++ show x)
774 752635d3 Iustin Pop
              False
775 9cbc1edb Iustin Pop
776 525bfb36 Iustin Pop
-- | Check mdsk setting.
777 8fcf251f Iustin Pop
prop_Node_setMdsk node mx =
778 8fcf251f Iustin Pop
    Node.loDsk node' >= 0 &&
779 8fcf251f Iustin Pop
    fromIntegral (Node.loDsk node') <= Node.tDsk node &&
780 8fcf251f Iustin Pop
    Node.availDisk node' >= 0 &&
781 8fcf251f Iustin Pop
    Node.availDisk node' <= Node.fDsk node' &&
782 82ea2874 Iustin Pop
    fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
783 82ea2874 Iustin Pop
    Node.mDsk node' == mx'
784 8fcf251f Iustin Pop
    where _types = (node::Node.Node, mx::SmallRatio)
785 8fcf251f Iustin Pop
          node' = Node.setMdsk node mx'
786 8fcf251f Iustin Pop
          SmallRatio mx' = mx
787 8fcf251f Iustin Pop
788 8fcf251f Iustin Pop
-- Check tag maps
789 8fcf251f Iustin Pop
prop_Node_tagMaps_idempotent tags =
790 72bb6b4e Iustin Pop
    Node.delTags (Node.addTags m tags) tags ==? m
791 4a007641 Iustin Pop
    where m = Data.Map.empty
792 8fcf251f Iustin Pop
793 8fcf251f Iustin Pop
prop_Node_tagMaps_reject tags =
794 8fcf251f Iustin Pop
    not (null tags) ==>
795 72bb6b4e Iustin Pop
    all (\t -> Node.rejectAddTags m [t]) tags
796 4a007641 Iustin Pop
    where m = Node.addTags Data.Map.empty tags
797 8fcf251f Iustin Pop
798 82ea2874 Iustin Pop
prop_Node_showField node =
799 82ea2874 Iustin Pop
  forAll (elements Node.defaultFields) $ \ field ->
800 82ea2874 Iustin Pop
  fst (Node.showHeader field) /= Types.unknownField &&
801 82ea2874 Iustin Pop
  Node.showField node field /= Types.unknownField
802 82ea2874 Iustin Pop
803 d8bcd0a8 Iustin Pop
prop_Node_computeGroups nodes =
804 d8bcd0a8 Iustin Pop
  let ng = Node.computeGroups nodes
805 d8bcd0a8 Iustin Pop
      onlyuuid = map fst ng
806 d8bcd0a8 Iustin Pop
  in length nodes == sum (map (length . snd) ng) &&
807 d8bcd0a8 Iustin Pop
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
808 d8bcd0a8 Iustin Pop
     length (nub onlyuuid) == length onlyuuid &&
809 cc532bdd Iustin Pop
     (null nodes || not (null ng))
810 d8bcd0a8 Iustin Pop
811 23fe06c2 Iustin Pop
testSuite "Node"
812 23fe06c2 Iustin Pop
              [ 'prop_Node_setAlias
813 23fe06c2 Iustin Pop
              , 'prop_Node_setOffline
814 23fe06c2 Iustin Pop
              , 'prop_Node_setMcpu
815 23fe06c2 Iustin Pop
              , 'prop_Node_setXmem
816 23fe06c2 Iustin Pop
              , 'prop_Node_addPriFM
817 23fe06c2 Iustin Pop
              , 'prop_Node_addPriFD
818 23fe06c2 Iustin Pop
              , 'prop_Node_addPriFC
819 23fe06c2 Iustin Pop
              , 'prop_Node_addSec
820 23fe06c2 Iustin Pop
              , 'prop_Node_rMem
821 23fe06c2 Iustin Pop
              , 'prop_Node_setMdsk
822 23fe06c2 Iustin Pop
              , 'prop_Node_tagMaps_idempotent
823 23fe06c2 Iustin Pop
              , 'prop_Node_tagMaps_reject
824 23fe06c2 Iustin Pop
              , 'prop_Node_showField
825 23fe06c2 Iustin Pop
              , 'prop_Node_computeGroups
826 23fe06c2 Iustin Pop
              ]
827 cf35a869 Iustin Pop
828 525bfb36 Iustin Pop
-- ** Cluster tests
829 cf35a869 Iustin Pop
830 525bfb36 Iustin Pop
-- | Check that the cluster score is close to zero for a homogeneous
831 525bfb36 Iustin Pop
-- cluster.
832 8e4f6d56 Iustin Pop
prop_Score_Zero node =
833 8e4f6d56 Iustin Pop
    forAll (choose (1, 1024)) $ \count ->
834 3a3c1eb4 Iustin Pop
    (not (Node.offline node) && not (Node.failN1 node) && (count > 0) &&
835 2060348b Iustin Pop
     (Node.tDsk node > 0) && (Node.tMem node > 0)) ==>
836 cf35a869 Iustin Pop
    let fn = Node.buildPeers node Container.empty
837 9bb5721c Iustin Pop
        nlst = replicate count fn
838 9bb5721c Iustin Pop
        score = Cluster.compCVNodes nlst
839 cf35a869 Iustin Pop
    -- we can't say == 0 here as the floating point errors accumulate;
840 cf35a869 Iustin Pop
    -- this should be much lower than the default score in CLI.hs
841 8e4f6d56 Iustin Pop
    in score <= 1e-12
842 cf35a869 Iustin Pop
843 525bfb36 Iustin Pop
-- | Check that cluster stats are sane.
844 8e4f6d56 Iustin Pop
prop_CStats_sane node =
845 8e4f6d56 Iustin Pop
    forAll (choose (1, 1024)) $ \count ->
846 8e4f6d56 Iustin Pop
    (not (Node.offline node) && not (Node.failN1 node) &&
847 3fea6959 Iustin Pop
     (Node.availDisk node > 0) && (Node.availMem node > 0)) ==>
848 8fcf251f Iustin Pop
    let fn = Node.buildPeers node Container.empty
849 8fcf251f Iustin Pop
        nlst = zip [1..] $ replicate count fn::[(Types.Ndx, Node.Node)]
850 cb0c77ff Iustin Pop
        nl = Container.fromList nlst
851 8fcf251f Iustin Pop
        cstats = Cluster.totalResources nl
852 8fcf251f Iustin Pop
    in Cluster.csAdsk cstats >= 0 &&
853 8fcf251f Iustin Pop
       Cluster.csAdsk cstats <= Cluster.csFdsk cstats
854 8fcf251f Iustin Pop
855 3fea6959 Iustin Pop
-- | Check that one instance is allocated correctly, without
856 525bfb36 Iustin Pop
-- rebalances needed.
857 3fea6959 Iustin Pop
prop_ClusterAlloc_sane node inst =
858 3fea6959 Iustin Pop
    forAll (choose (5, 20)) $ \count ->
859 3fea6959 Iustin Pop
    not (Node.offline node)
860 3fea6959 Iustin Pop
            && not (Node.failN1 node)
861 3fea6959 Iustin Pop
            && Node.availDisk node > 0
862 3fea6959 Iustin Pop
            && Node.availMem node > 0
863 3fea6959 Iustin Pop
            ==>
864 3fea6959 Iustin Pop
    let nl = makeSmallCluster node count
865 3fea6959 Iustin Pop
        il = Container.empty
866 3fea6959 Iustin Pop
        inst' = setInstanceSmallerThanNode node inst
867 6d0bc5ca Iustin Pop
    in case Cluster.genAllocNodes defGroupList nl 2 True >>=
868 6d0bc5ca Iustin Pop
       Cluster.tryAlloc nl il inst' of
869 3fea6959 Iustin Pop
         Types.Bad _ -> False
870 85d0ddc3 Iustin Pop
         Types.Ok as ->
871 129734d3 Iustin Pop
             case Cluster.asSolution as of
872 129734d3 Iustin Pop
               Nothing -> False
873 129734d3 Iustin Pop
               Just (xnl, xi, _, cv) ->
874 7d3f4253 Iustin Pop
                   let il' = Container.add (Instance.idx xi) xi il
875 3fea6959 Iustin Pop
                       tbl = Cluster.Table xnl il' cv []
876 e08424a8 Guido Trotter
                   in not (canBalance tbl True True False)
877 3fea6959 Iustin Pop
878 3fea6959 Iustin Pop
-- | Checks that on a 2-5 node cluster, we can allocate a random
879 3fea6959 Iustin Pop
-- instance spec via tiered allocation (whatever the original instance
880 525bfb36 Iustin Pop
-- spec), on either one or two nodes.
881 3fea6959 Iustin Pop
prop_ClusterCanTieredAlloc node inst =
882 3fea6959 Iustin Pop
    forAll (choose (2, 5)) $ \count ->
883 3fea6959 Iustin Pop
    forAll (choose (1, 2)) $ \rqnodes ->
884 3fea6959 Iustin Pop
    not (Node.offline node)
885 3fea6959 Iustin Pop
            && not (Node.failN1 node)
886 3fea6959 Iustin Pop
            && isNodeBig node 4
887 3fea6959 Iustin Pop
            ==>
888 3fea6959 Iustin Pop
    let nl = makeSmallCluster node count
889 3fea6959 Iustin Pop
        il = Container.empty
890 6d0bc5ca Iustin Pop
        allocnodes = Cluster.genAllocNodes defGroupList nl rqnodes True
891 41b5c85a Iustin Pop
    in case allocnodes >>= \allocnodes' ->
892 8f48f67d Iustin Pop
        Cluster.tieredAlloc nl il (Just 1) inst allocnodes' [] [] of
893 3fea6959 Iustin Pop
         Types.Bad _ -> False
894 d5ccec02 Iustin Pop
         Types.Ok (_, _, il', ixes, cstats) -> not (null ixes) &&
895 d5ccec02 Iustin Pop
                                      IntMap.size il' == length ixes &&
896 d5ccec02 Iustin Pop
                                      length ixes == length cstats
897 3fea6959 Iustin Pop
898 3fea6959 Iustin Pop
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
899 525bfb36 Iustin Pop
-- we can also evacuate it.
900 3fea6959 Iustin Pop
prop_ClusterAllocEvac node inst =
901 3fea6959 Iustin Pop
    forAll (choose (4, 8)) $ \count ->
902 3fea6959 Iustin Pop
    not (Node.offline node)
903 3fea6959 Iustin Pop
            && not (Node.failN1 node)
904 3fea6959 Iustin Pop
            && isNodeBig node 4
905 3fea6959 Iustin Pop
            ==>
906 3fea6959 Iustin Pop
    let nl = makeSmallCluster node count
907 3fea6959 Iustin Pop
        il = Container.empty
908 3fea6959 Iustin Pop
        inst' = setInstanceSmallerThanNode node inst
909 6d0bc5ca Iustin Pop
    in case Cluster.genAllocNodes defGroupList nl 2 True >>=
910 6d0bc5ca Iustin Pop
       Cluster.tryAlloc nl il inst' of
911 3fea6959 Iustin Pop
         Types.Bad _ -> False
912 85d0ddc3 Iustin Pop
         Types.Ok as ->
913 129734d3 Iustin Pop
             case Cluster.asSolution as of
914 129734d3 Iustin Pop
               Nothing -> False
915 129734d3 Iustin Pop
               Just (xnl, xi, _, _) ->
916 3fea6959 Iustin Pop
                   let sdx = Instance.sNode xi
917 3fea6959 Iustin Pop
                       il' = Container.add (Instance.idx xi) xi il
918 6804faa0 Iustin Pop
                   in case IAlloc.processRelocate defGroupList xnl il'
919 6804faa0 Iustin Pop
                          (Instance.idx xi) 1 [sdx] of
920 6804faa0 Iustin Pop
                        Types.Ok _ -> True
921 3fea6959 Iustin Pop
                        _ -> False
922 3fea6959 Iustin Pop
923 3fea6959 Iustin Pop
-- | Check that allocating multiple instances on a cluster, then
924 525bfb36 Iustin Pop
-- adding an empty node, results in a valid rebalance.
925 00c75986 Iustin Pop
prop_ClusterAllocBalance =
926 00c75986 Iustin Pop
    forAll (genNode (Just 5) (Just 128)) $ \node ->
927 3fea6959 Iustin Pop
    forAll (choose (3, 5)) $ \count ->
928 00c75986 Iustin Pop
    not (Node.offline node) && not (Node.failN1 node) ==>
929 3fea6959 Iustin Pop
    let nl = makeSmallCluster node count
930 3fea6959 Iustin Pop
        (hnode, nl') = IntMap.deleteFindMax nl
931 3fea6959 Iustin Pop
        il = Container.empty
932 6d0bc5ca Iustin Pop
        allocnodes = Cluster.genAllocNodes defGroupList nl' 2 True
933 3fea6959 Iustin Pop
        i_templ = createInstance Types.unitMem Types.unitDsk Types.unitCpu
934 41b5c85a Iustin Pop
    in case allocnodes >>= \allocnodes' ->
935 8f48f67d Iustin Pop
        Cluster.iterateAlloc nl' il (Just 5) i_templ allocnodes' [] [] of
936 3fea6959 Iustin Pop
         Types.Bad _ -> False
937 d5ccec02 Iustin Pop
         Types.Ok (_, xnl, il', _, _) ->
938 3fea6959 Iustin Pop
                   let ynl = Container.add (Node.idx hnode) hnode xnl
939 3fea6959 Iustin Pop
                       cv = Cluster.compCV ynl
940 3fea6959 Iustin Pop
                       tbl = Cluster.Table ynl il' cv []
941 e08424a8 Guido Trotter
                   in canBalance tbl True True False
942 3fea6959 Iustin Pop
943 525bfb36 Iustin Pop
-- | Checks consistency.
944 32b8d9c0 Iustin Pop
prop_ClusterCheckConsistency node inst =
945 32b8d9c0 Iustin Pop
  let nl = makeSmallCluster node 3
946 32b8d9c0 Iustin Pop
      [node1, node2, node3] = Container.elems nl
947 10ef6b4e Iustin Pop
      node3' = node3 { Node.group = 1 }
948 32b8d9c0 Iustin Pop
      nl' = Container.add (Node.idx node3') node3' nl
949 32b8d9c0 Iustin Pop
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
950 32b8d9c0 Iustin Pop
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
951 32b8d9c0 Iustin Pop
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
952 cb0c77ff Iustin Pop
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
953 32b8d9c0 Iustin Pop
  in null (ccheck [(0, inst1)]) &&
954 32b8d9c0 Iustin Pop
     null (ccheck [(0, inst2)]) &&
955 32b8d9c0 Iustin Pop
     (not . null $ ccheck [(0, inst3)])
956 32b8d9c0 Iustin Pop
957 525bfb36 Iustin Pop
-- | For now, we only test that we don't lose instances during the split.
958 f4161783 Iustin Pop
prop_ClusterSplitCluster node inst =
959 f4161783 Iustin Pop
  forAll (choose (0, 100)) $ \icnt ->
960 f4161783 Iustin Pop
  let nl = makeSmallCluster node 2
961 f4161783 Iustin Pop
      (nl', il') = foldl (\(ns, is) _ -> assignInstance ns is inst 0 1)
962 f4161783 Iustin Pop
                   (nl, Container.empty) [1..icnt]
963 f4161783 Iustin Pop
      gni = Cluster.splitCluster nl' il'
964 f4161783 Iustin Pop
  in sum (map (Container.size . snd . snd) gni) == icnt &&
965 f4161783 Iustin Pop
     all (\(guuid, (nl'', _)) -> all ((== guuid) . Node.group)
966 f4161783 Iustin Pop
                                 (Container.elems nl'')) gni
967 32b8d9c0 Iustin Pop
968 23fe06c2 Iustin Pop
testSuite "Cluster"
969 23fe06c2 Iustin Pop
              [ 'prop_Score_Zero
970 23fe06c2 Iustin Pop
              , 'prop_CStats_sane
971 23fe06c2 Iustin Pop
              , 'prop_ClusterAlloc_sane
972 23fe06c2 Iustin Pop
              , 'prop_ClusterCanTieredAlloc
973 23fe06c2 Iustin Pop
              , 'prop_ClusterAllocEvac
974 23fe06c2 Iustin Pop
              , 'prop_ClusterAllocBalance
975 23fe06c2 Iustin Pop
              , 'prop_ClusterCheckConsistency
976 23fe06c2 Iustin Pop
              , 'prop_ClusterSplitCluster
977 23fe06c2 Iustin Pop
              ]
978 88f25dd0 Iustin Pop
979 525bfb36 Iustin Pop
-- ** OpCodes tests
980 88f25dd0 Iustin Pop
981 525bfb36 Iustin Pop
-- | Check that opcode serialization is idempotent.
982 88f25dd0 Iustin Pop
prop_OpCodes_serialization op =
983 88f25dd0 Iustin Pop
  case J.readJSON (J.showJSON op) of
984 72bb6b4e Iustin Pop
    J.Error e -> printTestCase ("Cannot deserialise: " ++ e) False
985 72bb6b4e Iustin Pop
    J.Ok op' -> op ==? op'
986 4a007641 Iustin Pop
  where _types = op::OpCodes.OpCode
987 88f25dd0 Iustin Pop
988 23fe06c2 Iustin Pop
testSuite "OpCodes"
989 23fe06c2 Iustin Pop
              [ 'prop_OpCodes_serialization ]
990 c088674b Iustin Pop
991 525bfb36 Iustin Pop
-- ** Jobs tests
992 525bfb36 Iustin Pop
993 525bfb36 Iustin Pop
-- | Check that (queued) job\/opcode status serialization is idempotent.
994 db079755 Iustin Pop
prop_OpStatus_serialization os =
995 db079755 Iustin Pop
  case J.readJSON (J.showJSON os) of
996 72bb6b4e Iustin Pop
    J.Error e -> printTestCase ("Cannot deserialise: " ++ e) False
997 72bb6b4e Iustin Pop
    J.Ok os' -> os ==? os'
998 db079755 Iustin Pop
  where _types = os::Jobs.OpStatus
999 db079755 Iustin Pop
1000 db079755 Iustin Pop
prop_JobStatus_serialization js =
1001 db079755 Iustin Pop
  case J.readJSON (J.showJSON js) of
1002 72bb6b4e Iustin Pop
    J.Error e -> printTestCase ("Cannot deserialise: " ++ e) False
1003 72bb6b4e Iustin Pop
    J.Ok js' -> js ==? js'
1004 db079755 Iustin Pop
  where _types = js::Jobs.JobStatus
1005 db079755 Iustin Pop
1006 23fe06c2 Iustin Pop
testSuite "Jobs"
1007 23fe06c2 Iustin Pop
              [ 'prop_OpStatus_serialization
1008 23fe06c2 Iustin Pop
              , 'prop_JobStatus_serialization
1009 23fe06c2 Iustin Pop
              ]
1010 db079755 Iustin Pop
1011 525bfb36 Iustin Pop
-- ** Loader tests
1012 c088674b Iustin Pop
1013 c088674b Iustin Pop
prop_Loader_lookupNode ktn inst node =
1014 72bb6b4e Iustin Pop
  Loader.lookupNode nl inst node ==? Data.Map.lookup node nl
1015 99b63608 Iustin Pop
  where nl = Data.Map.fromList ktn
1016 c088674b Iustin Pop
1017 c088674b Iustin Pop
prop_Loader_lookupInstance kti inst =
1018 72bb6b4e Iustin Pop
  Loader.lookupInstance il inst ==? Data.Map.lookup inst il
1019 99b63608 Iustin Pop
  where il = Data.Map.fromList kti
1020 99b63608 Iustin Pop
1021 99b63608 Iustin Pop
prop_Loader_assignIndices nodes =
1022 99b63608 Iustin Pop
  Data.Map.size nassoc == length nodes &&
1023 99b63608 Iustin Pop
  Container.size kt == length nodes &&
1024 99b63608 Iustin Pop
  (if not (null nodes)
1025 99b63608 Iustin Pop
   then maximum (IntMap.keys kt) == length nodes - 1
1026 c088674b Iustin Pop
   else True)
1027 99b63608 Iustin Pop
  where (nassoc, kt) = Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
1028 c088674b Iustin Pop
1029 c088674b Iustin Pop
-- | Checks that the number of primary instances recorded on the nodes
1030 525bfb36 Iustin Pop
-- is zero.
1031 c088674b Iustin Pop
prop_Loader_mergeData ns =
1032 cb0c77ff Iustin Pop
  let na = Container.fromList $ map (\n -> (Node.idx n, n)) ns
1033 2d1708e0 Guido Trotter
  in case Loader.mergeData [] [] [] []
1034 f4f6eb0b Iustin Pop
         (Loader.emptyCluster {Loader.cdNodes = na}) of
1035 c088674b Iustin Pop
    Types.Bad _ -> False
1036 017a0c3d Iustin Pop
    Types.Ok (Loader.ClusterData _ nl il _) ->
1037 c088674b Iustin Pop
      let nodes = Container.elems nl
1038 c088674b Iustin Pop
          instances = Container.elems il
1039 c088674b Iustin Pop
      in (sum . map (length . Node.pList)) nodes == 0 &&
1040 4a007641 Iustin Pop
         null instances
1041 c088674b Iustin Pop
1042 efe98965 Guido Trotter
-- | Check that compareNameComponent on equal strings works.
1043 efe98965 Guido Trotter
prop_Loader_compareNameComponent_equal :: String -> Bool
1044 efe98965 Guido Trotter
prop_Loader_compareNameComponent_equal s =
1045 efe98965 Guido Trotter
  Loader.compareNameComponent s s ==
1046 efe98965 Guido Trotter
    Loader.LookupResult Loader.ExactMatch s
1047 efe98965 Guido Trotter
1048 efe98965 Guido Trotter
-- | Check that compareNameComponent on prefix strings works.
1049 efe98965 Guido Trotter
prop_Loader_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
1050 efe98965 Guido Trotter
prop_Loader_compareNameComponent_prefix (NonEmpty s1) s2 =
1051 efe98965 Guido Trotter
  Loader.compareNameComponent (s1 ++ "." ++ s2) s1 ==
1052 efe98965 Guido Trotter
    Loader.LookupResult Loader.PartialMatch s1
1053 efe98965 Guido Trotter
1054 23fe06c2 Iustin Pop
testSuite "Loader"
1055 23fe06c2 Iustin Pop
              [ 'prop_Loader_lookupNode
1056 23fe06c2 Iustin Pop
              , 'prop_Loader_lookupInstance
1057 23fe06c2 Iustin Pop
              , 'prop_Loader_assignIndices
1058 23fe06c2 Iustin Pop
              , 'prop_Loader_mergeData
1059 23fe06c2 Iustin Pop
              , 'prop_Loader_compareNameComponent_equal
1060 23fe06c2 Iustin Pop
              , 'prop_Loader_compareNameComponent_prefix
1061 23fe06c2 Iustin Pop
              ]
1062 3c002a13 Iustin Pop
1063 3c002a13 Iustin Pop
-- ** Types tests
1064 3c002a13 Iustin Pop
1065 0047d4e2 Iustin Pop
prop_Types_AllocPolicy_serialisation apol =
1066 0047d4e2 Iustin Pop
    case J.readJSON (J.showJSON apol) of
1067 0047d4e2 Iustin Pop
      J.Ok p -> printTestCase ("invalid deserialisation " ++ show p) $
1068 0047d4e2 Iustin Pop
                p == apol
1069 0047d4e2 Iustin Pop
      J.Error s -> printTestCase ("failed to deserialise: " ++ s) False
1070 0047d4e2 Iustin Pop
    where _types = apol::Types.AllocPolicy
1071 0047d4e2 Iustin Pop
1072 0047d4e2 Iustin Pop
prop_Types_DiskTemplate_serialisation dt =
1073 0047d4e2 Iustin Pop
    case J.readJSON (J.showJSON dt) of
1074 0047d4e2 Iustin Pop
      J.Ok p -> printTestCase ("invalid deserialisation " ++ show p) $
1075 0047d4e2 Iustin Pop
                p == dt
1076 0047d4e2 Iustin Pop
      J.Error s -> printTestCase ("failed to deserialise: " ++ s)
1077 0047d4e2 Iustin Pop
                   False
1078 0047d4e2 Iustin Pop
    where _types = dt::Types.DiskTemplate
1079 0047d4e2 Iustin Pop
1080 0047d4e2 Iustin Pop
prop_Types_opToResult op =
1081 0047d4e2 Iustin Pop
    case op of
1082 0047d4e2 Iustin Pop
      Types.OpFail _ -> Types.isBad r
1083 0047d4e2 Iustin Pop
      Types.OpGood v -> case r of
1084 0047d4e2 Iustin Pop
                          Types.Bad _ -> False
1085 0047d4e2 Iustin Pop
                          Types.Ok v' -> v == v'
1086 0047d4e2 Iustin Pop
    where r = Types.opToResult op
1087 0047d4e2 Iustin Pop
          _types = op::Types.OpResult Int
1088 0047d4e2 Iustin Pop
1089 0047d4e2 Iustin Pop
prop_Types_eitherToResult ei =
1090 0047d4e2 Iustin Pop
    case ei of
1091 0047d4e2 Iustin Pop
      Left _ -> Types.isBad r
1092 0047d4e2 Iustin Pop
      Right v -> case r of
1093 0047d4e2 Iustin Pop
                   Types.Bad _ -> False
1094 0047d4e2 Iustin Pop
                   Types.Ok v' -> v == v'
1095 0047d4e2 Iustin Pop
    where r = Types.eitherToResult ei
1096 0047d4e2 Iustin Pop
          _types = ei::Either String Int
1097 3c002a13 Iustin Pop
1098 23fe06c2 Iustin Pop
testSuite "Types"
1099 23fe06c2 Iustin Pop
              [ 'prop_Types_AllocPolicy_serialisation
1100 23fe06c2 Iustin Pop
              , 'prop_Types_DiskTemplate_serialisation
1101 23fe06c2 Iustin Pop
              , 'prop_Types_opToResult
1102 23fe06c2 Iustin Pop
              , 'prop_Types_eitherToResult
1103 23fe06c2 Iustin Pop
              ]