Statistics
| Branch: | Tag: | Revision:

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

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