Statistics
| Branch: | Tag: | Revision:

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

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