Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ bfe6c954

History | View | Annotate | Download (36.1 kB)

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