Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 96bc2003

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