Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 22fac87d

History | View | Annotate | Download (37.1 kB)

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