Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 23fe06c2

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