Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 3c1e4af0

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