Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 981bb5cf

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