Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (60.7 kB)

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