Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 9f8b97ce

History | View | Annotate | Download (37.8 kB)

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