Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (43.9 kB)

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