Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / QC.hs @ a334d536

History | View | Annotate | Download (29.2 kB)

1 9b1e1cc9 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 a070c426 Iustin Pop
Copyright (C) 2009, 2010 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 7dd5ee6c Iustin Pop
    ) where
38 15f4c8ca Iustin Pop
39 15f4c8ca Iustin Pop
import Test.QuickCheck
40 7dd5ee6c Iustin Pop
import Test.QuickCheck.Batch
41 d8bcd0a8 Iustin Pop
import Data.List (findIndex, intercalate, nub)
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 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.PeerMap as PeerMap
60 223dbe53 Iustin Pop
import qualified Ganeti.HTools.Rapi
61 223dbe53 Iustin Pop
import qualified Ganeti.HTools.Simu
62 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Text as Text
63 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Types as Types
64 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Utils as Utils
65 223dbe53 Iustin Pop
import qualified Ganeti.HTools.Version
66 15f4c8ca Iustin Pop
67 3fea6959 Iustin Pop
-- * Constants
68 3fea6959 Iustin Pop
69 8fcf251f Iustin Pop
-- | Maximum memory (1TiB, somewhat random value)
70 8fcf251f Iustin Pop
maxMem :: Int
71 8fcf251f Iustin Pop
maxMem = 1024 * 1024
72 8fcf251f Iustin Pop
73 49f9627a Iustin Pop
-- | Maximum disk (8TiB, somewhat random value)
74 8fcf251f Iustin Pop
maxDsk :: Int
75 49f9627a Iustin Pop
maxDsk = 1024 * 1024 * 8
76 8fcf251f Iustin Pop
77 8fcf251f Iustin Pop
-- | Max CPUs (1024, somewhat random value)
78 8fcf251f Iustin Pop
maxCpu :: Int
79 8fcf251f Iustin Pop
maxCpu = 1024
80 8fcf251f Iustin Pop
81 3fea6959 Iustin Pop
-- * Helper functions
82 3fea6959 Iustin Pop
83 79a72ce7 Iustin Pop
-- | Simple checker for whether OpResult is fail or pass
84 79a72ce7 Iustin Pop
isFailure :: Types.OpResult a -> Bool
85 79a72ce7 Iustin Pop
isFailure (Types.OpFail _) = True
86 79a72ce7 Iustin Pop
isFailure _ = False
87 79a72ce7 Iustin Pop
88 3fea6959 Iustin Pop
-- | Update an instance to be smaller than a node
89 3fea6959 Iustin Pop
setInstanceSmallerThanNode node inst =
90 4a007641 Iustin Pop
    inst { Instance.mem = Node.availMem node `div` 2
91 4a007641 Iustin Pop
         , Instance.dsk = Node.availDisk node `div` 2
92 4a007641 Iustin Pop
         , Instance.vcpus = Node.availCpu node `div` 2
93 3fea6959 Iustin Pop
         }
94 3fea6959 Iustin Pop
95 3fea6959 Iustin Pop
-- | Create an instance given its spec
96 3fea6959 Iustin Pop
createInstance mem dsk vcpus =
97 3fea6959 Iustin Pop
    Instance.create "inst-unnamed" mem dsk vcpus "running" [] (-1) (-1)
98 3fea6959 Iustin Pop
99 3fea6959 Iustin Pop
-- | Create a small cluster by repeating a node spec
100 3fea6959 Iustin Pop
makeSmallCluster :: Node.Node -> Int -> Node.List
101 3fea6959 Iustin Pop
makeSmallCluster node count =
102 3fea6959 Iustin Pop
    let fn = Node.buildPeers node Container.empty
103 3fea6959 Iustin Pop
        namelst = map (\n -> (Node.name n, n)) (replicate count fn)
104 3fea6959 Iustin Pop
        (_, nlst) = Loader.assignIndices namelst
105 99b63608 Iustin Pop
    in nlst
106 3fea6959 Iustin Pop
107 3fea6959 Iustin Pop
-- | Checks if a node is "big" enough
108 3fea6959 Iustin Pop
isNodeBig :: Node.Node -> Int -> Bool
109 3fea6959 Iustin Pop
isNodeBig node size = Node.availDisk node > size * Types.unitDsk
110 3fea6959 Iustin Pop
                      && Node.availMem node > size * Types.unitMem
111 3fea6959 Iustin Pop
                      && Node.availCpu node > size * Types.unitCpu
112 3fea6959 Iustin Pop
113 3fea6959 Iustin Pop
canBalance :: Cluster.Table -> Bool -> Bool -> Bool
114 848b65c9 Iustin Pop
canBalance tbl dm evac = isJust $ Cluster.tryBalance tbl dm evac 0 0
115 3fea6959 Iustin Pop
116 f4161783 Iustin Pop
-- | Assigns a new fresh instance to a cluster; this is not
117 f4161783 Iustin Pop
-- allocation, so no resource checks are done
118 f4161783 Iustin Pop
assignInstance :: Node.List -> Instance.List -> Instance.Instance ->
119 f4161783 Iustin Pop
                  Types.Idx -> Types.Idx ->
120 f4161783 Iustin Pop
                  (Node.List, Instance.List)
121 f4161783 Iustin Pop
assignInstance nl il inst pdx sdx =
122 f4161783 Iustin Pop
  let pnode = Container.find pdx nl
123 f4161783 Iustin Pop
      snode = Container.find sdx nl
124 f4161783 Iustin Pop
      maxiidx = if Container.null il
125 f4161783 Iustin Pop
                then 0
126 f4161783 Iustin Pop
                else fst (Container.findMax il) + 1
127 f4161783 Iustin Pop
      inst' = inst { Instance.idx = maxiidx,
128 f4161783 Iustin Pop
                     Instance.pNode = pdx, Instance.sNode = sdx }
129 f4161783 Iustin Pop
      pnode' = Node.setPri pnode inst'
130 f4161783 Iustin Pop
      snode' = Node.setSec snode inst'
131 f4161783 Iustin Pop
      nl' = Container.addTwo pdx pnode' sdx snode' nl
132 f4161783 Iustin Pop
      il' = Container.add maxiidx inst' il
133 f4161783 Iustin Pop
  in (nl', il')
134 f4161783 Iustin Pop
135 3fea6959 Iustin Pop
-- * Arbitrary instances
136 3fea6959 Iustin Pop
137 15f4c8ca Iustin Pop
-- copied from the introduction to quickcheck
138 15f4c8ca Iustin Pop
instance Arbitrary Char where
139 095d7ac0 Iustin Pop
    arbitrary = choose ('\32', '\128')
140 15f4c8ca Iustin Pop
141 a070c426 Iustin Pop
newtype DNSChar = DNSChar { dnsGetChar::Char }
142 a070c426 Iustin Pop
instance Arbitrary DNSChar where
143 a070c426 Iustin Pop
    arbitrary = do
144 a070c426 Iustin Pop
      x <- elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
145 a070c426 Iustin Pop
      return (DNSChar x)
146 a070c426 Iustin Pop
147 a070c426 Iustin Pop
getName :: Gen String
148 a070c426 Iustin Pop
getName = do
149 a070c426 Iustin Pop
  n <- choose (1, 64)
150 a070c426 Iustin Pop
  dn <- vector n::Gen [DNSChar]
151 a070c426 Iustin Pop
  return (map dnsGetChar dn)
152 a070c426 Iustin Pop
153 a070c426 Iustin Pop
154 a070c426 Iustin Pop
getFQDN :: Gen String
155 a070c426 Iustin Pop
getFQDN = do
156 a070c426 Iustin Pop
  felem <- getName
157 a070c426 Iustin Pop
  ncomps <- choose (1, 4)
158 a070c426 Iustin Pop
  frest <- vector ncomps::Gen [[DNSChar]]
159 a070c426 Iustin Pop
  let frest' = map (map dnsGetChar) frest
160 a070c426 Iustin Pop
  return (felem ++ "." ++ intercalate "." frest')
161 a070c426 Iustin Pop
162 15f4c8ca Iustin Pop
-- let's generate a random instance
163 15f4c8ca Iustin Pop
instance Arbitrary Instance.Instance where
164 15f4c8ca Iustin Pop
    arbitrary = do
165 a070c426 Iustin Pop
      name <- getFQDN
166 8fcf251f Iustin Pop
      mem <- choose (0, maxMem)
167 8fcf251f Iustin Pop
      dsk <- choose (0, maxDsk)
168 1ae7a904 Iustin Pop
      run_st <- elements ["ERROR_up", "ERROR_down", "ADMIN_down"
169 1ae7a904 Iustin Pop
                         , "ERROR_nodedown", "ERROR_nodeoffline"
170 1ae7a904 Iustin Pop
                         , "running"
171 1ae7a904 Iustin Pop
                         , "no_such_status1", "no_such_status2"]
172 15f4c8ca Iustin Pop
      pn <- arbitrary
173 15f4c8ca Iustin Pop
      sn <- arbitrary
174 8fcf251f Iustin Pop
      vcpus <- choose (0, maxCpu)
175 434c15d5 Iustin Pop
      return $ Instance.create name mem dsk vcpus run_st [] pn sn
176 15f4c8ca Iustin Pop
177 15f4c8ca Iustin Pop
-- and a random node
178 15f4c8ca Iustin Pop
instance Arbitrary Node.Node where
179 15f4c8ca Iustin Pop
    arbitrary = do
180 a070c426 Iustin Pop
      name <- getFQDN
181 8fcf251f Iustin Pop
      mem_t <- choose (0, maxMem)
182 15f4c8ca Iustin Pop
      mem_f <- choose (0, mem_t)
183 15f4c8ca Iustin Pop
      mem_n <- choose (0, mem_t - mem_f)
184 8fcf251f Iustin Pop
      dsk_t <- choose (0, maxDsk)
185 15f4c8ca Iustin Pop
      dsk_f <- choose (0, dsk_t)
186 8fcf251f Iustin Pop
      cpu_t <- choose (0, maxCpu)
187 15f4c8ca Iustin Pop
      offl <- arbitrary
188 15f4c8ca Iustin Pop
      let n = Node.create name (fromIntegral mem_t) mem_n mem_f
189 8fcf251f Iustin Pop
              (fromIntegral dsk_t) dsk_f (fromIntegral cpu_t) offl
190 c4d98278 Iustin Pop
              Utils.defaultGroupID
191 9cf4267a Iustin Pop
          n' = Node.buildPeers n Container.empty
192 15f4c8ca Iustin Pop
      return n'
193 15f4c8ca Iustin Pop
194 88f25dd0 Iustin Pop
-- replace disks
195 88f25dd0 Iustin Pop
instance Arbitrary OpCodes.ReplaceDisksMode where
196 88f25dd0 Iustin Pop
  arbitrary = elements [ OpCodes.ReplaceOnPrimary
197 88f25dd0 Iustin Pop
                       , OpCodes.ReplaceOnSecondary
198 88f25dd0 Iustin Pop
                       , OpCodes.ReplaceNewSecondary
199 88f25dd0 Iustin Pop
                       , OpCodes.ReplaceAuto
200 88f25dd0 Iustin Pop
                       ]
201 88f25dd0 Iustin Pop
202 88f25dd0 Iustin Pop
instance Arbitrary OpCodes.OpCode where
203 88f25dd0 Iustin Pop
  arbitrary = do
204 88f25dd0 Iustin Pop
    op_id <- elements [ "OP_TEST_DELAY"
205 88f25dd0 Iustin Pop
                      , "OP_INSTANCE_REPLACE_DISKS"
206 88f25dd0 Iustin Pop
                      , "OP_INSTANCE_FAILOVER"
207 88f25dd0 Iustin Pop
                      , "OP_INSTANCE_MIGRATE"
208 88f25dd0 Iustin Pop
                      ]
209 88f25dd0 Iustin Pop
    (case op_id of
210 88f25dd0 Iustin Pop
        "OP_TEST_DELAY" ->
211 88f25dd0 Iustin Pop
          liftM3 OpCodes.OpTestDelay arbitrary arbitrary arbitrary
212 88f25dd0 Iustin Pop
        "OP_INSTANCE_REPLACE_DISKS" ->
213 88f25dd0 Iustin Pop
          liftM5 OpCodes.OpReplaceDisks arbitrary arbitrary
214 88f25dd0 Iustin Pop
          arbitrary arbitrary arbitrary
215 88f25dd0 Iustin Pop
        "OP_INSTANCE_FAILOVER" ->
216 88f25dd0 Iustin Pop
          liftM2 OpCodes.OpFailoverInstance arbitrary arbitrary
217 88f25dd0 Iustin Pop
        "OP_INSTANCE_MIGRATE" ->
218 88f25dd0 Iustin Pop
          liftM3 OpCodes.OpMigrateInstance arbitrary arbitrary arbitrary
219 88f25dd0 Iustin Pop
        _ -> fail "Wrong opcode")
220 88f25dd0 Iustin Pop
221 db079755 Iustin Pop
instance Arbitrary Jobs.OpStatus where
222 db079755 Iustin Pop
  arbitrary = elements [minBound..maxBound]
223 db079755 Iustin Pop
224 db079755 Iustin Pop
instance Arbitrary Jobs.JobStatus where
225 db079755 Iustin Pop
  arbitrary = elements [minBound..maxBound]
226 db079755 Iustin Pop
227 3fea6959 Iustin Pop
-- * Actual tests
228 8fcf251f Iustin Pop
229 691dcd2a Iustin Pop
-- If the list is not just an empty element, and if the elements do
230 691dcd2a Iustin Pop
-- not contain commas, then join+split should be idepotent
231 691dcd2a Iustin Pop
prop_Utils_commaJoinSplit lst = lst /= [""] &&
232 691dcd2a Iustin Pop
                                all (not . elem ',') lst ==>
233 691dcd2a Iustin Pop
                                Utils.sepSplit ',' (Utils.commaJoin lst) == lst
234 691dcd2a Iustin Pop
-- Split and join should always be idempotent
235 691dcd2a Iustin Pop
prop_Utils_commaSplitJoin s = Utils.commaJoin (Utils.sepSplit ',' s) == s
236 691dcd2a Iustin Pop
237 691dcd2a Iustin Pop
testUtils =
238 691dcd2a Iustin Pop
  [ run prop_Utils_commaJoinSplit
239 691dcd2a Iustin Pop
  , run prop_Utils_commaSplitJoin
240 691dcd2a Iustin Pop
  ]
241 691dcd2a Iustin Pop
242 15f4c8ca Iustin Pop
-- | Make sure add is idempotent
243 fbb95f28 Iustin Pop
prop_PeerMap_addIdempotent pmap key em =
244 15f4c8ca Iustin Pop
    fn puniq == fn (fn puniq)
245 7bc82927 Iustin Pop
    where _types = (pmap::PeerMap.PeerMap,
246 fbb95f28 Iustin Pop
                    key::PeerMap.Key, em::PeerMap.Elem)
247 fbb95f28 Iustin Pop
          fn = PeerMap.add key em
248 7bc82927 Iustin Pop
          puniq = PeerMap.accumArray const pmap
249 15f4c8ca Iustin Pop
250 15f4c8ca Iustin Pop
-- | Make sure remove is idempotent
251 15f4c8ca Iustin Pop
prop_PeerMap_removeIdempotent pmap key =
252 15f4c8ca Iustin Pop
    fn puniq == fn (fn puniq)
253 7bc82927 Iustin Pop
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
254 7bc82927 Iustin Pop
          fn = PeerMap.remove key
255 15f4c8ca Iustin Pop
          puniq = PeerMap.accumArray const pmap
256 15f4c8ca Iustin Pop
257 15f4c8ca Iustin Pop
-- | Make sure a missing item returns 0
258 15f4c8ca Iustin Pop
prop_PeerMap_findMissing pmap key =
259 15f4c8ca Iustin Pop
    PeerMap.find key (PeerMap.remove key puniq) == 0
260 7bc82927 Iustin Pop
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
261 15f4c8ca Iustin Pop
          puniq = PeerMap.accumArray const pmap
262 15f4c8ca Iustin Pop
263 15f4c8ca Iustin Pop
-- | Make sure an added item is found
264 fbb95f28 Iustin Pop
prop_PeerMap_addFind pmap key em =
265 fbb95f28 Iustin Pop
    PeerMap.find key (PeerMap.add key em puniq) == em
266 7bc82927 Iustin Pop
    where _types = (pmap::PeerMap.PeerMap,
267 fbb95f28 Iustin Pop
                    key::PeerMap.Key, em::PeerMap.Elem)
268 7bc82927 Iustin Pop
          puniq = PeerMap.accumArray const pmap
269 15f4c8ca Iustin Pop
270 15f4c8ca Iustin Pop
-- | Manual check that maxElem returns the maximum indeed, or 0 for null
271 15f4c8ca Iustin Pop
prop_PeerMap_maxElem pmap =
272 15f4c8ca Iustin Pop
    PeerMap.maxElem puniq == if null puniq then 0
273 15f4c8ca Iustin Pop
                             else (maximum . snd . unzip) puniq
274 7bc82927 Iustin Pop
    where _types = pmap::PeerMap.PeerMap
275 15f4c8ca Iustin Pop
          puniq = PeerMap.accumArray const pmap
276 15f4c8ca Iustin Pop
277 c15f7183 Iustin Pop
testPeerMap =
278 7dd5ee6c Iustin Pop
    [ run prop_PeerMap_addIdempotent
279 7dd5ee6c Iustin Pop
    , run prop_PeerMap_removeIdempotent
280 7dd5ee6c Iustin Pop
    , run prop_PeerMap_maxElem
281 7dd5ee6c Iustin Pop
    , run prop_PeerMap_addFind
282 7dd5ee6c Iustin Pop
    , run prop_PeerMap_findMissing
283 7dd5ee6c Iustin Pop
    ]
284 7dd5ee6c Iustin Pop
285 095d7ac0 Iustin Pop
-- Container tests
286 095d7ac0 Iustin Pop
287 095d7ac0 Iustin Pop
prop_Container_addTwo cdata i1 i2 =
288 095d7ac0 Iustin Pop
    fn i1 i2 cont == fn i2 i1 cont &&
289 095d7ac0 Iustin Pop
       fn i1 i2 cont == fn i1 i2 (fn i1 i2 cont)
290 095d7ac0 Iustin Pop
    where _types = (cdata::[Int],
291 095d7ac0 Iustin Pop
                    i1::Int, i2::Int)
292 095d7ac0 Iustin Pop
          cont = foldl (\c x -> Container.add x x c) Container.empty cdata
293 095d7ac0 Iustin Pop
          fn x1 x2 = Container.addTwo x1 x1 x2 x2
294 095d7ac0 Iustin Pop
295 5ef78537 Iustin Pop
prop_Container_nameOf node =
296 5ef78537 Iustin Pop
  let nl = makeSmallCluster node 1
297 5ef78537 Iustin Pop
      fnode = head (Container.elems nl)
298 5ef78537 Iustin Pop
  in Container.nameOf nl (Node.idx fnode) == Node.name fnode
299 5ef78537 Iustin Pop
300 5ef78537 Iustin Pop
-- We test that in a cluster, given a random node, we can find it by
301 5ef78537 Iustin Pop
-- its name and alias, as long as all names and aliases are unique,
302 5ef78537 Iustin Pop
-- and that we fail to find a non-existing name
303 5ef78537 Iustin Pop
prop_Container_findByName node othername =
304 5ef78537 Iustin Pop
  forAll (choose (1, 20)) $ \ cnt ->
305 5ef78537 Iustin Pop
  forAll (choose (0, cnt - 1)) $ \ fidx ->
306 5ef78537 Iustin Pop
  forAll (vector cnt) $ \ names ->
307 5ef78537 Iustin Pop
  (length . nub) (map fst names ++ map snd names) ==
308 5ef78537 Iustin Pop
  length names * 2 &&
309 5ef78537 Iustin Pop
  not (othername `elem` (map fst names ++ map snd names)) ==>
310 5ef78537 Iustin Pop
  let nl = makeSmallCluster node cnt
311 5ef78537 Iustin Pop
      nodes = Container.elems nl
312 5ef78537 Iustin Pop
      nodes' = map (\((name, alias), nn) -> (Node.idx nn,
313 5ef78537 Iustin Pop
                                             nn { Node.name = name,
314 5ef78537 Iustin Pop
                                                  Node.alias = alias }))
315 5ef78537 Iustin Pop
               $ zip names nodes
316 5ef78537 Iustin Pop
      nl' = Container.fromAssocList nodes'
317 5ef78537 Iustin Pop
      target = snd (nodes' !! fidx)
318 5ef78537 Iustin Pop
  in Container.findByName nl' (Node.name target) == Just target &&
319 5ef78537 Iustin Pop
     Container.findByName nl' (Node.alias target) == Just target &&
320 5ef78537 Iustin Pop
     Container.findByName nl' othername == Nothing
321 5ef78537 Iustin Pop
322 c15f7183 Iustin Pop
testContainer =
323 5ef78537 Iustin Pop
    [ run prop_Container_addTwo
324 5ef78537 Iustin Pop
    , run prop_Container_nameOf
325 5ef78537 Iustin Pop
    , run prop_Container_findByName
326 5ef78537 Iustin Pop
    ]
327 095d7ac0 Iustin Pop
328 7bc82927 Iustin Pop
-- Simple instance tests, we only have setter/getters
329 7bc82927 Iustin Pop
330 39d11971 Iustin Pop
prop_Instance_creat inst =
331 39d11971 Iustin Pop
    Instance.name inst == Instance.alias inst
332 39d11971 Iustin Pop
333 7bc82927 Iustin Pop
prop_Instance_setIdx inst idx =
334 7bc82927 Iustin Pop
    Instance.idx (Instance.setIdx inst idx) == idx
335 7bc82927 Iustin Pop
    where _types = (inst::Instance.Instance, idx::Types.Idx)
336 7bc82927 Iustin Pop
337 7bc82927 Iustin Pop
prop_Instance_setName inst name =
338 39d11971 Iustin Pop
    Instance.name newinst == name &&
339 39d11971 Iustin Pop
    Instance.alias newinst == name
340 39d11971 Iustin Pop
    where _types = (inst::Instance.Instance, name::String)
341 39d11971 Iustin Pop
          newinst = Instance.setName inst name
342 39d11971 Iustin Pop
343 39d11971 Iustin Pop
prop_Instance_setAlias inst name =
344 39d11971 Iustin Pop
    Instance.name newinst == Instance.name inst &&
345 39d11971 Iustin Pop
    Instance.alias newinst == name
346 7bc82927 Iustin Pop
    where _types = (inst::Instance.Instance, name::String)
347 39d11971 Iustin Pop
          newinst = Instance.setAlias inst name
348 7bc82927 Iustin Pop
349 7bc82927 Iustin Pop
prop_Instance_setPri inst pdx =
350 2060348b Iustin Pop
    Instance.pNode (Instance.setPri inst pdx) == pdx
351 7bc82927 Iustin Pop
    where _types = (inst::Instance.Instance, pdx::Types.Ndx)
352 7bc82927 Iustin Pop
353 7bc82927 Iustin Pop
prop_Instance_setSec inst sdx =
354 2060348b Iustin Pop
    Instance.sNode (Instance.setSec inst sdx) == sdx
355 7bc82927 Iustin Pop
    where _types = (inst::Instance.Instance, sdx::Types.Ndx)
356 7bc82927 Iustin Pop
357 7bc82927 Iustin Pop
prop_Instance_setBoth inst pdx sdx =
358 2060348b Iustin Pop
    Instance.pNode si == pdx && Instance.sNode si == sdx
359 7bc82927 Iustin Pop
    where _types = (inst::Instance.Instance, pdx::Types.Ndx, sdx::Types.Ndx)
360 7bc82927 Iustin Pop
          si = Instance.setBoth inst pdx sdx
361 7bc82927 Iustin Pop
362 1ae7a904 Iustin Pop
prop_Instance_runStatus_True inst =
363 1ae7a904 Iustin Pop
    let run_st = Instance.running inst
364 2060348b Iustin Pop
        run_tx = Instance.runSt inst
365 1ae7a904 Iustin Pop
    in
366 a46f34d7 Iustin Pop
      run_tx `elem` Instance.runningStates ==> run_st
367 1ae7a904 Iustin Pop
368 1ae7a904 Iustin Pop
prop_Instance_runStatus_False inst =
369 1ae7a904 Iustin Pop
    let run_st = Instance.running inst
370 2060348b Iustin Pop
        run_tx = Instance.runSt inst
371 1ae7a904 Iustin Pop
    in
372 a46f34d7 Iustin Pop
      run_tx `notElem` Instance.runningStates ==> not run_st
373 1ae7a904 Iustin Pop
374 8fcf251f Iustin Pop
prop_Instance_shrinkMG inst =
375 8fcf251f Iustin Pop
    Instance.mem inst >= 2 * Types.unitMem ==>
376 8fcf251f Iustin Pop
        case Instance.shrinkByType inst Types.FailMem of
377 8fcf251f Iustin Pop
          Types.Ok inst' ->
378 8fcf251f Iustin Pop
              Instance.mem inst' == Instance.mem inst - Types.unitMem
379 8fcf251f Iustin Pop
          _ -> False
380 8fcf251f Iustin Pop
381 8fcf251f Iustin Pop
prop_Instance_shrinkMF inst =
382 8fcf251f Iustin Pop
    Instance.mem inst < 2 * Types.unitMem ==>
383 06fb841e Iustin Pop
        Types.isBad $ Instance.shrinkByType inst Types.FailMem
384 8fcf251f Iustin Pop
385 8fcf251f Iustin Pop
prop_Instance_shrinkCG inst =
386 8fcf251f Iustin Pop
    Instance.vcpus inst >= 2 * Types.unitCpu ==>
387 8fcf251f Iustin Pop
        case Instance.shrinkByType inst Types.FailCPU of
388 8fcf251f Iustin Pop
          Types.Ok inst' ->
389 8fcf251f Iustin Pop
              Instance.vcpus inst' == Instance.vcpus inst - Types.unitCpu
390 8fcf251f Iustin Pop
          _ -> False
391 8fcf251f Iustin Pop
392 8fcf251f Iustin Pop
prop_Instance_shrinkCF inst =
393 8fcf251f Iustin Pop
    Instance.vcpus inst < 2 * Types.unitCpu ==>
394 06fb841e Iustin Pop
        Types.isBad $ Instance.shrinkByType inst Types.FailCPU
395 8fcf251f Iustin Pop
396 8fcf251f Iustin Pop
prop_Instance_shrinkDG inst =
397 8fcf251f Iustin Pop
    Instance.dsk inst >= 2 * Types.unitDsk ==>
398 8fcf251f Iustin Pop
        case Instance.shrinkByType inst Types.FailDisk of
399 8fcf251f Iustin Pop
          Types.Ok inst' ->
400 8fcf251f Iustin Pop
              Instance.dsk inst' == Instance.dsk inst - Types.unitDsk
401 8fcf251f Iustin Pop
          _ -> False
402 8fcf251f Iustin Pop
403 8fcf251f Iustin Pop
prop_Instance_shrinkDF inst =
404 8fcf251f Iustin Pop
    Instance.dsk inst < 2 * Types.unitDsk ==>
405 06fb841e Iustin Pop
        Types.isBad $ Instance.shrinkByType inst Types.FailDisk
406 8fcf251f Iustin Pop
407 8fcf251f Iustin Pop
prop_Instance_setMovable inst m =
408 8fcf251f Iustin Pop
    Instance.movable inst' == m
409 4a007641 Iustin Pop
    where inst' = Instance.setMovable inst m
410 8fcf251f Iustin Pop
411 c15f7183 Iustin Pop
testInstance =
412 39d11971 Iustin Pop
    [ run prop_Instance_creat
413 39d11971 Iustin Pop
    , run prop_Instance_setIdx
414 7dd5ee6c Iustin Pop
    , run prop_Instance_setName
415 39d11971 Iustin Pop
    , run prop_Instance_setAlias
416 7dd5ee6c Iustin Pop
    , run prop_Instance_setPri
417 7dd5ee6c Iustin Pop
    , run prop_Instance_setSec
418 7dd5ee6c Iustin Pop
    , run prop_Instance_setBoth
419 1ae7a904 Iustin Pop
    , run prop_Instance_runStatus_True
420 1ae7a904 Iustin Pop
    , run prop_Instance_runStatus_False
421 8fcf251f Iustin Pop
    , run prop_Instance_shrinkMG
422 8fcf251f Iustin Pop
    , run prop_Instance_shrinkMF
423 8fcf251f Iustin Pop
    , run prop_Instance_shrinkCG
424 8fcf251f Iustin Pop
    , run prop_Instance_shrinkCF
425 8fcf251f Iustin Pop
    , run prop_Instance_shrinkDG
426 8fcf251f Iustin Pop
    , run prop_Instance_shrinkDF
427 8fcf251f Iustin Pop
    , run prop_Instance_setMovable
428 1ae7a904 Iustin Pop
    ]
429 1ae7a904 Iustin Pop
430 1ae7a904 Iustin Pop
-- Instance text loader tests
431 1ae7a904 Iustin Pop
432 1ae7a904 Iustin Pop
prop_Text_Load_Instance name mem dsk vcpus status pnode snode pdx sdx =
433 39d11971 Iustin Pop
    not (null pnode) && pdx >= 0 && sdx >= 0 ==>
434 1ae7a904 Iustin Pop
    let vcpus_s = show vcpus
435 1ae7a904 Iustin Pop
        dsk_s = show dsk
436 1ae7a904 Iustin Pop
        mem_s = show mem
437 1ae7a904 Iustin Pop
        rsdx = if pdx == sdx
438 1ae7a904 Iustin Pop
               then sdx + 1
439 1ae7a904 Iustin Pop
               else sdx
440 39d11971 Iustin Pop
        ndx = if null snode
441 39d11971 Iustin Pop
              then [(pnode, pdx)]
442 39d11971 Iustin Pop
              else [(pnode, pdx), (snode, rsdx)]
443 99b63608 Iustin Pop
        nl = Data.Map.fromList ndx
444 434c15d5 Iustin Pop
        tags = ""
445 99b63608 Iustin Pop
        inst = Text.loadInst nl
446 39d11971 Iustin Pop
               [name, mem_s, dsk_s, vcpus_s, status, pnode, snode, tags]::
447 39d11971 Iustin Pop
               Maybe (String, Instance.Instance)
448 99b63608 Iustin Pop
        fail1 = Text.loadInst nl
449 39d11971 Iustin Pop
               [name, mem_s, dsk_s, vcpus_s, status, pnode, pnode, tags]::
450 1ae7a904 Iustin Pop
               Maybe (String, Instance.Instance)
451 1ae7a904 Iustin Pop
        _types = ( name::String, mem::Int, dsk::Int
452 1ae7a904 Iustin Pop
                 , vcpus::Int, status::String
453 1ae7a904 Iustin Pop
                 , pnode::String, snode::String
454 1ae7a904 Iustin Pop
                 , pdx::Types.Ndx, sdx::Types.Ndx)
455 1ae7a904 Iustin Pop
    in
456 1ae7a904 Iustin Pop
      case inst of
457 1ae7a904 Iustin Pop
        Nothing -> False
458 1ae7a904 Iustin Pop
        Just (_, i) ->
459 1ae7a904 Iustin Pop
            (Instance.name i == name &&
460 1ae7a904 Iustin Pop
             Instance.vcpus i == vcpus &&
461 1ae7a904 Iustin Pop
             Instance.mem i == mem &&
462 2060348b Iustin Pop
             Instance.pNode i == pdx &&
463 39d11971 Iustin Pop
             Instance.sNode i == (if null snode
464 39d11971 Iustin Pop
                                  then Node.noSecondary
465 39d11971 Iustin Pop
                                  else rsdx) &&
466 39d11971 Iustin Pop
             isNothing fail1)
467 39d11971 Iustin Pop
468 39d11971 Iustin Pop
prop_Text_Load_InstanceFail ktn fields =
469 99b63608 Iustin Pop
    length fields /= 8 ==> isNothing $ Text.loadInst nl fields
470 99b63608 Iustin Pop
    where nl = Data.Map.fromList ktn
471 39d11971 Iustin Pop
472 39d11971 Iustin Pop
prop_Text_Load_Node name tm nm fm td fd tc fo =
473 39d11971 Iustin Pop
    let conv v = if v < 0
474 39d11971 Iustin Pop
                    then "?"
475 39d11971 Iustin Pop
                    else show v
476 39d11971 Iustin Pop
        tm_s = conv tm
477 39d11971 Iustin Pop
        nm_s = conv nm
478 39d11971 Iustin Pop
        fm_s = conv fm
479 39d11971 Iustin Pop
        td_s = conv td
480 39d11971 Iustin Pop
        fd_s = conv fd
481 39d11971 Iustin Pop
        tc_s = conv tc
482 39d11971 Iustin Pop
        fo_s = if fo
483 39d11971 Iustin Pop
               then "Y"
484 39d11971 Iustin Pop
               else "N"
485 39d11971 Iustin Pop
        any_broken = any (< 0) [tm, nm, fm, td, fd, tc]
486 39d11971 Iustin Pop
    in case Text.loadNode [name, tm_s, nm_s, fm_s, td_s, fd_s, tc_s, fo_s] of
487 39d11971 Iustin Pop
         Nothing -> False
488 39d11971 Iustin Pop
         Just (name', node) ->
489 39d11971 Iustin Pop
             if fo || any_broken
490 39d11971 Iustin Pop
             then Node.offline node
491 4a007641 Iustin Pop
             else Node.name node == name' && name' == name &&
492 4a007641 Iustin Pop
                  Node.alias node == name &&
493 4a007641 Iustin Pop
                  Node.tMem node == fromIntegral tm &&
494 4a007641 Iustin Pop
                  Node.nMem node == nm &&
495 4a007641 Iustin Pop
                  Node.fMem node == fm &&
496 4a007641 Iustin Pop
                  Node.tDsk node == fromIntegral td &&
497 4a007641 Iustin Pop
                  Node.fDsk node == fd &&
498 4a007641 Iustin Pop
                  Node.tCpu node == fromIntegral tc
499 39d11971 Iustin Pop
500 39d11971 Iustin Pop
prop_Text_Load_NodeFail fields =
501 39d11971 Iustin Pop
    length fields /= 8 ==> isNothing $ Text.loadNode fields
502 1ae7a904 Iustin Pop
503 50811e2c Iustin Pop
prop_Text_NodeLSIdempotent node =
504 50811e2c Iustin Pop
    (Text.loadNode .
505 50811e2c Iustin Pop
         Utils.sepSplit '|' . Text.serializeNode) n ==
506 50811e2c Iustin Pop
    Just (Node.name n, n)
507 50811e2c Iustin Pop
    -- override failN1 to what loadNode returns by default
508 50811e2c Iustin Pop
    where n = node { Node.failN1 = True, Node.offline = False }
509 50811e2c Iustin Pop
510 c15f7183 Iustin Pop
testText =
511 1ae7a904 Iustin Pop
    [ run prop_Text_Load_Instance
512 39d11971 Iustin Pop
    , run prop_Text_Load_InstanceFail
513 39d11971 Iustin Pop
    , run prop_Text_Load_Node
514 39d11971 Iustin Pop
    , run prop_Text_Load_NodeFail
515 50811e2c Iustin Pop
    , run prop_Text_NodeLSIdempotent
516 7dd5ee6c Iustin Pop
    ]
517 7dd5ee6c Iustin Pop
518 7dd5ee6c Iustin Pop
-- Node tests
519 7dd5ee6c Iustin Pop
520 82ea2874 Iustin Pop
prop_Node_setAlias node name =
521 82ea2874 Iustin Pop
    Node.name newnode == Node.name node &&
522 82ea2874 Iustin Pop
    Node.alias newnode == name
523 82ea2874 Iustin Pop
    where _types = (node::Node.Node, name::String)
524 82ea2874 Iustin Pop
          newnode = Node.setAlias node name
525 82ea2874 Iustin Pop
526 82ea2874 Iustin Pop
prop_Node_setOffline node status =
527 82ea2874 Iustin Pop
    Node.offline newnode == status
528 82ea2874 Iustin Pop
    where newnode = Node.setOffline node status
529 82ea2874 Iustin Pop
530 82ea2874 Iustin Pop
prop_Node_setXmem node xm =
531 82ea2874 Iustin Pop
    Node.xMem newnode == xm
532 82ea2874 Iustin Pop
    where newnode = Node.setXmem node xm
533 82ea2874 Iustin Pop
534 82ea2874 Iustin Pop
prop_Node_setMcpu node mc =
535 82ea2874 Iustin Pop
    Node.mCpu newnode == mc
536 82ea2874 Iustin Pop
    where newnode = Node.setMcpu node mc
537 82ea2874 Iustin Pop
538 7bc82927 Iustin Pop
-- | Check that an instance add with too high memory or disk will be rejected
539 8fcf251f Iustin Pop
prop_Node_addPriFM node inst = Instance.mem inst >= Node.fMem node &&
540 8fcf251f Iustin Pop
                               not (Node.failN1 node)
541 8fcf251f Iustin Pop
                               ==>
542 8fcf251f Iustin Pop
                               case Node.addPri node inst'' of
543 8fcf251f Iustin Pop
                                 Types.OpFail Types.FailMem -> True
544 8fcf251f Iustin Pop
                                 _ -> False
545 15f4c8ca Iustin Pop
    where _types = (node::Node.Node, inst::Instance.Instance)
546 8fcf251f Iustin Pop
          inst' = setInstanceSmallerThanNode node inst
547 8fcf251f Iustin Pop
          inst'' = inst' { Instance.mem = Instance.mem inst }
548 8fcf251f Iustin Pop
549 8fcf251f Iustin Pop
prop_Node_addPriFD node inst = Instance.dsk inst >= Node.fDsk node &&
550 8fcf251f Iustin Pop
                               not (Node.failN1 node)
551 8fcf251f Iustin Pop
                               ==>
552 8fcf251f Iustin Pop
                               case Node.addPri node inst'' of
553 8fcf251f Iustin Pop
                                 Types.OpFail Types.FailDisk -> True
554 8fcf251f Iustin Pop
                                 _ -> False
555 8fcf251f Iustin Pop
    where _types = (node::Node.Node, inst::Instance.Instance)
556 8fcf251f Iustin Pop
          inst' = setInstanceSmallerThanNode node inst
557 8fcf251f Iustin Pop
          inst'' = inst' { Instance.dsk = Instance.dsk inst }
558 8fcf251f Iustin Pop
559 8fcf251f Iustin Pop
prop_Node_addPriFC node inst = Instance.vcpus inst > Node.availCpu node &&
560 8fcf251f Iustin Pop
                               not (Node.failN1 node)
561 8fcf251f Iustin Pop
                               ==>
562 8fcf251f Iustin Pop
                               case Node.addPri node inst'' of
563 8fcf251f Iustin Pop
                                 Types.OpFail Types.FailCPU -> True
564 8fcf251f Iustin Pop
                                 _ -> False
565 8fcf251f Iustin Pop
    where _types = (node::Node.Node, inst::Instance.Instance)
566 8fcf251f Iustin Pop
          inst' = setInstanceSmallerThanNode node inst
567 8fcf251f Iustin Pop
          inst'' = inst' { Instance.vcpus = Instance.vcpus inst }
568 7bc82927 Iustin Pop
569 7bc82927 Iustin Pop
-- | Check that an instance add with too high memory or disk will be rejected
570 15f4c8ca Iustin Pop
prop_Node_addSec node inst pdx =
571 2060348b Iustin Pop
    (Instance.mem inst >= (Node.fMem node - Node.rMem node) ||
572 2060348b Iustin Pop
     Instance.dsk inst >= Node.fDsk node) &&
573 9f6dcdea Iustin Pop
    not (Node.failN1 node)
574 79a72ce7 Iustin Pop
    ==> isFailure (Node.addSec node inst pdx)
575 15f4c8ca Iustin Pop
        where _types = (node::Node.Node, inst::Instance.Instance, pdx::Int)
576 7dd5ee6c Iustin Pop
577 8fcf251f Iustin Pop
newtype SmallRatio = SmallRatio Double deriving Show
578 8fcf251f Iustin Pop
instance Arbitrary SmallRatio where
579 8fcf251f Iustin Pop
    arbitrary = do
580 8fcf251f Iustin Pop
      v <- choose (0, 1)
581 8fcf251f Iustin Pop
      return $ SmallRatio v
582 8fcf251f Iustin Pop
583 8fcf251f Iustin Pop
-- | Check mdsk setting
584 8fcf251f Iustin Pop
prop_Node_setMdsk node mx =
585 8fcf251f Iustin Pop
    Node.loDsk node' >= 0 &&
586 8fcf251f Iustin Pop
    fromIntegral (Node.loDsk node') <= Node.tDsk node &&
587 8fcf251f Iustin Pop
    Node.availDisk node' >= 0 &&
588 8fcf251f Iustin Pop
    Node.availDisk node' <= Node.fDsk node' &&
589 82ea2874 Iustin Pop
    fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
590 82ea2874 Iustin Pop
    Node.mDsk node' == mx'
591 8fcf251f Iustin Pop
    where _types = (node::Node.Node, mx::SmallRatio)
592 8fcf251f Iustin Pop
          node' = Node.setMdsk node mx'
593 8fcf251f Iustin Pop
          SmallRatio mx' = mx
594 8fcf251f Iustin Pop
595 8fcf251f Iustin Pop
-- Check tag maps
596 8fcf251f Iustin Pop
prop_Node_tagMaps_idempotent tags =
597 8fcf251f Iustin Pop
    Node.delTags (Node.addTags m tags) tags == m
598 4a007641 Iustin Pop
    where m = Data.Map.empty
599 8fcf251f Iustin Pop
600 8fcf251f Iustin Pop
prop_Node_tagMaps_reject tags =
601 8fcf251f Iustin Pop
    not (null tags) ==>
602 8fcf251f Iustin Pop
    any (\t -> Node.rejectAddTags m [t]) tags
603 4a007641 Iustin Pop
    where m = Node.addTags Data.Map.empty tags
604 8fcf251f Iustin Pop
605 82ea2874 Iustin Pop
prop_Node_showField node =
606 82ea2874 Iustin Pop
  forAll (elements Node.defaultFields) $ \ field ->
607 82ea2874 Iustin Pop
  fst (Node.showHeader field) /= Types.unknownField &&
608 82ea2874 Iustin Pop
  Node.showField node field /= Types.unknownField
609 82ea2874 Iustin Pop
610 d8bcd0a8 Iustin Pop
611 d8bcd0a8 Iustin Pop
prop_Node_computeGroups nodes =
612 d8bcd0a8 Iustin Pop
  let ng = Node.computeGroups nodes
613 d8bcd0a8 Iustin Pop
      onlyuuid = map fst ng
614 d8bcd0a8 Iustin Pop
  in length nodes == sum (map (length . snd) ng) &&
615 d8bcd0a8 Iustin Pop
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
616 d8bcd0a8 Iustin Pop
     length (nub onlyuuid) == length onlyuuid &&
617 d8bcd0a8 Iustin Pop
     if null nodes then True else not (null ng)
618 d8bcd0a8 Iustin Pop
619 c15f7183 Iustin Pop
testNode =
620 82ea2874 Iustin Pop
    [ run prop_Node_setAlias
621 82ea2874 Iustin Pop
    , run prop_Node_setOffline
622 82ea2874 Iustin Pop
    , run prop_Node_setMcpu
623 82ea2874 Iustin Pop
    , run prop_Node_setXmem
624 82ea2874 Iustin Pop
    , run prop_Node_addPriFM
625 8fcf251f Iustin Pop
    , run prop_Node_addPriFD
626 8fcf251f Iustin Pop
    , run prop_Node_addPriFC
627 7dd5ee6c Iustin Pop
    , run prop_Node_addSec
628 8fcf251f Iustin Pop
    , run prop_Node_setMdsk
629 8fcf251f Iustin Pop
    , run prop_Node_tagMaps_idempotent
630 8fcf251f Iustin Pop
    , run prop_Node_tagMaps_reject
631 82ea2874 Iustin Pop
    , run prop_Node_showField
632 d8bcd0a8 Iustin Pop
    , run prop_Node_computeGroups
633 7dd5ee6c Iustin Pop
    ]
634 cf35a869 Iustin Pop
635 cf35a869 Iustin Pop
636 cf35a869 Iustin Pop
-- Cluster tests
637 cf35a869 Iustin Pop
638 cf35a869 Iustin Pop
-- | Check that the cluster score is close to zero for a homogeneous cluster
639 cf35a869 Iustin Pop
prop_Score_Zero node count =
640 3a3c1eb4 Iustin Pop
    (not (Node.offline node) && not (Node.failN1 node) && (count > 0) &&
641 2060348b Iustin Pop
     (Node.tDsk node > 0) && (Node.tMem node > 0)) ==>
642 cf35a869 Iustin Pop
    let fn = Node.buildPeers node Container.empty
643 3a3c1eb4 Iustin Pop
        nlst = zip [1..] $ replicate count fn::[(Types.Ndx, Node.Node)]
644 cf35a869 Iustin Pop
        nl = Container.fromAssocList nlst
645 cf35a869 Iustin Pop
        score = Cluster.compCV nl
646 cf35a869 Iustin Pop
    -- we can't say == 0 here as the floating point errors accumulate;
647 cf35a869 Iustin Pop
    -- this should be much lower than the default score in CLI.hs
648 685f5bc6 Iustin Pop
    in score <= 1e-15
649 cf35a869 Iustin Pop
650 8fcf251f Iustin Pop
-- | Check that cluster stats are sane
651 8fcf251f Iustin Pop
prop_CStats_sane node count =
652 8fcf251f Iustin Pop
    (not (Node.offline node) && not (Node.failN1 node) && (count > 0) &&
653 3fea6959 Iustin Pop
     (Node.availDisk node > 0) && (Node.availMem node > 0)) ==>
654 8fcf251f Iustin Pop
    let fn = Node.buildPeers node Container.empty
655 8fcf251f Iustin Pop
        nlst = zip [1..] $ replicate count fn::[(Types.Ndx, Node.Node)]
656 8fcf251f Iustin Pop
        nl = Container.fromAssocList nlst
657 8fcf251f Iustin Pop
        cstats = Cluster.totalResources nl
658 8fcf251f Iustin Pop
    in Cluster.csAdsk cstats >= 0 &&
659 8fcf251f Iustin Pop
       Cluster.csAdsk cstats <= Cluster.csFdsk cstats
660 8fcf251f Iustin Pop
661 3fea6959 Iustin Pop
-- | Check that one instance is allocated correctly, without
662 3fea6959 Iustin Pop
-- rebalances needed
663 3fea6959 Iustin Pop
prop_ClusterAlloc_sane node inst =
664 3fea6959 Iustin Pop
    forAll (choose (5, 20)) $ \count ->
665 3fea6959 Iustin Pop
    not (Node.offline node)
666 3fea6959 Iustin Pop
            && not (Node.failN1 node)
667 3fea6959 Iustin Pop
            && Node.availDisk node > 0
668 3fea6959 Iustin Pop
            && Node.availMem node > 0
669 3fea6959 Iustin Pop
            ==>
670 3fea6959 Iustin Pop
    let nl = makeSmallCluster node count
671 3fea6959 Iustin Pop
        il = Container.empty
672 3fea6959 Iustin Pop
        rqnodes = 2
673 3fea6959 Iustin Pop
        inst' = setInstanceSmallerThanNode node inst
674 3fea6959 Iustin Pop
    in case Cluster.tryAlloc nl il inst' rqnodes of
675 3fea6959 Iustin Pop
         Types.Bad _ -> False
676 9e35522c Iustin Pop
         Types.Ok (_, _, sols3) ->
677 3fea6959 Iustin Pop
             case sols3 of
678 3fea6959 Iustin Pop
               [] -> False
679 a334d536 Iustin Pop
               (xnl, xi, _, cv):[] ->
680 7d3f4253 Iustin Pop
                   let il' = Container.add (Instance.idx xi) xi il
681 3fea6959 Iustin Pop
                       tbl = Cluster.Table xnl il' cv []
682 3fea6959 Iustin Pop
                   in not (canBalance tbl True False)
683 3fea6959 Iustin Pop
               _ -> False
684 3fea6959 Iustin Pop
685 3fea6959 Iustin Pop
-- | Checks that on a 2-5 node cluster, we can allocate a random
686 3fea6959 Iustin Pop
-- instance spec via tiered allocation (whatever the original instance
687 3fea6959 Iustin Pop
-- spec), on either one or two nodes
688 3fea6959 Iustin Pop
prop_ClusterCanTieredAlloc node inst =
689 3fea6959 Iustin Pop
    forAll (choose (2, 5)) $ \count ->
690 3fea6959 Iustin Pop
    forAll (choose (1, 2)) $ \rqnodes ->
691 3fea6959 Iustin Pop
    not (Node.offline node)
692 3fea6959 Iustin Pop
            && not (Node.failN1 node)
693 3fea6959 Iustin Pop
            && isNodeBig node 4
694 3fea6959 Iustin Pop
            ==>
695 3fea6959 Iustin Pop
    let nl = makeSmallCluster node count
696 3fea6959 Iustin Pop
        il = Container.empty
697 3fea6959 Iustin Pop
    in case Cluster.tieredAlloc nl il inst rqnodes [] of
698 3fea6959 Iustin Pop
         Types.Bad _ -> False
699 e3ae9508 Iustin Pop
         Types.Ok (_, _, il', ixes) -> not (null ixes) &&
700 e3ae9508 Iustin Pop
                                      IntMap.size il' == length ixes
701 3fea6959 Iustin Pop
702 3fea6959 Iustin Pop
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
703 3fea6959 Iustin Pop
-- we can also evacuate it
704 3fea6959 Iustin Pop
prop_ClusterAllocEvac node inst =
705 3fea6959 Iustin Pop
    forAll (choose (4, 8)) $ \count ->
706 3fea6959 Iustin Pop
    not (Node.offline node)
707 3fea6959 Iustin Pop
            && not (Node.failN1 node)
708 3fea6959 Iustin Pop
            && isNodeBig node 4
709 3fea6959 Iustin Pop
            ==>
710 3fea6959 Iustin Pop
    let nl = makeSmallCluster node count
711 3fea6959 Iustin Pop
        il = Container.empty
712 3fea6959 Iustin Pop
        rqnodes = 2
713 3fea6959 Iustin Pop
        inst' = setInstanceSmallerThanNode node inst
714 3fea6959 Iustin Pop
    in case Cluster.tryAlloc nl il inst' rqnodes of
715 3fea6959 Iustin Pop
         Types.Bad _ -> False
716 9e35522c Iustin Pop
         Types.Ok (_, _, sols3) ->
717 3fea6959 Iustin Pop
             case sols3 of
718 3fea6959 Iustin Pop
               [] -> False
719 a334d536 Iustin Pop
               (xnl, xi, _, _):[] ->
720 3fea6959 Iustin Pop
                   let sdx = Instance.sNode xi
721 3fea6959 Iustin Pop
                       il' = Container.add (Instance.idx xi) xi il
722 3fea6959 Iustin Pop
                   in case Cluster.tryEvac xnl il' [sdx] of
723 3fea6959 Iustin Pop
                        Just _ -> True
724 3fea6959 Iustin Pop
                        _ -> False
725 3fea6959 Iustin Pop
               _ -> False
726 3fea6959 Iustin Pop
727 3fea6959 Iustin Pop
-- | Check that allocating multiple instances on a cluster, then
728 3fea6959 Iustin Pop
-- adding an empty node, results in a valid rebalance
729 3fea6959 Iustin Pop
prop_ClusterAllocBalance node =
730 3fea6959 Iustin Pop
    forAll (choose (3, 5)) $ \count ->
731 3fea6959 Iustin Pop
    not (Node.offline node)
732 3fea6959 Iustin Pop
            && not (Node.failN1 node)
733 3fea6959 Iustin Pop
            && isNodeBig node 4
734 3fea6959 Iustin Pop
            && not (isNodeBig node 8)
735 3fea6959 Iustin Pop
            ==>
736 3fea6959 Iustin Pop
    let nl = makeSmallCluster node count
737 3fea6959 Iustin Pop
        (hnode, nl') = IntMap.deleteFindMax nl
738 3fea6959 Iustin Pop
        il = Container.empty
739 3fea6959 Iustin Pop
        rqnodes = 2
740 3fea6959 Iustin Pop
        i_templ = createInstance Types.unitMem Types.unitDsk Types.unitCpu
741 3fea6959 Iustin Pop
    in case Cluster.iterateAlloc nl' il i_templ rqnodes [] of
742 3fea6959 Iustin Pop
         Types.Bad _ -> False
743 e3ae9508 Iustin Pop
         Types.Ok (_, xnl, il', _) ->
744 3fea6959 Iustin Pop
                   let ynl = Container.add (Node.idx hnode) hnode xnl
745 3fea6959 Iustin Pop
                       cv = Cluster.compCV ynl
746 3fea6959 Iustin Pop
                       tbl = Cluster.Table ynl il' cv []
747 3fea6959 Iustin Pop
                   in canBalance tbl True False
748 3fea6959 Iustin Pop
749 32b8d9c0 Iustin Pop
-- | Checks consistency
750 32b8d9c0 Iustin Pop
prop_ClusterCheckConsistency node inst =
751 32b8d9c0 Iustin Pop
  let nl = makeSmallCluster node 3
752 32b8d9c0 Iustin Pop
      [node1, node2, node3] = Container.elems nl
753 32b8d9c0 Iustin Pop
      node3' = node3 { Node.group = "other-uuid" }
754 32b8d9c0 Iustin Pop
      nl' = Container.add (Node.idx node3') node3' nl
755 32b8d9c0 Iustin Pop
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
756 32b8d9c0 Iustin Pop
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
757 32b8d9c0 Iustin Pop
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
758 32b8d9c0 Iustin Pop
      ccheck = Cluster.findSplitInstances nl' . Container.fromAssocList
759 32b8d9c0 Iustin Pop
  in null (ccheck [(0, inst1)]) &&
760 32b8d9c0 Iustin Pop
     null (ccheck [(0, inst2)]) &&
761 32b8d9c0 Iustin Pop
     (not . null $ ccheck [(0, inst3)])
762 32b8d9c0 Iustin Pop
763 f4161783 Iustin Pop
-- For now, we only test that we don't lose instances during the split
764 f4161783 Iustin Pop
prop_ClusterSplitCluster node inst =
765 f4161783 Iustin Pop
  forAll (choose (0, 100)) $ \icnt ->
766 f4161783 Iustin Pop
  let nl = makeSmallCluster node 2
767 f4161783 Iustin Pop
      (nl', il') = foldl (\(ns, is) _ -> assignInstance ns is inst 0 1)
768 f4161783 Iustin Pop
                   (nl, Container.empty) [1..icnt]
769 f4161783 Iustin Pop
      gni = Cluster.splitCluster nl' il'
770 f4161783 Iustin Pop
  in sum (map (Container.size . snd . snd) gni) == icnt &&
771 f4161783 Iustin Pop
     all (\(guuid, (nl'', _)) -> all ((== guuid) . Node.group)
772 f4161783 Iustin Pop
                                 (Container.elems nl'')) gni
773 32b8d9c0 Iustin Pop
774 c15f7183 Iustin Pop
testCluster =
775 cf35a869 Iustin Pop
    [ run prop_Score_Zero
776 8fcf251f Iustin Pop
    , run prop_CStats_sane
777 3fea6959 Iustin Pop
    , run prop_ClusterAlloc_sane
778 3fea6959 Iustin Pop
    , run prop_ClusterCanTieredAlloc
779 3fea6959 Iustin Pop
    , run prop_ClusterAllocEvac
780 3fea6959 Iustin Pop
    , run prop_ClusterAllocBalance
781 32b8d9c0 Iustin Pop
    , run prop_ClusterCheckConsistency
782 f4161783 Iustin Pop
    , run prop_ClusterSplitCluster
783 cf35a869 Iustin Pop
    ]
784 88f25dd0 Iustin Pop
785 88f25dd0 Iustin Pop
-- | Check that opcode serialization is idempotent
786 88f25dd0 Iustin Pop
787 88f25dd0 Iustin Pop
prop_OpCodes_serialization op =
788 88f25dd0 Iustin Pop
  case J.readJSON (J.showJSON op) of
789 88f25dd0 Iustin Pop
    J.Error _ -> False
790 88f25dd0 Iustin Pop
    J.Ok op' -> op == op'
791 4a007641 Iustin Pop
  where _types = op::OpCodes.OpCode
792 88f25dd0 Iustin Pop
793 88f25dd0 Iustin Pop
testOpCodes =
794 88f25dd0 Iustin Pop
  [ run prop_OpCodes_serialization
795 88f25dd0 Iustin Pop
  ]
796 c088674b Iustin Pop
797 95446d7a Iustin Pop
-- | Check that (queued) job\/opcode status serialization is idempotent
798 db079755 Iustin Pop
prop_OpStatus_serialization os =
799 db079755 Iustin Pop
  case J.readJSON (J.showJSON os) of
800 db079755 Iustin Pop
    J.Error _ -> False
801 db079755 Iustin Pop
    J.Ok os' -> os == os'
802 db079755 Iustin Pop
  where _types = os::Jobs.OpStatus
803 db079755 Iustin Pop
804 db079755 Iustin Pop
prop_JobStatus_serialization js =
805 db079755 Iustin Pop
  case J.readJSON (J.showJSON js) of
806 db079755 Iustin Pop
    J.Error _ -> False
807 db079755 Iustin Pop
    J.Ok js' -> js == js'
808 db079755 Iustin Pop
  where _types = js::Jobs.JobStatus
809 db079755 Iustin Pop
810 db079755 Iustin Pop
testJobs =
811 db079755 Iustin Pop
  [ run prop_OpStatus_serialization
812 db079755 Iustin Pop
  , run prop_JobStatus_serialization
813 db079755 Iustin Pop
  ]
814 db079755 Iustin Pop
815 c088674b Iustin Pop
-- | Loader tests
816 c088674b Iustin Pop
817 c088674b Iustin Pop
prop_Loader_lookupNode ktn inst node =
818 99b63608 Iustin Pop
  Loader.lookupNode nl inst node == Data.Map.lookup node nl
819 99b63608 Iustin Pop
  where nl = Data.Map.fromList ktn
820 c088674b Iustin Pop
821 c088674b Iustin Pop
prop_Loader_lookupInstance kti inst =
822 99b63608 Iustin Pop
  Loader.lookupInstance il inst == Data.Map.lookup inst il
823 99b63608 Iustin Pop
  where il = Data.Map.fromList kti
824 99b63608 Iustin Pop
825 99b63608 Iustin Pop
prop_Loader_assignIndices nodes =
826 99b63608 Iustin Pop
  Data.Map.size nassoc == length nodes &&
827 99b63608 Iustin Pop
  Container.size kt == length nodes &&
828 99b63608 Iustin Pop
  (if not (null nodes)
829 99b63608 Iustin Pop
   then maximum (IntMap.keys kt) == length nodes - 1
830 c088674b Iustin Pop
   else True)
831 99b63608 Iustin Pop
  where (nassoc, kt) = Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
832 c088674b Iustin Pop
833 c088674b Iustin Pop
834 c088674b Iustin Pop
-- | Checks that the number of primary instances recorded on the nodes
835 c088674b Iustin Pop
-- is zero
836 c088674b Iustin Pop
prop_Loader_mergeData ns =
837 99b63608 Iustin Pop
  let na = Container.fromAssocList $ map (\n -> (Node.idx n, n)) ns
838 99b63608 Iustin Pop
  in case Loader.mergeData [] [] [] (na, Container.empty, []) of
839 c088674b Iustin Pop
    Types.Bad _ -> False
840 c088674b Iustin Pop
    Types.Ok (nl, il, _) ->
841 c088674b Iustin Pop
      let nodes = Container.elems nl
842 c088674b Iustin Pop
          instances = Container.elems il
843 c088674b Iustin Pop
      in (sum . map (length . Node.pList)) nodes == 0 &&
844 4a007641 Iustin Pop
         null instances
845 c088674b Iustin Pop
846 c088674b Iustin Pop
testLoader =
847 c088674b Iustin Pop
  [ run prop_Loader_lookupNode
848 c088674b Iustin Pop
  , run prop_Loader_lookupInstance
849 c088674b Iustin Pop
  , run prop_Loader_assignIndices
850 c088674b Iustin Pop
  , run prop_Loader_mergeData
851 c088674b Iustin Pop
  ]