Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (62.3 kB)

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