Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 5cefb2b2

History | View | Annotate | Download (63.7 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 e1dde6ad Iustin Pop
  , testSimu
36 d5dfae0a Iustin Pop
  , testOpCodes
37 d5dfae0a Iustin Pop
  , testJobs
38 d5dfae0a Iustin Pop
  , testCluster
39 d5dfae0a Iustin Pop
  , testLoader
40 d5dfae0a Iustin Pop
  , testTypes
41 8b5a517a Iustin Pop
  , testCLI
42 3ad57194 Iustin Pop
  , testJSON
43 d5dfae0a Iustin Pop
  ) where
44 15f4c8ca Iustin Pop
45 15f4c8ca Iustin Pop
import Test.QuickCheck
46 e1dde6ad Iustin Pop
import Text.Printf (printf)
47 bc782180 Iustin Pop
import Data.List (findIndex, intercalate, nub, isPrefixOf)
48 e1dde6ad Iustin Pop
import qualified Data.Set as Set
49 15f4c8ca Iustin Pop
import Data.Maybe
50 88f25dd0 Iustin Pop
import Control.Monad
51 5cefb2b2 Iustin Pop
import Control.Applicative
52 89298c04 Iustin Pop
import qualified System.Console.GetOpt as GetOpt
53 88f25dd0 Iustin Pop
import qualified Text.JSON as J
54 8fcf251f Iustin Pop
import qualified Data.Map
55 3fea6959 Iustin Pop
import qualified Data.IntMap as IntMap
56 89298c04 Iustin Pop
57 88f25dd0 Iustin Pop
import qualified Ganeti.OpCodes as OpCodes
58 db079755 Iustin Pop
import qualified Ganeti.Jobs as Jobs
59 223dbe53 Iustin Pop
import qualified Ganeti.Luxi
60 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.CLI as CLI
61 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
62 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Container as Container
63 223dbe53 Iustin Pop
import qualified Ganeti.HTools.ExtLoader
64 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.IAlloc as IAlloc
65 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
66 b69be409 Iustin Pop
import qualified Ganeti.HTools.JSON as JSON
67 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Loader as Loader
68 223dbe53 Iustin Pop
import qualified Ganeti.HTools.Luxi
69 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Node as Node
70 10ef6b4e Iustin Pop
import qualified Ganeti.HTools.Group as Group
71 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.PeerMap as PeerMap
72 c478f837 Iustin Pop
import qualified Ganeti.HTools.Rapi
73 e1dde6ad Iustin Pop
import qualified Ganeti.HTools.Simu as Simu
74 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Text as Text
75 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Types as Types
76 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Utils as Utils
77 223dbe53 Iustin Pop
import qualified Ganeti.HTools.Version
78 e82271f8 Iustin Pop
import qualified Ganeti.Constants as C
79 15f4c8ca Iustin Pop
80 a292b4e0 Iustin Pop
import qualified Ganeti.HTools.Program as Program
81 33b9d92d Iustin Pop
import qualified Ganeti.HTools.Program.Hail
82 33b9d92d Iustin Pop
import qualified Ganeti.HTools.Program.Hbal
83 33b9d92d Iustin Pop
import qualified Ganeti.HTools.Program.Hscan
84 33b9d92d Iustin Pop
import qualified Ganeti.HTools.Program.Hspace
85 33b9d92d Iustin Pop
86 23fe06c2 Iustin Pop
import Ganeti.HTools.QCHelper (testSuite)
87 8e4f6d56 Iustin Pop
88 3fea6959 Iustin Pop
-- * Constants
89 3fea6959 Iustin Pop
90 525bfb36 Iustin Pop
-- | Maximum memory (1TiB, somewhat random value).
91 8fcf251f Iustin Pop
maxMem :: Int
92 8fcf251f Iustin Pop
maxMem = 1024 * 1024
93 8fcf251f Iustin Pop
94 525bfb36 Iustin Pop
-- | Maximum disk (8TiB, somewhat random value).
95 8fcf251f Iustin Pop
maxDsk :: Int
96 49f9627a Iustin Pop
maxDsk = 1024 * 1024 * 8
97 8fcf251f Iustin Pop
98 525bfb36 Iustin Pop
-- | Max CPUs (1024, somewhat random value).
99 8fcf251f Iustin Pop
maxCpu :: Int
100 8fcf251f Iustin Pop
maxCpu = 1024
101 8fcf251f Iustin Pop
102 c22d4dd4 Iustin Pop
-- | Max vcpu ratio (random value).
103 c22d4dd4 Iustin Pop
maxVcpuRatio :: Double
104 c22d4dd4 Iustin Pop
maxVcpuRatio = 1024.0
105 c22d4dd4 Iustin Pop
106 c22d4dd4 Iustin Pop
-- | Max spindle ratio (random value).
107 c22d4dd4 Iustin Pop
maxSpindleRatio :: Double
108 c22d4dd4 Iustin Pop
maxSpindleRatio = 1024.0
109 c22d4dd4 Iustin Pop
110 5cefb2b2 Iustin Pop
-- | Max nodes, used just to limit arbitrary instances for smaller
111 5cefb2b2 Iustin Pop
-- opcode definitions (e.g. list of nodes in OpTestDelay).
112 5cefb2b2 Iustin Pop
maxNodes :: Int
113 5cefb2b2 Iustin Pop
maxNodes = 32
114 5cefb2b2 Iustin Pop
115 5cefb2b2 Iustin Pop
-- | Max opcodes or jobs in a submit job and submit many jobs.
116 5cefb2b2 Iustin Pop
maxOpCodes :: Int
117 5cefb2b2 Iustin Pop
maxOpCodes = 16
118 5cefb2b2 Iustin Pop
119 7806125e Iustin Pop
-- | All disk templates (used later)
120 7806125e Iustin Pop
allDiskTemplates :: [Types.DiskTemplate]
121 7806125e Iustin Pop
allDiskTemplates = [minBound..maxBound]
122 7806125e Iustin Pop
123 6cff91f5 Iustin Pop
-- | Null iPolicy, and by null we mean very liberal.
124 6cff91f5 Iustin Pop
nullIPolicy = Types.IPolicy
125 6cff91f5 Iustin Pop
  { Types.iPolicyMinSpec = Types.ISpec { Types.iSpecMemorySize = 0
126 6cff91f5 Iustin Pop
                                       , Types.iSpecCpuCount   = 0
127 6cff91f5 Iustin Pop
                                       , Types.iSpecDiskSize   = 0
128 6cff91f5 Iustin Pop
                                       , Types.iSpecDiskCount  = 0
129 6cff91f5 Iustin Pop
                                       , Types.iSpecNicCount   = 0
130 d953a965 Renรฉ Nussbaumer
                                       , Types.iSpecSpindleUse = 0
131 6cff91f5 Iustin Pop
                                       }
132 6cff91f5 Iustin Pop
  , Types.iPolicyMaxSpec = Types.ISpec { Types.iSpecMemorySize = maxBound
133 6cff91f5 Iustin Pop
                                       , Types.iSpecCpuCount   = maxBound
134 6cff91f5 Iustin Pop
                                       , Types.iSpecDiskSize   = maxBound
135 6cff91f5 Iustin Pop
                                       , Types.iSpecDiskCount  = C.maxDisks
136 6cff91f5 Iustin Pop
                                       , Types.iSpecNicCount   = C.maxNics
137 d953a965 Renรฉ Nussbaumer
                                       , Types.iSpecSpindleUse = maxBound
138 6cff91f5 Iustin Pop
                                       }
139 6cff91f5 Iustin Pop
  , Types.iPolicyStdSpec = Types.ISpec { Types.iSpecMemorySize = Types.unitMem
140 6cff91f5 Iustin Pop
                                       , Types.iSpecCpuCount   = Types.unitCpu
141 6cff91f5 Iustin Pop
                                       , Types.iSpecDiskSize   = Types.unitDsk
142 6cff91f5 Iustin Pop
                                       , Types.iSpecDiskCount  = 1
143 6cff91f5 Iustin Pop
                                       , Types.iSpecNicCount   = 1
144 d953a965 Renรฉ Nussbaumer
                                       , Types.iSpecSpindleUse = 1
145 6cff91f5 Iustin Pop
                                       }
146 64946775 Iustin Pop
  , Types.iPolicyDiskTemplates = [minBound..maxBound]
147 c22d4dd4 Iustin Pop
  , Types.iPolicyVcpuRatio = maxVcpuRatio -- somewhat random value, high
148 c22d4dd4 Iustin Pop
                                          -- enough to not impact us
149 c22d4dd4 Iustin Pop
  , Types.iPolicySpindleRatio = maxSpindleRatio
150 6cff91f5 Iustin Pop
  }
151 6cff91f5 Iustin Pop
152 6cff91f5 Iustin Pop
153 10ef6b4e Iustin Pop
defGroup :: Group.Group
154 10ef6b4e Iustin Pop
defGroup = flip Group.setIdx 0 $
155 f3f76ccc Iustin Pop
             Group.create "default" Types.defaultGroupID Types.AllocPreferred
156 6cff91f5 Iustin Pop
                  nullIPolicy
157 10ef6b4e Iustin Pop
158 10ef6b4e Iustin Pop
defGroupList :: Group.List
159 cb0c77ff Iustin Pop
defGroupList = Container.fromList [(Group.idx defGroup, defGroup)]
160 10ef6b4e Iustin Pop
161 10ef6b4e Iustin Pop
defGroupAssoc :: Data.Map.Map String Types.Gdx
162 10ef6b4e Iustin Pop
defGroupAssoc = Data.Map.singleton (Group.uuid defGroup) (Group.idx defGroup)
163 10ef6b4e Iustin Pop
164 3fea6959 Iustin Pop
-- * Helper functions
165 3fea6959 Iustin Pop
166 525bfb36 Iustin Pop
-- | Simple checker for whether OpResult is fail or pass.
167 79a72ce7 Iustin Pop
isFailure :: Types.OpResult a -> Bool
168 79a72ce7 Iustin Pop
isFailure (Types.OpFail _) = True
169 79a72ce7 Iustin Pop
isFailure _ = False
170 79a72ce7 Iustin Pop
171 72bb6b4e Iustin Pop
-- | Checks for equality with proper annotation.
172 72bb6b4e Iustin Pop
(==?) :: (Show a, Eq a) => a -> a -> Property
173 72bb6b4e Iustin Pop
(==?) x y = printTestCase
174 72bb6b4e Iustin Pop
            ("Expected equality, but '" ++
175 72bb6b4e Iustin Pop
             show x ++ "' /= '" ++ show y ++ "'") (x == y)
176 72bb6b4e Iustin Pop
infix 3 ==?
177 72bb6b4e Iustin Pop
178 96bc2003 Iustin Pop
-- | Show a message and fail the test.
179 96bc2003 Iustin Pop
failTest :: String -> Property
180 96bc2003 Iustin Pop
failTest msg = printTestCase msg False
181 96bc2003 Iustin Pop
182 525bfb36 Iustin Pop
-- | Update an instance to be smaller than a node.
183 3fea6959 Iustin Pop
setInstanceSmallerThanNode node inst =
184 d5dfae0a Iustin Pop
  inst { Instance.mem = Node.availMem node `div` 2
185 d5dfae0a Iustin Pop
       , Instance.dsk = Node.availDisk node `div` 2
186 d5dfae0a Iustin Pop
       , Instance.vcpus = Node.availCpu node `div` 2
187 d5dfae0a Iustin Pop
       }
188 3fea6959 Iustin Pop
189 525bfb36 Iustin Pop
-- | Create an instance given its spec.
190 3fea6959 Iustin Pop
createInstance mem dsk vcpus =
191 d5dfae0a Iustin Pop
  Instance.create "inst-unnamed" mem dsk vcpus Types.Running [] True (-1) (-1)
192 981bb5cf Renรฉ Nussbaumer
    Types.DTDrbd8 1
193 3fea6959 Iustin Pop
194 525bfb36 Iustin Pop
-- | Create a small cluster by repeating a node spec.
195 3fea6959 Iustin Pop
makeSmallCluster :: Node.Node -> Int -> Node.List
196 3fea6959 Iustin Pop
makeSmallCluster node count =
197 e73c5fe2 Iustin Pop
  let origname = Node.name node
198 e73c5fe2 Iustin Pop
      origalias = Node.alias node
199 e73c5fe2 Iustin Pop
      nodes = map (\idx -> node { Node.name = origname ++ "-" ++ show idx
200 e73c5fe2 Iustin Pop
                                , Node.alias = origalias ++ "-" ++ show idx })
201 e73c5fe2 Iustin Pop
              [1..count]
202 e73c5fe2 Iustin Pop
      fn = flip Node.buildPeers Container.empty
203 e73c5fe2 Iustin Pop
      namelst = map (\n -> (Node.name n, fn n)) nodes
204 d5dfae0a Iustin Pop
      (_, nlst) = Loader.assignIndices namelst
205 d5dfae0a Iustin Pop
  in nlst
206 3fea6959 Iustin Pop
207 3603605a Iustin Pop
-- | Make a small cluster, both nodes and instances.
208 3603605a Iustin Pop
makeSmallEmptyCluster :: Node.Node -> Int -> Instance.Instance
209 3603605a Iustin Pop
                      -> (Node.List, Instance.List, Instance.Instance)
210 3603605a Iustin Pop
makeSmallEmptyCluster node count inst =
211 3603605a Iustin Pop
  (makeSmallCluster node count, Container.empty,
212 3603605a Iustin Pop
   setInstanceSmallerThanNode node inst)
213 3603605a Iustin Pop
214 525bfb36 Iustin Pop
-- | Checks if a node is "big" enough.
215 d6f9f5bd Iustin Pop
isNodeBig :: Int -> Node.Node -> Bool
216 d6f9f5bd Iustin Pop
isNodeBig size node = Node.availDisk node > size * Types.unitDsk
217 3fea6959 Iustin Pop
                      && Node.availMem node > size * Types.unitMem
218 3fea6959 Iustin Pop
                      && Node.availCpu node > size * Types.unitCpu
219 3fea6959 Iustin Pop
220 e08424a8 Guido Trotter
canBalance :: Cluster.Table -> Bool -> Bool -> Bool -> Bool
221 e08424a8 Guido Trotter
canBalance tbl dm im evac = isJust $ Cluster.tryBalance tbl dm im evac 0 0
222 3fea6959 Iustin Pop
223 f4161783 Iustin Pop
-- | Assigns a new fresh instance to a cluster; this is not
224 525bfb36 Iustin Pop
-- allocation, so no resource checks are done.
225 f4161783 Iustin Pop
assignInstance :: Node.List -> Instance.List -> Instance.Instance ->
226 f4161783 Iustin Pop
                  Types.Idx -> Types.Idx ->
227 f4161783 Iustin Pop
                  (Node.List, Instance.List)
228 f4161783 Iustin Pop
assignInstance nl il inst pdx sdx =
229 f4161783 Iustin Pop
  let pnode = Container.find pdx nl
230 f4161783 Iustin Pop
      snode = Container.find sdx nl
231 f4161783 Iustin Pop
      maxiidx = if Container.null il
232 d5dfae0a Iustin Pop
                  then 0
233 d5dfae0a Iustin Pop
                  else fst (Container.findMax il) + 1
234 f4161783 Iustin Pop
      inst' = inst { Instance.idx = maxiidx,
235 f4161783 Iustin Pop
                     Instance.pNode = pdx, Instance.sNode = sdx }
236 f4161783 Iustin Pop
      pnode' = Node.setPri pnode inst'
237 f4161783 Iustin Pop
      snode' = Node.setSec snode inst'
238 f4161783 Iustin Pop
      nl' = Container.addTwo pdx pnode' sdx snode' nl
239 f4161783 Iustin Pop
      il' = Container.add maxiidx inst' il
240 f4161783 Iustin Pop
  in (nl', il')
241 f4161783 Iustin Pop
242 a2a0bcd8 Iustin Pop
-- | Generates a list of a given size with non-duplicate elements.
243 a2a0bcd8 Iustin Pop
genUniquesList :: (Eq a, Arbitrary a) => Int -> Gen [a]
244 a2a0bcd8 Iustin Pop
genUniquesList cnt =
245 a2a0bcd8 Iustin Pop
  foldM (\lst _ -> do
246 a2a0bcd8 Iustin Pop
           newelem <- arbitrary `suchThat` (`notElem` lst)
247 a2a0bcd8 Iustin Pop
           return (newelem:lst)) [] [1..cnt]
248 a2a0bcd8 Iustin Pop
249 ac1c0a07 Iustin Pop
-- | Checks if an instance is mirrored.
250 ac1c0a07 Iustin Pop
isMirrored :: Instance.Instance -> Bool
251 fafd0773 Iustin Pop
isMirrored = (/= Types.MirrorNone) . Instance.mirrorType
252 ac1c0a07 Iustin Pop
253 ac1c0a07 Iustin Pop
-- | Returns the possible change node types for a disk template.
254 ac1c0a07 Iustin Pop
evacModeOptions :: Types.MirrorType -> [Types.EvacMode]
255 ac1c0a07 Iustin Pop
evacModeOptions Types.MirrorNone     = []
256 ac1c0a07 Iustin Pop
evacModeOptions Types.MirrorInternal = [minBound..maxBound] -- DRBD can do all
257 ac1c0a07 Iustin Pop
evacModeOptions Types.MirrorExternal = [Types.ChangePrimary, Types.ChangeAll]
258 ac1c0a07 Iustin Pop
259 3fea6959 Iustin Pop
-- * Arbitrary instances
260 3fea6959 Iustin Pop
261 525bfb36 Iustin Pop
-- | Defines a DNS name.
262 a070c426 Iustin Pop
newtype DNSChar = DNSChar { dnsGetChar::Char }
263 525bfb36 Iustin Pop
264 a070c426 Iustin Pop
instance Arbitrary DNSChar where
265 d5dfae0a Iustin Pop
  arbitrary = do
266 d5dfae0a Iustin Pop
    x <- elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
267 d5dfae0a Iustin Pop
    return (DNSChar x)
268 a070c426 Iustin Pop
269 a2a0bcd8 Iustin Pop
-- | Generates a single name component.
270 a070c426 Iustin Pop
getName :: Gen String
271 a070c426 Iustin Pop
getName = do
272 a070c426 Iustin Pop
  n <- choose (1, 64)
273 5cefb2b2 Iustin Pop
  dn <- vector n
274 a070c426 Iustin Pop
  return (map dnsGetChar dn)
275 a070c426 Iustin Pop
276 a2a0bcd8 Iustin Pop
-- | Generates an entire FQDN.
277 a070c426 Iustin Pop
getFQDN :: Gen String
278 a070c426 Iustin Pop
getFQDN = do
279 a070c426 Iustin Pop
  ncomps <- choose (1, 4)
280 5cefb2b2 Iustin Pop
  names <- vectorOf ncomps getName
281 a2a0bcd8 Iustin Pop
  return $ intercalate "." names
282 a070c426 Iustin Pop
283 5cefb2b2 Iustin Pop
-- | Combinator that generates a 'Maybe' using a sub-combinator.
284 5cefb2b2 Iustin Pop
getMaybe :: Gen a -> Gen (Maybe a)
285 5cefb2b2 Iustin Pop
getMaybe subgen = do
286 5cefb2b2 Iustin Pop
  bool <- arbitrary
287 5cefb2b2 Iustin Pop
  if bool
288 5cefb2b2 Iustin Pop
    then Just <$> subgen
289 5cefb2b2 Iustin Pop
    else return Nothing
290 5cefb2b2 Iustin Pop
291 5cefb2b2 Iustin Pop
-- | Generates a fields list. This uses the same character set as a
292 5cefb2b2 Iustin Pop
-- DNS name (just for simplicity).
293 5cefb2b2 Iustin Pop
getFields :: Gen [String]
294 5cefb2b2 Iustin Pop
getFields = do
295 5cefb2b2 Iustin Pop
  n <- choose (1, 32)
296 5cefb2b2 Iustin Pop
  vectorOf n getName
297 5cefb2b2 Iustin Pop
298 dce9bbb3 Iustin Pop
-- | Defines a tag type.
299 dce9bbb3 Iustin Pop
newtype TagChar = TagChar { tagGetChar :: Char }
300 dce9bbb3 Iustin Pop
301 dce9bbb3 Iustin Pop
-- | All valid tag chars. This doesn't need to match _exactly_
302 dce9bbb3 Iustin Pop
-- Ganeti's own tag regex, just enough for it to be close.
303 dce9bbb3 Iustin Pop
tagChar :: [Char]
304 dce9bbb3 Iustin Pop
tagChar = ['a'..'z'] ++ ['A'..'Z'] ++ ['0'..'9'] ++ ".+*/:@-"
305 dce9bbb3 Iustin Pop
306 dce9bbb3 Iustin Pop
instance Arbitrary TagChar where
307 dce9bbb3 Iustin Pop
  arbitrary = do
308 dce9bbb3 Iustin Pop
    c <- elements tagChar
309 dce9bbb3 Iustin Pop
    return (TagChar c)
310 dce9bbb3 Iustin Pop
311 dce9bbb3 Iustin Pop
-- | Generates a tag
312 dce9bbb3 Iustin Pop
genTag :: Gen [TagChar]
313 dce9bbb3 Iustin Pop
genTag = do
314 dce9bbb3 Iustin Pop
  -- the correct value would be C.maxTagLen, but that's way too
315 dce9bbb3 Iustin Pop
  -- verbose in unittests, and at the moment I don't see any possible
316 dce9bbb3 Iustin Pop
  -- bugs with longer tags and the way we use tags in htools
317 dce9bbb3 Iustin Pop
  n <- choose (1, 10)
318 dce9bbb3 Iustin Pop
  vector n
319 dce9bbb3 Iustin Pop
320 dce9bbb3 Iustin Pop
-- | Generates a list of tags (correctly upper bounded).
321 dce9bbb3 Iustin Pop
genTags :: Gen [String]
322 dce9bbb3 Iustin Pop
genTags = do
323 dce9bbb3 Iustin Pop
  -- the correct value would be C.maxTagsPerObj, but per the comment
324 dce9bbb3 Iustin Pop
  -- in genTag, we don't use tags enough in htools to warrant testing
325 dce9bbb3 Iustin Pop
  -- such big values
326 dce9bbb3 Iustin Pop
  n <- choose (0, 10::Int)
327 dce9bbb3 Iustin Pop
  tags <- mapM (const genTag) [1..n]
328 dce9bbb3 Iustin Pop
  return $ map (map tagGetChar) tags
329 dce9bbb3 Iustin Pop
330 7dd14211 Agata Murawska
instance Arbitrary Types.InstanceStatus where
331 e1bf27bb Agata Murawska
    arbitrary = elements [minBound..maxBound]
332 7dd14211 Agata Murawska
333 59ed268d Iustin Pop
-- | Generates a random instance with maximum disk/mem/cpu values.
334 59ed268d Iustin Pop
genInstanceSmallerThan :: Int -> Int -> Int -> Gen Instance.Instance
335 59ed268d Iustin Pop
genInstanceSmallerThan lim_mem lim_dsk lim_cpu = do
336 59ed268d Iustin Pop
  name <- getFQDN
337 59ed268d Iustin Pop
  mem <- choose (0, lim_mem)
338 59ed268d Iustin Pop
  dsk <- choose (0, lim_dsk)
339 59ed268d Iustin Pop
  run_st <- arbitrary
340 59ed268d Iustin Pop
  pn <- arbitrary
341 59ed268d Iustin Pop
  sn <- arbitrary
342 59ed268d Iustin Pop
  vcpus <- choose (0, lim_cpu)
343 64946775 Iustin Pop
  dt <- arbitrary
344 64946775 Iustin Pop
  return $ Instance.create name mem dsk vcpus run_st [] True pn sn dt 1
345 59ed268d Iustin Pop
346 59ed268d Iustin Pop
-- | Generates an instance smaller than a node.
347 59ed268d Iustin Pop
genInstanceSmallerThanNode :: Node.Node -> Gen Instance.Instance
348 59ed268d Iustin Pop
genInstanceSmallerThanNode node =
349 59ed268d Iustin Pop
  genInstanceSmallerThan (Node.availMem node `div` 2)
350 59ed268d Iustin Pop
                         (Node.availDisk node `div` 2)
351 59ed268d Iustin Pop
                         (Node.availCpu node `div` 2)
352 59ed268d Iustin Pop
353 15f4c8ca Iustin Pop
-- let's generate a random instance
354 15f4c8ca Iustin Pop
instance Arbitrary Instance.Instance where
355 59ed268d Iustin Pop
  arbitrary = genInstanceSmallerThan maxMem maxDsk maxCpu
356 15f4c8ca Iustin Pop
357 525bfb36 Iustin Pop
-- | Generas an arbitrary node based on sizing information.
358 525bfb36 Iustin Pop
genNode :: Maybe Int -- ^ Minimum node size in terms of units
359 525bfb36 Iustin Pop
        -> Maybe Int -- ^ Maximum node size (when Nothing, bounded
360 525bfb36 Iustin Pop
                     -- just by the max... constants)
361 525bfb36 Iustin Pop
        -> Gen Node.Node
362 00c75986 Iustin Pop
genNode min_multiplier max_multiplier = do
363 00c75986 Iustin Pop
  let (base_mem, base_dsk, base_cpu) =
364 d5dfae0a Iustin Pop
        case min_multiplier of
365 d5dfae0a Iustin Pop
          Just mm -> (mm * Types.unitMem,
366 d5dfae0a Iustin Pop
                      mm * Types.unitDsk,
367 d5dfae0a Iustin Pop
                      mm * Types.unitCpu)
368 d5dfae0a Iustin Pop
          Nothing -> (0, 0, 0)
369 00c75986 Iustin Pop
      (top_mem, top_dsk, top_cpu)  =
370 d5dfae0a Iustin Pop
        case max_multiplier of
371 d5dfae0a Iustin Pop
          Just mm -> (mm * Types.unitMem,
372 d5dfae0a Iustin Pop
                      mm * Types.unitDsk,
373 d5dfae0a Iustin Pop
                      mm * Types.unitCpu)
374 d5dfae0a Iustin Pop
          Nothing -> (maxMem, maxDsk, maxCpu)
375 00c75986 Iustin Pop
  name  <- getFQDN
376 00c75986 Iustin Pop
  mem_t <- choose (base_mem, top_mem)
377 00c75986 Iustin Pop
  mem_f <- choose (base_mem, mem_t)
378 00c75986 Iustin Pop
  mem_n <- choose (0, mem_t - mem_f)
379 00c75986 Iustin Pop
  dsk_t <- choose (base_dsk, top_dsk)
380 00c75986 Iustin Pop
  dsk_f <- choose (base_dsk, dsk_t)
381 00c75986 Iustin Pop
  cpu_t <- choose (base_cpu, top_cpu)
382 00c75986 Iustin Pop
  offl  <- arbitrary
383 00c75986 Iustin Pop
  let n = Node.create name (fromIntegral mem_t) mem_n mem_f
384 8bc34c7b Iustin Pop
          (fromIntegral dsk_t) dsk_f (fromIntegral cpu_t) offl 1 0
385 d6eec019 Iustin Pop
      n' = Node.setPolicy nullIPolicy n
386 d6eec019 Iustin Pop
  return $ Node.buildPeers n' Container.empty
387 00c75986 Iustin Pop
388 d6f9f5bd Iustin Pop
-- | Helper function to generate a sane node.
389 d6f9f5bd Iustin Pop
genOnlineNode :: Gen Node.Node
390 d6f9f5bd Iustin Pop
genOnlineNode = do
391 d6f9f5bd Iustin Pop
  arbitrary `suchThat` (\n -> not (Node.offline n) &&
392 d6f9f5bd Iustin Pop
                              not (Node.failN1 n) &&
393 d6f9f5bd Iustin Pop
                              Node.availDisk n > 0 &&
394 d6f9f5bd Iustin Pop
                              Node.availMem n > 0 &&
395 d6f9f5bd Iustin Pop
                              Node.availCpu n > 0)
396 d6f9f5bd Iustin Pop
397 15f4c8ca Iustin Pop
-- and a random node
398 15f4c8ca Iustin Pop
instance Arbitrary Node.Node where
399 d5dfae0a Iustin Pop
  arbitrary = genNode Nothing Nothing
400 15f4c8ca Iustin Pop
401 88f25dd0 Iustin Pop
-- replace disks
402 88f25dd0 Iustin Pop
instance Arbitrary OpCodes.ReplaceDisksMode where
403 e1bf27bb Agata Murawska
  arbitrary = elements [minBound..maxBound]
404 88f25dd0 Iustin Pop
405 88f25dd0 Iustin Pop
instance Arbitrary OpCodes.OpCode where
406 88f25dd0 Iustin Pop
  arbitrary = do
407 88f25dd0 Iustin Pop
    op_id <- elements [ "OP_TEST_DELAY"
408 88f25dd0 Iustin Pop
                      , "OP_INSTANCE_REPLACE_DISKS"
409 88f25dd0 Iustin Pop
                      , "OP_INSTANCE_FAILOVER"
410 88f25dd0 Iustin Pop
                      , "OP_INSTANCE_MIGRATE"
411 88f25dd0 Iustin Pop
                      ]
412 3603605a Iustin Pop
    case op_id of
413 3603605a Iustin Pop
      "OP_TEST_DELAY" ->
414 5cefb2b2 Iustin Pop
        OpCodes.OpTestDelay <$> arbitrary <*> arbitrary
415 5cefb2b2 Iustin Pop
                 <*> resize maxNodes (listOf getFQDN)
416 3603605a Iustin Pop
      "OP_INSTANCE_REPLACE_DISKS" ->
417 5cefb2b2 Iustin Pop
        OpCodes.OpInstanceReplaceDisks <$> getFQDN <*> getMaybe getFQDN <*>
418 5cefb2b2 Iustin Pop
          arbitrary <*> resize C.maxDisks arbitrary <*> getMaybe getName
419 3603605a Iustin Pop
      "OP_INSTANCE_FAILOVER" ->
420 5cefb2b2 Iustin Pop
        OpCodes.OpInstanceFailover <$> getFQDN <*> arbitrary <*>
421 5cefb2b2 Iustin Pop
          getMaybe getFQDN
422 3603605a Iustin Pop
      "OP_INSTANCE_MIGRATE" ->
423 5cefb2b2 Iustin Pop
        OpCodes.OpInstanceMigrate <$> getFQDN <*> arbitrary <*>
424 5cefb2b2 Iustin Pop
          arbitrary <*> arbitrary <*> getMaybe getFQDN
425 3603605a Iustin Pop
      _ -> fail "Wrong opcode"
426 88f25dd0 Iustin Pop
427 db079755 Iustin Pop
instance Arbitrary Jobs.OpStatus where
428 db079755 Iustin Pop
  arbitrary = elements [minBound..maxBound]
429 db079755 Iustin Pop
430 db079755 Iustin Pop
instance Arbitrary Jobs.JobStatus where
431 db079755 Iustin Pop
  arbitrary = elements [minBound..maxBound]
432 db079755 Iustin Pop
433 525bfb36 Iustin Pop
newtype SmallRatio = SmallRatio Double deriving Show
434 525bfb36 Iustin Pop
instance Arbitrary SmallRatio where
435 d5dfae0a Iustin Pop
  arbitrary = do
436 d5dfae0a Iustin Pop
    v <- choose (0, 1)
437 d5dfae0a Iustin Pop
    return $ SmallRatio v
438 525bfb36 Iustin Pop
439 3c002a13 Iustin Pop
instance Arbitrary Types.AllocPolicy where
440 3c002a13 Iustin Pop
  arbitrary = elements [minBound..maxBound]
441 3c002a13 Iustin Pop
442 3c002a13 Iustin Pop
instance Arbitrary Types.DiskTemplate where
443 3c002a13 Iustin Pop
  arbitrary = elements [minBound..maxBound]
444 3c002a13 Iustin Pop
445 0047d4e2 Iustin Pop
instance Arbitrary Types.FailMode where
446 d5dfae0a Iustin Pop
  arbitrary = elements [minBound..maxBound]
447 0047d4e2 Iustin Pop
448 aa1d552d Iustin Pop
instance Arbitrary Types.EvacMode where
449 aa1d552d Iustin Pop
  arbitrary = elements [minBound..maxBound]
450 aa1d552d Iustin Pop
451 0047d4e2 Iustin Pop
instance Arbitrary a => Arbitrary (Types.OpResult a) where
452 d5dfae0a Iustin Pop
  arbitrary = arbitrary >>= \c ->
453 3603605a Iustin Pop
              if c
454 5cefb2b2 Iustin Pop
                then Types.OpGood <$> arbitrary
455 5cefb2b2 Iustin Pop
                else Types.OpFail <$> arbitrary
456 0047d4e2 Iustin Pop
457 00b70680 Iustin Pop
instance Arbitrary Types.ISpec where
458 00b70680 Iustin Pop
  arbitrary = do
459 7806125e Iustin Pop
    mem_s <- arbitrary::Gen (NonNegative Int)
460 00b70680 Iustin Pop
    dsk_c <- arbitrary::Gen (NonNegative Int)
461 00b70680 Iustin Pop
    dsk_s <- arbitrary::Gen (NonNegative Int)
462 7806125e Iustin Pop
    cpu_c <- arbitrary::Gen (NonNegative Int)
463 7806125e Iustin Pop
    nic_c <- arbitrary::Gen (NonNegative Int)
464 d953a965 Renรฉ Nussbaumer
    su    <- arbitrary::Gen (NonNegative Int)
465 7806125e Iustin Pop
    return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
466 7806125e Iustin Pop
                       , Types.iSpecCpuCount   = fromIntegral cpu_c
467 00b70680 Iustin Pop
                       , Types.iSpecDiskSize   = fromIntegral dsk_s
468 00b70680 Iustin Pop
                       , Types.iSpecDiskCount  = fromIntegral dsk_c
469 7806125e Iustin Pop
                       , Types.iSpecNicCount   = fromIntegral nic_c
470 d953a965 Renรฉ Nussbaumer
                       , Types.iSpecSpindleUse = fromIntegral su
471 00b70680 Iustin Pop
                       }
472 00b70680 Iustin Pop
473 7806125e Iustin Pop
-- | Generates an ispec bigger than the given one.
474 7806125e Iustin Pop
genBiggerISpec :: Types.ISpec -> Gen Types.ISpec
475 7806125e Iustin Pop
genBiggerISpec imin = do
476 7806125e Iustin Pop
  mem_s <- choose (Types.iSpecMemorySize imin, maxBound)
477 7806125e Iustin Pop
  dsk_c <- choose (Types.iSpecDiskCount imin, maxBound)
478 7806125e Iustin Pop
  dsk_s <- choose (Types.iSpecDiskSize imin, maxBound)
479 7806125e Iustin Pop
  cpu_c <- choose (Types.iSpecCpuCount imin, maxBound)
480 7806125e Iustin Pop
  nic_c <- choose (Types.iSpecNicCount imin, maxBound)
481 d953a965 Renรฉ Nussbaumer
  su    <- choose (Types.iSpecSpindleUse imin, maxBound)
482 7806125e Iustin Pop
  return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
483 7806125e Iustin Pop
                     , Types.iSpecCpuCount   = fromIntegral cpu_c
484 7806125e Iustin Pop
                     , Types.iSpecDiskSize   = fromIntegral dsk_s
485 7806125e Iustin Pop
                     , Types.iSpecDiskCount  = fromIntegral dsk_c
486 7806125e Iustin Pop
                     , Types.iSpecNicCount   = fromIntegral nic_c
487 d953a965 Renรฉ Nussbaumer
                     , Types.iSpecSpindleUse = fromIntegral su
488 7806125e Iustin Pop
                     }
489 00b70680 Iustin Pop
490 00b70680 Iustin Pop
instance Arbitrary Types.IPolicy where
491 00b70680 Iustin Pop
  arbitrary = do
492 00b70680 Iustin Pop
    imin <- arbitrary
493 7806125e Iustin Pop
    istd <- genBiggerISpec imin
494 7806125e Iustin Pop
    imax <- genBiggerISpec istd
495 7806125e Iustin Pop
    num_tmpl <- choose (0, length allDiskTemplates)
496 7806125e Iustin Pop
    dts  <- genUniquesList num_tmpl
497 c22d4dd4 Iustin Pop
    vcpu_ratio <- choose (1.0, maxVcpuRatio)
498 c22d4dd4 Iustin Pop
    spindle_ratio <- choose (1.0, maxSpindleRatio)
499 00b70680 Iustin Pop
    return Types.IPolicy { Types.iPolicyMinSpec = imin
500 00b70680 Iustin Pop
                         , Types.iPolicyStdSpec = istd
501 00b70680 Iustin Pop
                         , Types.iPolicyMaxSpec = imax
502 00b70680 Iustin Pop
                         , Types.iPolicyDiskTemplates = dts
503 e8fa4ff6 Iustin Pop
                         , Types.iPolicyVcpuRatio = vcpu_ratio
504 c22d4dd4 Iustin Pop
                         , Types.iPolicySpindleRatio = spindle_ratio
505 00b70680 Iustin Pop
                         }
506 00b70680 Iustin Pop
507 3fea6959 Iustin Pop
-- * Actual tests
508 8fcf251f Iustin Pop
509 525bfb36 Iustin Pop
-- ** Utils tests
510 525bfb36 Iustin Pop
511 468b828e Iustin Pop
-- | Helper to generate a small string that doesn't contain commas.
512 468b828e Iustin Pop
genNonCommaString = do
513 468b828e Iustin Pop
  size <- choose (0, 20) -- arbitrary max size
514 468b828e Iustin Pop
  vectorOf size (arbitrary `suchThat` ((/=) ','))
515 468b828e Iustin Pop
516 525bfb36 Iustin Pop
-- | If the list is not just an empty element, and if the elements do
517 525bfb36 Iustin Pop
-- not contain commas, then join+split should be idempotent.
518 a1cd7c1e Iustin Pop
prop_Utils_commaJoinSplit =
519 468b828e Iustin Pop
  forAll (choose (0, 20)) $ \llen ->
520 468b828e Iustin Pop
  forAll (vectorOf llen genNonCommaString `suchThat` ((/=) [""])) $ \lst ->
521 d5dfae0a Iustin Pop
  Utils.sepSplit ',' (Utils.commaJoin lst) ==? lst
522 a1cd7c1e Iustin Pop
523 525bfb36 Iustin Pop
-- | Split and join should always be idempotent.
524 72bb6b4e Iustin Pop
prop_Utils_commaSplitJoin s =
525 d5dfae0a Iustin Pop
  Utils.commaJoin (Utils.sepSplit ',' s) ==? s
526 691dcd2a Iustin Pop
527 a810ad21 Iustin Pop
-- | fromObjWithDefault, we test using the Maybe monad and an integer
528 525bfb36 Iustin Pop
-- value.
529 a810ad21 Iustin Pop
prop_Utils_fromObjWithDefault def_value random_key =
530 d5dfae0a Iustin Pop
  -- a missing key will be returned with the default
531 b69be409 Iustin Pop
  JSON.fromObjWithDefault [] random_key def_value == Just def_value &&
532 d5dfae0a Iustin Pop
  -- a found key will be returned as is, not with default
533 b69be409 Iustin Pop
  JSON.fromObjWithDefault [(random_key, J.showJSON def_value)]
534 d5dfae0a Iustin Pop
       random_key (def_value+1) == Just def_value
535 d5dfae0a Iustin Pop
    where _types = def_value :: Integer
536 a810ad21 Iustin Pop
537 bfe6c954 Guido Trotter
-- | Test that functional if' behaves like the syntactic sugar if.
538 72bb6b4e Iustin Pop
prop_Utils_if'if :: Bool -> Int -> Int -> Gen Prop
539 72bb6b4e Iustin Pop
prop_Utils_if'if cnd a b =
540 d5dfae0a Iustin Pop
  Utils.if' cnd a b ==? if cnd then a else b
541 bfe6c954 Guido Trotter
542 22fac87d Guido Trotter
-- | Test basic select functionality
543 72bb6b4e Iustin Pop
prop_Utils_select :: Int      -- ^ Default result
544 72bb6b4e Iustin Pop
                  -> [Int]    -- ^ List of False values
545 72bb6b4e Iustin Pop
                  -> [Int]    -- ^ List of True values
546 72bb6b4e Iustin Pop
                  -> Gen Prop -- ^ Test result
547 22fac87d Guido Trotter
prop_Utils_select def lst1 lst2 =
548 3603605a Iustin Pop
  Utils.select def (flist ++ tlist) ==? expectedresult
549 ba1260ba Iustin Pop
    where expectedresult = Utils.if' (null lst2) def (head lst2)
550 ba1260ba Iustin Pop
          flist = zip (repeat False) lst1
551 ba1260ba Iustin Pop
          tlist = zip (repeat True)  lst2
552 22fac87d Guido Trotter
553 22fac87d Guido Trotter
-- | Test basic select functionality with undefined default
554 72bb6b4e Iustin Pop
prop_Utils_select_undefd :: [Int]            -- ^ List of False values
555 22fac87d Guido Trotter
                         -> NonEmptyList Int -- ^ List of True values
556 72bb6b4e Iustin Pop
                         -> Gen Prop         -- ^ Test result
557 22fac87d Guido Trotter
prop_Utils_select_undefd lst1 (NonEmpty lst2) =
558 3603605a Iustin Pop
  Utils.select undefined (flist ++ tlist) ==? head lst2
559 ba1260ba Iustin Pop
    where flist = zip (repeat False) lst1
560 ba1260ba Iustin Pop
          tlist = zip (repeat True)  lst2
561 22fac87d Guido Trotter
562 22fac87d Guido Trotter
-- | Test basic select functionality with undefined list values
563 72bb6b4e Iustin Pop
prop_Utils_select_undefv :: [Int]            -- ^ List of False values
564 22fac87d Guido Trotter
                         -> NonEmptyList Int -- ^ List of True values
565 72bb6b4e Iustin Pop
                         -> Gen Prop         -- ^ Test result
566 22fac87d Guido Trotter
prop_Utils_select_undefv lst1 (NonEmpty lst2) =
567 72bb6b4e Iustin Pop
  Utils.select undefined cndlist ==? head lst2
568 ba1260ba Iustin Pop
    where flist = zip (repeat False) lst1
569 ba1260ba Iustin Pop
          tlist = zip (repeat True)  lst2
570 ba1260ba Iustin Pop
          cndlist = flist ++ tlist ++ [undefined]
571 bfe6c954 Guido Trotter
572 1cb92fac Iustin Pop
prop_Utils_parseUnit (NonNegative n) =
573 1cdcf8f3 Iustin Pop
  Utils.parseUnit (show n) ==? Types.Ok n .&&.
574 1cdcf8f3 Iustin Pop
  Utils.parseUnit (show n ++ "m") ==? Types.Ok n .&&.
575 1cdcf8f3 Iustin Pop
  Utils.parseUnit (show n ++ "M") ==? Types.Ok (truncate n_mb::Int) .&&.
576 1cdcf8f3 Iustin Pop
  Utils.parseUnit (show n ++ "g") ==? Types.Ok (n*1024) .&&.
577 1cdcf8f3 Iustin Pop
  Utils.parseUnit (show n ++ "G") ==? Types.Ok (truncate n_gb::Int) .&&.
578 1cdcf8f3 Iustin Pop
  Utils.parseUnit (show n ++ "t") ==? Types.Ok (n*1048576) .&&.
579 1cdcf8f3 Iustin Pop
  Utils.parseUnit (show n ++ "T") ==? Types.Ok (truncate n_tb::Int) .&&.
580 1cdcf8f3 Iustin Pop
  printTestCase "Internal error/overflow?"
581 1cdcf8f3 Iustin Pop
    (n_mb >=0 && n_gb >= 0 && n_tb >= 0) .&&.
582 1cdcf8f3 Iustin Pop
  property (Types.isBad (Utils.parseUnit (show n ++ "x")::Types.Result Int))
583 1cdcf8f3 Iustin Pop
  where _types = (n::Int)
584 1cdcf8f3 Iustin Pop
        n_mb = (fromIntegral n::Rational) * 1000 * 1000 / 1024 / 1024
585 1cdcf8f3 Iustin Pop
        n_gb = n_mb * 1000
586 1cdcf8f3 Iustin Pop
        n_tb = n_gb * 1000
587 1cb92fac Iustin Pop
588 525bfb36 Iustin Pop
-- | Test list for the Utils module.
589 23fe06c2 Iustin Pop
testSuite "Utils"
590 d5dfae0a Iustin Pop
            [ 'prop_Utils_commaJoinSplit
591 d5dfae0a Iustin Pop
            , 'prop_Utils_commaSplitJoin
592 d5dfae0a Iustin Pop
            , 'prop_Utils_fromObjWithDefault
593 d5dfae0a Iustin Pop
            , 'prop_Utils_if'if
594 d5dfae0a Iustin Pop
            , 'prop_Utils_select
595 d5dfae0a Iustin Pop
            , 'prop_Utils_select_undefd
596 d5dfae0a Iustin Pop
            , 'prop_Utils_select_undefv
597 d5dfae0a Iustin Pop
            , 'prop_Utils_parseUnit
598 d5dfae0a Iustin Pop
            ]
599 691dcd2a Iustin Pop
600 525bfb36 Iustin Pop
-- ** PeerMap tests
601 525bfb36 Iustin Pop
602 525bfb36 Iustin Pop
-- | Make sure add is idempotent.
603 fbb95f28 Iustin Pop
prop_PeerMap_addIdempotent pmap key em =
604 d5dfae0a Iustin Pop
  fn puniq ==? fn (fn puniq)
605 7bc82927 Iustin Pop
    where _types = (pmap::PeerMap.PeerMap,
606 fbb95f28 Iustin Pop
                    key::PeerMap.Key, em::PeerMap.Elem)
607 fbb95f28 Iustin Pop
          fn = PeerMap.add key em
608 7bc82927 Iustin Pop
          puniq = PeerMap.accumArray const pmap
609 15f4c8ca Iustin Pop
610 525bfb36 Iustin Pop
-- | Make sure remove is idempotent.
611 15f4c8ca Iustin Pop
prop_PeerMap_removeIdempotent pmap key =
612 d5dfae0a Iustin Pop
  fn puniq ==? fn (fn puniq)
613 7bc82927 Iustin Pop
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
614 7bc82927 Iustin Pop
          fn = PeerMap.remove key
615 15f4c8ca Iustin Pop
          puniq = PeerMap.accumArray const pmap
616 15f4c8ca Iustin Pop
617 525bfb36 Iustin Pop
-- | Make sure a missing item returns 0.
618 15f4c8ca Iustin Pop
prop_PeerMap_findMissing pmap key =
619 d5dfae0a Iustin Pop
  PeerMap.find key (PeerMap.remove key puniq) ==? 0
620 7bc82927 Iustin Pop
    where _types = (pmap::PeerMap.PeerMap, key::PeerMap.Key)
621 15f4c8ca Iustin Pop
          puniq = PeerMap.accumArray const pmap
622 15f4c8ca Iustin Pop
623 525bfb36 Iustin Pop
-- | Make sure an added item is found.
624 fbb95f28 Iustin Pop
prop_PeerMap_addFind pmap key em =
625 d5dfae0a Iustin Pop
  PeerMap.find key (PeerMap.add key em puniq) ==? em
626 7bc82927 Iustin Pop
    where _types = (pmap::PeerMap.PeerMap,
627 fbb95f28 Iustin Pop
                    key::PeerMap.Key, em::PeerMap.Elem)
628 7bc82927 Iustin Pop
          puniq = PeerMap.accumArray const pmap
629 15f4c8ca Iustin Pop
630 525bfb36 Iustin Pop
-- | Manual check that maxElem returns the maximum indeed, or 0 for null.
631 15f4c8ca Iustin Pop
prop_PeerMap_maxElem pmap =
632 d5dfae0a Iustin Pop
  PeerMap.maxElem puniq ==? if null puniq then 0
633 72bb6b4e Iustin Pop
                              else (maximum . snd . unzip) puniq
634 7bc82927 Iustin Pop
    where _types = pmap::PeerMap.PeerMap
635 15f4c8ca Iustin Pop
          puniq = PeerMap.accumArray const pmap
636 15f4c8ca Iustin Pop
637 525bfb36 Iustin Pop
-- | List of tests for the PeerMap module.
638 23fe06c2 Iustin Pop
testSuite "PeerMap"
639 d5dfae0a Iustin Pop
            [ 'prop_PeerMap_addIdempotent
640 d5dfae0a Iustin Pop
            , 'prop_PeerMap_removeIdempotent
641 d5dfae0a Iustin Pop
            , 'prop_PeerMap_maxElem
642 d5dfae0a Iustin Pop
            , 'prop_PeerMap_addFind
643 d5dfae0a Iustin Pop
            , 'prop_PeerMap_findMissing
644 d5dfae0a Iustin Pop
            ]
645 7dd5ee6c Iustin Pop
646 525bfb36 Iustin Pop
-- ** Container tests
647 095d7ac0 Iustin Pop
648 3603605a Iustin Pop
-- we silence the following due to hlint bug fixed in later versions
649 3603605a Iustin Pop
{-# ANN prop_Container_addTwo "HLint: ignore Avoid lambda" #-}
650 095d7ac0 Iustin Pop
prop_Container_addTwo cdata i1 i2 =
651 d5dfae0a Iustin Pop
  fn i1 i2 cont == fn i2 i1 cont &&
652 d5dfae0a Iustin Pop
  fn i1 i2 cont == fn i1 i2 (fn i1 i2 cont)
653 095d7ac0 Iustin Pop
    where _types = (cdata::[Int],
654 095d7ac0 Iustin Pop
                    i1::Int, i2::Int)
655 095d7ac0 Iustin Pop
          cont = foldl (\c x -> Container.add x x c) Container.empty cdata
656 095d7ac0 Iustin Pop
          fn x1 x2 = Container.addTwo x1 x1 x2 x2
657 095d7ac0 Iustin Pop
658 5ef78537 Iustin Pop
prop_Container_nameOf node =
659 5ef78537 Iustin Pop
  let nl = makeSmallCluster node 1
660 5ef78537 Iustin Pop
      fnode = head (Container.elems nl)
661 72bb6b4e Iustin Pop
  in Container.nameOf nl (Node.idx fnode) ==? Node.name fnode
662 5ef78537 Iustin Pop
663 525bfb36 Iustin Pop
-- | We test that in a cluster, given a random node, we can find it by
664 5ef78537 Iustin Pop
-- its name and alias, as long as all names and aliases are unique,
665 525bfb36 Iustin Pop
-- and that we fail to find a non-existing name.
666 a2a0bcd8 Iustin Pop
prop_Container_findByName node =
667 5ef78537 Iustin Pop
  forAll (choose (1, 20)) $ \ cnt ->
668 5ef78537 Iustin Pop
  forAll (choose (0, cnt - 1)) $ \ fidx ->
669 a2a0bcd8 Iustin Pop
  forAll (genUniquesList (cnt * 2)) $ \ allnames ->
670 a2a0bcd8 Iustin Pop
  forAll (arbitrary `suchThat` (`notElem` allnames)) $ \ othername ->
671 a2a0bcd8 Iustin Pop
  let names = zip (take cnt allnames) (drop cnt allnames)
672 a2a0bcd8 Iustin Pop
      nl = makeSmallCluster node cnt
673 5ef78537 Iustin Pop
      nodes = Container.elems nl
674 5ef78537 Iustin Pop
      nodes' = map (\((name, alias), nn) -> (Node.idx nn,
675 5ef78537 Iustin Pop
                                             nn { Node.name = name,
676 5ef78537 Iustin Pop
                                                  Node.alias = alias }))
677 5ef78537 Iustin Pop
               $ zip names nodes
678 cb0c77ff Iustin Pop
      nl' = Container.fromList nodes'
679 5ef78537 Iustin Pop
      target = snd (nodes' !! fidx)
680 5ef78537 Iustin Pop
  in Container.findByName nl' (Node.name target) == Just target &&
681 5ef78537 Iustin Pop
     Container.findByName nl' (Node.alias target) == Just target &&
682 3603605a Iustin Pop
     isNothing (Container.findByName nl' othername)
683 5ef78537 Iustin Pop
684 23fe06c2 Iustin Pop
testSuite "Container"
685 d5dfae0a Iustin Pop
            [ 'prop_Container_addTwo
686 d5dfae0a Iustin Pop
            , 'prop_Container_nameOf
687 d5dfae0a Iustin Pop
            , 'prop_Container_findByName
688 d5dfae0a Iustin Pop
            ]
689 095d7ac0 Iustin Pop
690 525bfb36 Iustin Pop
-- ** Instance tests
691 525bfb36 Iustin Pop
692 7bc82927 Iustin Pop
-- Simple instance tests, we only have setter/getters
693 7bc82927 Iustin Pop
694 39d11971 Iustin Pop
prop_Instance_creat inst =
695 d5dfae0a Iustin Pop
  Instance.name inst ==? Instance.alias inst
696 39d11971 Iustin Pop
697 7bc82927 Iustin Pop
prop_Instance_setIdx inst idx =
698 d5dfae0a Iustin Pop
  Instance.idx (Instance.setIdx inst idx) ==? idx
699 7bc82927 Iustin Pop
    where _types = (inst::Instance.Instance, idx::Types.Idx)
700 7bc82927 Iustin Pop
701 7bc82927 Iustin Pop
prop_Instance_setName inst name =
702 d5dfae0a Iustin Pop
  Instance.name newinst == name &&
703 d5dfae0a Iustin Pop
  Instance.alias newinst == name
704 39d11971 Iustin Pop
    where _types = (inst::Instance.Instance, name::String)
705 39d11971 Iustin Pop
          newinst = Instance.setName inst name
706 39d11971 Iustin Pop
707 39d11971 Iustin Pop
prop_Instance_setAlias inst name =
708 d5dfae0a Iustin Pop
  Instance.name newinst == Instance.name inst &&
709 d5dfae0a Iustin Pop
  Instance.alias newinst == name
710 7bc82927 Iustin Pop
    where _types = (inst::Instance.Instance, name::String)
711 39d11971 Iustin Pop
          newinst = Instance.setAlias inst name
712 7bc82927 Iustin Pop
713 7bc82927 Iustin Pop
prop_Instance_setPri inst pdx =
714 d5dfae0a Iustin Pop
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
715 7bc82927 Iustin Pop
    where _types = (inst::Instance.Instance, pdx::Types.Ndx)
716 7bc82927 Iustin Pop
717 7bc82927 Iustin Pop
prop_Instance_setSec inst sdx =
718 d5dfae0a Iustin Pop
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
719 7bc82927 Iustin Pop
    where _types = (inst::Instance.Instance, sdx::Types.Ndx)
720 7bc82927 Iustin Pop
721 7bc82927 Iustin Pop
prop_Instance_setBoth inst pdx sdx =
722 d5dfae0a Iustin Pop
  Instance.pNode si == pdx && Instance.sNode si == sdx
723 7bc82927 Iustin Pop
    where _types = (inst::Instance.Instance, pdx::Types.Ndx, sdx::Types.Ndx)
724 7bc82927 Iustin Pop
          si = Instance.setBoth inst pdx sdx
725 7bc82927 Iustin Pop
726 8fcf251f Iustin Pop
prop_Instance_shrinkMG inst =
727 d5dfae0a Iustin Pop
  Instance.mem inst >= 2 * Types.unitMem ==>
728 d5dfae0a Iustin Pop
    case Instance.shrinkByType inst Types.FailMem of
729 d5dfae0a Iustin Pop
      Types.Ok inst' -> Instance.mem inst' == Instance.mem inst - Types.unitMem
730 d5dfae0a Iustin Pop
      _ -> False
731 8fcf251f Iustin Pop
732 8fcf251f Iustin Pop
prop_Instance_shrinkMF inst =
733 d5dfae0a Iustin Pop
  forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
734 41085bd3 Iustin Pop
    let inst' = inst { Instance.mem = mem}
735 41085bd3 Iustin Pop
    in Types.isBad $ Instance.shrinkByType inst' Types.FailMem
736 8fcf251f Iustin Pop
737 8fcf251f Iustin Pop
prop_Instance_shrinkCG inst =
738 d5dfae0a Iustin Pop
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
739 d5dfae0a Iustin Pop
    case Instance.shrinkByType inst Types.FailCPU of
740 d5dfae0a Iustin Pop
      Types.Ok inst' ->
741 d5dfae0a Iustin Pop
        Instance.vcpus inst' == Instance.vcpus inst - Types.unitCpu
742 d5dfae0a Iustin Pop
      _ -> False
743 8fcf251f Iustin Pop
744 8fcf251f Iustin Pop
prop_Instance_shrinkCF inst =
745 d5dfae0a Iustin Pop
  forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
746 41085bd3 Iustin Pop
    let inst' = inst { Instance.vcpus = vcpus }
747 41085bd3 Iustin Pop
    in Types.isBad $ Instance.shrinkByType inst' Types.FailCPU
748 8fcf251f Iustin Pop
749 8fcf251f Iustin Pop
prop_Instance_shrinkDG inst =
750 d5dfae0a Iustin Pop
  Instance.dsk inst >= 2 * Types.unitDsk ==>
751 d5dfae0a Iustin Pop
    case Instance.shrinkByType inst Types.FailDisk of
752 d5dfae0a Iustin Pop
      Types.Ok inst' ->
753 d5dfae0a Iustin Pop
        Instance.dsk inst' == Instance.dsk inst - Types.unitDsk
754 d5dfae0a Iustin Pop
      _ -> False
755 8fcf251f Iustin Pop
756 8fcf251f Iustin Pop
prop_Instance_shrinkDF inst =
757 d5dfae0a Iustin Pop
  forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
758 41085bd3 Iustin Pop
    let inst' = inst { Instance.dsk = dsk }
759 41085bd3 Iustin Pop
    in Types.isBad $ Instance.shrinkByType inst' Types.FailDisk
760 8fcf251f Iustin Pop
761 8fcf251f Iustin Pop
prop_Instance_setMovable inst m =
762 d5dfae0a Iustin Pop
  Instance.movable inst' ==? m
763 4a007641 Iustin Pop
    where inst' = Instance.setMovable inst m
764 8fcf251f Iustin Pop
765 23fe06c2 Iustin Pop
testSuite "Instance"
766 d5dfae0a Iustin Pop
            [ 'prop_Instance_creat
767 d5dfae0a Iustin Pop
            , 'prop_Instance_setIdx
768 d5dfae0a Iustin Pop
            , 'prop_Instance_setName
769 d5dfae0a Iustin Pop
            , 'prop_Instance_setAlias
770 d5dfae0a Iustin Pop
            , 'prop_Instance_setPri
771 d5dfae0a Iustin Pop
            , 'prop_Instance_setSec
772 d5dfae0a Iustin Pop
            , 'prop_Instance_setBoth
773 d5dfae0a Iustin Pop
            , 'prop_Instance_shrinkMG
774 d5dfae0a Iustin Pop
            , 'prop_Instance_shrinkMF
775 d5dfae0a Iustin Pop
            , 'prop_Instance_shrinkCG
776 d5dfae0a Iustin Pop
            , 'prop_Instance_shrinkCF
777 d5dfae0a Iustin Pop
            , 'prop_Instance_shrinkDG
778 d5dfae0a Iustin Pop
            , 'prop_Instance_shrinkDF
779 d5dfae0a Iustin Pop
            , 'prop_Instance_setMovable
780 d5dfae0a Iustin Pop
            ]
781 1ae7a904 Iustin Pop
782 e1dde6ad Iustin Pop
-- ** Backends
783 e1dde6ad Iustin Pop
784 e1dde6ad Iustin Pop
-- *** Text backend tests
785 525bfb36 Iustin Pop
786 1ae7a904 Iustin Pop
-- Instance text loader tests
787 1ae7a904 Iustin Pop
788 a1cd7c1e Iustin Pop
prop_Text_Load_Instance name mem dsk vcpus status
789 a1cd7c1e Iustin Pop
                        (NonEmpty pnode) snode
790 52cc1370 Renรฉ Nussbaumer
                        (NonNegative pdx) (NonNegative sdx) autobal dt su =
791 d5dfae0a Iustin Pop
  pnode /= snode && pdx /= sdx ==>
792 d5dfae0a Iustin Pop
  let vcpus_s = show vcpus
793 d5dfae0a Iustin Pop
      dsk_s = show dsk
794 d5dfae0a Iustin Pop
      mem_s = show mem
795 52cc1370 Renรฉ Nussbaumer
      su_s = show su
796 d5dfae0a Iustin Pop
      status_s = Types.instanceStatusToRaw status
797 d5dfae0a Iustin Pop
      ndx = if null snode
798 39d11971 Iustin Pop
              then [(pnode, pdx)]
799 309e7c9a Iustin Pop
              else [(pnode, pdx), (snode, sdx)]
800 d5dfae0a Iustin Pop
      nl = Data.Map.fromList ndx
801 d5dfae0a Iustin Pop
      tags = ""
802 d5dfae0a Iustin Pop
      sbal = if autobal then "Y" else "N"
803 d5dfae0a Iustin Pop
      sdt = Types.diskTemplateToRaw dt
804 d5dfae0a Iustin Pop
      inst = Text.loadInst nl
805 d5dfae0a Iustin Pop
             [name, mem_s, dsk_s, vcpus_s, status_s,
806 52cc1370 Renรฉ Nussbaumer
              sbal, pnode, snode, sdt, tags, su_s]
807 d5dfae0a Iustin Pop
      fail1 = Text.loadInst nl
808 d5dfae0a Iustin Pop
              [name, mem_s, dsk_s, vcpus_s, status_s,
809 d5dfae0a Iustin Pop
               sbal, pnode, pnode, tags]
810 d5dfae0a Iustin Pop
      _types = ( name::String, mem::Int, dsk::Int
811 d5dfae0a Iustin Pop
               , vcpus::Int, status::Types.InstanceStatus
812 d5dfae0a Iustin Pop
               , snode::String
813 d5dfae0a Iustin Pop
               , autobal::Bool)
814 d5dfae0a Iustin Pop
  in case inst of
815 96bc2003 Iustin Pop
       Types.Bad msg -> failTest $ "Failed to load instance: " ++ msg
816 d5dfae0a Iustin Pop
       Types.Ok (_, i) -> printTestCase "Mismatch in some field while\
817 d5dfae0a Iustin Pop
                                        \ loading the instance" $
818 d5dfae0a Iustin Pop
               Instance.name i == name &&
819 d5dfae0a Iustin Pop
               Instance.vcpus i == vcpus &&
820 d5dfae0a Iustin Pop
               Instance.mem i == mem &&
821 d5dfae0a Iustin Pop
               Instance.pNode i == pdx &&
822 d5dfae0a Iustin Pop
               Instance.sNode i == (if null snode
823 d5dfae0a Iustin Pop
                                      then Node.noSecondary
824 d5dfae0a Iustin Pop
                                      else sdx) &&
825 d5dfae0a Iustin Pop
               Instance.autoBalance i == autobal &&
826 ec629280 Renรฉ Nussbaumer
               Instance.spindleUse i == su &&
827 d5dfae0a Iustin Pop
               Types.isBad fail1
828 39d11971 Iustin Pop
829 39d11971 Iustin Pop
prop_Text_Load_InstanceFail ktn fields =
830 52cc1370 Renรฉ Nussbaumer
  length fields /= 10 && length fields /= 11 ==>
831 bc782180 Iustin Pop
    case Text.loadInst nl fields of
832 96bc2003 Iustin Pop
      Types.Ok _ -> failTest "Managed to load instance from invalid data"
833 6429e8d8 Iustin Pop
      Types.Bad msg -> printTestCase ("Unrecognised error message: " ++ msg) $
834 6429e8d8 Iustin Pop
                       "Invalid/incomplete instance data: '" `isPrefixOf` msg
835 99b63608 Iustin Pop
    where nl = Data.Map.fromList ktn
836 39d11971 Iustin Pop
837 39d11971 Iustin Pop
prop_Text_Load_Node name tm nm fm td fd tc fo =
838 d5dfae0a Iustin Pop
  let conv v = if v < 0
839 d5dfae0a Iustin Pop
                 then "?"
840 d5dfae0a Iustin Pop
                 else show v
841 d5dfae0a Iustin Pop
      tm_s = conv tm
842 d5dfae0a Iustin Pop
      nm_s = conv nm
843 d5dfae0a Iustin Pop
      fm_s = conv fm
844 d5dfae0a Iustin Pop
      td_s = conv td
845 d5dfae0a Iustin Pop
      fd_s = conv fd
846 d5dfae0a Iustin Pop
      tc_s = conv tc
847 d5dfae0a Iustin Pop
      fo_s = if fo
848 39d11971 Iustin Pop
               then "Y"
849 39d11971 Iustin Pop
               else "N"
850 d5dfae0a Iustin Pop
      any_broken = any (< 0) [tm, nm, fm, td, fd, tc]
851 d5dfae0a Iustin Pop
      gid = Group.uuid defGroup
852 d5dfae0a Iustin Pop
  in case Text.loadNode defGroupAssoc
853 d5dfae0a Iustin Pop
       [name, tm_s, nm_s, fm_s, td_s, fd_s, tc_s, fo_s, gid] of
854 d5dfae0a Iustin Pop
       Nothing -> False
855 d5dfae0a Iustin Pop
       Just (name', node) ->
856 d5dfae0a Iustin Pop
         if fo || any_broken
857 d5dfae0a Iustin Pop
           then Node.offline node
858 d5dfae0a Iustin Pop
           else Node.name node == name' && name' == name &&
859 d5dfae0a Iustin Pop
                Node.alias node == name &&
860 d5dfae0a Iustin Pop
                Node.tMem node == fromIntegral tm &&
861 d5dfae0a Iustin Pop
                Node.nMem node == nm &&
862 d5dfae0a Iustin Pop
                Node.fMem node == fm &&
863 d5dfae0a Iustin Pop
                Node.tDsk node == fromIntegral td &&
864 d5dfae0a Iustin Pop
                Node.fDsk node == fd &&
865 d5dfae0a Iustin Pop
                Node.tCpu node == fromIntegral tc
866 39d11971 Iustin Pop
867 39d11971 Iustin Pop
prop_Text_Load_NodeFail fields =
868 d5dfae0a Iustin Pop
  length fields /= 8 ==> isNothing $ Text.loadNode Data.Map.empty fields
869 1ae7a904 Iustin Pop
870 50811e2c Iustin Pop
prop_Text_NodeLSIdempotent node =
871 d5dfae0a Iustin Pop
  (Text.loadNode defGroupAssoc.
872 487e1962 Iustin Pop
       Utils.sepSplit '|' . Text.serializeNode defGroupList) n ==?
873 d5dfae0a Iustin Pop
  Just (Node.name n, n)
874 50811e2c Iustin Pop
    -- override failN1 to what loadNode returns by default
875 487e1962 Iustin Pop
    where n = Node.setPolicy Types.defIPolicy $
876 487e1962 Iustin Pop
              node { Node.failN1 = True, Node.offline = False }
877 50811e2c Iustin Pop
878 bcd17bf0 Iustin Pop
prop_Text_ISpecIdempotent ispec =
879 bcd17bf0 Iustin Pop
  case Text.loadISpec "dummy" . Utils.sepSplit ',' .
880 bcd17bf0 Iustin Pop
       Text.serializeISpec $ ispec of
881 96bc2003 Iustin Pop
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
882 bcd17bf0 Iustin Pop
    Types.Ok ispec' -> ispec ==? ispec'
883 bcd17bf0 Iustin Pop
884 bcd17bf0 Iustin Pop
prop_Text_IPolicyIdempotent ipol =
885 bcd17bf0 Iustin Pop
  case Text.loadIPolicy . Utils.sepSplit '|' $
886 bcd17bf0 Iustin Pop
       Text.serializeIPolicy owner ipol of
887 96bc2003 Iustin Pop
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
888 bcd17bf0 Iustin Pop
    Types.Ok res -> (owner, ipol) ==? res
889 bcd17bf0 Iustin Pop
  where owner = "dummy"
890 bcd17bf0 Iustin Pop
891 dce9bbb3 Iustin Pop
-- | This property, while being in the text tests, does more than just
892 dce9bbb3 Iustin Pop
-- test end-to-end the serialisation and loading back workflow; it
893 dce9bbb3 Iustin Pop
-- also tests the Loader.mergeData and the actuall
894 dce9bbb3 Iustin Pop
-- Cluster.iterateAlloc (for well-behaving w.r.t. instance
895 dce9bbb3 Iustin Pop
-- allocations, not for the business logic). As such, it's a quite
896 dce9bbb3 Iustin Pop
-- complex and slow test, and that's the reason we restrict it to
897 dce9bbb3 Iustin Pop
-- small cluster sizes.
898 dce9bbb3 Iustin Pop
prop_Text_CreateSerialise =
899 dce9bbb3 Iustin Pop
  forAll genTags $ \ctags ->
900 dce9bbb3 Iustin Pop
  forAll (choose (1, 20)) $ \maxiter ->
901 dce9bbb3 Iustin Pop
  forAll (choose (2, 10)) $ \count ->
902 dce9bbb3 Iustin Pop
  forAll genOnlineNode $ \node ->
903 59ed268d Iustin Pop
  forAll (genInstanceSmallerThanNode node) $ \inst ->
904 a7667ba6 Iustin Pop
  let nl = makeSmallCluster node count
905 c6e8fb9c Iustin Pop
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
906 dce9bbb3 Iustin Pop
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>= \allocn ->
907 a7667ba6 Iustin Pop
     Cluster.iterateAlloc nl Container.empty (Just maxiter) inst allocn [] []
908 dce9bbb3 Iustin Pop
     of
909 96bc2003 Iustin Pop
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
910 dce9bbb3 Iustin Pop
       Types.Ok (_, _, _, [], _) -> printTestCase
911 dce9bbb3 Iustin Pop
                                    "Failed to allocate: no allocations" False
912 dce9bbb3 Iustin Pop
       Types.Ok (_, nl', il', _, _) ->
913 dce9bbb3 Iustin Pop
         let cdata = Loader.ClusterData defGroupList nl' il' ctags
914 dce9bbb3 Iustin Pop
                     Types.defIPolicy
915 dce9bbb3 Iustin Pop
             saved = Text.serializeCluster cdata
916 dce9bbb3 Iustin Pop
         in case Text.parseData saved >>= Loader.mergeData [] [] [] [] of
917 96bc2003 Iustin Pop
              Types.Bad msg -> failTest $ "Failed to load/merge: " ++ msg
918 dce9bbb3 Iustin Pop
              Types.Ok (Loader.ClusterData gl2 nl2 il2 ctags2 cpol2) ->
919 dce9bbb3 Iustin Pop
                ctags ==? ctags2 .&&.
920 dce9bbb3 Iustin Pop
                Types.defIPolicy ==? cpol2 .&&.
921 dce9bbb3 Iustin Pop
                il' ==? il2 .&&.
922 b37f4a76 Iustin Pop
                defGroupList ==? gl2 .&&.
923 b37f4a76 Iustin Pop
                nl' ==? nl2
924 dce9bbb3 Iustin Pop
925 23fe06c2 Iustin Pop
testSuite "Text"
926 d5dfae0a Iustin Pop
            [ 'prop_Text_Load_Instance
927 d5dfae0a Iustin Pop
            , 'prop_Text_Load_InstanceFail
928 d5dfae0a Iustin Pop
            , 'prop_Text_Load_Node
929 d5dfae0a Iustin Pop
            , 'prop_Text_Load_NodeFail
930 d5dfae0a Iustin Pop
            , 'prop_Text_NodeLSIdempotent
931 bcd17bf0 Iustin Pop
            , 'prop_Text_ISpecIdempotent
932 bcd17bf0 Iustin Pop
            , 'prop_Text_IPolicyIdempotent
933 dce9bbb3 Iustin Pop
            , 'prop_Text_CreateSerialise
934 d5dfae0a Iustin Pop
            ]
935 7dd5ee6c Iustin Pop
936 e1dde6ad Iustin Pop
-- *** Simu backend
937 e1dde6ad Iustin Pop
938 e1dde6ad Iustin Pop
-- | Generates a tuple of specs for simulation.
939 e1dde6ad Iustin Pop
genSimuSpec :: Gen (String, Int, Int, Int, Int)
940 e1dde6ad Iustin Pop
genSimuSpec = do
941 e1dde6ad Iustin Pop
  pol <- elements [C.allocPolicyPreferred,
942 e1dde6ad Iustin Pop
                   C.allocPolicyLastResort, C.allocPolicyUnallocable,
943 e1dde6ad Iustin Pop
                  "p", "a", "u"]
944 e1dde6ad Iustin Pop
 -- should be reasonable (nodes/group), bigger values only complicate
945 e1dde6ad Iustin Pop
 -- the display of failed tests, and we don't care (in this particular
946 e1dde6ad Iustin Pop
 -- test) about big node groups
947 e1dde6ad Iustin Pop
  nodes <- choose (0, 20)
948 e1dde6ad Iustin Pop
  dsk <- choose (0, maxDsk)
949 e1dde6ad Iustin Pop
  mem <- choose (0, maxMem)
950 e1dde6ad Iustin Pop
  cpu <- choose (0, maxCpu)
951 e1dde6ad Iustin Pop
  return (pol, nodes, dsk, mem, cpu)
952 e1dde6ad Iustin Pop
953 e1dde6ad Iustin Pop
-- | Checks that given a set of corrects specs, we can load them
954 e1dde6ad Iustin Pop
-- successfully, and that at high-level the values look right.
955 e1dde6ad Iustin Pop
prop_SimuLoad =
956 e1dde6ad Iustin Pop
  forAll (choose (0, 10)) $ \ngroups ->
957 e1dde6ad Iustin Pop
  forAll (replicateM ngroups genSimuSpec) $ \specs ->
958 e1dde6ad Iustin Pop
  let strspecs = map (\(p, n, d, m, c) -> printf "%s,%d,%d,%d,%d"
959 e1dde6ad Iustin Pop
                                          p n d m c::String) specs
960 e1dde6ad Iustin Pop
      totnodes = sum $ map (\(_, n, _, _, _) -> n) specs
961 e1dde6ad Iustin Pop
      mdc_in = concatMap (\(_, n, d, m, c) ->
962 e1dde6ad Iustin Pop
                            replicate n (fromIntegral m, fromIntegral d,
963 e1dde6ad Iustin Pop
                                         fromIntegral c,
964 e1dde6ad Iustin Pop
                                         fromIntegral m, fromIntegral d)) specs
965 e1dde6ad Iustin Pop
  in case Simu.parseData strspecs of
966 e1dde6ad Iustin Pop
       Types.Bad msg -> failTest $ "Failed to load specs: " ++ msg
967 e1dde6ad Iustin Pop
       Types.Ok (Loader.ClusterData gl nl il tags ipol) ->
968 e1dde6ad Iustin Pop
         let nodes = map snd $ IntMap.toAscList nl
969 e1dde6ad Iustin Pop
             nidx = map Node.idx nodes
970 e1dde6ad Iustin Pop
             mdc_out = map (\n -> (Node.tMem n, Node.tDsk n, Node.tCpu n,
971 e1dde6ad Iustin Pop
                                   Node.fMem n, Node.fDsk n)) nodes
972 e1dde6ad Iustin Pop
         in
973 e1dde6ad Iustin Pop
         Container.size gl ==? ngroups .&&.
974 e1dde6ad Iustin Pop
         Container.size nl ==? totnodes .&&.
975 e1dde6ad Iustin Pop
         Container.size il ==? 0 .&&.
976 e1dde6ad Iustin Pop
         length tags ==? 0 .&&.
977 e1dde6ad Iustin Pop
         ipol ==? Types.defIPolicy .&&.
978 e1dde6ad Iustin Pop
         nidx ==? [1..totnodes] .&&.
979 e1dde6ad Iustin Pop
         mdc_in ==? mdc_out .&&.
980 e1dde6ad Iustin Pop
         map Group.iPolicy (Container.elems gl) ==?
981 e1dde6ad Iustin Pop
             replicate ngroups Types.defIPolicy
982 e1dde6ad Iustin Pop
983 e1dde6ad Iustin Pop
testSuite "Simu"
984 e1dde6ad Iustin Pop
            [ 'prop_SimuLoad
985 e1dde6ad Iustin Pop
            ]
986 e1dde6ad Iustin Pop
987 525bfb36 Iustin Pop
-- ** Node tests
988 7dd5ee6c Iustin Pop
989 82ea2874 Iustin Pop
prop_Node_setAlias node name =
990 d5dfae0a Iustin Pop
  Node.name newnode == Node.name node &&
991 d5dfae0a Iustin Pop
  Node.alias newnode == name
992 82ea2874 Iustin Pop
    where _types = (node::Node.Node, name::String)
993 82ea2874 Iustin Pop
          newnode = Node.setAlias node name
994 82ea2874 Iustin Pop
995 82ea2874 Iustin Pop
prop_Node_setOffline node status =
996 d5dfae0a Iustin Pop
  Node.offline newnode ==? status
997 82ea2874 Iustin Pop
    where newnode = Node.setOffline node status
998 82ea2874 Iustin Pop
999 82ea2874 Iustin Pop
prop_Node_setXmem node xm =
1000 d5dfae0a Iustin Pop
  Node.xMem newnode ==? xm
1001 82ea2874 Iustin Pop
    where newnode = Node.setXmem node xm
1002 82ea2874 Iustin Pop
1003 82ea2874 Iustin Pop
prop_Node_setMcpu node mc =
1004 487e1962 Iustin Pop
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
1005 82ea2874 Iustin Pop
    where newnode = Node.setMcpu node mc
1006 82ea2874 Iustin Pop
1007 525bfb36 Iustin Pop
-- | Check that an instance add with too high memory or disk will be
1008 525bfb36 Iustin Pop
-- rejected.
1009 d5dfae0a Iustin Pop
prop_Node_addPriFM node inst =
1010 d5dfae0a Iustin Pop
  Instance.mem inst >= Node.fMem node && not (Node.failN1 node) &&
1011 7959cbb9 Iustin Pop
  not (Instance.isOffline inst) ==>
1012 d5dfae0a Iustin Pop
  case Node.addPri node inst'' of
1013 d5dfae0a Iustin Pop
    Types.OpFail Types.FailMem -> True
1014 d5dfae0a Iustin Pop
    _ -> False
1015 d5dfae0a Iustin Pop
  where _types = (node::Node.Node, inst::Instance.Instance)
1016 d5dfae0a Iustin Pop
        inst' = setInstanceSmallerThanNode node inst
1017 d5dfae0a Iustin Pop
        inst'' = inst' { Instance.mem = Instance.mem inst }
1018 d5dfae0a Iustin Pop
1019 53bddadd Iustin Pop
-- | Check that adding a primary instance with too much disk fails
1020 53bddadd Iustin Pop
-- with type FailDisk.
1021 d5dfae0a Iustin Pop
prop_Node_addPriFD node inst =
1022 53bddadd Iustin Pop
  forAll (elements Instance.localStorageTemplates) $ \dt ->
1023 d5dfae0a Iustin Pop
  Instance.dsk inst >= Node.fDsk node && not (Node.failN1 node) ==>
1024 53bddadd Iustin Pop
  let inst' = setInstanceSmallerThanNode node inst
1025 53bddadd Iustin Pop
      inst'' = inst' { Instance.dsk = Instance.dsk inst
1026 53bddadd Iustin Pop
                     , Instance.diskTemplate = dt }
1027 53bddadd Iustin Pop
  in case Node.addPri node inst'' of
1028 53bddadd Iustin Pop
       Types.OpFail Types.FailDisk -> True
1029 53bddadd Iustin Pop
       _ -> False
1030 53bddadd Iustin Pop
1031 53bddadd Iustin Pop
-- | Check that adding a primary instance with too many VCPUs fails
1032 53bddadd Iustin Pop
-- with type FailCPU.
1033 3c1e4af0 Iustin Pop
prop_Node_addPriFC =
1034 3c1e4af0 Iustin Pop
  forAll (choose (1, maxCpu)) $ \extra ->
1035 746b7aa6 Iustin Pop
  forAll genOnlineNode $ \node ->
1036 7959cbb9 Iustin Pop
  forAll (arbitrary `suchThat` Instance.notOffline) $ \inst ->
1037 746b7aa6 Iustin Pop
  let inst' = setInstanceSmallerThanNode node inst
1038 746b7aa6 Iustin Pop
      inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
1039 746b7aa6 Iustin Pop
  in case Node.addPri node inst'' of
1040 746b7aa6 Iustin Pop
       Types.OpFail Types.FailCPU -> property True
1041 746b7aa6 Iustin Pop
       v -> failTest $ "Expected OpFail FailCPU, but got " ++ show v
1042 7bc82927 Iustin Pop
1043 525bfb36 Iustin Pop
-- | Check that an instance add with too high memory or disk will be
1044 525bfb36 Iustin Pop
-- rejected.
1045 15f4c8ca Iustin Pop
prop_Node_addSec node inst pdx =
1046 d5dfae0a Iustin Pop
  ((Instance.mem inst >= (Node.fMem node - Node.rMem node) &&
1047 7959cbb9 Iustin Pop
    not (Instance.isOffline inst)) ||
1048 d5dfae0a Iustin Pop
   Instance.dsk inst >= Node.fDsk node) &&
1049 d5dfae0a Iustin Pop
  not (Node.failN1 node) ==>
1050 d5dfae0a Iustin Pop
      isFailure (Node.addSec node inst pdx)
1051 15f4c8ca Iustin Pop
        where _types = (node::Node.Node, inst::Instance.Instance, pdx::Int)
1052 7dd5ee6c Iustin Pop
1053 45c4d54d Iustin Pop
-- | Check that an offline instance with reasonable disk size but
1054 45c4d54d Iustin Pop
-- extra mem/cpu can always be added.
1055 c6b7e804 Iustin Pop
prop_Node_addOfflinePri (NonNegative extra_mem) (NonNegative extra_cpu) =
1056 a2a0bcd8 Iustin Pop
  forAll genOnlineNode $ \node ->
1057 45c4d54d Iustin Pop
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1058 45c4d54d Iustin Pop
  let inst' = inst { Instance.runSt = Types.AdminOffline
1059 45c4d54d Iustin Pop
                   , Instance.mem = Node.availMem node + extra_mem
1060 45c4d54d Iustin Pop
                   , Instance.vcpus = Node.availCpu node + extra_cpu }
1061 c6b7e804 Iustin Pop
  in case Node.addPri node inst' of
1062 c6b7e804 Iustin Pop
       Types.OpGood _ -> property True
1063 c6b7e804 Iustin Pop
       v -> failTest $ "Expected OpGood, but got: " ++ show v
1064 c6b7e804 Iustin Pop
1065 c6b7e804 Iustin Pop
-- | Check that an offline instance with reasonable disk size but
1066 c6b7e804 Iustin Pop
-- extra mem/cpu can always be added.
1067 c6b7e804 Iustin Pop
prop_Node_addOfflineSec (NonNegative extra_mem) (NonNegative extra_cpu) pdx =
1068 c6b7e804 Iustin Pop
  forAll genOnlineNode $ \node ->
1069 c6b7e804 Iustin Pop
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1070 c6b7e804 Iustin Pop
  let inst' = inst { Instance.runSt = Types.AdminOffline
1071 c6b7e804 Iustin Pop
                   , Instance.mem = Node.availMem node + extra_mem
1072 c6b7e804 Iustin Pop
                   , Instance.vcpus = Node.availCpu node + extra_cpu
1073 c6b7e804 Iustin Pop
                   , Instance.diskTemplate = Types.DTDrbd8 }
1074 c6b7e804 Iustin Pop
  in case Node.addSec node inst' pdx of
1075 c6b7e804 Iustin Pop
       Types.OpGood _ -> property True
1076 45c4d54d Iustin Pop
       v -> failTest $ "Expected OpGood/OpGood, but got: " ++ show v
1077 61bbbed7 Agata Murawska
1078 525bfb36 Iustin Pop
-- | Checks for memory reservation changes.
1079 752635d3 Iustin Pop
prop_Node_rMem inst =
1080 7959cbb9 Iustin Pop
  not (Instance.isOffline inst) ==>
1081 5c52dae6 Iustin Pop
  forAll (genOnlineNode `suchThat` ((> Types.unitMem) . Node.fMem)) $ \node ->
1082 d5dfae0a Iustin Pop
  -- ab = auto_balance, nb = non-auto_balance
1083 d5dfae0a Iustin Pop
  -- we use -1 as the primary node of the instance
1084 e7b4d0e1 Iustin Pop
  let inst' = inst { Instance.pNode = -1, Instance.autoBalance = True
1085 e7b4d0e1 Iustin Pop
                   , Instance.diskTemplate = Types.DTDrbd8 }
1086 d5dfae0a Iustin Pop
      inst_ab = setInstanceSmallerThanNode node inst'
1087 d5dfae0a Iustin Pop
      inst_nb = inst_ab { Instance.autoBalance = False }
1088 d5dfae0a Iustin Pop
      -- now we have the two instances, identical except the
1089 d5dfae0a Iustin Pop
      -- autoBalance attribute
1090 d5dfae0a Iustin Pop
      orig_rmem = Node.rMem node
1091 d5dfae0a Iustin Pop
      inst_idx = Instance.idx inst_ab
1092 d5dfae0a Iustin Pop
      node_add_ab = Node.addSec node inst_ab (-1)
1093 d5dfae0a Iustin Pop
      node_add_nb = Node.addSec node inst_nb (-1)
1094 d5dfae0a Iustin Pop
      node_del_ab = liftM (`Node.removeSec` inst_ab) node_add_ab
1095 d5dfae0a Iustin Pop
      node_del_nb = liftM (`Node.removeSec` inst_nb) node_add_nb
1096 d5dfae0a Iustin Pop
  in case (node_add_ab, node_add_nb, node_del_ab, node_del_nb) of
1097 d5dfae0a Iustin Pop
       (Types.OpGood a_ab, Types.OpGood a_nb,
1098 d5dfae0a Iustin Pop
        Types.OpGood d_ab, Types.OpGood d_nb) ->
1099 d5dfae0a Iustin Pop
         printTestCase "Consistency checks failed" $
1100 d5dfae0a Iustin Pop
           Node.rMem a_ab >  orig_rmem &&
1101 d5dfae0a Iustin Pop
           Node.rMem a_ab - orig_rmem == Instance.mem inst_ab &&
1102 d5dfae0a Iustin Pop
           Node.rMem a_nb == orig_rmem &&
1103 d5dfae0a Iustin Pop
           Node.rMem d_ab == orig_rmem &&
1104 d5dfae0a Iustin Pop
           Node.rMem d_nb == orig_rmem &&
1105 d5dfae0a Iustin Pop
           -- this is not related to rMem, but as good a place to
1106 d5dfae0a Iustin Pop
           -- test as any
1107 d5dfae0a Iustin Pop
           inst_idx `elem` Node.sList a_ab &&
1108 3603605a Iustin Pop
           inst_idx `notElem` Node.sList d_ab
1109 96bc2003 Iustin Pop
       x -> failTest $ "Failed to add/remove instances: " ++ show x
1110 9cbc1edb Iustin Pop
1111 525bfb36 Iustin Pop
-- | Check mdsk setting.
1112 8fcf251f Iustin Pop
prop_Node_setMdsk node mx =
1113 d5dfae0a Iustin Pop
  Node.loDsk node' >= 0 &&
1114 d5dfae0a Iustin Pop
  fromIntegral (Node.loDsk node') <= Node.tDsk node &&
1115 d5dfae0a Iustin Pop
  Node.availDisk node' >= 0 &&
1116 d5dfae0a Iustin Pop
  Node.availDisk node' <= Node.fDsk node' &&
1117 d5dfae0a Iustin Pop
  fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
1118 d5dfae0a Iustin Pop
  Node.mDsk node' == mx'
1119 8fcf251f Iustin Pop
    where _types = (node::Node.Node, mx::SmallRatio)
1120 8fcf251f Iustin Pop
          node' = Node.setMdsk node mx'
1121 8fcf251f Iustin Pop
          SmallRatio mx' = mx
1122 8fcf251f Iustin Pop
1123 8fcf251f Iustin Pop
-- Check tag maps
1124 15e3d31c Iustin Pop
prop_Node_tagMaps_idempotent =
1125 15e3d31c Iustin Pop
  forAll genTags $ \tags ->
1126 d5dfae0a Iustin Pop
  Node.delTags (Node.addTags m tags) tags ==? m
1127 4a007641 Iustin Pop
    where m = Data.Map.empty
1128 8fcf251f Iustin Pop
1129 15e3d31c Iustin Pop
prop_Node_tagMaps_reject =
1130 15e3d31c Iustin Pop
  forAll (genTags `suchThat` (not . null)) $ \tags ->
1131 15e3d31c Iustin Pop
  let m = Node.addTags Data.Map.empty tags
1132 15e3d31c Iustin Pop
  in all (\t -> Node.rejectAddTags m [t]) tags
1133 8fcf251f Iustin Pop
1134 82ea2874 Iustin Pop
prop_Node_showField node =
1135 82ea2874 Iustin Pop
  forAll (elements Node.defaultFields) $ \ field ->
1136 82ea2874 Iustin Pop
  fst (Node.showHeader field) /= Types.unknownField &&
1137 82ea2874 Iustin Pop
  Node.showField node field /= Types.unknownField
1138 82ea2874 Iustin Pop
1139 d8bcd0a8 Iustin Pop
prop_Node_computeGroups nodes =
1140 d8bcd0a8 Iustin Pop
  let ng = Node.computeGroups nodes
1141 d8bcd0a8 Iustin Pop
      onlyuuid = map fst ng
1142 d8bcd0a8 Iustin Pop
  in length nodes == sum (map (length . snd) ng) &&
1143 d8bcd0a8 Iustin Pop
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
1144 d8bcd0a8 Iustin Pop
     length (nub onlyuuid) == length onlyuuid &&
1145 cc532bdd Iustin Pop
     (null nodes || not (null ng))
1146 d8bcd0a8 Iustin Pop
1147 eae69eee Iustin Pop
-- Check idempotence of add/remove operations
1148 eae69eee Iustin Pop
prop_Node_addPri_idempotent =
1149 eae69eee Iustin Pop
  forAll genOnlineNode $ \node ->
1150 eae69eee Iustin Pop
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1151 eae69eee Iustin Pop
  case Node.addPri node inst of
1152 eae69eee Iustin Pop
    Types.OpGood node' -> Node.removePri node' inst ==? node
1153 eae69eee Iustin Pop
    _ -> failTest "Can't add instance"
1154 eae69eee Iustin Pop
1155 eae69eee Iustin Pop
prop_Node_addSec_idempotent =
1156 eae69eee Iustin Pop
  forAll genOnlineNode $ \node ->
1157 eae69eee Iustin Pop
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1158 eae69eee Iustin Pop
  let pdx = Node.idx node + 1
1159 eae69eee Iustin Pop
      inst' = Instance.setPri inst pdx
1160 90669369 Iustin Pop
      inst'' = inst' { Instance.diskTemplate = Types.DTDrbd8 }
1161 90669369 Iustin Pop
  in case Node.addSec node inst'' pdx of
1162 90669369 Iustin Pop
       Types.OpGood node' -> Node.removeSec node' inst'' ==? node
1163 eae69eee Iustin Pop
       _ -> failTest "Can't add instance"
1164 eae69eee Iustin Pop
1165 23fe06c2 Iustin Pop
testSuite "Node"
1166 d5dfae0a Iustin Pop
            [ 'prop_Node_setAlias
1167 d5dfae0a Iustin Pop
            , 'prop_Node_setOffline
1168 d5dfae0a Iustin Pop
            , 'prop_Node_setMcpu
1169 d5dfae0a Iustin Pop
            , 'prop_Node_setXmem
1170 d5dfae0a Iustin Pop
            , 'prop_Node_addPriFM
1171 d5dfae0a Iustin Pop
            , 'prop_Node_addPriFD
1172 d5dfae0a Iustin Pop
            , 'prop_Node_addPriFC
1173 d5dfae0a Iustin Pop
            , 'prop_Node_addSec
1174 c6b7e804 Iustin Pop
            , 'prop_Node_addOfflinePri
1175 c6b7e804 Iustin Pop
            , 'prop_Node_addOfflineSec
1176 d5dfae0a Iustin Pop
            , 'prop_Node_rMem
1177 d5dfae0a Iustin Pop
            , 'prop_Node_setMdsk
1178 d5dfae0a Iustin Pop
            , 'prop_Node_tagMaps_idempotent
1179 d5dfae0a Iustin Pop
            , 'prop_Node_tagMaps_reject
1180 d5dfae0a Iustin Pop
            , 'prop_Node_showField
1181 d5dfae0a Iustin Pop
            , 'prop_Node_computeGroups
1182 eae69eee Iustin Pop
            , 'prop_Node_addPri_idempotent
1183 eae69eee Iustin Pop
            , 'prop_Node_addSec_idempotent
1184 d5dfae0a Iustin Pop
            ]
1185 cf35a869 Iustin Pop
1186 525bfb36 Iustin Pop
-- ** Cluster tests
1187 cf35a869 Iustin Pop
1188 525bfb36 Iustin Pop
-- | Check that the cluster score is close to zero for a homogeneous
1189 525bfb36 Iustin Pop
-- cluster.
1190 8e4f6d56 Iustin Pop
prop_Score_Zero node =
1191 d5dfae0a Iustin Pop
  forAll (choose (1, 1024)) $ \count ->
1192 3a3c1eb4 Iustin Pop
    (not (Node.offline node) && not (Node.failN1 node) && (count > 0) &&
1193 2060348b Iustin Pop
     (Node.tDsk node > 0) && (Node.tMem node > 0)) ==>
1194 d5dfae0a Iustin Pop
  let fn = Node.buildPeers node Container.empty
1195 d5dfae0a Iustin Pop
      nlst = replicate count fn
1196 d5dfae0a Iustin Pop
      score = Cluster.compCVNodes nlst
1197 d5dfae0a Iustin Pop
  -- we can't say == 0 here as the floating point errors accumulate;
1198 d5dfae0a Iustin Pop
  -- this should be much lower than the default score in CLI.hs
1199 d5dfae0a Iustin Pop
  in score <= 1e-12
1200 cf35a869 Iustin Pop
1201 525bfb36 Iustin Pop
-- | Check that cluster stats are sane.
1202 d6f9f5bd Iustin Pop
prop_CStats_sane =
1203 d5dfae0a Iustin Pop
  forAll (choose (1, 1024)) $ \count ->
1204 d6f9f5bd Iustin Pop
  forAll genOnlineNode $ \node ->
1205 d5dfae0a Iustin Pop
  let fn = Node.buildPeers node Container.empty
1206 d5dfae0a Iustin Pop
      nlst = zip [1..] $ replicate count fn::[(Types.Ndx, Node.Node)]
1207 d5dfae0a Iustin Pop
      nl = Container.fromList nlst
1208 d5dfae0a Iustin Pop
      cstats = Cluster.totalResources nl
1209 d5dfae0a Iustin Pop
  in Cluster.csAdsk cstats >= 0 &&
1210 d5dfae0a Iustin Pop
     Cluster.csAdsk cstats <= Cluster.csFdsk cstats
1211 8fcf251f Iustin Pop
1212 3fea6959 Iustin Pop
-- | Check that one instance is allocated correctly, without
1213 525bfb36 Iustin Pop
-- rebalances needed.
1214 d6f9f5bd Iustin Pop
prop_ClusterAlloc_sane inst =
1215 d5dfae0a Iustin Pop
  forAll (choose (5, 20)) $ \count ->
1216 d6f9f5bd Iustin Pop
  forAll genOnlineNode $ \node ->
1217 3603605a Iustin Pop
  let (nl, il, inst') = makeSmallEmptyCluster node count inst
1218 c6e8fb9c Iustin Pop
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1219 c6e8fb9c Iustin Pop
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1220 d5dfae0a Iustin Pop
     Cluster.tryAlloc nl il inst' of
1221 d5dfae0a Iustin Pop
       Types.Bad _ -> False
1222 d5dfae0a Iustin Pop
       Types.Ok as ->
1223 d5dfae0a Iustin Pop
         case Cluster.asSolution as of
1224 d5dfae0a Iustin Pop
           Nothing -> False
1225 d5dfae0a Iustin Pop
           Just (xnl, xi, _, cv) ->
1226 d5dfae0a Iustin Pop
             let il' = Container.add (Instance.idx xi) xi il
1227 d5dfae0a Iustin Pop
                 tbl = Cluster.Table xnl il' cv []
1228 d5dfae0a Iustin Pop
             in not (canBalance tbl True True False)
1229 3fea6959 Iustin Pop
1230 3fea6959 Iustin Pop
-- | Checks that on a 2-5 node cluster, we can allocate a random
1231 3fea6959 Iustin Pop
-- instance spec via tiered allocation (whatever the original instance
1232 37483aa5 Iustin Pop
-- spec), on either one or two nodes. Furthermore, we test that
1233 37483aa5 Iustin Pop
-- computed allocation statistics are correct.
1234 d6f9f5bd Iustin Pop
prop_ClusterCanTieredAlloc inst =
1235 d5dfae0a Iustin Pop
  forAll (choose (2, 5)) $ \count ->
1236 d6f9f5bd Iustin Pop
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1237 d5dfae0a Iustin Pop
  let nl = makeSmallCluster node count
1238 d5dfae0a Iustin Pop
      il = Container.empty
1239 c6e8fb9c Iustin Pop
      rqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1240 d5dfae0a Iustin Pop
      allocnodes = Cluster.genAllocNodes defGroupList nl rqnodes True
1241 d5dfae0a Iustin Pop
  in case allocnodes >>= \allocnodes' ->
1242 d5dfae0a Iustin Pop
    Cluster.tieredAlloc nl il (Just 1) inst allocnodes' [] [] of
1243 37483aa5 Iustin Pop
       Types.Bad msg -> failTest $ "Failed to tiered alloc: " ++ msg
1244 37483aa5 Iustin Pop
       Types.Ok (_, nl', il', ixes, cstats) ->
1245 37483aa5 Iustin Pop
         let (ai_alloc, ai_pool, ai_unav) =
1246 37483aa5 Iustin Pop
               Cluster.computeAllocationDelta
1247 37483aa5 Iustin Pop
                (Cluster.totalResources nl)
1248 37483aa5 Iustin Pop
                (Cluster.totalResources nl')
1249 37483aa5 Iustin Pop
             all_nodes = Container.elems nl
1250 37483aa5 Iustin Pop
         in property (not (null ixes)) .&&.
1251 37483aa5 Iustin Pop
            IntMap.size il' ==? length ixes .&&.
1252 37483aa5 Iustin Pop
            length ixes ==? length cstats .&&.
1253 37483aa5 Iustin Pop
            sum (map Types.allocInfoVCpus [ai_alloc, ai_pool, ai_unav]) ==?
1254 37483aa5 Iustin Pop
              sum (map Node.hiCpu all_nodes) .&&.
1255 37483aa5 Iustin Pop
            sum (map Types.allocInfoNCpus [ai_alloc, ai_pool, ai_unav]) ==?
1256 37483aa5 Iustin Pop
              sum (map Node.tCpu all_nodes) .&&.
1257 37483aa5 Iustin Pop
            sum (map Types.allocInfoMem [ai_alloc, ai_pool, ai_unav]) ==?
1258 37483aa5 Iustin Pop
              truncate (sum (map Node.tMem all_nodes)) .&&.
1259 37483aa5 Iustin Pop
            sum (map Types.allocInfoDisk [ai_alloc, ai_pool, ai_unav]) ==?
1260 37483aa5 Iustin Pop
              truncate (sum (map Node.tDsk all_nodes))
1261 3fea6959 Iustin Pop
1262 6a855aaa Iustin Pop
-- | Helper function to create a cluster with the given range of nodes
1263 6a855aaa Iustin Pop
-- and allocate an instance on it.
1264 6a855aaa Iustin Pop
genClusterAlloc count node inst =
1265 6a855aaa Iustin Pop
  let nl = makeSmallCluster node count
1266 c6e8fb9c Iustin Pop
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1267 c6e8fb9c Iustin Pop
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1268 6a855aaa Iustin Pop
     Cluster.tryAlloc nl Container.empty inst of
1269 6a855aaa Iustin Pop
       Types.Bad _ -> Types.Bad "Can't allocate"
1270 d5dfae0a Iustin Pop
       Types.Ok as ->
1271 d5dfae0a Iustin Pop
         case Cluster.asSolution as of
1272 6a855aaa Iustin Pop
           Nothing -> Types.Bad "Empty solution?"
1273 d5dfae0a Iustin Pop
           Just (xnl, xi, _, _) ->
1274 6a855aaa Iustin Pop
             let xil = Container.add (Instance.idx xi) xi Container.empty
1275 6a855aaa Iustin Pop
             in Types.Ok (xnl, xil, xi)
1276 6a855aaa Iustin Pop
1277 6a855aaa Iustin Pop
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1278 6a855aaa Iustin Pop
-- we can also relocate it.
1279 6a855aaa Iustin Pop
prop_ClusterAllocRelocate =
1280 6a855aaa Iustin Pop
  forAll (choose (4, 8)) $ \count ->
1281 6a855aaa Iustin Pop
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1282 7018af9c Iustin Pop
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1283 6a855aaa Iustin Pop
  case genClusterAlloc count node inst of
1284 6a855aaa Iustin Pop
    Types.Bad msg -> failTest msg
1285 6a855aaa Iustin Pop
    Types.Ok (nl, il, inst') ->
1286 6a855aaa Iustin Pop
      case IAlloc.processRelocate defGroupList nl il
1287 7018af9c Iustin Pop
             (Instance.idx inst) 1
1288 7018af9c Iustin Pop
             [(if Instance.diskTemplate inst' == Types.DTDrbd8
1289 7018af9c Iustin Pop
                 then Instance.sNode
1290 7018af9c Iustin Pop
                 else Instance.pNode) inst'] of
1291 7018af9c Iustin Pop
        Types.Ok _ -> property True
1292 6a855aaa Iustin Pop
        Types.Bad msg -> failTest $ "Failed to relocate: " ++ msg
1293 6a855aaa Iustin Pop
1294 6a855aaa Iustin Pop
-- | Helper property checker for the result of a nodeEvac or
1295 6a855aaa Iustin Pop
-- changeGroup operation.
1296 6a855aaa Iustin Pop
check_EvacMode grp inst result =
1297 6a855aaa Iustin Pop
  case result of
1298 6a855aaa Iustin Pop
    Types.Bad msg -> failTest $ "Couldn't evacuate/change group:" ++ msg
1299 6a855aaa Iustin Pop
    Types.Ok (_, _, es) ->
1300 6a855aaa Iustin Pop
      let moved = Cluster.esMoved es
1301 6a855aaa Iustin Pop
          failed = Cluster.esFailed es
1302 6a855aaa Iustin Pop
          opcodes = not . null $ Cluster.esOpCodes es
1303 6a855aaa Iustin Pop
      in failmsg ("'failed' not empty: " ++ show failed) (null failed) .&&.
1304 6a855aaa Iustin Pop
         failmsg "'opcodes' is null" opcodes .&&.
1305 6a855aaa Iustin Pop
         case moved of
1306 6a855aaa Iustin Pop
           [(idx', gdx, _)] -> failmsg "invalid instance moved" (idx == idx')
1307 6a855aaa Iustin Pop
                               .&&.
1308 6a855aaa Iustin Pop
                               failmsg "wrong target group"
1309 6a855aaa Iustin Pop
                                         (gdx == Group.idx grp)
1310 6a855aaa Iustin Pop
           v -> failmsg  ("invalid solution: " ++ show v) False
1311 6a855aaa Iustin Pop
  where failmsg = \msg -> printTestCase ("Failed to evacuate: " ++ msg)
1312 6a855aaa Iustin Pop
        idx = Instance.idx inst
1313 6a855aaa Iustin Pop
1314 6a855aaa Iustin Pop
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1315 6a855aaa Iustin Pop
-- we can also node-evacuate it.
1316 6a855aaa Iustin Pop
prop_ClusterAllocEvacuate =
1317 6a855aaa Iustin Pop
  forAll (choose (4, 8)) $ \count ->
1318 6a855aaa Iustin Pop
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1319 ac1c0a07 Iustin Pop
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1320 6a855aaa Iustin Pop
  case genClusterAlloc count node inst of
1321 6a855aaa Iustin Pop
    Types.Bad msg -> failTest msg
1322 6a855aaa Iustin Pop
    Types.Ok (nl, il, inst') ->
1323 6a855aaa Iustin Pop
      conjoin $ map (\mode -> check_EvacMode defGroup inst' $
1324 6a855aaa Iustin Pop
                              Cluster.tryNodeEvac defGroupList nl il mode
1325 ac1c0a07 Iustin Pop
                                [Instance.idx inst']) .
1326 fafd0773 Iustin Pop
                              evacModeOptions .
1327 fafd0773 Iustin Pop
                              Instance.mirrorType $ inst'
1328 6a855aaa Iustin Pop
1329 6a855aaa Iustin Pop
-- | Checks that on a 4-8 node cluster with two node groups, once we
1330 6a855aaa Iustin Pop
-- allocate an instance on the first node group, we can also change
1331 6a855aaa Iustin Pop
-- its group.
1332 6a855aaa Iustin Pop
prop_ClusterAllocChangeGroup =
1333 6a855aaa Iustin Pop
  forAll (choose (4, 8)) $ \count ->
1334 6a855aaa Iustin Pop
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1335 ac1c0a07 Iustin Pop
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1336 6a855aaa Iustin Pop
  case genClusterAlloc count node inst of
1337 6a855aaa Iustin Pop
    Types.Bad msg -> failTest msg
1338 6a855aaa Iustin Pop
    Types.Ok (nl, il, inst') ->
1339 6a855aaa Iustin Pop
      -- we need to add a second node group and nodes to the cluster
1340 6a855aaa Iustin Pop
      let nl2 = Container.elems $ makeSmallCluster node count
1341 6a855aaa Iustin Pop
          grp2 = Group.setIdx defGroup (Group.idx defGroup + 1)
1342 6a855aaa Iustin Pop
          maxndx = maximum . map Node.idx $ nl2
1343 6a855aaa Iustin Pop
          nl3 = map (\n -> n { Node.group = Group.idx grp2
1344 6a855aaa Iustin Pop
                             , Node.idx = Node.idx n + maxndx }) nl2
1345 6a855aaa Iustin Pop
          nl4 = Container.fromList . map (\n -> (Node.idx n, n)) $ nl3
1346 6a855aaa Iustin Pop
          gl' = Container.add (Group.idx grp2) grp2 defGroupList
1347 6a855aaa Iustin Pop
          nl' = IntMap.union nl nl4
1348 6a855aaa Iustin Pop
      in check_EvacMode grp2 inst' $
1349 6a855aaa Iustin Pop
         Cluster.tryChangeGroup gl' nl' il [] [Instance.idx inst']
1350 3fea6959 Iustin Pop
1351 3fea6959 Iustin Pop
-- | Check that allocating multiple instances on a cluster, then
1352 525bfb36 Iustin Pop
-- adding an empty node, results in a valid rebalance.
1353 00c75986 Iustin Pop
prop_ClusterAllocBalance =
1354 d5dfae0a Iustin Pop
  forAll (genNode (Just 5) (Just 128)) $ \node ->
1355 d5dfae0a Iustin Pop
  forAll (choose (3, 5)) $ \count ->
1356 d5dfae0a Iustin Pop
  not (Node.offline node) && not (Node.failN1 node) ==>
1357 d5dfae0a Iustin Pop
  let nl = makeSmallCluster node count
1358 d5dfae0a Iustin Pop
      (hnode, nl') = IntMap.deleteFindMax nl
1359 d5dfae0a Iustin Pop
      il = Container.empty
1360 d5dfae0a Iustin Pop
      allocnodes = Cluster.genAllocNodes defGroupList nl' 2 True
1361 d5dfae0a Iustin Pop
      i_templ = createInstance Types.unitMem Types.unitDsk Types.unitCpu
1362 d5dfae0a Iustin Pop
  in case allocnodes >>= \allocnodes' ->
1363 d5dfae0a Iustin Pop
    Cluster.iterateAlloc nl' il (Just 5) i_templ allocnodes' [] [] of
1364 96bc2003 Iustin Pop
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
1365 96bc2003 Iustin Pop
       Types.Ok (_, _, _, [], _) -> failTest "Failed to allocate: no instances"
1366 d5dfae0a Iustin Pop
       Types.Ok (_, xnl, il', _, _) ->
1367 d5dfae0a Iustin Pop
         let ynl = Container.add (Node.idx hnode) hnode xnl
1368 d5dfae0a Iustin Pop
             cv = Cluster.compCV ynl
1369 d5dfae0a Iustin Pop
             tbl = Cluster.Table ynl il' cv []
1370 6cff91f5 Iustin Pop
         in printTestCase "Failed to rebalance" $
1371 6cff91f5 Iustin Pop
            canBalance tbl True True False
1372 3fea6959 Iustin Pop
1373 525bfb36 Iustin Pop
-- | Checks consistency.
1374 32b8d9c0 Iustin Pop
prop_ClusterCheckConsistency node inst =
1375 32b8d9c0 Iustin Pop
  let nl = makeSmallCluster node 3
1376 32b8d9c0 Iustin Pop
      [node1, node2, node3] = Container.elems nl
1377 10ef6b4e Iustin Pop
      node3' = node3 { Node.group = 1 }
1378 32b8d9c0 Iustin Pop
      nl' = Container.add (Node.idx node3') node3' nl
1379 32b8d9c0 Iustin Pop
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
1380 32b8d9c0 Iustin Pop
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
1381 32b8d9c0 Iustin Pop
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
1382 cb0c77ff Iustin Pop
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
1383 32b8d9c0 Iustin Pop
  in null (ccheck [(0, inst1)]) &&
1384 32b8d9c0 Iustin Pop
     null (ccheck [(0, inst2)]) &&
1385 32b8d9c0 Iustin Pop
     (not . null $ ccheck [(0, inst3)])
1386 32b8d9c0 Iustin Pop
1387 525bfb36 Iustin Pop
-- | For now, we only test that we don't lose instances during the split.
1388 f4161783 Iustin Pop
prop_ClusterSplitCluster node inst =
1389 f4161783 Iustin Pop
  forAll (choose (0, 100)) $ \icnt ->
1390 f4161783 Iustin Pop
  let nl = makeSmallCluster node 2
1391 f4161783 Iustin Pop
      (nl', il') = foldl (\(ns, is) _ -> assignInstance ns is inst 0 1)
1392 f4161783 Iustin Pop
                   (nl, Container.empty) [1..icnt]
1393 f4161783 Iustin Pop
      gni = Cluster.splitCluster nl' il'
1394 f4161783 Iustin Pop
  in sum (map (Container.size . snd . snd) gni) == icnt &&
1395 f4161783 Iustin Pop
     all (\(guuid, (nl'', _)) -> all ((== guuid) . Node.group)
1396 f4161783 Iustin Pop
                                 (Container.elems nl'')) gni
1397 32b8d9c0 Iustin Pop
1398 00b70680 Iustin Pop
-- | Helper function to check if we can allocate an instance on a
1399 00b70680 Iustin Pop
-- given node list.
1400 00b70680 Iustin Pop
canAllocOn :: Node.List -> Int -> Instance.Instance -> Bool
1401 00b70680 Iustin Pop
canAllocOn nl reqnodes inst =
1402 00b70680 Iustin Pop
  case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1403 00b70680 Iustin Pop
       Cluster.tryAlloc nl (Container.empty) inst of
1404 00b70680 Iustin Pop
       Types.Bad _ -> False
1405 00b70680 Iustin Pop
       Types.Ok as ->
1406 00b70680 Iustin Pop
         case Cluster.asSolution as of
1407 00b70680 Iustin Pop
           Nothing -> False
1408 00b70680 Iustin Pop
           Just _ -> True
1409 00b70680 Iustin Pop
1410 00b70680 Iustin Pop
-- | Checks that allocation obeys minimum and maximum instance
1411 00b70680 Iustin Pop
-- policies. The unittest generates a random node, duplicates it count
1412 00b70680 Iustin Pop
-- times, and generates a random instance that can be allocated on
1413 00b70680 Iustin Pop
-- this mini-cluster; it then checks that after applying a policy that
1414 00b70680 Iustin Pop
-- the instance doesn't fits, the allocation fails.
1415 00b70680 Iustin Pop
prop_ClusterAllocPolicy node =
1416 00b70680 Iustin Pop
  -- rqn is the required nodes (1 or 2)
1417 00b70680 Iustin Pop
  forAll (choose (1, 2)) $ \rqn ->
1418 00b70680 Iustin Pop
  forAll (choose (5, 20)) $ \count ->
1419 00b70680 Iustin Pop
  forAll (arbitrary `suchThat` (canAllocOn (makeSmallCluster node count) rqn))
1420 00b70680 Iustin Pop
         $ \inst ->
1421 00b70680 Iustin Pop
  forAll (arbitrary `suchThat` (isFailure .
1422 00b70680 Iustin Pop
                                Instance.instMatchesPolicy inst)) $ \ipol ->
1423 00b70680 Iustin Pop
  let node' = Node.setPolicy ipol node
1424 00b70680 Iustin Pop
      nl = makeSmallCluster node' count
1425 00b70680 Iustin Pop
  in not $ canAllocOn nl rqn inst
1426 00b70680 Iustin Pop
1427 23fe06c2 Iustin Pop
testSuite "Cluster"
1428 d5dfae0a Iustin Pop
            [ 'prop_Score_Zero
1429 d5dfae0a Iustin Pop
            , 'prop_CStats_sane
1430 d5dfae0a Iustin Pop
            , 'prop_ClusterAlloc_sane
1431 d5dfae0a Iustin Pop
            , 'prop_ClusterCanTieredAlloc
1432 6a855aaa Iustin Pop
            , 'prop_ClusterAllocRelocate
1433 6a855aaa Iustin Pop
            , 'prop_ClusterAllocEvacuate
1434 6a855aaa Iustin Pop
            , 'prop_ClusterAllocChangeGroup
1435 d5dfae0a Iustin Pop
            , 'prop_ClusterAllocBalance
1436 d5dfae0a Iustin Pop
            , 'prop_ClusterCheckConsistency
1437 d5dfae0a Iustin Pop
            , 'prop_ClusterSplitCluster
1438 00b70680 Iustin Pop
            , 'prop_ClusterAllocPolicy
1439 d5dfae0a Iustin Pop
            ]
1440 88f25dd0 Iustin Pop
1441 525bfb36 Iustin Pop
-- ** OpCodes tests
1442 88f25dd0 Iustin Pop
1443 525bfb36 Iustin Pop
-- | Check that opcode serialization is idempotent.
1444 88f25dd0 Iustin Pop
prop_OpCodes_serialization op =
1445 88f25dd0 Iustin Pop
  case J.readJSON (J.showJSON op) of
1446 96bc2003 Iustin Pop
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1447 72bb6b4e Iustin Pop
    J.Ok op' -> op ==? op'
1448 4a007641 Iustin Pop
  where _types = op::OpCodes.OpCode
1449 88f25dd0 Iustin Pop
1450 23fe06c2 Iustin Pop
testSuite "OpCodes"
1451 d5dfae0a Iustin Pop
            [ 'prop_OpCodes_serialization ]
1452 c088674b Iustin Pop
1453 525bfb36 Iustin Pop
-- ** Jobs tests
1454 525bfb36 Iustin Pop
1455 525bfb36 Iustin Pop
-- | Check that (queued) job\/opcode status serialization is idempotent.
1456 db079755 Iustin Pop
prop_OpStatus_serialization os =
1457 db079755 Iustin Pop
  case J.readJSON (J.showJSON os) of
1458 96bc2003 Iustin Pop
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1459 72bb6b4e Iustin Pop
    J.Ok os' -> os ==? os'
1460 db079755 Iustin Pop
  where _types = os::Jobs.OpStatus
1461 db079755 Iustin Pop
1462 db079755 Iustin Pop
prop_JobStatus_serialization js =
1463 db079755 Iustin Pop
  case J.readJSON (J.showJSON js) of
1464 96bc2003 Iustin Pop
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1465 72bb6b4e Iustin Pop
    J.Ok js' -> js ==? js'
1466 db079755 Iustin Pop
  where _types = js::Jobs.JobStatus
1467 db079755 Iustin Pop
1468 23fe06c2 Iustin Pop
testSuite "Jobs"
1469 d5dfae0a Iustin Pop
            [ 'prop_OpStatus_serialization
1470 d5dfae0a Iustin Pop
            , 'prop_JobStatus_serialization
1471 d5dfae0a Iustin Pop
            ]
1472 db079755 Iustin Pop
1473 525bfb36 Iustin Pop
-- ** Loader tests
1474 c088674b Iustin Pop
1475 c088674b Iustin Pop
prop_Loader_lookupNode ktn inst node =
1476 72bb6b4e Iustin Pop
  Loader.lookupNode nl inst node ==? Data.Map.lookup node nl
1477 d5dfae0a Iustin Pop
    where nl = Data.Map.fromList ktn
1478 c088674b Iustin Pop
1479 c088674b Iustin Pop
prop_Loader_lookupInstance kti inst =
1480 72bb6b4e Iustin Pop
  Loader.lookupInstance il inst ==? Data.Map.lookup inst il
1481 d5dfae0a Iustin Pop
    where il = Data.Map.fromList kti
1482 99b63608 Iustin Pop
1483 3074ccaf Iustin Pop
prop_Loader_assignIndices =
1484 3074ccaf Iustin Pop
  -- generate nodes with unique names
1485 3074ccaf Iustin Pop
  forAll (arbitrary `suchThat`
1486 3074ccaf Iustin Pop
          (\nodes ->
1487 3074ccaf Iustin Pop
             let names = map Node.name nodes
1488 3074ccaf Iustin Pop
             in length names == length (nub names))) $ \nodes ->
1489 3074ccaf Iustin Pop
  let (nassoc, kt) =
1490 3074ccaf Iustin Pop
        Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
1491 3074ccaf Iustin Pop
  in Data.Map.size nassoc == length nodes &&
1492 3074ccaf Iustin Pop
     Container.size kt == length nodes &&
1493 3074ccaf Iustin Pop
     if not (null nodes)
1494 3074ccaf Iustin Pop
       then maximum (IntMap.keys kt) == length nodes - 1
1495 3074ccaf Iustin Pop
       else True
1496 c088674b Iustin Pop
1497 c088674b Iustin Pop
-- | Checks that the number of primary instances recorded on the nodes
1498 525bfb36 Iustin Pop
-- is zero.
1499 c088674b Iustin Pop
prop_Loader_mergeData ns =
1500 cb0c77ff Iustin Pop
  let na = Container.fromList $ map (\n -> (Node.idx n, n)) ns
1501 2d1708e0 Guido Trotter
  in case Loader.mergeData [] [] [] []
1502 f4f6eb0b Iustin Pop
         (Loader.emptyCluster {Loader.cdNodes = na}) of
1503 c088674b Iustin Pop
    Types.Bad _ -> False
1504 71375ef7 Iustin Pop
    Types.Ok (Loader.ClusterData _ nl il _ _) ->
1505 c088674b Iustin Pop
      let nodes = Container.elems nl
1506 c088674b Iustin Pop
          instances = Container.elems il
1507 c088674b Iustin Pop
      in (sum . map (length . Node.pList)) nodes == 0 &&
1508 4a007641 Iustin Pop
         null instances
1509 c088674b Iustin Pop
1510 efe98965 Guido Trotter
-- | Check that compareNameComponent on equal strings works.
1511 efe98965 Guido Trotter
prop_Loader_compareNameComponent_equal :: String -> Bool
1512 efe98965 Guido Trotter
prop_Loader_compareNameComponent_equal s =
1513 efe98965 Guido Trotter
  Loader.compareNameComponent s s ==
1514 efe98965 Guido Trotter
    Loader.LookupResult Loader.ExactMatch s
1515 efe98965 Guido Trotter
1516 efe98965 Guido Trotter
-- | Check that compareNameComponent on prefix strings works.
1517 efe98965 Guido Trotter
prop_Loader_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
1518 efe98965 Guido Trotter
prop_Loader_compareNameComponent_prefix (NonEmpty s1) s2 =
1519 efe98965 Guido Trotter
  Loader.compareNameComponent (s1 ++ "." ++ s2) s1 ==
1520 efe98965 Guido Trotter
    Loader.LookupResult Loader.PartialMatch s1
1521 efe98965 Guido Trotter
1522 23fe06c2 Iustin Pop
testSuite "Loader"
1523 d5dfae0a Iustin Pop
            [ 'prop_Loader_lookupNode
1524 d5dfae0a Iustin Pop
            , 'prop_Loader_lookupInstance
1525 d5dfae0a Iustin Pop
            , 'prop_Loader_assignIndices
1526 d5dfae0a Iustin Pop
            , 'prop_Loader_mergeData
1527 d5dfae0a Iustin Pop
            , 'prop_Loader_compareNameComponent_equal
1528 d5dfae0a Iustin Pop
            , 'prop_Loader_compareNameComponent_prefix
1529 d5dfae0a Iustin Pop
            ]
1530 3c002a13 Iustin Pop
1531 3c002a13 Iustin Pop
-- ** Types tests
1532 3c002a13 Iustin Pop
1533 0047d4e2 Iustin Pop
prop_Types_AllocPolicy_serialisation apol =
1534 d5dfae0a Iustin Pop
  case J.readJSON (J.showJSON apol) of
1535 aa1d552d Iustin Pop
    J.Ok p -> p ==? apol
1536 96bc2003 Iustin Pop
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1537 d5dfae0a Iustin Pop
      where _types = apol::Types.AllocPolicy
1538 0047d4e2 Iustin Pop
1539 0047d4e2 Iustin Pop
prop_Types_DiskTemplate_serialisation dt =
1540 d5dfae0a Iustin Pop
  case J.readJSON (J.showJSON dt) of
1541 aa1d552d Iustin Pop
    J.Ok p -> p ==? dt
1542 96bc2003 Iustin Pop
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1543 d5dfae0a Iustin Pop
      where _types = dt::Types.DiskTemplate
1544 0047d4e2 Iustin Pop
1545 aa1d552d Iustin Pop
prop_Types_ISpec_serialisation ispec =
1546 aa1d552d Iustin Pop
  case J.readJSON (J.showJSON ispec) of
1547 aa1d552d Iustin Pop
    J.Ok p -> p ==? ispec
1548 96bc2003 Iustin Pop
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1549 aa1d552d Iustin Pop
      where _types = ispec::Types.ISpec
1550 aa1d552d Iustin Pop
1551 aa1d552d Iustin Pop
prop_Types_IPolicy_serialisation ipol =
1552 aa1d552d Iustin Pop
  case J.readJSON (J.showJSON ipol) of
1553 aa1d552d Iustin Pop
    J.Ok p -> p ==? ipol
1554 96bc2003 Iustin Pop
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1555 aa1d552d Iustin Pop
      where _types = ipol::Types.IPolicy
1556 aa1d552d Iustin Pop
1557 aa1d552d Iustin Pop
prop_Types_EvacMode_serialisation em =
1558 aa1d552d Iustin Pop
  case J.readJSON (J.showJSON em) of
1559 aa1d552d Iustin Pop
    J.Ok p -> p ==? em
1560 96bc2003 Iustin Pop
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1561 aa1d552d Iustin Pop
      where _types = em::Types.EvacMode
1562 aa1d552d Iustin Pop
1563 0047d4e2 Iustin Pop
prop_Types_opToResult op =
1564 d5dfae0a Iustin Pop
  case op of
1565 d5dfae0a Iustin Pop
    Types.OpFail _ -> Types.isBad r
1566 d5dfae0a Iustin Pop
    Types.OpGood v -> case r of
1567 d5dfae0a Iustin Pop
                        Types.Bad _ -> False
1568 d5dfae0a Iustin Pop
                        Types.Ok v' -> v == v'
1569 d5dfae0a Iustin Pop
  where r = Types.opToResult op
1570 d5dfae0a Iustin Pop
        _types = op::Types.OpResult Int
1571 0047d4e2 Iustin Pop
1572 0047d4e2 Iustin Pop
prop_Types_eitherToResult ei =
1573 d5dfae0a Iustin Pop
  case ei of
1574 d5dfae0a Iustin Pop
    Left _ -> Types.isBad r
1575 d5dfae0a Iustin Pop
    Right v -> case r of
1576 d5dfae0a Iustin Pop
                 Types.Bad _ -> False
1577 d5dfae0a Iustin Pop
                 Types.Ok v' -> v == v'
1578 0047d4e2 Iustin Pop
    where r = Types.eitherToResult ei
1579 0047d4e2 Iustin Pop
          _types = ei::Either String Int
1580 3c002a13 Iustin Pop
1581 23fe06c2 Iustin Pop
testSuite "Types"
1582 d5dfae0a Iustin Pop
            [ 'prop_Types_AllocPolicy_serialisation
1583 d5dfae0a Iustin Pop
            , 'prop_Types_DiskTemplate_serialisation
1584 aa1d552d Iustin Pop
            , 'prop_Types_ISpec_serialisation
1585 aa1d552d Iustin Pop
            , 'prop_Types_IPolicy_serialisation
1586 aa1d552d Iustin Pop
            , 'prop_Types_EvacMode_serialisation
1587 d5dfae0a Iustin Pop
            , 'prop_Types_opToResult
1588 d5dfae0a Iustin Pop
            , 'prop_Types_eitherToResult
1589 d5dfae0a Iustin Pop
            ]
1590 8b5a517a Iustin Pop
1591 8b5a517a Iustin Pop
-- ** CLI tests
1592 8b5a517a Iustin Pop
1593 8b5a517a Iustin Pop
-- | Test correct parsing.
1594 8b5a517a Iustin Pop
prop_CLI_parseISpec descr dsk mem cpu =
1595 8b5a517a Iustin Pop
  let str = printf "%d,%d,%d" dsk mem cpu
1596 8b5a517a Iustin Pop
  in CLI.parseISpecString descr str ==? Types.Ok (Types.RSpec cpu mem dsk)
1597 8b5a517a Iustin Pop
1598 8b5a517a Iustin Pop
-- | Test parsing failure due to wrong section count.
1599 8b5a517a Iustin Pop
prop_CLI_parseISpecFail descr =
1600 8b5a517a Iustin Pop
  forAll (choose (0,100) `suchThat` ((/=) 3)) $ \nelems ->
1601 8b5a517a Iustin Pop
  forAll (replicateM nelems arbitrary) $ \values ->
1602 8b5a517a Iustin Pop
  let str = intercalate "," $ map show (values::[Int])
1603 8b5a517a Iustin Pop
  in case CLI.parseISpecString descr str of
1604 8b5a517a Iustin Pop
       Types.Ok v -> failTest $ "Expected failure, got " ++ show v
1605 8b5a517a Iustin Pop
       _ -> property True
1606 8b5a517a Iustin Pop
1607 a7ea861a Iustin Pop
-- | Test parseYesNo.
1608 a7ea861a Iustin Pop
prop_CLI_parseYesNo def testval val =
1609 a7ea861a Iustin Pop
  forAll (elements [val, "yes", "no"]) $ \actual_val ->
1610 a7ea861a Iustin Pop
  if testval
1611 a7ea861a Iustin Pop
    then CLI.parseYesNo def Nothing ==? Types.Ok def
1612 a7ea861a Iustin Pop
    else let result = CLI.parseYesNo def (Just actual_val)
1613 a7ea861a Iustin Pop
         in if actual_val `elem` ["yes", "no"]
1614 a7ea861a Iustin Pop
              then result ==? Types.Ok (actual_val == "yes")
1615 a7ea861a Iustin Pop
              else property $ Types.isBad result
1616 a7ea861a Iustin Pop
1617 89298c04 Iustin Pop
-- | Helper to check for correct parsing of string arg.
1618 89298c04 Iustin Pop
checkStringArg val (opt, fn) =
1619 89298c04 Iustin Pop
  let GetOpt.Option _ longs _ _ = opt
1620 89298c04 Iustin Pop
  in case longs of
1621 89298c04 Iustin Pop
       [] -> failTest "no long options?"
1622 89298c04 Iustin Pop
       cmdarg:_ ->
1623 89298c04 Iustin Pop
         case CLI.parseOptsInner ["--" ++ cmdarg ++ "=" ++ val] "prog" [opt] of
1624 89298c04 Iustin Pop
           Left e -> failTest $ "Failed to parse option: " ++ show e
1625 89298c04 Iustin Pop
           Right (options, _) -> fn options ==? Just val
1626 89298c04 Iustin Pop
1627 89298c04 Iustin Pop
-- | Test a few string arguments.
1628 89298c04 Iustin Pop
prop_CLI_StringArg argument =
1629 89298c04 Iustin Pop
  let args = [ (CLI.oDataFile,      CLI.optDataFile)
1630 89298c04 Iustin Pop
             , (CLI.oDynuFile,      CLI.optDynuFile)
1631 89298c04 Iustin Pop
             , (CLI.oSaveCluster,   CLI.optSaveCluster)
1632 89298c04 Iustin Pop
             , (CLI.oReplay,        CLI.optReplay)
1633 89298c04 Iustin Pop
             , (CLI.oPrintCommands, CLI.optShowCmds)
1634 89298c04 Iustin Pop
             , (CLI.oLuxiSocket,    CLI.optLuxi)
1635 89298c04 Iustin Pop
             ]
1636 89298c04 Iustin Pop
  in conjoin $ map (checkStringArg argument) args
1637 89298c04 Iustin Pop
1638 a292b4e0 Iustin Pop
-- | Helper to test that a given option is accepted OK with quick exit.
1639 a292b4e0 Iustin Pop
checkEarlyExit name options param =
1640 a292b4e0 Iustin Pop
  case CLI.parseOptsInner [param] name options of
1641 a292b4e0 Iustin Pop
    Left (code, _) -> if code == 0
1642 a292b4e0 Iustin Pop
                          then property True
1643 a292b4e0 Iustin Pop
                          else failTest $ "Program " ++ name ++
1644 a292b4e0 Iustin Pop
                                 " returns invalid code " ++ show code ++
1645 a292b4e0 Iustin Pop
                                 " for option " ++ param
1646 a292b4e0 Iustin Pop
    _ -> failTest $ "Program " ++ name ++ " doesn't consider option " ++
1647 a292b4e0 Iustin Pop
         param ++ " as early exit one"
1648 a292b4e0 Iustin Pop
1649 a292b4e0 Iustin Pop
-- | Test that all binaries support some common options. There is
1650 a292b4e0 Iustin Pop
-- nothing actually random about this test...
1651 a292b4e0 Iustin Pop
prop_CLI_stdopts =
1652 a292b4e0 Iustin Pop
  let params = ["-h", "--help", "-V", "--version"]
1653 a292b4e0 Iustin Pop
      opts = map (\(name, (_, o)) -> (name, o)) Program.personalities
1654 a292b4e0 Iustin Pop
      -- apply checkEarlyExit across the cartesian product of params and opts
1655 a292b4e0 Iustin Pop
  in conjoin [checkEarlyExit n o p | p <- params, (n, o) <- opts]
1656 a292b4e0 Iustin Pop
1657 8b5a517a Iustin Pop
testSuite "CLI"
1658 8b5a517a Iustin Pop
          [ 'prop_CLI_parseISpec
1659 8b5a517a Iustin Pop
          , 'prop_CLI_parseISpecFail
1660 a7ea861a Iustin Pop
          , 'prop_CLI_parseYesNo
1661 89298c04 Iustin Pop
          , 'prop_CLI_StringArg
1662 a292b4e0 Iustin Pop
          , 'prop_CLI_stdopts
1663 8b5a517a Iustin Pop
          ]
1664 3ad57194 Iustin Pop
1665 3ad57194 Iustin Pop
-- * JSON tests
1666 3ad57194 Iustin Pop
1667 3ad57194 Iustin Pop
prop_JSON_toArray :: [Int] -> Property
1668 3ad57194 Iustin Pop
prop_JSON_toArray intarr =
1669 3ad57194 Iustin Pop
  let arr = map J.showJSON intarr in
1670 3ad57194 Iustin Pop
  case JSON.toArray (J.JSArray arr) of
1671 3ad57194 Iustin Pop
    Types.Ok arr' -> arr ==? arr'
1672 3ad57194 Iustin Pop
    Types.Bad err -> failTest $ "Failed to parse array: " ++ err
1673 3ad57194 Iustin Pop
1674 3ad57194 Iustin Pop
prop_JSON_toArrayFail :: Int -> String -> Bool -> Property
1675 3ad57194 Iustin Pop
prop_JSON_toArrayFail i s b =
1676 3ad57194 Iustin Pop
  -- poor man's instance Arbitrary JSValue
1677 3ad57194 Iustin Pop
  forAll (elements [J.showJSON i, J.showJSON s, J.showJSON b]) $ \item ->
1678 3ad57194 Iustin Pop
  case JSON.toArray item of
1679 3ad57194 Iustin Pop
    Types.Bad _ -> property True
1680 3ad57194 Iustin Pop
    Types.Ok result -> failTest $ "Unexpected parse, got " ++ show result
1681 3ad57194 Iustin Pop
1682 3ad57194 Iustin Pop
testSuite "JSON"
1683 3ad57194 Iustin Pop
          [ 'prop_JSON_toArray
1684 3ad57194 Iustin Pop
          , 'prop_JSON_toArrayFail
1685 3ad57194 Iustin Pop
          ]