Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (62.2 kB)

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