Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 6804faa0

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