Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 2e5eb96a

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