Statistics
| Branch: | Tag: | Revision:

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

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