Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 468b828e

History | View | Annotate | Download (57.7 kB)

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