Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / QC.hs @ a423b510

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