Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QC.hs @ 4a1dc2bf

History | View | Annotate | Download (78.7 kB)

1 23fe06c2 Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 fce98abd Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans -fno-warn-unused-imports #-}
3 fce98abd Iustin Pop
4 fce98abd Iustin Pop
-- FIXME: should remove the no-warn-unused-imports option, once we get
5 fce98abd Iustin Pop
-- around to testing function from all modules; until then, we keep
6 fce98abd Iustin Pop
-- the (unused) imports here to generate correct coverage (0 for
7 fce98abd Iustin Pop
-- modules we don't use)
8 23fe06c2 Iustin Pop
9 525bfb36 Iustin Pop
{-| Unittests for ganeti-htools.
10 e2fa2baf Iustin Pop
11 e2fa2baf Iustin Pop
-}
12 e2fa2baf Iustin Pop
13 e2fa2baf Iustin Pop
{-
14 e2fa2baf Iustin Pop
15 d6eec019 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
16 e2fa2baf Iustin Pop
17 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
18 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
19 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
20 e2fa2baf Iustin Pop
(at your option) any later version.
21 e2fa2baf Iustin Pop
22 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
23 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
24 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
25 e2fa2baf Iustin Pop
General Public License for more details.
26 e2fa2baf Iustin Pop
27 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
28 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
29 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
30 e2fa2baf Iustin Pop
02110-1301, USA.
31 e2fa2baf Iustin Pop
32 e2fa2baf Iustin Pop
-}
33 e2fa2baf Iustin Pop
34 15f4c8ca Iustin Pop
module Ganeti.HTools.QC
35 d5dfae0a Iustin Pop
  ( testUtils
36 d5dfae0a Iustin Pop
  , testPeerMap
37 d5dfae0a Iustin Pop
  , testContainer
38 d5dfae0a Iustin Pop
  , testInstance
39 d5dfae0a Iustin Pop
  , testNode
40 d5dfae0a Iustin Pop
  , testText
41 e1dde6ad Iustin Pop
  , testSimu
42 d5dfae0a Iustin Pop
  , testOpCodes
43 d5dfae0a Iustin Pop
  , testJobs
44 d5dfae0a Iustin Pop
  , testCluster
45 d5dfae0a Iustin Pop
  , testLoader
46 d5dfae0a Iustin Pop
  , testTypes
47 8b5a517a Iustin Pop
  , testCLI
48 3ad57194 Iustin Pop
  , testJSON
49 2c4eb054 Iustin Pop
  , testLuxi
50 c5b4a186 Iustin Pop
  , testSsconf
51 66f74cae Agata Murawska
  , testRpc
52 dc6a0f82 Iustin Pop
  , testQlang
53 d5dfae0a Iustin Pop
  ) where
54 15f4c8ca Iustin Pop
55 60f7f6a4 Iustin Pop
import qualified Test.HUnit as HUnit
56 15f4c8ca Iustin Pop
import Test.QuickCheck
57 66f74cae Agata Murawska
import Test.QuickCheck.Monadic (assert, monadicIO, run, stop)
58 e1dde6ad Iustin Pop
import Text.Printf (printf)
59 9990c068 Iustin Pop
import Data.List (intercalate, nub, isPrefixOf, sort, (\\))
60 15f4c8ca Iustin Pop
import Data.Maybe
61 f2374060 Iustin Pop
import qualified Data.Set as Set
62 88f25dd0 Iustin Pop
import Control.Monad
63 5cefb2b2 Iustin Pop
import Control.Applicative
64 89298c04 Iustin Pop
import qualified System.Console.GetOpt as GetOpt
65 88f25dd0 Iustin Pop
import qualified Text.JSON as J
66 8fcf251f Iustin Pop
import qualified Data.Map
67 3fea6959 Iustin Pop
import qualified Data.IntMap as IntMap
68 13f2321c Iustin Pop
import Control.Concurrent (forkIO)
69 13f2321c Iustin Pop
import Control.Exception (bracket, catchJust)
70 13f2321c Iustin Pop
import System.Directory (getTemporaryDirectory, removeFile)
71 60f7f6a4 Iustin Pop
import System.Environment (getEnv)
72 60f7f6a4 Iustin Pop
import System.Exit (ExitCode(..))
73 13f2321c Iustin Pop
import System.IO (hClose, openTempFile)
74 60f7f6a4 Iustin Pop
import System.IO.Error (isEOFErrorType, ioeGetErrorType, isDoesNotExistError)
75 60f7f6a4 Iustin Pop
import System.Process (readProcessWithExitCode)
76 89298c04 Iustin Pop
77 96eccc1f Iustin Pop
import qualified Ganeti.Confd as Confd
78 96eccc1f Iustin Pop
import qualified Ganeti.Config as Config
79 96eccc1f Iustin Pop
import qualified Ganeti.Daemon as Daemon
80 96eccc1f Iustin Pop
import qualified Ganeti.Hash as Hash
81 2fc5653f Iustin Pop
import qualified Ganeti.BasicTypes as BasicTypes
82 db079755 Iustin Pop
import qualified Ganeti.Jobs as Jobs
83 96eccc1f Iustin Pop
import qualified Ganeti.Logging as Logging
84 cdd495ae Iustin Pop
import qualified Ganeti.Luxi as Luxi
85 96eccc1f Iustin Pop
import qualified Ganeti.Objects as Objects
86 96eccc1f Iustin Pop
import qualified Ganeti.OpCodes as OpCodes
87 dc6a0f82 Iustin Pop
import qualified Ganeti.Qlang as Qlang
88 d4709cce Agata Murawska
import qualified Ganeti.Rpc as Rpc
89 96eccc1f Iustin Pop
import qualified Ganeti.Runtime as Runtime
90 c5b4a186 Iustin Pop
import qualified Ganeti.Ssconf as Ssconf
91 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.CLI as CLI
92 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
93 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Container as Container
94 223dbe53 Iustin Pop
import qualified Ganeti.HTools.ExtLoader
95 96eccc1f Iustin Pop
import qualified Ganeti.HTools.Group as Group
96 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.IAlloc as IAlloc
97 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
98 b69be409 Iustin Pop
import qualified Ganeti.HTools.JSON as JSON
99 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Loader as Loader
100 cdd495ae Iustin Pop
import qualified Ganeti.HTools.Luxi as HTools.Luxi
101 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Node as Node
102 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.PeerMap as PeerMap
103 c478f837 Iustin Pop
import qualified Ganeti.HTools.Rapi
104 e1dde6ad Iustin Pop
import qualified Ganeti.HTools.Simu as Simu
105 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Text as Text
106 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Types as Types
107 15f4c8ca Iustin Pop
import qualified Ganeti.HTools.Utils as Utils
108 223dbe53 Iustin Pop
import qualified Ganeti.HTools.Version
109 e82271f8 Iustin Pop
import qualified Ganeti.Constants as C
110 15f4c8ca Iustin Pop
111 a292b4e0 Iustin Pop
import qualified Ganeti.HTools.Program as Program
112 33b9d92d Iustin Pop
import qualified Ganeti.HTools.Program.Hail
113 33b9d92d Iustin Pop
import qualified Ganeti.HTools.Program.Hbal
114 33b9d92d Iustin Pop
import qualified Ganeti.HTools.Program.Hscan
115 33b9d92d Iustin Pop
import qualified Ganeti.HTools.Program.Hspace
116 33b9d92d Iustin Pop
117 23fe06c2 Iustin Pop
import Ganeti.HTools.QCHelper (testSuite)
118 8e4f6d56 Iustin Pop
119 3fea6959 Iustin Pop
-- * Constants
120 3fea6959 Iustin Pop
121 525bfb36 Iustin Pop
-- | Maximum memory (1TiB, somewhat random value).
122 8fcf251f Iustin Pop
maxMem :: Int
123 8fcf251f Iustin Pop
maxMem = 1024 * 1024
124 8fcf251f Iustin Pop
125 525bfb36 Iustin Pop
-- | Maximum disk (8TiB, somewhat random value).
126 8fcf251f Iustin Pop
maxDsk :: Int
127 49f9627a Iustin Pop
maxDsk = 1024 * 1024 * 8
128 8fcf251f Iustin Pop
129 525bfb36 Iustin Pop
-- | Max CPUs (1024, somewhat random value).
130 8fcf251f Iustin Pop
maxCpu :: Int
131 8fcf251f Iustin Pop
maxCpu = 1024
132 8fcf251f Iustin Pop
133 c22d4dd4 Iustin Pop
-- | Max vcpu ratio (random value).
134 c22d4dd4 Iustin Pop
maxVcpuRatio :: Double
135 c22d4dd4 Iustin Pop
maxVcpuRatio = 1024.0
136 c22d4dd4 Iustin Pop
137 c22d4dd4 Iustin Pop
-- | Max spindle ratio (random value).
138 c22d4dd4 Iustin Pop
maxSpindleRatio :: Double
139 c22d4dd4 Iustin Pop
maxSpindleRatio = 1024.0
140 c22d4dd4 Iustin Pop
141 5cefb2b2 Iustin Pop
-- | Max nodes, used just to limit arbitrary instances for smaller
142 5cefb2b2 Iustin Pop
-- opcode definitions (e.g. list of nodes in OpTestDelay).
143 5cefb2b2 Iustin Pop
maxNodes :: Int
144 5cefb2b2 Iustin Pop
maxNodes = 32
145 5cefb2b2 Iustin Pop
146 5cefb2b2 Iustin Pop
-- | Max opcodes or jobs in a submit job and submit many jobs.
147 5cefb2b2 Iustin Pop
maxOpCodes :: Int
148 5cefb2b2 Iustin Pop
maxOpCodes = 16
149 5cefb2b2 Iustin Pop
150 7806125e Iustin Pop
-- | All disk templates (used later)
151 7806125e Iustin Pop
allDiskTemplates :: [Types.DiskTemplate]
152 7806125e Iustin Pop
allDiskTemplates = [minBound..maxBound]
153 7806125e Iustin Pop
154 6cff91f5 Iustin Pop
-- | Null iPolicy, and by null we mean very liberal.
155 fce98abd Iustin Pop
nullIPolicy :: Types.IPolicy
156 6cff91f5 Iustin Pop
nullIPolicy = Types.IPolicy
157 6cff91f5 Iustin Pop
  { Types.iPolicyMinSpec = Types.ISpec { Types.iSpecMemorySize = 0
158 6cff91f5 Iustin Pop
                                       , Types.iSpecCpuCount   = 0
159 6cff91f5 Iustin Pop
                                       , Types.iSpecDiskSize   = 0
160 6cff91f5 Iustin Pop
                                       , Types.iSpecDiskCount  = 0
161 6cff91f5 Iustin Pop
                                       , Types.iSpecNicCount   = 0
162 d953a965 Renรฉ Nussbaumer
                                       , Types.iSpecSpindleUse = 0
163 6cff91f5 Iustin Pop
                                       }
164 6cff91f5 Iustin Pop
  , Types.iPolicyMaxSpec = Types.ISpec { Types.iSpecMemorySize = maxBound
165 6cff91f5 Iustin Pop
                                       , Types.iSpecCpuCount   = maxBound
166 6cff91f5 Iustin Pop
                                       , Types.iSpecDiskSize   = maxBound
167 6cff91f5 Iustin Pop
                                       , Types.iSpecDiskCount  = C.maxDisks
168 6cff91f5 Iustin Pop
                                       , Types.iSpecNicCount   = C.maxNics
169 d953a965 Renรฉ Nussbaumer
                                       , Types.iSpecSpindleUse = maxBound
170 6cff91f5 Iustin Pop
                                       }
171 6cff91f5 Iustin Pop
  , Types.iPolicyStdSpec = Types.ISpec { Types.iSpecMemorySize = Types.unitMem
172 6cff91f5 Iustin Pop
                                       , Types.iSpecCpuCount   = Types.unitCpu
173 6cff91f5 Iustin Pop
                                       , Types.iSpecDiskSize   = Types.unitDsk
174 6cff91f5 Iustin Pop
                                       , Types.iSpecDiskCount  = 1
175 6cff91f5 Iustin Pop
                                       , Types.iSpecNicCount   = 1
176 d953a965 Renรฉ Nussbaumer
                                       , Types.iSpecSpindleUse = 1
177 6cff91f5 Iustin Pop
                                       }
178 64946775 Iustin Pop
  , Types.iPolicyDiskTemplates = [minBound..maxBound]
179 c22d4dd4 Iustin Pop
  , Types.iPolicyVcpuRatio = maxVcpuRatio -- somewhat random value, high
180 c22d4dd4 Iustin Pop
                                          -- enough to not impact us
181 c22d4dd4 Iustin Pop
  , Types.iPolicySpindleRatio = maxSpindleRatio
182 6cff91f5 Iustin Pop
  }
183 6cff91f5 Iustin Pop
184 6cff91f5 Iustin Pop
185 10ef6b4e Iustin Pop
defGroup :: Group.Group
186 10ef6b4e Iustin Pop
defGroup = flip Group.setIdx 0 $
187 f3f76ccc Iustin Pop
             Group.create "default" Types.defaultGroupID Types.AllocPreferred
188 6cff91f5 Iustin Pop
                  nullIPolicy
189 10ef6b4e Iustin Pop
190 10ef6b4e Iustin Pop
defGroupList :: Group.List
191 cb0c77ff Iustin Pop
defGroupList = Container.fromList [(Group.idx defGroup, defGroup)]
192 10ef6b4e Iustin Pop
193 10ef6b4e Iustin Pop
defGroupAssoc :: Data.Map.Map String Types.Gdx
194 10ef6b4e Iustin Pop
defGroupAssoc = Data.Map.singleton (Group.uuid defGroup) (Group.idx defGroup)
195 10ef6b4e Iustin Pop
196 3fea6959 Iustin Pop
-- * Helper functions
197 3fea6959 Iustin Pop
198 525bfb36 Iustin Pop
-- | Simple checker for whether OpResult is fail or pass.
199 79a72ce7 Iustin Pop
isFailure :: Types.OpResult a -> Bool
200 79a72ce7 Iustin Pop
isFailure (Types.OpFail _) = True
201 79a72ce7 Iustin Pop
isFailure _ = False
202 79a72ce7 Iustin Pop
203 72bb6b4e Iustin Pop
-- | Checks for equality with proper annotation.
204 72bb6b4e Iustin Pop
(==?) :: (Show a, Eq a) => a -> a -> Property
205 72bb6b4e Iustin Pop
(==?) x y = printTestCase
206 72bb6b4e Iustin Pop
            ("Expected equality, but '" ++
207 72bb6b4e Iustin Pop
             show x ++ "' /= '" ++ show y ++ "'") (x == y)
208 72bb6b4e Iustin Pop
infix 3 ==?
209 72bb6b4e Iustin Pop
210 96bc2003 Iustin Pop
-- | Show a message and fail the test.
211 96bc2003 Iustin Pop
failTest :: String -> Property
212 96bc2003 Iustin Pop
failTest msg = printTestCase msg False
213 96bc2003 Iustin Pop
214 60f7f6a4 Iustin Pop
-- | Return the python binary to use. If the PYTHON environment
215 60f7f6a4 Iustin Pop
-- variable is defined, use its value, otherwise use just \"python\".
216 60f7f6a4 Iustin Pop
pythonCmd :: IO String
217 60f7f6a4 Iustin Pop
pythonCmd = catchJust (guard . isDoesNotExistError)
218 60f7f6a4 Iustin Pop
            (getEnv "PYTHON") (const (return "python"))
219 60f7f6a4 Iustin Pop
220 60f7f6a4 Iustin Pop
-- | Run Python with an expression, returning the exit code, standard
221 60f7f6a4 Iustin Pop
-- output and error.
222 60f7f6a4 Iustin Pop
runPython :: String -> String -> IO (ExitCode, String, String)
223 60f7f6a4 Iustin Pop
runPython expr stdin = do
224 60f7f6a4 Iustin Pop
  py_binary <- pythonCmd
225 60f7f6a4 Iustin Pop
  readProcessWithExitCode py_binary ["-c", expr] stdin
226 60f7f6a4 Iustin Pop
227 60f7f6a4 Iustin Pop
-- | Check python exit code, and fail via HUnit assertions if
228 60f7f6a4 Iustin Pop
-- non-zero. Otherwise, return the standard output.
229 60f7f6a4 Iustin Pop
checkPythonResult :: (ExitCode, String, String) -> IO String
230 60f7f6a4 Iustin Pop
checkPythonResult (py_code, py_stdout, py_stderr) = do
231 60f7f6a4 Iustin Pop
  HUnit.assertEqual ("python exited with error: " ++ py_stderr)
232 60f7f6a4 Iustin Pop
       ExitSuccess py_code
233 60f7f6a4 Iustin Pop
  return py_stdout
234 60f7f6a4 Iustin Pop
235 525bfb36 Iustin Pop
-- | Update an instance to be smaller than a node.
236 fce98abd Iustin Pop
setInstanceSmallerThanNode :: Node.Node
237 fce98abd Iustin Pop
                           -> Instance.Instance -> Instance.Instance
238 3fea6959 Iustin Pop
setInstanceSmallerThanNode node inst =
239 d5dfae0a Iustin Pop
  inst { Instance.mem = Node.availMem node `div` 2
240 d5dfae0a Iustin Pop
       , Instance.dsk = Node.availDisk node `div` 2
241 d5dfae0a Iustin Pop
       , Instance.vcpus = Node.availCpu node `div` 2
242 d5dfae0a Iustin Pop
       }
243 3fea6959 Iustin Pop
244 525bfb36 Iustin Pop
-- | Create an instance given its spec.
245 fce98abd Iustin Pop
createInstance :: Int -> Int -> Int -> Instance.Instance
246 3fea6959 Iustin Pop
createInstance mem dsk vcpus =
247 d5dfae0a Iustin Pop
  Instance.create "inst-unnamed" mem dsk vcpus Types.Running [] True (-1) (-1)
248 981bb5cf Renรฉ Nussbaumer
    Types.DTDrbd8 1
249 3fea6959 Iustin Pop
250 525bfb36 Iustin Pop
-- | Create a small cluster by repeating a node spec.
251 3fea6959 Iustin Pop
makeSmallCluster :: Node.Node -> Int -> Node.List
252 3fea6959 Iustin Pop
makeSmallCluster node count =
253 e73c5fe2 Iustin Pop
  let origname = Node.name node
254 e73c5fe2 Iustin Pop
      origalias = Node.alias node
255 e73c5fe2 Iustin Pop
      nodes = map (\idx -> node { Node.name = origname ++ "-" ++ show idx
256 e73c5fe2 Iustin Pop
                                , Node.alias = origalias ++ "-" ++ show idx })
257 e73c5fe2 Iustin Pop
              [1..count]
258 e73c5fe2 Iustin Pop
      fn = flip Node.buildPeers Container.empty
259 e73c5fe2 Iustin Pop
      namelst = map (\n -> (Node.name n, fn n)) nodes
260 d5dfae0a Iustin Pop
      (_, nlst) = Loader.assignIndices namelst
261 d5dfae0a Iustin Pop
  in nlst
262 3fea6959 Iustin Pop
263 3603605a Iustin Pop
-- | Make a small cluster, both nodes and instances.
264 3603605a Iustin Pop
makeSmallEmptyCluster :: Node.Node -> Int -> Instance.Instance
265 3603605a Iustin Pop
                      -> (Node.List, Instance.List, Instance.Instance)
266 3603605a Iustin Pop
makeSmallEmptyCluster node count inst =
267 3603605a Iustin Pop
  (makeSmallCluster node count, Container.empty,
268 3603605a Iustin Pop
   setInstanceSmallerThanNode node inst)
269 3603605a Iustin Pop
270 525bfb36 Iustin Pop
-- | Checks if a node is "big" enough.
271 d6f9f5bd Iustin Pop
isNodeBig :: Int -> Node.Node -> Bool
272 d6f9f5bd Iustin Pop
isNodeBig size node = Node.availDisk node > size * Types.unitDsk
273 3fea6959 Iustin Pop
                      && Node.availMem node > size * Types.unitMem
274 3fea6959 Iustin Pop
                      && Node.availCpu node > size * Types.unitCpu
275 3fea6959 Iustin Pop
276 e08424a8 Guido Trotter
canBalance :: Cluster.Table -> Bool -> Bool -> Bool -> Bool
277 e08424a8 Guido Trotter
canBalance tbl dm im evac = isJust $ Cluster.tryBalance tbl dm im evac 0 0
278 3fea6959 Iustin Pop
279 f4161783 Iustin Pop
-- | Assigns a new fresh instance to a cluster; this is not
280 525bfb36 Iustin Pop
-- allocation, so no resource checks are done.
281 f4161783 Iustin Pop
assignInstance :: Node.List -> Instance.List -> Instance.Instance ->
282 f4161783 Iustin Pop
                  Types.Idx -> Types.Idx ->
283 f4161783 Iustin Pop
                  (Node.List, Instance.List)
284 f4161783 Iustin Pop
assignInstance nl il inst pdx sdx =
285 f4161783 Iustin Pop
  let pnode = Container.find pdx nl
286 f4161783 Iustin Pop
      snode = Container.find sdx nl
287 f4161783 Iustin Pop
      maxiidx = if Container.null il
288 d5dfae0a Iustin Pop
                  then 0
289 d5dfae0a Iustin Pop
                  else fst (Container.findMax il) + 1
290 f4161783 Iustin Pop
      inst' = inst { Instance.idx = maxiidx,
291 f4161783 Iustin Pop
                     Instance.pNode = pdx, Instance.sNode = sdx }
292 f4161783 Iustin Pop
      pnode' = Node.setPri pnode inst'
293 f4161783 Iustin Pop
      snode' = Node.setSec snode inst'
294 f4161783 Iustin Pop
      nl' = Container.addTwo pdx pnode' sdx snode' nl
295 f4161783 Iustin Pop
      il' = Container.add maxiidx inst' il
296 f4161783 Iustin Pop
  in (nl', il')
297 f4161783 Iustin Pop
298 a2a0bcd8 Iustin Pop
-- | Generates a list of a given size with non-duplicate elements.
299 a2a0bcd8 Iustin Pop
genUniquesList :: (Eq a, Arbitrary a) => Int -> Gen [a]
300 a2a0bcd8 Iustin Pop
genUniquesList cnt =
301 a2a0bcd8 Iustin Pop
  foldM (\lst _ -> do
302 a2a0bcd8 Iustin Pop
           newelem <- arbitrary `suchThat` (`notElem` lst)
303 a2a0bcd8 Iustin Pop
           return (newelem:lst)) [] [1..cnt]
304 a2a0bcd8 Iustin Pop
305 ac1c0a07 Iustin Pop
-- | Checks if an instance is mirrored.
306 ac1c0a07 Iustin Pop
isMirrored :: Instance.Instance -> Bool
307 fafd0773 Iustin Pop
isMirrored = (/= Types.MirrorNone) . Instance.mirrorType
308 ac1c0a07 Iustin Pop
309 ac1c0a07 Iustin Pop
-- | Returns the possible change node types for a disk template.
310 ac1c0a07 Iustin Pop
evacModeOptions :: Types.MirrorType -> [Types.EvacMode]
311 ac1c0a07 Iustin Pop
evacModeOptions Types.MirrorNone     = []
312 ac1c0a07 Iustin Pop
evacModeOptions Types.MirrorInternal = [minBound..maxBound] -- DRBD can do all
313 ac1c0a07 Iustin Pop
evacModeOptions Types.MirrorExternal = [Types.ChangePrimary, Types.ChangeAll]
314 ac1c0a07 Iustin Pop
315 3fea6959 Iustin Pop
-- * Arbitrary instances
316 3fea6959 Iustin Pop
317 525bfb36 Iustin Pop
-- | Defines a DNS name.
318 a070c426 Iustin Pop
newtype DNSChar = DNSChar { dnsGetChar::Char }
319 525bfb36 Iustin Pop
320 a070c426 Iustin Pop
instance Arbitrary DNSChar where
321 d5dfae0a Iustin Pop
  arbitrary = do
322 d5dfae0a Iustin Pop
    x <- elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
323 d5dfae0a Iustin Pop
    return (DNSChar x)
324 a070c426 Iustin Pop
325 13f2321c Iustin Pop
instance Show DNSChar where
326 13f2321c Iustin Pop
  show = show . dnsGetChar
327 13f2321c Iustin Pop
328 a2a0bcd8 Iustin Pop
-- | Generates a single name component.
329 a070c426 Iustin Pop
getName :: Gen String
330 a070c426 Iustin Pop
getName = do
331 a070c426 Iustin Pop
  n <- choose (1, 64)
332 5cefb2b2 Iustin Pop
  dn <- vector n
333 a070c426 Iustin Pop
  return (map dnsGetChar dn)
334 a070c426 Iustin Pop
335 a2a0bcd8 Iustin Pop
-- | Generates an entire FQDN.
336 a070c426 Iustin Pop
getFQDN :: Gen String
337 a070c426 Iustin Pop
getFQDN = do
338 a070c426 Iustin Pop
  ncomps <- choose (1, 4)
339 5cefb2b2 Iustin Pop
  names <- vectorOf ncomps getName
340 a2a0bcd8 Iustin Pop
  return $ intercalate "." names
341 a070c426 Iustin Pop
342 5cefb2b2 Iustin Pop
-- | Combinator that generates a 'Maybe' using a sub-combinator.
343 5cefb2b2 Iustin Pop
getMaybe :: Gen a -> Gen (Maybe a)
344 5cefb2b2 Iustin Pop
getMaybe subgen = do
345 5cefb2b2 Iustin Pop
  bool <- arbitrary
346 5cefb2b2 Iustin Pop
  if bool
347 5cefb2b2 Iustin Pop
    then Just <$> subgen
348 5cefb2b2 Iustin Pop
    else return Nothing
349 5cefb2b2 Iustin Pop
350 5cefb2b2 Iustin Pop
-- | Generates a fields list. This uses the same character set as a
351 5cefb2b2 Iustin Pop
-- DNS name (just for simplicity).
352 5cefb2b2 Iustin Pop
getFields :: Gen [String]
353 5cefb2b2 Iustin Pop
getFields = do
354 5cefb2b2 Iustin Pop
  n <- choose (1, 32)
355 5cefb2b2 Iustin Pop
  vectorOf n getName
356 5cefb2b2 Iustin Pop
357 dce9bbb3 Iustin Pop
-- | Defines a tag type.
358 dce9bbb3 Iustin Pop
newtype TagChar = TagChar { tagGetChar :: Char }
359 dce9bbb3 Iustin Pop
360 dce9bbb3 Iustin Pop
-- | All valid tag chars. This doesn't need to match _exactly_
361 dce9bbb3 Iustin Pop
-- Ganeti's own tag regex, just enough for it to be close.
362 dce9bbb3 Iustin Pop
tagChar :: [Char]
363 dce9bbb3 Iustin Pop
tagChar = ['a'..'z'] ++ ['A'..'Z'] ++ ['0'..'9'] ++ ".+*/:@-"
364 dce9bbb3 Iustin Pop
365 dce9bbb3 Iustin Pop
instance Arbitrary TagChar where
366 dce9bbb3 Iustin Pop
  arbitrary = do
367 dce9bbb3 Iustin Pop
    c <- elements tagChar
368 dce9bbb3 Iustin Pop
    return (TagChar c)
369 dce9bbb3 Iustin Pop
370 dce9bbb3 Iustin Pop
-- | Generates a tag
371 dce9bbb3 Iustin Pop
genTag :: Gen [TagChar]
372 dce9bbb3 Iustin Pop
genTag = do
373 dce9bbb3 Iustin Pop
  -- the correct value would be C.maxTagLen, but that's way too
374 dce9bbb3 Iustin Pop
  -- verbose in unittests, and at the moment I don't see any possible
375 dce9bbb3 Iustin Pop
  -- bugs with longer tags and the way we use tags in htools
376 dce9bbb3 Iustin Pop
  n <- choose (1, 10)
377 dce9bbb3 Iustin Pop
  vector n
378 dce9bbb3 Iustin Pop
379 dce9bbb3 Iustin Pop
-- | Generates a list of tags (correctly upper bounded).
380 dce9bbb3 Iustin Pop
genTags :: Gen [String]
381 dce9bbb3 Iustin Pop
genTags = do
382 dce9bbb3 Iustin Pop
  -- the correct value would be C.maxTagsPerObj, but per the comment
383 dce9bbb3 Iustin Pop
  -- in genTag, we don't use tags enough in htools to warrant testing
384 dce9bbb3 Iustin Pop
  -- such big values
385 dce9bbb3 Iustin Pop
  n <- choose (0, 10::Int)
386 dce9bbb3 Iustin Pop
  tags <- mapM (const genTag) [1..n]
387 dce9bbb3 Iustin Pop
  return $ map (map tagGetChar) tags
388 dce9bbb3 Iustin Pop
389 7dd14211 Agata Murawska
instance Arbitrary Types.InstanceStatus where
390 e1bf27bb Agata Murawska
    arbitrary = elements [minBound..maxBound]
391 7dd14211 Agata Murawska
392 59ed268d Iustin Pop
-- | Generates a random instance with maximum disk/mem/cpu values.
393 59ed268d Iustin Pop
genInstanceSmallerThan :: Int -> Int -> Int -> Gen Instance.Instance
394 59ed268d Iustin Pop
genInstanceSmallerThan lim_mem lim_dsk lim_cpu = do
395 59ed268d Iustin Pop
  name <- getFQDN
396 59ed268d Iustin Pop
  mem <- choose (0, lim_mem)
397 59ed268d Iustin Pop
  dsk <- choose (0, lim_dsk)
398 59ed268d Iustin Pop
  run_st <- arbitrary
399 59ed268d Iustin Pop
  pn <- arbitrary
400 59ed268d Iustin Pop
  sn <- arbitrary
401 59ed268d Iustin Pop
  vcpus <- choose (0, lim_cpu)
402 64946775 Iustin Pop
  dt <- arbitrary
403 64946775 Iustin Pop
  return $ Instance.create name mem dsk vcpus run_st [] True pn sn dt 1
404 59ed268d Iustin Pop
405 59ed268d Iustin Pop
-- | Generates an instance smaller than a node.
406 59ed268d Iustin Pop
genInstanceSmallerThanNode :: Node.Node -> Gen Instance.Instance
407 59ed268d Iustin Pop
genInstanceSmallerThanNode node =
408 59ed268d Iustin Pop
  genInstanceSmallerThan (Node.availMem node `div` 2)
409 59ed268d Iustin Pop
                         (Node.availDisk node `div` 2)
410 59ed268d Iustin Pop
                         (Node.availCpu node `div` 2)
411 59ed268d Iustin Pop
412 15f4c8ca Iustin Pop
-- let's generate a random instance
413 15f4c8ca Iustin Pop
instance Arbitrary Instance.Instance where
414 59ed268d Iustin Pop
  arbitrary = genInstanceSmallerThan maxMem maxDsk maxCpu
415 15f4c8ca Iustin Pop
416 525bfb36 Iustin Pop
-- | Generas an arbitrary node based on sizing information.
417 525bfb36 Iustin Pop
genNode :: Maybe Int -- ^ Minimum node size in terms of units
418 525bfb36 Iustin Pop
        -> Maybe Int -- ^ Maximum node size (when Nothing, bounded
419 525bfb36 Iustin Pop
                     -- just by the max... constants)
420 525bfb36 Iustin Pop
        -> Gen Node.Node
421 00c75986 Iustin Pop
genNode min_multiplier max_multiplier = do
422 00c75986 Iustin Pop
  let (base_mem, base_dsk, base_cpu) =
423 d5dfae0a Iustin Pop
        case min_multiplier of
424 d5dfae0a Iustin Pop
          Just mm -> (mm * Types.unitMem,
425 d5dfae0a Iustin Pop
                      mm * Types.unitDsk,
426 d5dfae0a Iustin Pop
                      mm * Types.unitCpu)
427 d5dfae0a Iustin Pop
          Nothing -> (0, 0, 0)
428 00c75986 Iustin Pop
      (top_mem, top_dsk, top_cpu)  =
429 d5dfae0a Iustin Pop
        case max_multiplier of
430 d5dfae0a Iustin Pop
          Just mm -> (mm * Types.unitMem,
431 d5dfae0a Iustin Pop
                      mm * Types.unitDsk,
432 d5dfae0a Iustin Pop
                      mm * Types.unitCpu)
433 d5dfae0a Iustin Pop
          Nothing -> (maxMem, maxDsk, maxCpu)
434 00c75986 Iustin Pop
  name  <- getFQDN
435 00c75986 Iustin Pop
  mem_t <- choose (base_mem, top_mem)
436 00c75986 Iustin Pop
  mem_f <- choose (base_mem, mem_t)
437 00c75986 Iustin Pop
  mem_n <- choose (0, mem_t - mem_f)
438 00c75986 Iustin Pop
  dsk_t <- choose (base_dsk, top_dsk)
439 00c75986 Iustin Pop
  dsk_f <- choose (base_dsk, dsk_t)
440 00c75986 Iustin Pop
  cpu_t <- choose (base_cpu, top_cpu)
441 00c75986 Iustin Pop
  offl  <- arbitrary
442 00c75986 Iustin Pop
  let n = Node.create name (fromIntegral mem_t) mem_n mem_f
443 8bc34c7b Iustin Pop
          (fromIntegral dsk_t) dsk_f (fromIntegral cpu_t) offl 1 0
444 d6eec019 Iustin Pop
      n' = Node.setPolicy nullIPolicy n
445 d6eec019 Iustin Pop
  return $ Node.buildPeers n' Container.empty
446 00c75986 Iustin Pop
447 d6f9f5bd Iustin Pop
-- | Helper function to generate a sane node.
448 d6f9f5bd Iustin Pop
genOnlineNode :: Gen Node.Node
449 d6f9f5bd Iustin Pop
genOnlineNode = do
450 d6f9f5bd Iustin Pop
  arbitrary `suchThat` (\n -> not (Node.offline n) &&
451 d6f9f5bd Iustin Pop
                              not (Node.failN1 n) &&
452 d6f9f5bd Iustin Pop
                              Node.availDisk n > 0 &&
453 d6f9f5bd Iustin Pop
                              Node.availMem n > 0 &&
454 d6f9f5bd Iustin Pop
                              Node.availCpu n > 0)
455 d6f9f5bd Iustin Pop
456 15f4c8ca Iustin Pop
-- and a random node
457 15f4c8ca Iustin Pop
instance Arbitrary Node.Node where
458 d5dfae0a Iustin Pop
  arbitrary = genNode Nothing Nothing
459 15f4c8ca Iustin Pop
460 88f25dd0 Iustin Pop
-- replace disks
461 88f25dd0 Iustin Pop
instance Arbitrary OpCodes.ReplaceDisksMode where
462 e1bf27bb Agata Murawska
  arbitrary = elements [minBound..maxBound]
463 88f25dd0 Iustin Pop
464 4a1dc2bf Iustin Pop
instance Arbitrary OpCodes.DiskIndex where
465 4a1dc2bf Iustin Pop
  arbitrary = choose (0, C.maxDisks - 1) >>= OpCodes.mkDiskIndex
466 4a1dc2bf Iustin Pop
467 88f25dd0 Iustin Pop
instance Arbitrary OpCodes.OpCode where
468 88f25dd0 Iustin Pop
  arbitrary = do
469 a583ec5d Iustin Pop
    op_id <- elements OpCodes.allOpIDs
470 3603605a Iustin Pop
    case op_id of
471 3603605a Iustin Pop
      "OP_TEST_DELAY" ->
472 5cefb2b2 Iustin Pop
        OpCodes.OpTestDelay <$> arbitrary <*> arbitrary
473 5cefb2b2 Iustin Pop
                 <*> resize maxNodes (listOf getFQDN)
474 3603605a Iustin Pop
      "OP_INSTANCE_REPLACE_DISKS" ->
475 5cefb2b2 Iustin Pop
        OpCodes.OpInstanceReplaceDisks <$> getFQDN <*> getMaybe getFQDN <*>
476 5cefb2b2 Iustin Pop
          arbitrary <*> resize C.maxDisks arbitrary <*> getMaybe getName
477 3603605a Iustin Pop
      "OP_INSTANCE_FAILOVER" ->
478 5cefb2b2 Iustin Pop
        OpCodes.OpInstanceFailover <$> getFQDN <*> arbitrary <*>
479 5cefb2b2 Iustin Pop
          getMaybe getFQDN
480 3603605a Iustin Pop
      "OP_INSTANCE_MIGRATE" ->
481 5cefb2b2 Iustin Pop
        OpCodes.OpInstanceMigrate <$> getFQDN <*> arbitrary <*>
482 5cefb2b2 Iustin Pop
          arbitrary <*> arbitrary <*> getMaybe getFQDN
483 3603605a Iustin Pop
      _ -> fail "Wrong opcode"
484 88f25dd0 Iustin Pop
485 db079755 Iustin Pop
instance Arbitrary Jobs.OpStatus where
486 db079755 Iustin Pop
  arbitrary = elements [minBound..maxBound]
487 db079755 Iustin Pop
488 db079755 Iustin Pop
instance Arbitrary Jobs.JobStatus where
489 db079755 Iustin Pop
  arbitrary = elements [minBound..maxBound]
490 db079755 Iustin Pop
491 525bfb36 Iustin Pop
newtype SmallRatio = SmallRatio Double deriving Show
492 525bfb36 Iustin Pop
instance Arbitrary SmallRatio where
493 d5dfae0a Iustin Pop
  arbitrary = do
494 d5dfae0a Iustin Pop
    v <- choose (0, 1)
495 d5dfae0a Iustin Pop
    return $ SmallRatio v
496 525bfb36 Iustin Pop
497 3c002a13 Iustin Pop
instance Arbitrary Types.AllocPolicy where
498 3c002a13 Iustin Pop
  arbitrary = elements [minBound..maxBound]
499 3c002a13 Iustin Pop
500 3c002a13 Iustin Pop
instance Arbitrary Types.DiskTemplate where
501 3c002a13 Iustin Pop
  arbitrary = elements [minBound..maxBound]
502 3c002a13 Iustin Pop
503 0047d4e2 Iustin Pop
instance Arbitrary Types.FailMode where
504 d5dfae0a Iustin Pop
  arbitrary = elements [minBound..maxBound]
505 0047d4e2 Iustin Pop
506 aa1d552d Iustin Pop
instance Arbitrary Types.EvacMode where
507 aa1d552d Iustin Pop
  arbitrary = elements [minBound..maxBound]
508 aa1d552d Iustin Pop
509 0047d4e2 Iustin Pop
instance Arbitrary a => Arbitrary (Types.OpResult a) where
510 d5dfae0a Iustin Pop
  arbitrary = arbitrary >>= \c ->
511 3603605a Iustin Pop
              if c
512 5cefb2b2 Iustin Pop
                then Types.OpGood <$> arbitrary
513 5cefb2b2 Iustin Pop
                else Types.OpFail <$> arbitrary
514 0047d4e2 Iustin Pop
515 00b70680 Iustin Pop
instance Arbitrary Types.ISpec where
516 00b70680 Iustin Pop
  arbitrary = do
517 7806125e Iustin Pop
    mem_s <- arbitrary::Gen (NonNegative Int)
518 00b70680 Iustin Pop
    dsk_c <- arbitrary::Gen (NonNegative Int)
519 00b70680 Iustin Pop
    dsk_s <- arbitrary::Gen (NonNegative Int)
520 7806125e Iustin Pop
    cpu_c <- arbitrary::Gen (NonNegative Int)
521 7806125e Iustin Pop
    nic_c <- arbitrary::Gen (NonNegative Int)
522 d953a965 Renรฉ Nussbaumer
    su    <- arbitrary::Gen (NonNegative Int)
523 7806125e Iustin Pop
    return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
524 7806125e Iustin Pop
                       , Types.iSpecCpuCount   = fromIntegral cpu_c
525 00b70680 Iustin Pop
                       , Types.iSpecDiskSize   = fromIntegral dsk_s
526 00b70680 Iustin Pop
                       , Types.iSpecDiskCount  = fromIntegral dsk_c
527 7806125e Iustin Pop
                       , Types.iSpecNicCount   = fromIntegral nic_c
528 d953a965 Renรฉ Nussbaumer
                       , Types.iSpecSpindleUse = fromIntegral su
529 00b70680 Iustin Pop
                       }
530 00b70680 Iustin Pop
531 7806125e Iustin Pop
-- | Generates an ispec bigger than the given one.
532 7806125e Iustin Pop
genBiggerISpec :: Types.ISpec -> Gen Types.ISpec
533 7806125e Iustin Pop
genBiggerISpec imin = do
534 7806125e Iustin Pop
  mem_s <- choose (Types.iSpecMemorySize imin, maxBound)
535 7806125e Iustin Pop
  dsk_c <- choose (Types.iSpecDiskCount imin, maxBound)
536 7806125e Iustin Pop
  dsk_s <- choose (Types.iSpecDiskSize imin, maxBound)
537 7806125e Iustin Pop
  cpu_c <- choose (Types.iSpecCpuCount imin, maxBound)
538 7806125e Iustin Pop
  nic_c <- choose (Types.iSpecNicCount imin, maxBound)
539 d953a965 Renรฉ Nussbaumer
  su    <- choose (Types.iSpecSpindleUse imin, maxBound)
540 7806125e Iustin Pop
  return Types.ISpec { Types.iSpecMemorySize = fromIntegral mem_s
541 7806125e Iustin Pop
                     , Types.iSpecCpuCount   = fromIntegral cpu_c
542 7806125e Iustin Pop
                     , Types.iSpecDiskSize   = fromIntegral dsk_s
543 7806125e Iustin Pop
                     , Types.iSpecDiskCount  = fromIntegral dsk_c
544 7806125e Iustin Pop
                     , Types.iSpecNicCount   = fromIntegral nic_c
545 d953a965 Renรฉ Nussbaumer
                     , Types.iSpecSpindleUse = fromIntegral su
546 7806125e Iustin Pop
                     }
547 00b70680 Iustin Pop
548 00b70680 Iustin Pop
instance Arbitrary Types.IPolicy where
549 00b70680 Iustin Pop
  arbitrary = do
550 00b70680 Iustin Pop
    imin <- arbitrary
551 7806125e Iustin Pop
    istd <- genBiggerISpec imin
552 7806125e Iustin Pop
    imax <- genBiggerISpec istd
553 7806125e Iustin Pop
    num_tmpl <- choose (0, length allDiskTemplates)
554 7806125e Iustin Pop
    dts  <- genUniquesList num_tmpl
555 c22d4dd4 Iustin Pop
    vcpu_ratio <- choose (1.0, maxVcpuRatio)
556 c22d4dd4 Iustin Pop
    spindle_ratio <- choose (1.0, maxSpindleRatio)
557 00b70680 Iustin Pop
    return Types.IPolicy { Types.iPolicyMinSpec = imin
558 00b70680 Iustin Pop
                         , Types.iPolicyStdSpec = istd
559 00b70680 Iustin Pop
                         , Types.iPolicyMaxSpec = imax
560 00b70680 Iustin Pop
                         , Types.iPolicyDiskTemplates = dts
561 e8fa4ff6 Iustin Pop
                         , Types.iPolicyVcpuRatio = vcpu_ratio
562 c22d4dd4 Iustin Pop
                         , Types.iPolicySpindleRatio = spindle_ratio
563 00b70680 Iustin Pop
                         }
564 00b70680 Iustin Pop
565 66f74cae Agata Murawska
instance Arbitrary Objects.Hypervisor where
566 66f74cae Agata Murawska
  arbitrary = elements [minBound..maxBound]
567 66f74cae Agata Murawska
568 a957e150 Iustin Pop
instance Arbitrary Objects.PartialNDParams where
569 7514fe92 Iustin Pop
  arbitrary = Objects.PartialNDParams <$> arbitrary <*> arbitrary
570 a957e150 Iustin Pop
571 66f74cae Agata Murawska
instance Arbitrary Objects.Node where
572 66f74cae Agata Murawska
  arbitrary = Objects.Node <$> getFQDN <*> getFQDN <*> getFQDN
573 66f74cae Agata Murawska
              <*> arbitrary <*> arbitrary <*> arbitrary <*> getFQDN
574 66f74cae Agata Murawska
              <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
575 a957e150 Iustin Pop
              <*> arbitrary <*> arbitrary <*> getFQDN <*> arbitrary
576 f2374060 Iustin Pop
              <*> (Set.fromList <$> genTags)
577 66f74cae Agata Murawska
578 66f74cae Agata Murawska
instance Arbitrary Rpc.RpcCallAllInstancesInfo where
579 66f74cae Agata Murawska
  arbitrary = Rpc.RpcCallAllInstancesInfo <$> arbitrary
580 66f74cae Agata Murawska
581 66f74cae Agata Murawska
instance Arbitrary Rpc.RpcCallInstanceList where
582 66f74cae Agata Murawska
  arbitrary = Rpc.RpcCallInstanceList <$> arbitrary
583 66f74cae Agata Murawska
584 66f74cae Agata Murawska
instance Arbitrary Rpc.RpcCallNodeInfo where
585 66f74cae Agata Murawska
  arbitrary = Rpc.RpcCallNodeInfo <$> arbitrary <*> arbitrary
586 66f74cae Agata Murawska
587 dc6a0f82 Iustin Pop
-- | Custom 'Qlang.Filter' generator (top-level), which enforces a
588 e8a25d62 Iustin Pop
-- (sane) limit on the depth of the generated filters.
589 dc6a0f82 Iustin Pop
genFilter :: Gen Qlang.Filter
590 e8a25d62 Iustin Pop
genFilter = choose (0, 10) >>= genFilter'
591 e8a25d62 Iustin Pop
592 e8a25d62 Iustin Pop
-- | Custom generator for filters that correctly halves the state of
593 e8a25d62 Iustin Pop
-- the generators at each recursive step, per the QuickCheck
594 e8a25d62 Iustin Pop
-- documentation, in order not to run out of memory.
595 dc6a0f82 Iustin Pop
genFilter' :: Int -> Gen Qlang.Filter
596 e8a25d62 Iustin Pop
genFilter' 0 =
597 dc6a0f82 Iustin Pop
  oneof [ return Qlang.EmptyFilter
598 dc6a0f82 Iustin Pop
        , Qlang.TrueFilter     <$> getName
599 dc6a0f82 Iustin Pop
        , Qlang.EQFilter       <$> getName <*> value
600 dc6a0f82 Iustin Pop
        , Qlang.LTFilter       <$> getName <*> value
601 dc6a0f82 Iustin Pop
        , Qlang.GTFilter       <$> getName <*> value
602 dc6a0f82 Iustin Pop
        , Qlang.LEFilter       <$> getName <*> value
603 dc6a0f82 Iustin Pop
        , Qlang.GEFilter       <$> getName <*> value
604 dc6a0f82 Iustin Pop
        , Qlang.RegexpFilter   <$> getName <*> getName
605 dc6a0f82 Iustin Pop
        , Qlang.ContainsFilter <$> getName <*> value
606 e8a25d62 Iustin Pop
        ]
607 dc6a0f82 Iustin Pop
    where value = oneof [ Qlang.QuotedString <$> getName
608 dc6a0f82 Iustin Pop
                        , Qlang.NumericValue <$> arbitrary
609 e8a25d62 Iustin Pop
                        ]
610 e8a25d62 Iustin Pop
genFilter' n = do
611 dc6a0f82 Iustin Pop
  oneof [ Qlang.AndFilter  <$> vectorOf n'' (genFilter' n')
612 dc6a0f82 Iustin Pop
        , Qlang.OrFilter   <$> vectorOf n'' (genFilter' n')
613 dc6a0f82 Iustin Pop
        , Qlang.NotFilter  <$> genFilter' n'
614 e8a25d62 Iustin Pop
        ]
615 e8a25d62 Iustin Pop
  where n' = n `div` 2 -- sub-filter generator size
616 e8a25d62 Iustin Pop
        n'' = max n' 2 -- but we don't want empty or 1-element lists,
617 e8a25d62 Iustin Pop
                       -- so use this for and/or filter list length
618 e8a25d62 Iustin Pop
619 8a9ee1e9 Iustin Pop
instance Arbitrary Qlang.ItemType where
620 8a9ee1e9 Iustin Pop
  arbitrary = elements [minBound..maxBound]
621 8a9ee1e9 Iustin Pop
622 3fea6959 Iustin Pop
-- * Actual tests
623 8fcf251f Iustin Pop
624 525bfb36 Iustin Pop
-- ** Utils tests
625 525bfb36 Iustin Pop
626 468b828e Iustin Pop
-- | Helper to generate a small string that doesn't contain commas.
627 fce98abd Iustin Pop
genNonCommaString :: Gen [Char]
628 468b828e Iustin Pop
genNonCommaString = do
629 468b828e Iustin Pop
  size <- choose (0, 20) -- arbitrary max size
630 468b828e Iustin Pop
  vectorOf size (arbitrary `suchThat` ((/=) ','))
631 468b828e Iustin Pop
632 525bfb36 Iustin Pop
-- | If the list is not just an empty element, and if the elements do
633 525bfb36 Iustin Pop
-- not contain commas, then join+split should be idempotent.
634 fce98abd Iustin Pop
prop_Utils_commaJoinSplit :: Property
635 a1cd7c1e Iustin Pop
prop_Utils_commaJoinSplit =
636 468b828e Iustin Pop
  forAll (choose (0, 20)) $ \llen ->
637 468b828e Iustin Pop
  forAll (vectorOf llen genNonCommaString `suchThat` ((/=) [""])) $ \lst ->
638 d5dfae0a Iustin Pop
  Utils.sepSplit ',' (Utils.commaJoin lst) ==? lst
639 a1cd7c1e Iustin Pop
640 525bfb36 Iustin Pop
-- | Split and join should always be idempotent.
641 fce98abd Iustin Pop
prop_Utils_commaSplitJoin :: [Char] -> Property
642 72bb6b4e Iustin Pop
prop_Utils_commaSplitJoin s =
643 d5dfae0a Iustin Pop
  Utils.commaJoin (Utils.sepSplit ',' s) ==? s
644 691dcd2a Iustin Pop
645 a810ad21 Iustin Pop
-- | fromObjWithDefault, we test using the Maybe monad and an integer
646 525bfb36 Iustin Pop
-- value.
647 fce98abd Iustin Pop
prop_Utils_fromObjWithDefault :: Integer -> String -> Bool
648 a810ad21 Iustin Pop
prop_Utils_fromObjWithDefault def_value random_key =
649 d5dfae0a Iustin Pop
  -- a missing key will be returned with the default
650 b69be409 Iustin Pop
  JSON.fromObjWithDefault [] random_key def_value == Just def_value &&
651 d5dfae0a Iustin Pop
  -- a found key will be returned as is, not with default
652 b69be409 Iustin Pop
  JSON.fromObjWithDefault [(random_key, J.showJSON def_value)]
653 d5dfae0a Iustin Pop
       random_key (def_value+1) == Just def_value
654 a810ad21 Iustin Pop
655 bfe6c954 Guido Trotter
-- | Test that functional if' behaves like the syntactic sugar if.
656 72bb6b4e Iustin Pop
prop_Utils_if'if :: Bool -> Int -> Int -> Gen Prop
657 72bb6b4e Iustin Pop
prop_Utils_if'if cnd a b =
658 d5dfae0a Iustin Pop
  Utils.if' cnd a b ==? if cnd then a else b
659 bfe6c954 Guido Trotter
660 22fac87d Guido Trotter
-- | Test basic select functionality
661 72bb6b4e Iustin Pop
prop_Utils_select :: Int      -- ^ Default result
662 72bb6b4e Iustin Pop
                  -> [Int]    -- ^ List of False values
663 72bb6b4e Iustin Pop
                  -> [Int]    -- ^ List of True values
664 72bb6b4e Iustin Pop
                  -> Gen Prop -- ^ Test result
665 22fac87d Guido Trotter
prop_Utils_select def lst1 lst2 =
666 3603605a Iustin Pop
  Utils.select def (flist ++ tlist) ==? expectedresult
667 ba1260ba Iustin Pop
    where expectedresult = Utils.if' (null lst2) def (head lst2)
668 ba1260ba Iustin Pop
          flist = zip (repeat False) lst1
669 ba1260ba Iustin Pop
          tlist = zip (repeat True)  lst2
670 22fac87d Guido Trotter
671 22fac87d Guido Trotter
-- | Test basic select functionality with undefined default
672 72bb6b4e Iustin Pop
prop_Utils_select_undefd :: [Int]            -- ^ List of False values
673 22fac87d Guido Trotter
                         -> NonEmptyList Int -- ^ List of True values
674 72bb6b4e Iustin Pop
                         -> Gen Prop         -- ^ Test result
675 22fac87d Guido Trotter
prop_Utils_select_undefd lst1 (NonEmpty lst2) =
676 3603605a Iustin Pop
  Utils.select undefined (flist ++ tlist) ==? head lst2
677 ba1260ba Iustin Pop
    where flist = zip (repeat False) lst1
678 ba1260ba Iustin Pop
          tlist = zip (repeat True)  lst2
679 22fac87d Guido Trotter
680 22fac87d Guido Trotter
-- | Test basic select functionality with undefined list values
681 72bb6b4e Iustin Pop
prop_Utils_select_undefv :: [Int]            -- ^ List of False values
682 22fac87d Guido Trotter
                         -> NonEmptyList Int -- ^ List of True values
683 72bb6b4e Iustin Pop
                         -> Gen Prop         -- ^ Test result
684 22fac87d Guido Trotter
prop_Utils_select_undefv lst1 (NonEmpty lst2) =
685 72bb6b4e Iustin Pop
  Utils.select undefined cndlist ==? head lst2
686 ba1260ba Iustin Pop
    where flist = zip (repeat False) lst1
687 ba1260ba Iustin Pop
          tlist = zip (repeat True)  lst2
688 ba1260ba Iustin Pop
          cndlist = flist ++ tlist ++ [undefined]
689 bfe6c954 Guido Trotter
690 fce98abd Iustin Pop
prop_Utils_parseUnit :: NonNegative Int -> Property
691 1cb92fac Iustin Pop
prop_Utils_parseUnit (NonNegative n) =
692 1cdcf8f3 Iustin Pop
  Utils.parseUnit (show n) ==? Types.Ok n .&&.
693 1cdcf8f3 Iustin Pop
  Utils.parseUnit (show n ++ "m") ==? Types.Ok n .&&.
694 1cdcf8f3 Iustin Pop
  Utils.parseUnit (show n ++ "M") ==? Types.Ok (truncate n_mb::Int) .&&.
695 1cdcf8f3 Iustin Pop
  Utils.parseUnit (show n ++ "g") ==? Types.Ok (n*1024) .&&.
696 1cdcf8f3 Iustin Pop
  Utils.parseUnit (show n ++ "G") ==? Types.Ok (truncate n_gb::Int) .&&.
697 1cdcf8f3 Iustin Pop
  Utils.parseUnit (show n ++ "t") ==? Types.Ok (n*1048576) .&&.
698 1cdcf8f3 Iustin Pop
  Utils.parseUnit (show n ++ "T") ==? Types.Ok (truncate n_tb::Int) .&&.
699 1cdcf8f3 Iustin Pop
  printTestCase "Internal error/overflow?"
700 1cdcf8f3 Iustin Pop
    (n_mb >=0 && n_gb >= 0 && n_tb >= 0) .&&.
701 1cdcf8f3 Iustin Pop
  property (Types.isBad (Utils.parseUnit (show n ++ "x")::Types.Result Int))
702 fce98abd Iustin Pop
  where n_mb = (fromIntegral n::Rational) * 1000 * 1000 / 1024 / 1024
703 1cdcf8f3 Iustin Pop
        n_gb = n_mb * 1000
704 1cdcf8f3 Iustin Pop
        n_tb = n_gb * 1000
705 1cb92fac Iustin Pop
706 525bfb36 Iustin Pop
-- | Test list for the Utils module.
707 23fe06c2 Iustin Pop
testSuite "Utils"
708 d5dfae0a Iustin Pop
            [ 'prop_Utils_commaJoinSplit
709 d5dfae0a Iustin Pop
            , 'prop_Utils_commaSplitJoin
710 d5dfae0a Iustin Pop
            , 'prop_Utils_fromObjWithDefault
711 d5dfae0a Iustin Pop
            , 'prop_Utils_if'if
712 d5dfae0a Iustin Pop
            , 'prop_Utils_select
713 d5dfae0a Iustin Pop
            , 'prop_Utils_select_undefd
714 d5dfae0a Iustin Pop
            , 'prop_Utils_select_undefv
715 d5dfae0a Iustin Pop
            , 'prop_Utils_parseUnit
716 d5dfae0a Iustin Pop
            ]
717 691dcd2a Iustin Pop
718 525bfb36 Iustin Pop
-- ** PeerMap tests
719 525bfb36 Iustin Pop
720 525bfb36 Iustin Pop
-- | Make sure add is idempotent.
721 fce98abd Iustin Pop
prop_PeerMap_addIdempotent :: PeerMap.PeerMap
722 fce98abd Iustin Pop
                           -> PeerMap.Key -> PeerMap.Elem -> Property
723 fbb95f28 Iustin Pop
prop_PeerMap_addIdempotent pmap key em =
724 d5dfae0a Iustin Pop
  fn puniq ==? fn (fn puniq)
725 fce98abd Iustin Pop
    where fn = PeerMap.add key em
726 7bc82927 Iustin Pop
          puniq = PeerMap.accumArray const pmap
727 15f4c8ca Iustin Pop
728 525bfb36 Iustin Pop
-- | Make sure remove is idempotent.
729 fce98abd Iustin Pop
prop_PeerMap_removeIdempotent :: PeerMap.PeerMap -> PeerMap.Key -> Property
730 15f4c8ca Iustin Pop
prop_PeerMap_removeIdempotent pmap key =
731 d5dfae0a Iustin Pop
  fn puniq ==? fn (fn puniq)
732 fce98abd Iustin Pop
    where fn = PeerMap.remove key
733 15f4c8ca Iustin Pop
          puniq = PeerMap.accumArray const pmap
734 15f4c8ca Iustin Pop
735 525bfb36 Iustin Pop
-- | Make sure a missing item returns 0.
736 fce98abd Iustin Pop
prop_PeerMap_findMissing :: PeerMap.PeerMap -> PeerMap.Key -> Property
737 15f4c8ca Iustin Pop
prop_PeerMap_findMissing pmap key =
738 d5dfae0a Iustin Pop
  PeerMap.find key (PeerMap.remove key puniq) ==? 0
739 fce98abd Iustin Pop
    where puniq = PeerMap.accumArray const pmap
740 15f4c8ca Iustin Pop
741 525bfb36 Iustin Pop
-- | Make sure an added item is found.
742 fce98abd Iustin Pop
prop_PeerMap_addFind :: PeerMap.PeerMap
743 fce98abd Iustin Pop
                     -> PeerMap.Key -> PeerMap.Elem -> Property
744 fbb95f28 Iustin Pop
prop_PeerMap_addFind pmap key em =
745 d5dfae0a Iustin Pop
  PeerMap.find key (PeerMap.add key em puniq) ==? em
746 fce98abd Iustin Pop
    where puniq = PeerMap.accumArray const pmap
747 15f4c8ca Iustin Pop
748 525bfb36 Iustin Pop
-- | Manual check that maxElem returns the maximum indeed, or 0 for null.
749 fce98abd Iustin Pop
prop_PeerMap_maxElem :: PeerMap.PeerMap -> Property
750 15f4c8ca Iustin Pop
prop_PeerMap_maxElem pmap =
751 d5dfae0a Iustin Pop
  PeerMap.maxElem puniq ==? if null puniq then 0
752 72bb6b4e Iustin Pop
                              else (maximum . snd . unzip) puniq
753 fce98abd Iustin Pop
    where puniq = PeerMap.accumArray const pmap
754 15f4c8ca Iustin Pop
755 525bfb36 Iustin Pop
-- | List of tests for the PeerMap module.
756 23fe06c2 Iustin Pop
testSuite "PeerMap"
757 d5dfae0a Iustin Pop
            [ 'prop_PeerMap_addIdempotent
758 d5dfae0a Iustin Pop
            , 'prop_PeerMap_removeIdempotent
759 d5dfae0a Iustin Pop
            , 'prop_PeerMap_maxElem
760 d5dfae0a Iustin Pop
            , 'prop_PeerMap_addFind
761 d5dfae0a Iustin Pop
            , 'prop_PeerMap_findMissing
762 d5dfae0a Iustin Pop
            ]
763 7dd5ee6c Iustin Pop
764 525bfb36 Iustin Pop
-- ** Container tests
765 095d7ac0 Iustin Pop
766 3603605a Iustin Pop
-- we silence the following due to hlint bug fixed in later versions
767 3603605a Iustin Pop
{-# ANN prop_Container_addTwo "HLint: ignore Avoid lambda" #-}
768 fce98abd Iustin Pop
prop_Container_addTwo :: [Container.Key] -> Int -> Int -> Bool
769 095d7ac0 Iustin Pop
prop_Container_addTwo cdata i1 i2 =
770 d5dfae0a Iustin Pop
  fn i1 i2 cont == fn i2 i1 cont &&
771 d5dfae0a Iustin Pop
  fn i1 i2 cont == fn i1 i2 (fn i1 i2 cont)
772 fce98abd Iustin Pop
    where cont = foldl (\c x -> Container.add x x c) Container.empty cdata
773 095d7ac0 Iustin Pop
          fn x1 x2 = Container.addTwo x1 x1 x2 x2
774 095d7ac0 Iustin Pop
775 fce98abd Iustin Pop
prop_Container_nameOf :: Node.Node -> Property
776 5ef78537 Iustin Pop
prop_Container_nameOf node =
777 5ef78537 Iustin Pop
  let nl = makeSmallCluster node 1
778 5ef78537 Iustin Pop
      fnode = head (Container.elems nl)
779 72bb6b4e Iustin Pop
  in Container.nameOf nl (Node.idx fnode) ==? Node.name fnode
780 5ef78537 Iustin Pop
781 525bfb36 Iustin Pop
-- | We test that in a cluster, given a random node, we can find it by
782 5ef78537 Iustin Pop
-- its name and alias, as long as all names and aliases are unique,
783 525bfb36 Iustin Pop
-- and that we fail to find a non-existing name.
784 112aee5f Iustin Pop
prop_Container_findByName :: Property
785 232fc505 Iustin Pop
prop_Container_findByName =
786 232fc505 Iustin Pop
  forAll (genNode (Just 1) Nothing) $ \node ->
787 5ef78537 Iustin Pop
  forAll (choose (1, 20)) $ \ cnt ->
788 5ef78537 Iustin Pop
  forAll (choose (0, cnt - 1)) $ \ fidx ->
789 a2a0bcd8 Iustin Pop
  forAll (genUniquesList (cnt * 2)) $ \ allnames ->
790 a2a0bcd8 Iustin Pop
  forAll (arbitrary `suchThat` (`notElem` allnames)) $ \ othername ->
791 a2a0bcd8 Iustin Pop
  let names = zip (take cnt allnames) (drop cnt allnames)
792 a2a0bcd8 Iustin Pop
      nl = makeSmallCluster node cnt
793 5ef78537 Iustin Pop
      nodes = Container.elems nl
794 5ef78537 Iustin Pop
      nodes' = map (\((name, alias), nn) -> (Node.idx nn,
795 5ef78537 Iustin Pop
                                             nn { Node.name = name,
796 5ef78537 Iustin Pop
                                                  Node.alias = alias }))
797 5ef78537 Iustin Pop
               $ zip names nodes
798 cb0c77ff Iustin Pop
      nl' = Container.fromList nodes'
799 5ef78537 Iustin Pop
      target = snd (nodes' !! fidx)
800 232fc505 Iustin Pop
  in Container.findByName nl' (Node.name target) ==? Just target .&&.
801 232fc505 Iustin Pop
     Container.findByName nl' (Node.alias target) ==? Just target .&&.
802 232fc505 Iustin Pop
     printTestCase "Found non-existing name"
803 232fc505 Iustin Pop
       (isNothing (Container.findByName nl' othername))
804 5ef78537 Iustin Pop
805 23fe06c2 Iustin Pop
testSuite "Container"
806 d5dfae0a Iustin Pop
            [ 'prop_Container_addTwo
807 d5dfae0a Iustin Pop
            , 'prop_Container_nameOf
808 d5dfae0a Iustin Pop
            , 'prop_Container_findByName
809 d5dfae0a Iustin Pop
            ]
810 095d7ac0 Iustin Pop
811 525bfb36 Iustin Pop
-- ** Instance tests
812 525bfb36 Iustin Pop
813 7bc82927 Iustin Pop
-- Simple instance tests, we only have setter/getters
814 7bc82927 Iustin Pop
815 fce98abd Iustin Pop
prop_Instance_creat :: Instance.Instance -> Property
816 39d11971 Iustin Pop
prop_Instance_creat inst =
817 d5dfae0a Iustin Pop
  Instance.name inst ==? Instance.alias inst
818 39d11971 Iustin Pop
819 fce98abd Iustin Pop
prop_Instance_setIdx :: Instance.Instance -> Types.Idx -> Property
820 7bc82927 Iustin Pop
prop_Instance_setIdx inst idx =
821 d5dfae0a Iustin Pop
  Instance.idx (Instance.setIdx inst idx) ==? idx
822 7bc82927 Iustin Pop
823 fce98abd Iustin Pop
prop_Instance_setName :: Instance.Instance -> String -> Bool
824 7bc82927 Iustin Pop
prop_Instance_setName inst name =
825 d5dfae0a Iustin Pop
  Instance.name newinst == name &&
826 d5dfae0a Iustin Pop
  Instance.alias newinst == name
827 fce98abd Iustin Pop
    where newinst = Instance.setName inst name
828 39d11971 Iustin Pop
829 fce98abd Iustin Pop
prop_Instance_setAlias :: Instance.Instance -> String -> Bool
830 39d11971 Iustin Pop
prop_Instance_setAlias inst name =
831 d5dfae0a Iustin Pop
  Instance.name newinst == Instance.name inst &&
832 d5dfae0a Iustin Pop
  Instance.alias newinst == name
833 fce98abd Iustin Pop
    where newinst = Instance.setAlias inst name
834 7bc82927 Iustin Pop
835 fce98abd Iustin Pop
prop_Instance_setPri :: Instance.Instance -> Types.Ndx -> Property
836 7bc82927 Iustin Pop
prop_Instance_setPri inst pdx =
837 d5dfae0a Iustin Pop
  Instance.pNode (Instance.setPri inst pdx) ==? pdx
838 7bc82927 Iustin Pop
839 fce98abd Iustin Pop
prop_Instance_setSec :: Instance.Instance -> Types.Ndx -> Property
840 7bc82927 Iustin Pop
prop_Instance_setSec inst sdx =
841 d5dfae0a Iustin Pop
  Instance.sNode (Instance.setSec inst sdx) ==? sdx
842 7bc82927 Iustin Pop
843 fce98abd Iustin Pop
prop_Instance_setBoth :: Instance.Instance -> Types.Ndx -> Types.Ndx -> Bool
844 7bc82927 Iustin Pop
prop_Instance_setBoth inst pdx sdx =
845 d5dfae0a Iustin Pop
  Instance.pNode si == pdx && Instance.sNode si == sdx
846 fce98abd Iustin Pop
    where si = Instance.setBoth inst pdx sdx
847 7bc82927 Iustin Pop
848 fce98abd Iustin Pop
prop_Instance_shrinkMG :: Instance.Instance -> Property
849 8fcf251f Iustin Pop
prop_Instance_shrinkMG inst =
850 d5dfae0a Iustin Pop
  Instance.mem inst >= 2 * Types.unitMem ==>
851 d5dfae0a Iustin Pop
    case Instance.shrinkByType inst Types.FailMem of
852 d5dfae0a Iustin Pop
      Types.Ok inst' -> Instance.mem inst' == Instance.mem inst - Types.unitMem
853 d5dfae0a Iustin Pop
      _ -> False
854 8fcf251f Iustin Pop
855 fce98abd Iustin Pop
prop_Instance_shrinkMF :: Instance.Instance -> Property
856 8fcf251f Iustin Pop
prop_Instance_shrinkMF inst =
857 d5dfae0a Iustin Pop
  forAll (choose (0, 2 * Types.unitMem - 1)) $ \mem ->
858 41085bd3 Iustin Pop
    let inst' = inst { Instance.mem = mem}
859 41085bd3 Iustin Pop
    in Types.isBad $ Instance.shrinkByType inst' Types.FailMem
860 8fcf251f Iustin Pop
861 fce98abd Iustin Pop
prop_Instance_shrinkCG :: Instance.Instance -> Property
862 8fcf251f Iustin Pop
prop_Instance_shrinkCG inst =
863 d5dfae0a Iustin Pop
  Instance.vcpus inst >= 2 * Types.unitCpu ==>
864 d5dfae0a Iustin Pop
    case Instance.shrinkByType inst Types.FailCPU of
865 d5dfae0a Iustin Pop
      Types.Ok inst' ->
866 d5dfae0a Iustin Pop
        Instance.vcpus inst' == Instance.vcpus inst - Types.unitCpu
867 d5dfae0a Iustin Pop
      _ -> False
868 8fcf251f Iustin Pop
869 fce98abd Iustin Pop
prop_Instance_shrinkCF :: Instance.Instance -> Property
870 8fcf251f Iustin Pop
prop_Instance_shrinkCF inst =
871 d5dfae0a Iustin Pop
  forAll (choose (0, 2 * Types.unitCpu - 1)) $ \vcpus ->
872 41085bd3 Iustin Pop
    let inst' = inst { Instance.vcpus = vcpus }
873 41085bd3 Iustin Pop
    in Types.isBad $ Instance.shrinkByType inst' Types.FailCPU
874 8fcf251f Iustin Pop
875 fce98abd Iustin Pop
prop_Instance_shrinkDG :: Instance.Instance -> Property
876 8fcf251f Iustin Pop
prop_Instance_shrinkDG inst =
877 d5dfae0a Iustin Pop
  Instance.dsk inst >= 2 * Types.unitDsk ==>
878 d5dfae0a Iustin Pop
    case Instance.shrinkByType inst Types.FailDisk of
879 d5dfae0a Iustin Pop
      Types.Ok inst' ->
880 d5dfae0a Iustin Pop
        Instance.dsk inst' == Instance.dsk inst - Types.unitDsk
881 d5dfae0a Iustin Pop
      _ -> False
882 8fcf251f Iustin Pop
883 fce98abd Iustin Pop
prop_Instance_shrinkDF :: Instance.Instance -> Property
884 8fcf251f Iustin Pop
prop_Instance_shrinkDF inst =
885 d5dfae0a Iustin Pop
  forAll (choose (0, 2 * Types.unitDsk - 1)) $ \dsk ->
886 41085bd3 Iustin Pop
    let inst' = inst { Instance.dsk = dsk }
887 41085bd3 Iustin Pop
    in Types.isBad $ Instance.shrinkByType inst' Types.FailDisk
888 8fcf251f Iustin Pop
889 fce98abd Iustin Pop
prop_Instance_setMovable :: Instance.Instance -> Bool -> Property
890 8fcf251f Iustin Pop
prop_Instance_setMovable inst m =
891 d5dfae0a Iustin Pop
  Instance.movable inst' ==? m
892 4a007641 Iustin Pop
    where inst' = Instance.setMovable inst m
893 8fcf251f Iustin Pop
894 23fe06c2 Iustin Pop
testSuite "Instance"
895 d5dfae0a Iustin Pop
            [ 'prop_Instance_creat
896 d5dfae0a Iustin Pop
            , 'prop_Instance_setIdx
897 d5dfae0a Iustin Pop
            , 'prop_Instance_setName
898 d5dfae0a Iustin Pop
            , 'prop_Instance_setAlias
899 d5dfae0a Iustin Pop
            , 'prop_Instance_setPri
900 d5dfae0a Iustin Pop
            , 'prop_Instance_setSec
901 d5dfae0a Iustin Pop
            , 'prop_Instance_setBoth
902 d5dfae0a Iustin Pop
            , 'prop_Instance_shrinkMG
903 d5dfae0a Iustin Pop
            , 'prop_Instance_shrinkMF
904 d5dfae0a Iustin Pop
            , 'prop_Instance_shrinkCG
905 d5dfae0a Iustin Pop
            , 'prop_Instance_shrinkCF
906 d5dfae0a Iustin Pop
            , 'prop_Instance_shrinkDG
907 d5dfae0a Iustin Pop
            , 'prop_Instance_shrinkDF
908 d5dfae0a Iustin Pop
            , 'prop_Instance_setMovable
909 d5dfae0a Iustin Pop
            ]
910 1ae7a904 Iustin Pop
911 e1dde6ad Iustin Pop
-- ** Backends
912 e1dde6ad Iustin Pop
913 e1dde6ad Iustin Pop
-- *** Text backend tests
914 525bfb36 Iustin Pop
915 1ae7a904 Iustin Pop
-- Instance text loader tests
916 1ae7a904 Iustin Pop
917 fce98abd Iustin Pop
prop_Text_Load_Instance :: String -> Int -> Int -> Int -> Types.InstanceStatus
918 fce98abd Iustin Pop
                        -> NonEmptyList Char -> [Char]
919 fce98abd Iustin Pop
                        -> NonNegative Int -> NonNegative Int -> Bool
920 fce98abd Iustin Pop
                        -> Types.DiskTemplate -> Int -> Property
921 a1cd7c1e Iustin Pop
prop_Text_Load_Instance name mem dsk vcpus status
922 a1cd7c1e Iustin Pop
                        (NonEmpty pnode) snode
923 52cc1370 Renรฉ Nussbaumer
                        (NonNegative pdx) (NonNegative sdx) autobal dt su =
924 d5dfae0a Iustin Pop
  pnode /= snode && pdx /= sdx ==>
925 d5dfae0a Iustin Pop
  let vcpus_s = show vcpus
926 d5dfae0a Iustin Pop
      dsk_s = show dsk
927 d5dfae0a Iustin Pop
      mem_s = show mem
928 52cc1370 Renรฉ Nussbaumer
      su_s = show su
929 d5dfae0a Iustin Pop
      status_s = Types.instanceStatusToRaw status
930 d5dfae0a Iustin Pop
      ndx = if null snode
931 39d11971 Iustin Pop
              then [(pnode, pdx)]
932 309e7c9a Iustin Pop
              else [(pnode, pdx), (snode, sdx)]
933 d5dfae0a Iustin Pop
      nl = Data.Map.fromList ndx
934 d5dfae0a Iustin Pop
      tags = ""
935 d5dfae0a Iustin Pop
      sbal = if autobal then "Y" else "N"
936 d5dfae0a Iustin Pop
      sdt = Types.diskTemplateToRaw dt
937 d5dfae0a Iustin Pop
      inst = Text.loadInst nl
938 d5dfae0a Iustin Pop
             [name, mem_s, dsk_s, vcpus_s, status_s,
939 52cc1370 Renรฉ Nussbaumer
              sbal, pnode, snode, sdt, tags, su_s]
940 d5dfae0a Iustin Pop
      fail1 = Text.loadInst nl
941 d5dfae0a Iustin Pop
              [name, mem_s, dsk_s, vcpus_s, status_s,
942 d5dfae0a Iustin Pop
               sbal, pnode, pnode, tags]
943 d5dfae0a Iustin Pop
  in case inst of
944 96bc2003 Iustin Pop
       Types.Bad msg -> failTest $ "Failed to load instance: " ++ msg
945 d5dfae0a Iustin Pop
       Types.Ok (_, i) -> printTestCase "Mismatch in some field while\
946 d5dfae0a Iustin Pop
                                        \ loading the instance" $
947 d5dfae0a Iustin Pop
               Instance.name i == name &&
948 d5dfae0a Iustin Pop
               Instance.vcpus i == vcpus &&
949 d5dfae0a Iustin Pop
               Instance.mem i == mem &&
950 d5dfae0a Iustin Pop
               Instance.pNode i == pdx &&
951 d5dfae0a Iustin Pop
               Instance.sNode i == (if null snode
952 d5dfae0a Iustin Pop
                                      then Node.noSecondary
953 d5dfae0a Iustin Pop
                                      else sdx) &&
954 d5dfae0a Iustin Pop
               Instance.autoBalance i == autobal &&
955 ec629280 Renรฉ Nussbaumer
               Instance.spindleUse i == su &&
956 d5dfae0a Iustin Pop
               Types.isBad fail1
957 39d11971 Iustin Pop
958 fce98abd Iustin Pop
prop_Text_Load_InstanceFail :: [(String, Int)] -> [String] -> Property
959 39d11971 Iustin Pop
prop_Text_Load_InstanceFail ktn fields =
960 52cc1370 Renรฉ Nussbaumer
  length fields /= 10 && length fields /= 11 ==>
961 bc782180 Iustin Pop
    case Text.loadInst nl fields of
962 96bc2003 Iustin Pop
      Types.Ok _ -> failTest "Managed to load instance from invalid data"
963 6429e8d8 Iustin Pop
      Types.Bad msg -> printTestCase ("Unrecognised error message: " ++ msg) $
964 6429e8d8 Iustin Pop
                       "Invalid/incomplete instance data: '" `isPrefixOf` msg
965 99b63608 Iustin Pop
    where nl = Data.Map.fromList ktn
966 39d11971 Iustin Pop
967 fce98abd Iustin Pop
prop_Text_Load_Node :: String -> Int -> Int -> Int -> Int -> Int
968 fce98abd Iustin Pop
                    -> Int -> Bool -> Bool
969 39d11971 Iustin Pop
prop_Text_Load_Node name tm nm fm td fd tc fo =
970 d5dfae0a Iustin Pop
  let conv v = if v < 0
971 d5dfae0a Iustin Pop
                 then "?"
972 d5dfae0a Iustin Pop
                 else show v
973 d5dfae0a Iustin Pop
      tm_s = conv tm
974 d5dfae0a Iustin Pop
      nm_s = conv nm
975 d5dfae0a Iustin Pop
      fm_s = conv fm
976 d5dfae0a Iustin Pop
      td_s = conv td
977 d5dfae0a Iustin Pop
      fd_s = conv fd
978 d5dfae0a Iustin Pop
      tc_s = conv tc
979 d5dfae0a Iustin Pop
      fo_s = if fo
980 39d11971 Iustin Pop
               then "Y"
981 39d11971 Iustin Pop
               else "N"
982 d5dfae0a Iustin Pop
      any_broken = any (< 0) [tm, nm, fm, td, fd, tc]
983 d5dfae0a Iustin Pop
      gid = Group.uuid defGroup
984 d5dfae0a Iustin Pop
  in case Text.loadNode defGroupAssoc
985 d5dfae0a Iustin Pop
       [name, tm_s, nm_s, fm_s, td_s, fd_s, tc_s, fo_s, gid] of
986 d5dfae0a Iustin Pop
       Nothing -> False
987 d5dfae0a Iustin Pop
       Just (name', node) ->
988 d5dfae0a Iustin Pop
         if fo || any_broken
989 d5dfae0a Iustin Pop
           then Node.offline node
990 d5dfae0a Iustin Pop
           else Node.name node == name' && name' == name &&
991 d5dfae0a Iustin Pop
                Node.alias node == name &&
992 d5dfae0a Iustin Pop
                Node.tMem node == fromIntegral tm &&
993 d5dfae0a Iustin Pop
                Node.nMem node == nm &&
994 d5dfae0a Iustin Pop
                Node.fMem node == fm &&
995 d5dfae0a Iustin Pop
                Node.tDsk node == fromIntegral td &&
996 d5dfae0a Iustin Pop
                Node.fDsk node == fd &&
997 d5dfae0a Iustin Pop
                Node.tCpu node == fromIntegral tc
998 39d11971 Iustin Pop
999 fce98abd Iustin Pop
prop_Text_Load_NodeFail :: [String] -> Property
1000 39d11971 Iustin Pop
prop_Text_Load_NodeFail fields =
1001 d5dfae0a Iustin Pop
  length fields /= 8 ==> isNothing $ Text.loadNode Data.Map.empty fields
1002 1ae7a904 Iustin Pop
1003 112aee5f Iustin Pop
prop_Text_NodeLSIdempotent :: Property
1004 232fc505 Iustin Pop
prop_Text_NodeLSIdempotent =
1005 232fc505 Iustin Pop
  forAll (genNode (Just 1) Nothing) $ \node ->
1006 232fc505 Iustin Pop
  -- override failN1 to what loadNode returns by default
1007 232fc505 Iustin Pop
  let n = Node.setPolicy Types.defIPolicy $
1008 232fc505 Iustin Pop
          node { Node.failN1 = True, Node.offline = False }
1009 232fc505 Iustin Pop
  in
1010 232fc505 Iustin Pop
    (Text.loadNode defGroupAssoc.
1011 232fc505 Iustin Pop
         Utils.sepSplit '|' . Text.serializeNode defGroupList) n ==?
1012 232fc505 Iustin Pop
    Just (Node.name n, n)
1013 50811e2c Iustin Pop
1014 fce98abd Iustin Pop
prop_Text_ISpecIdempotent :: Types.ISpec -> Property
1015 bcd17bf0 Iustin Pop
prop_Text_ISpecIdempotent ispec =
1016 bcd17bf0 Iustin Pop
  case Text.loadISpec "dummy" . Utils.sepSplit ',' .
1017 bcd17bf0 Iustin Pop
       Text.serializeISpec $ ispec of
1018 96bc2003 Iustin Pop
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
1019 bcd17bf0 Iustin Pop
    Types.Ok ispec' -> ispec ==? ispec'
1020 bcd17bf0 Iustin Pop
1021 fce98abd Iustin Pop
prop_Text_IPolicyIdempotent :: Types.IPolicy -> Property
1022 bcd17bf0 Iustin Pop
prop_Text_IPolicyIdempotent ipol =
1023 bcd17bf0 Iustin Pop
  case Text.loadIPolicy . Utils.sepSplit '|' $
1024 bcd17bf0 Iustin Pop
       Text.serializeIPolicy owner ipol of
1025 96bc2003 Iustin Pop
    Types.Bad msg -> failTest $ "Failed to load ispec: " ++ msg
1026 bcd17bf0 Iustin Pop
    Types.Ok res -> (owner, ipol) ==? res
1027 bcd17bf0 Iustin Pop
  where owner = "dummy"
1028 bcd17bf0 Iustin Pop
1029 dce9bbb3 Iustin Pop
-- | This property, while being in the text tests, does more than just
1030 dce9bbb3 Iustin Pop
-- test end-to-end the serialisation and loading back workflow; it
1031 dce9bbb3 Iustin Pop
-- also tests the Loader.mergeData and the actuall
1032 dce9bbb3 Iustin Pop
-- Cluster.iterateAlloc (for well-behaving w.r.t. instance
1033 dce9bbb3 Iustin Pop
-- allocations, not for the business logic). As such, it's a quite
1034 dce9bbb3 Iustin Pop
-- complex and slow test, and that's the reason we restrict it to
1035 dce9bbb3 Iustin Pop
-- small cluster sizes.
1036 fce98abd Iustin Pop
prop_Text_CreateSerialise :: Property
1037 dce9bbb3 Iustin Pop
prop_Text_CreateSerialise =
1038 dce9bbb3 Iustin Pop
  forAll genTags $ \ctags ->
1039 dce9bbb3 Iustin Pop
  forAll (choose (1, 20)) $ \maxiter ->
1040 dce9bbb3 Iustin Pop
  forAll (choose (2, 10)) $ \count ->
1041 dce9bbb3 Iustin Pop
  forAll genOnlineNode $ \node ->
1042 59ed268d Iustin Pop
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1043 a7667ba6 Iustin Pop
  let nl = makeSmallCluster node count
1044 c6e8fb9c Iustin Pop
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1045 dce9bbb3 Iustin Pop
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>= \allocn ->
1046 a7667ba6 Iustin Pop
     Cluster.iterateAlloc nl Container.empty (Just maxiter) inst allocn [] []
1047 dce9bbb3 Iustin Pop
     of
1048 96bc2003 Iustin Pop
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
1049 dce9bbb3 Iustin Pop
       Types.Ok (_, _, _, [], _) -> printTestCase
1050 dce9bbb3 Iustin Pop
                                    "Failed to allocate: no allocations" False
1051 dce9bbb3 Iustin Pop
       Types.Ok (_, nl', il', _, _) ->
1052 dce9bbb3 Iustin Pop
         let cdata = Loader.ClusterData defGroupList nl' il' ctags
1053 dce9bbb3 Iustin Pop
                     Types.defIPolicy
1054 dce9bbb3 Iustin Pop
             saved = Text.serializeCluster cdata
1055 dce9bbb3 Iustin Pop
         in case Text.parseData saved >>= Loader.mergeData [] [] [] [] of
1056 96bc2003 Iustin Pop
              Types.Bad msg -> failTest $ "Failed to load/merge: " ++ msg
1057 dce9bbb3 Iustin Pop
              Types.Ok (Loader.ClusterData gl2 nl2 il2 ctags2 cpol2) ->
1058 dce9bbb3 Iustin Pop
                ctags ==? ctags2 .&&.
1059 dce9bbb3 Iustin Pop
                Types.defIPolicy ==? cpol2 .&&.
1060 dce9bbb3 Iustin Pop
                il' ==? il2 .&&.
1061 b37f4a76 Iustin Pop
                defGroupList ==? gl2 .&&.
1062 b37f4a76 Iustin Pop
                nl' ==? nl2
1063 dce9bbb3 Iustin Pop
1064 23fe06c2 Iustin Pop
testSuite "Text"
1065 d5dfae0a Iustin Pop
            [ 'prop_Text_Load_Instance
1066 d5dfae0a Iustin Pop
            , 'prop_Text_Load_InstanceFail
1067 d5dfae0a Iustin Pop
            , 'prop_Text_Load_Node
1068 d5dfae0a Iustin Pop
            , 'prop_Text_Load_NodeFail
1069 d5dfae0a Iustin Pop
            , 'prop_Text_NodeLSIdempotent
1070 bcd17bf0 Iustin Pop
            , 'prop_Text_ISpecIdempotent
1071 bcd17bf0 Iustin Pop
            , 'prop_Text_IPolicyIdempotent
1072 dce9bbb3 Iustin Pop
            , 'prop_Text_CreateSerialise
1073 d5dfae0a Iustin Pop
            ]
1074 7dd5ee6c Iustin Pop
1075 e1dde6ad Iustin Pop
-- *** Simu backend
1076 e1dde6ad Iustin Pop
1077 e1dde6ad Iustin Pop
-- | Generates a tuple of specs for simulation.
1078 e1dde6ad Iustin Pop
genSimuSpec :: Gen (String, Int, Int, Int, Int)
1079 e1dde6ad Iustin Pop
genSimuSpec = do
1080 e1dde6ad Iustin Pop
  pol <- elements [C.allocPolicyPreferred,
1081 e1dde6ad Iustin Pop
                   C.allocPolicyLastResort, C.allocPolicyUnallocable,
1082 e1dde6ad Iustin Pop
                  "p", "a", "u"]
1083 e1dde6ad Iustin Pop
 -- should be reasonable (nodes/group), bigger values only complicate
1084 e1dde6ad Iustin Pop
 -- the display of failed tests, and we don't care (in this particular
1085 e1dde6ad Iustin Pop
 -- test) about big node groups
1086 e1dde6ad Iustin Pop
  nodes <- choose (0, 20)
1087 e1dde6ad Iustin Pop
  dsk <- choose (0, maxDsk)
1088 e1dde6ad Iustin Pop
  mem <- choose (0, maxMem)
1089 e1dde6ad Iustin Pop
  cpu <- choose (0, maxCpu)
1090 e1dde6ad Iustin Pop
  return (pol, nodes, dsk, mem, cpu)
1091 e1dde6ad Iustin Pop
1092 e1dde6ad Iustin Pop
-- | Checks that given a set of corrects specs, we can load them
1093 e1dde6ad Iustin Pop
-- successfully, and that at high-level the values look right.
1094 2c4eb054 Iustin Pop
prop_Simu_Load :: Property
1095 2c4eb054 Iustin Pop
prop_Simu_Load =
1096 e1dde6ad Iustin Pop
  forAll (choose (0, 10)) $ \ngroups ->
1097 e1dde6ad Iustin Pop
  forAll (replicateM ngroups genSimuSpec) $ \specs ->
1098 e1dde6ad Iustin Pop
  let strspecs = map (\(p, n, d, m, c) -> printf "%s,%d,%d,%d,%d"
1099 e1dde6ad Iustin Pop
                                          p n d m c::String) specs
1100 e1dde6ad Iustin Pop
      totnodes = sum $ map (\(_, n, _, _, _) -> n) specs
1101 e1dde6ad Iustin Pop
      mdc_in = concatMap (\(_, n, d, m, c) ->
1102 e1dde6ad Iustin Pop
                            replicate n (fromIntegral m, fromIntegral d,
1103 e1dde6ad Iustin Pop
                                         fromIntegral c,
1104 fce98abd Iustin Pop
                                         fromIntegral m, fromIntegral d))
1105 fce98abd Iustin Pop
               specs :: [(Double, Double, Double, Int, Int)]
1106 e1dde6ad Iustin Pop
  in case Simu.parseData strspecs of
1107 e1dde6ad Iustin Pop
       Types.Bad msg -> failTest $ "Failed to load specs: " ++ msg
1108 e1dde6ad Iustin Pop
       Types.Ok (Loader.ClusterData gl nl il tags ipol) ->
1109 e1dde6ad Iustin Pop
         let nodes = map snd $ IntMap.toAscList nl
1110 e1dde6ad Iustin Pop
             nidx = map Node.idx nodes
1111 e1dde6ad Iustin Pop
             mdc_out = map (\n -> (Node.tMem n, Node.tDsk n, Node.tCpu n,
1112 e1dde6ad Iustin Pop
                                   Node.fMem n, Node.fDsk n)) nodes
1113 e1dde6ad Iustin Pop
         in
1114 e1dde6ad Iustin Pop
         Container.size gl ==? ngroups .&&.
1115 e1dde6ad Iustin Pop
         Container.size nl ==? totnodes .&&.
1116 e1dde6ad Iustin Pop
         Container.size il ==? 0 .&&.
1117 e1dde6ad Iustin Pop
         length tags ==? 0 .&&.
1118 e1dde6ad Iustin Pop
         ipol ==? Types.defIPolicy .&&.
1119 e1dde6ad Iustin Pop
         nidx ==? [1..totnodes] .&&.
1120 e1dde6ad Iustin Pop
         mdc_in ==? mdc_out .&&.
1121 e1dde6ad Iustin Pop
         map Group.iPolicy (Container.elems gl) ==?
1122 e1dde6ad Iustin Pop
             replicate ngroups Types.defIPolicy
1123 e1dde6ad Iustin Pop
1124 e1dde6ad Iustin Pop
testSuite "Simu"
1125 2c4eb054 Iustin Pop
            [ 'prop_Simu_Load
1126 e1dde6ad Iustin Pop
            ]
1127 e1dde6ad Iustin Pop
1128 525bfb36 Iustin Pop
-- ** Node tests
1129 7dd5ee6c Iustin Pop
1130 fce98abd Iustin Pop
prop_Node_setAlias :: Node.Node -> String -> Bool
1131 82ea2874 Iustin Pop
prop_Node_setAlias node name =
1132 d5dfae0a Iustin Pop
  Node.name newnode == Node.name node &&
1133 d5dfae0a Iustin Pop
  Node.alias newnode == name
1134 fce98abd Iustin Pop
    where newnode = Node.setAlias node name
1135 82ea2874 Iustin Pop
1136 fce98abd Iustin Pop
prop_Node_setOffline :: Node.Node -> Bool -> Property
1137 82ea2874 Iustin Pop
prop_Node_setOffline node status =
1138 d5dfae0a Iustin Pop
  Node.offline newnode ==? status
1139 82ea2874 Iustin Pop
    where newnode = Node.setOffline node status
1140 82ea2874 Iustin Pop
1141 fce98abd Iustin Pop
prop_Node_setXmem :: Node.Node -> Int -> Property
1142 82ea2874 Iustin Pop
prop_Node_setXmem node xm =
1143 d5dfae0a Iustin Pop
  Node.xMem newnode ==? xm
1144 82ea2874 Iustin Pop
    where newnode = Node.setXmem node xm
1145 82ea2874 Iustin Pop
1146 fce98abd Iustin Pop
prop_Node_setMcpu :: Node.Node -> Double -> Property
1147 82ea2874 Iustin Pop
prop_Node_setMcpu node mc =
1148 487e1962 Iustin Pop
  Types.iPolicyVcpuRatio (Node.iPolicy newnode) ==? mc
1149 82ea2874 Iustin Pop
    where newnode = Node.setMcpu node mc
1150 82ea2874 Iustin Pop
1151 525bfb36 Iustin Pop
-- | Check that an instance add with too high memory or disk will be
1152 525bfb36 Iustin Pop
-- rejected.
1153 fce98abd Iustin Pop
prop_Node_addPriFM :: Node.Node -> Instance.Instance -> Property
1154 d5dfae0a Iustin Pop
prop_Node_addPriFM node inst =
1155 d5dfae0a Iustin Pop
  Instance.mem inst >= Node.fMem node && not (Node.failN1 node) &&
1156 7959cbb9 Iustin Pop
  not (Instance.isOffline inst) ==>
1157 d5dfae0a Iustin Pop
  case Node.addPri node inst'' of
1158 d5dfae0a Iustin Pop
    Types.OpFail Types.FailMem -> True
1159 d5dfae0a Iustin Pop
    _ -> False
1160 fce98abd Iustin Pop
  where inst' = setInstanceSmallerThanNode node inst
1161 d5dfae0a Iustin Pop
        inst'' = inst' { Instance.mem = Instance.mem inst }
1162 d5dfae0a Iustin Pop
1163 53bddadd Iustin Pop
-- | Check that adding a primary instance with too much disk fails
1164 53bddadd Iustin Pop
-- with type FailDisk.
1165 fce98abd Iustin Pop
prop_Node_addPriFD :: Node.Node -> Instance.Instance -> Property
1166 d5dfae0a Iustin Pop
prop_Node_addPriFD node inst =
1167 53bddadd Iustin Pop
  forAll (elements Instance.localStorageTemplates) $ \dt ->
1168 d5dfae0a Iustin Pop
  Instance.dsk inst >= Node.fDsk node && not (Node.failN1 node) ==>
1169 53bddadd Iustin Pop
  let inst' = setInstanceSmallerThanNode node inst
1170 53bddadd Iustin Pop
      inst'' = inst' { Instance.dsk = Instance.dsk inst
1171 53bddadd Iustin Pop
                     , Instance.diskTemplate = dt }
1172 53bddadd Iustin Pop
  in case Node.addPri node inst'' of
1173 53bddadd Iustin Pop
       Types.OpFail Types.FailDisk -> True
1174 53bddadd Iustin Pop
       _ -> False
1175 53bddadd Iustin Pop
1176 53bddadd Iustin Pop
-- | Check that adding a primary instance with too many VCPUs fails
1177 53bddadd Iustin Pop
-- with type FailCPU.
1178 fce98abd Iustin Pop
prop_Node_addPriFC :: Property
1179 3c1e4af0 Iustin Pop
prop_Node_addPriFC =
1180 3c1e4af0 Iustin Pop
  forAll (choose (1, maxCpu)) $ \extra ->
1181 746b7aa6 Iustin Pop
  forAll genOnlineNode $ \node ->
1182 7959cbb9 Iustin Pop
  forAll (arbitrary `suchThat` Instance.notOffline) $ \inst ->
1183 746b7aa6 Iustin Pop
  let inst' = setInstanceSmallerThanNode node inst
1184 746b7aa6 Iustin Pop
      inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
1185 746b7aa6 Iustin Pop
  in case Node.addPri node inst'' of
1186 746b7aa6 Iustin Pop
       Types.OpFail Types.FailCPU -> property True
1187 746b7aa6 Iustin Pop
       v -> failTest $ "Expected OpFail FailCPU, but got " ++ show v
1188 7bc82927 Iustin Pop
1189 525bfb36 Iustin Pop
-- | Check that an instance add with too high memory or disk will be
1190 525bfb36 Iustin Pop
-- rejected.
1191 fce98abd Iustin Pop
prop_Node_addSec :: Node.Node -> Instance.Instance -> Int -> Property
1192 15f4c8ca Iustin Pop
prop_Node_addSec node inst pdx =
1193 d5dfae0a Iustin Pop
  ((Instance.mem inst >= (Node.fMem node - Node.rMem node) &&
1194 7959cbb9 Iustin Pop
    not (Instance.isOffline inst)) ||
1195 d5dfae0a Iustin Pop
   Instance.dsk inst >= Node.fDsk node) &&
1196 d5dfae0a Iustin Pop
  not (Node.failN1 node) ==>
1197 d5dfae0a Iustin Pop
      isFailure (Node.addSec node inst pdx)
1198 7dd5ee6c Iustin Pop
1199 45c4d54d Iustin Pop
-- | Check that an offline instance with reasonable disk size but
1200 45c4d54d Iustin Pop
-- extra mem/cpu can always be added.
1201 fce98abd Iustin Pop
prop_Node_addOfflinePri :: NonNegative Int -> NonNegative Int -> Property
1202 c6b7e804 Iustin Pop
prop_Node_addOfflinePri (NonNegative extra_mem) (NonNegative extra_cpu) =
1203 a2a0bcd8 Iustin Pop
  forAll genOnlineNode $ \node ->
1204 45c4d54d Iustin Pop
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1205 45c4d54d Iustin Pop
  let inst' = inst { Instance.runSt = Types.AdminOffline
1206 45c4d54d Iustin Pop
                   , Instance.mem = Node.availMem node + extra_mem
1207 45c4d54d Iustin Pop
                   , Instance.vcpus = Node.availCpu node + extra_cpu }
1208 c6b7e804 Iustin Pop
  in case Node.addPri node inst' of
1209 c6b7e804 Iustin Pop
       Types.OpGood _ -> property True
1210 c6b7e804 Iustin Pop
       v -> failTest $ "Expected OpGood, but got: " ++ show v
1211 c6b7e804 Iustin Pop
1212 c6b7e804 Iustin Pop
-- | Check that an offline instance with reasonable disk size but
1213 c6b7e804 Iustin Pop
-- extra mem/cpu can always be added.
1214 fce98abd Iustin Pop
prop_Node_addOfflineSec :: NonNegative Int -> NonNegative Int
1215 fce98abd Iustin Pop
                        -> Types.Ndx -> Property
1216 c6b7e804 Iustin Pop
prop_Node_addOfflineSec (NonNegative extra_mem) (NonNegative extra_cpu) pdx =
1217 c6b7e804 Iustin Pop
  forAll genOnlineNode $ \node ->
1218 c6b7e804 Iustin Pop
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1219 c6b7e804 Iustin Pop
  let inst' = inst { Instance.runSt = Types.AdminOffline
1220 c6b7e804 Iustin Pop
                   , Instance.mem = Node.availMem node + extra_mem
1221 c6b7e804 Iustin Pop
                   , Instance.vcpus = Node.availCpu node + extra_cpu
1222 c6b7e804 Iustin Pop
                   , Instance.diskTemplate = Types.DTDrbd8 }
1223 c6b7e804 Iustin Pop
  in case Node.addSec node inst' pdx of
1224 c6b7e804 Iustin Pop
       Types.OpGood _ -> property True
1225 45c4d54d Iustin Pop
       v -> failTest $ "Expected OpGood/OpGood, but got: " ++ show v
1226 61bbbed7 Agata Murawska
1227 525bfb36 Iustin Pop
-- | Checks for memory reservation changes.
1228 fce98abd Iustin Pop
prop_Node_rMem :: Instance.Instance -> Property
1229 752635d3 Iustin Pop
prop_Node_rMem inst =
1230 7959cbb9 Iustin Pop
  not (Instance.isOffline inst) ==>
1231 5c52dae6 Iustin Pop
  forAll (genOnlineNode `suchThat` ((> Types.unitMem) . Node.fMem)) $ \node ->
1232 d5dfae0a Iustin Pop
  -- ab = auto_balance, nb = non-auto_balance
1233 d5dfae0a Iustin Pop
  -- we use -1 as the primary node of the instance
1234 e7b4d0e1 Iustin Pop
  let inst' = inst { Instance.pNode = -1, Instance.autoBalance = True
1235 e7b4d0e1 Iustin Pop
                   , Instance.diskTemplate = Types.DTDrbd8 }
1236 d5dfae0a Iustin Pop
      inst_ab = setInstanceSmallerThanNode node inst'
1237 d5dfae0a Iustin Pop
      inst_nb = inst_ab { Instance.autoBalance = False }
1238 d5dfae0a Iustin Pop
      -- now we have the two instances, identical except the
1239 d5dfae0a Iustin Pop
      -- autoBalance attribute
1240 d5dfae0a Iustin Pop
      orig_rmem = Node.rMem node
1241 d5dfae0a Iustin Pop
      inst_idx = Instance.idx inst_ab
1242 d5dfae0a Iustin Pop
      node_add_ab = Node.addSec node inst_ab (-1)
1243 d5dfae0a Iustin Pop
      node_add_nb = Node.addSec node inst_nb (-1)
1244 d5dfae0a Iustin Pop
      node_del_ab = liftM (`Node.removeSec` inst_ab) node_add_ab
1245 d5dfae0a Iustin Pop
      node_del_nb = liftM (`Node.removeSec` inst_nb) node_add_nb
1246 d5dfae0a Iustin Pop
  in case (node_add_ab, node_add_nb, node_del_ab, node_del_nb) of
1247 d5dfae0a Iustin Pop
       (Types.OpGood a_ab, Types.OpGood a_nb,
1248 d5dfae0a Iustin Pop
        Types.OpGood d_ab, Types.OpGood d_nb) ->
1249 d5dfae0a Iustin Pop
         printTestCase "Consistency checks failed" $
1250 d5dfae0a Iustin Pop
           Node.rMem a_ab >  orig_rmem &&
1251 d5dfae0a Iustin Pop
           Node.rMem a_ab - orig_rmem == Instance.mem inst_ab &&
1252 d5dfae0a Iustin Pop
           Node.rMem a_nb == orig_rmem &&
1253 d5dfae0a Iustin Pop
           Node.rMem d_ab == orig_rmem &&
1254 d5dfae0a Iustin Pop
           Node.rMem d_nb == orig_rmem &&
1255 d5dfae0a Iustin Pop
           -- this is not related to rMem, but as good a place to
1256 d5dfae0a Iustin Pop
           -- test as any
1257 d5dfae0a Iustin Pop
           inst_idx `elem` Node.sList a_ab &&
1258 3603605a Iustin Pop
           inst_idx `notElem` Node.sList d_ab
1259 96bc2003 Iustin Pop
       x -> failTest $ "Failed to add/remove instances: " ++ show x
1260 9cbc1edb Iustin Pop
1261 525bfb36 Iustin Pop
-- | Check mdsk setting.
1262 fce98abd Iustin Pop
prop_Node_setMdsk :: Node.Node -> SmallRatio -> Bool
1263 8fcf251f Iustin Pop
prop_Node_setMdsk node mx =
1264 d5dfae0a Iustin Pop
  Node.loDsk node' >= 0 &&
1265 d5dfae0a Iustin Pop
  fromIntegral (Node.loDsk node') <= Node.tDsk node &&
1266 d5dfae0a Iustin Pop
  Node.availDisk node' >= 0 &&
1267 d5dfae0a Iustin Pop
  Node.availDisk node' <= Node.fDsk node' &&
1268 d5dfae0a Iustin Pop
  fromIntegral (Node.availDisk node') <= Node.tDsk node' &&
1269 d5dfae0a Iustin Pop
  Node.mDsk node' == mx'
1270 fce98abd Iustin Pop
    where node' = Node.setMdsk node mx'
1271 8fcf251f Iustin Pop
          SmallRatio mx' = mx
1272 8fcf251f Iustin Pop
1273 8fcf251f Iustin Pop
-- Check tag maps
1274 fce98abd Iustin Pop
prop_Node_tagMaps_idempotent :: Property
1275 15e3d31c Iustin Pop
prop_Node_tagMaps_idempotent =
1276 15e3d31c Iustin Pop
  forAll genTags $ \tags ->
1277 d5dfae0a Iustin Pop
  Node.delTags (Node.addTags m tags) tags ==? m
1278 4a007641 Iustin Pop
    where m = Data.Map.empty
1279 8fcf251f Iustin Pop
1280 fce98abd Iustin Pop
prop_Node_tagMaps_reject :: Property
1281 15e3d31c Iustin Pop
prop_Node_tagMaps_reject =
1282 15e3d31c Iustin Pop
  forAll (genTags `suchThat` (not . null)) $ \tags ->
1283 15e3d31c Iustin Pop
  let m = Node.addTags Data.Map.empty tags
1284 15e3d31c Iustin Pop
  in all (\t -> Node.rejectAddTags m [t]) tags
1285 8fcf251f Iustin Pop
1286 fce98abd Iustin Pop
prop_Node_showField :: Node.Node -> Property
1287 82ea2874 Iustin Pop
prop_Node_showField node =
1288 82ea2874 Iustin Pop
  forAll (elements Node.defaultFields) $ \ field ->
1289 82ea2874 Iustin Pop
  fst (Node.showHeader field) /= Types.unknownField &&
1290 82ea2874 Iustin Pop
  Node.showField node field /= Types.unknownField
1291 82ea2874 Iustin Pop
1292 fce98abd Iustin Pop
prop_Node_computeGroups :: [Node.Node] -> Bool
1293 d8bcd0a8 Iustin Pop
prop_Node_computeGroups nodes =
1294 d8bcd0a8 Iustin Pop
  let ng = Node.computeGroups nodes
1295 d8bcd0a8 Iustin Pop
      onlyuuid = map fst ng
1296 d8bcd0a8 Iustin Pop
  in length nodes == sum (map (length . snd) ng) &&
1297 d8bcd0a8 Iustin Pop
     all (\(guuid, ns) -> all ((== guuid) . Node.group) ns) ng &&
1298 d8bcd0a8 Iustin Pop
     length (nub onlyuuid) == length onlyuuid &&
1299 cc532bdd Iustin Pop
     (null nodes || not (null ng))
1300 d8bcd0a8 Iustin Pop
1301 eae69eee Iustin Pop
-- Check idempotence of add/remove operations
1302 fce98abd Iustin Pop
prop_Node_addPri_idempotent :: Property
1303 eae69eee Iustin Pop
prop_Node_addPri_idempotent =
1304 eae69eee Iustin Pop
  forAll genOnlineNode $ \node ->
1305 eae69eee Iustin Pop
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1306 eae69eee Iustin Pop
  case Node.addPri node inst of
1307 eae69eee Iustin Pop
    Types.OpGood node' -> Node.removePri node' inst ==? node
1308 eae69eee Iustin Pop
    _ -> failTest "Can't add instance"
1309 eae69eee Iustin Pop
1310 fce98abd Iustin Pop
prop_Node_addSec_idempotent :: Property
1311 eae69eee Iustin Pop
prop_Node_addSec_idempotent =
1312 eae69eee Iustin Pop
  forAll genOnlineNode $ \node ->
1313 eae69eee Iustin Pop
  forAll (genInstanceSmallerThanNode node) $ \inst ->
1314 eae69eee Iustin Pop
  let pdx = Node.idx node + 1
1315 eae69eee Iustin Pop
      inst' = Instance.setPri inst pdx
1316 90669369 Iustin Pop
      inst'' = inst' { Instance.diskTemplate = Types.DTDrbd8 }
1317 90669369 Iustin Pop
  in case Node.addSec node inst'' pdx of
1318 90669369 Iustin Pop
       Types.OpGood node' -> Node.removeSec node' inst'' ==? node
1319 eae69eee Iustin Pop
       _ -> failTest "Can't add instance"
1320 eae69eee Iustin Pop
1321 23fe06c2 Iustin Pop
testSuite "Node"
1322 d5dfae0a Iustin Pop
            [ 'prop_Node_setAlias
1323 d5dfae0a Iustin Pop
            , 'prop_Node_setOffline
1324 d5dfae0a Iustin Pop
            , 'prop_Node_setMcpu
1325 d5dfae0a Iustin Pop
            , 'prop_Node_setXmem
1326 d5dfae0a Iustin Pop
            , 'prop_Node_addPriFM
1327 d5dfae0a Iustin Pop
            , 'prop_Node_addPriFD
1328 d5dfae0a Iustin Pop
            , 'prop_Node_addPriFC
1329 d5dfae0a Iustin Pop
            , 'prop_Node_addSec
1330 c6b7e804 Iustin Pop
            , 'prop_Node_addOfflinePri
1331 c6b7e804 Iustin Pop
            , 'prop_Node_addOfflineSec
1332 d5dfae0a Iustin Pop
            , 'prop_Node_rMem
1333 d5dfae0a Iustin Pop
            , 'prop_Node_setMdsk
1334 d5dfae0a Iustin Pop
            , 'prop_Node_tagMaps_idempotent
1335 d5dfae0a Iustin Pop
            , 'prop_Node_tagMaps_reject
1336 d5dfae0a Iustin Pop
            , 'prop_Node_showField
1337 d5dfae0a Iustin Pop
            , 'prop_Node_computeGroups
1338 eae69eee Iustin Pop
            , 'prop_Node_addPri_idempotent
1339 eae69eee Iustin Pop
            , 'prop_Node_addSec_idempotent
1340 d5dfae0a Iustin Pop
            ]
1341 cf35a869 Iustin Pop
1342 525bfb36 Iustin Pop
-- ** Cluster tests
1343 cf35a869 Iustin Pop
1344 525bfb36 Iustin Pop
-- | Check that the cluster score is close to zero for a homogeneous
1345 525bfb36 Iustin Pop
-- cluster.
1346 2c4eb054 Iustin Pop
prop_Cluster_Score_Zero :: Node.Node -> Property
1347 2c4eb054 Iustin Pop
prop_Cluster_Score_Zero node =
1348 d5dfae0a Iustin Pop
  forAll (choose (1, 1024)) $ \count ->
1349 3a3c1eb4 Iustin Pop
    (not (Node.offline node) && not (Node.failN1 node) && (count > 0) &&
1350 2060348b Iustin Pop
     (Node.tDsk node > 0) && (Node.tMem node > 0)) ==>
1351 d5dfae0a Iustin Pop
  let fn = Node.buildPeers node Container.empty
1352 d5dfae0a Iustin Pop
      nlst = replicate count fn
1353 d5dfae0a Iustin Pop
      score = Cluster.compCVNodes nlst
1354 d5dfae0a Iustin Pop
  -- we can't say == 0 here as the floating point errors accumulate;
1355 d5dfae0a Iustin Pop
  -- this should be much lower than the default score in CLI.hs
1356 d5dfae0a Iustin Pop
  in score <= 1e-12
1357 cf35a869 Iustin Pop
1358 525bfb36 Iustin Pop
-- | Check that cluster stats are sane.
1359 2c4eb054 Iustin Pop
prop_Cluster_CStats_sane :: Property
1360 2c4eb054 Iustin Pop
prop_Cluster_CStats_sane =
1361 d5dfae0a Iustin Pop
  forAll (choose (1, 1024)) $ \count ->
1362 d6f9f5bd Iustin Pop
  forAll genOnlineNode $ \node ->
1363 d5dfae0a Iustin Pop
  let fn = Node.buildPeers node Container.empty
1364 d5dfae0a Iustin Pop
      nlst = zip [1..] $ replicate count fn::[(Types.Ndx, Node.Node)]
1365 d5dfae0a Iustin Pop
      nl = Container.fromList nlst
1366 d5dfae0a Iustin Pop
      cstats = Cluster.totalResources nl
1367 d5dfae0a Iustin Pop
  in Cluster.csAdsk cstats >= 0 &&
1368 d5dfae0a Iustin Pop
     Cluster.csAdsk cstats <= Cluster.csFdsk cstats
1369 8fcf251f Iustin Pop
1370 3fea6959 Iustin Pop
-- | Check that one instance is allocated correctly, without
1371 525bfb36 Iustin Pop
-- rebalances needed.
1372 2c4eb054 Iustin Pop
prop_Cluster_Alloc_sane :: Instance.Instance -> Property
1373 2c4eb054 Iustin Pop
prop_Cluster_Alloc_sane inst =
1374 d5dfae0a Iustin Pop
  forAll (choose (5, 20)) $ \count ->
1375 d6f9f5bd Iustin Pop
  forAll genOnlineNode $ \node ->
1376 3603605a Iustin Pop
  let (nl, il, inst') = makeSmallEmptyCluster node count inst
1377 c6e8fb9c Iustin Pop
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1378 c6e8fb9c Iustin Pop
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1379 d5dfae0a Iustin Pop
     Cluster.tryAlloc nl il inst' of
1380 d5dfae0a Iustin Pop
       Types.Bad _ -> False
1381 d5dfae0a Iustin Pop
       Types.Ok as ->
1382 d5dfae0a Iustin Pop
         case Cluster.asSolution as of
1383 d5dfae0a Iustin Pop
           Nothing -> False
1384 d5dfae0a Iustin Pop
           Just (xnl, xi, _, cv) ->
1385 d5dfae0a Iustin Pop
             let il' = Container.add (Instance.idx xi) xi il
1386 d5dfae0a Iustin Pop
                 tbl = Cluster.Table xnl il' cv []
1387 d5dfae0a Iustin Pop
             in not (canBalance tbl True True False)
1388 3fea6959 Iustin Pop
1389 3fea6959 Iustin Pop
-- | Checks that on a 2-5 node cluster, we can allocate a random
1390 3fea6959 Iustin Pop
-- instance spec via tiered allocation (whatever the original instance
1391 37483aa5 Iustin Pop
-- spec), on either one or two nodes. Furthermore, we test that
1392 37483aa5 Iustin Pop
-- computed allocation statistics are correct.
1393 2c4eb054 Iustin Pop
prop_Cluster_CanTieredAlloc :: Instance.Instance -> Property
1394 2c4eb054 Iustin Pop
prop_Cluster_CanTieredAlloc inst =
1395 d5dfae0a Iustin Pop
  forAll (choose (2, 5)) $ \count ->
1396 d6f9f5bd Iustin Pop
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1397 d5dfae0a Iustin Pop
  let nl = makeSmallCluster node count
1398 d5dfae0a Iustin Pop
      il = Container.empty
1399 c6e8fb9c Iustin Pop
      rqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1400 d5dfae0a Iustin Pop
      allocnodes = Cluster.genAllocNodes defGroupList nl rqnodes True
1401 d5dfae0a Iustin Pop
  in case allocnodes >>= \allocnodes' ->
1402 d5dfae0a Iustin Pop
    Cluster.tieredAlloc nl il (Just 1) inst allocnodes' [] [] of
1403 37483aa5 Iustin Pop
       Types.Bad msg -> failTest $ "Failed to tiered alloc: " ++ msg
1404 37483aa5 Iustin Pop
       Types.Ok (_, nl', il', ixes, cstats) ->
1405 37483aa5 Iustin Pop
         let (ai_alloc, ai_pool, ai_unav) =
1406 37483aa5 Iustin Pop
               Cluster.computeAllocationDelta
1407 37483aa5 Iustin Pop
                (Cluster.totalResources nl)
1408 37483aa5 Iustin Pop
                (Cluster.totalResources nl')
1409 37483aa5 Iustin Pop
             all_nodes = Container.elems nl
1410 37483aa5 Iustin Pop
         in property (not (null ixes)) .&&.
1411 37483aa5 Iustin Pop
            IntMap.size il' ==? length ixes .&&.
1412 37483aa5 Iustin Pop
            length ixes ==? length cstats .&&.
1413 37483aa5 Iustin Pop
            sum (map Types.allocInfoVCpus [ai_alloc, ai_pool, ai_unav]) ==?
1414 37483aa5 Iustin Pop
              sum (map Node.hiCpu all_nodes) .&&.
1415 37483aa5 Iustin Pop
            sum (map Types.allocInfoNCpus [ai_alloc, ai_pool, ai_unav]) ==?
1416 37483aa5 Iustin Pop
              sum (map Node.tCpu all_nodes) .&&.
1417 37483aa5 Iustin Pop
            sum (map Types.allocInfoMem [ai_alloc, ai_pool, ai_unav]) ==?
1418 37483aa5 Iustin Pop
              truncate (sum (map Node.tMem all_nodes)) .&&.
1419 37483aa5 Iustin Pop
            sum (map Types.allocInfoDisk [ai_alloc, ai_pool, ai_unav]) ==?
1420 37483aa5 Iustin Pop
              truncate (sum (map Node.tDsk all_nodes))
1421 3fea6959 Iustin Pop
1422 6a855aaa Iustin Pop
-- | Helper function to create a cluster with the given range of nodes
1423 6a855aaa Iustin Pop
-- and allocate an instance on it.
1424 fce98abd Iustin Pop
genClusterAlloc :: Int -> Node.Node -> Instance.Instance
1425 fce98abd Iustin Pop
                -> Types.Result (Node.List, Instance.List, Instance.Instance)
1426 6a855aaa Iustin Pop
genClusterAlloc count node inst =
1427 6a855aaa Iustin Pop
  let nl = makeSmallCluster node count
1428 c6e8fb9c Iustin Pop
      reqnodes = Instance.requiredNodes $ Instance.diskTemplate inst
1429 c6e8fb9c Iustin Pop
  in case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1430 6a855aaa Iustin Pop
     Cluster.tryAlloc nl Container.empty inst of
1431 6a855aaa Iustin Pop
       Types.Bad _ -> Types.Bad "Can't allocate"
1432 d5dfae0a Iustin Pop
       Types.Ok as ->
1433 d5dfae0a Iustin Pop
         case Cluster.asSolution as of
1434 6a855aaa Iustin Pop
           Nothing -> Types.Bad "Empty solution?"
1435 d5dfae0a Iustin Pop
           Just (xnl, xi, _, _) ->
1436 6a855aaa Iustin Pop
             let xil = Container.add (Instance.idx xi) xi Container.empty
1437 6a855aaa Iustin Pop
             in Types.Ok (xnl, xil, xi)
1438 6a855aaa Iustin Pop
1439 6a855aaa Iustin Pop
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1440 6a855aaa Iustin Pop
-- we can also relocate it.
1441 2c4eb054 Iustin Pop
prop_Cluster_AllocRelocate :: Property
1442 2c4eb054 Iustin Pop
prop_Cluster_AllocRelocate =
1443 6a855aaa Iustin Pop
  forAll (choose (4, 8)) $ \count ->
1444 6a855aaa Iustin Pop
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1445 7018af9c Iustin Pop
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1446 6a855aaa Iustin Pop
  case genClusterAlloc count node inst of
1447 6a855aaa Iustin Pop
    Types.Bad msg -> failTest msg
1448 6a855aaa Iustin Pop
    Types.Ok (nl, il, inst') ->
1449 6a855aaa Iustin Pop
      case IAlloc.processRelocate defGroupList nl il
1450 7018af9c Iustin Pop
             (Instance.idx inst) 1
1451 7018af9c Iustin Pop
             [(if Instance.diskTemplate inst' == Types.DTDrbd8
1452 7018af9c Iustin Pop
                 then Instance.sNode
1453 7018af9c Iustin Pop
                 else Instance.pNode) inst'] of
1454 7018af9c Iustin Pop
        Types.Ok _ -> property True
1455 6a855aaa Iustin Pop
        Types.Bad msg -> failTest $ "Failed to relocate: " ++ msg
1456 6a855aaa Iustin Pop
1457 6a855aaa Iustin Pop
-- | Helper property checker for the result of a nodeEvac or
1458 6a855aaa Iustin Pop
-- changeGroup operation.
1459 fce98abd Iustin Pop
check_EvacMode :: Group.Group -> Instance.Instance
1460 fce98abd Iustin Pop
               -> Types.Result (Node.List, Instance.List, Cluster.EvacSolution)
1461 fce98abd Iustin Pop
               -> Property
1462 6a855aaa Iustin Pop
check_EvacMode grp inst result =
1463 6a855aaa Iustin Pop
  case result of
1464 6a855aaa Iustin Pop
    Types.Bad msg -> failTest $ "Couldn't evacuate/change group:" ++ msg
1465 6a855aaa Iustin Pop
    Types.Ok (_, _, es) ->
1466 6a855aaa Iustin Pop
      let moved = Cluster.esMoved es
1467 6a855aaa Iustin Pop
          failed = Cluster.esFailed es
1468 6a855aaa Iustin Pop
          opcodes = not . null $ Cluster.esOpCodes es
1469 6a855aaa Iustin Pop
      in failmsg ("'failed' not empty: " ++ show failed) (null failed) .&&.
1470 6a855aaa Iustin Pop
         failmsg "'opcodes' is null" opcodes .&&.
1471 6a855aaa Iustin Pop
         case moved of
1472 6a855aaa Iustin Pop
           [(idx', gdx, _)] -> failmsg "invalid instance moved" (idx == idx')
1473 6a855aaa Iustin Pop
                               .&&.
1474 6a855aaa Iustin Pop
                               failmsg "wrong target group"
1475 6a855aaa Iustin Pop
                                         (gdx == Group.idx grp)
1476 6a855aaa Iustin Pop
           v -> failmsg  ("invalid solution: " ++ show v) False
1477 fce98abd Iustin Pop
  where failmsg :: String -> Bool -> Property
1478 fce98abd Iustin Pop
        failmsg = \msg -> printTestCase ("Failed to evacuate: " ++ msg)
1479 6a855aaa Iustin Pop
        idx = Instance.idx inst
1480 6a855aaa Iustin Pop
1481 6a855aaa Iustin Pop
-- | Checks that on a 4-8 node cluster, once we allocate an instance,
1482 6a855aaa Iustin Pop
-- we can also node-evacuate it.
1483 2c4eb054 Iustin Pop
prop_Cluster_AllocEvacuate :: Property
1484 2c4eb054 Iustin Pop
prop_Cluster_AllocEvacuate =
1485 6a855aaa Iustin Pop
  forAll (choose (4, 8)) $ \count ->
1486 6a855aaa Iustin Pop
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1487 ac1c0a07 Iustin Pop
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1488 6a855aaa Iustin Pop
  case genClusterAlloc count node inst of
1489 6a855aaa Iustin Pop
    Types.Bad msg -> failTest msg
1490 6a855aaa Iustin Pop
    Types.Ok (nl, il, inst') ->
1491 2cdaf225 Iustin Pop
      conjoin . map (\mode -> check_EvacMode defGroup inst' $
1492 6a855aaa Iustin Pop
                              Cluster.tryNodeEvac defGroupList nl il mode
1493 ac1c0a07 Iustin Pop
                                [Instance.idx inst']) .
1494 fafd0773 Iustin Pop
                              evacModeOptions .
1495 fafd0773 Iustin Pop
                              Instance.mirrorType $ inst'
1496 6a855aaa Iustin Pop
1497 6a855aaa Iustin Pop
-- | Checks that on a 4-8 node cluster with two node groups, once we
1498 6a855aaa Iustin Pop
-- allocate an instance on the first node group, we can also change
1499 6a855aaa Iustin Pop
-- its group.
1500 2c4eb054 Iustin Pop
prop_Cluster_AllocChangeGroup :: Property
1501 2c4eb054 Iustin Pop
prop_Cluster_AllocChangeGroup =
1502 6a855aaa Iustin Pop
  forAll (choose (4, 8)) $ \count ->
1503 6a855aaa Iustin Pop
  forAll (genOnlineNode `suchThat` (isNodeBig 4)) $ \node ->
1504 ac1c0a07 Iustin Pop
  forAll (genInstanceSmallerThanNode node `suchThat` isMirrored) $ \inst ->
1505 6a855aaa Iustin Pop
  case genClusterAlloc count node inst of
1506 6a855aaa Iustin Pop
    Types.Bad msg -> failTest msg
1507 6a855aaa Iustin Pop
    Types.Ok (nl, il, inst') ->
1508 6a855aaa Iustin Pop
      -- we need to add a second node group and nodes to the cluster
1509 6a855aaa Iustin Pop
      let nl2 = Container.elems $ makeSmallCluster node count
1510 6a855aaa Iustin Pop
          grp2 = Group.setIdx defGroup (Group.idx defGroup + 1)
1511 6a855aaa Iustin Pop
          maxndx = maximum . map Node.idx $ nl2
1512 6a855aaa Iustin Pop
          nl3 = map (\n -> n { Node.group = Group.idx grp2
1513 6a855aaa Iustin Pop
                             , Node.idx = Node.idx n + maxndx }) nl2
1514 6a855aaa Iustin Pop
          nl4 = Container.fromList . map (\n -> (Node.idx n, n)) $ nl3
1515 6a855aaa Iustin Pop
          gl' = Container.add (Group.idx grp2) grp2 defGroupList
1516 6a855aaa Iustin Pop
          nl' = IntMap.union nl nl4
1517 6a855aaa Iustin Pop
      in check_EvacMode grp2 inst' $
1518 6a855aaa Iustin Pop
         Cluster.tryChangeGroup gl' nl' il [] [Instance.idx inst']
1519 3fea6959 Iustin Pop
1520 3fea6959 Iustin Pop
-- | Check that allocating multiple instances on a cluster, then
1521 525bfb36 Iustin Pop
-- adding an empty node, results in a valid rebalance.
1522 2c4eb054 Iustin Pop
prop_Cluster_AllocBalance :: Property
1523 2c4eb054 Iustin Pop
prop_Cluster_AllocBalance =
1524 d5dfae0a Iustin Pop
  forAll (genNode (Just 5) (Just 128)) $ \node ->
1525 d5dfae0a Iustin Pop
  forAll (choose (3, 5)) $ \count ->
1526 d5dfae0a Iustin Pop
  not (Node.offline node) && not (Node.failN1 node) ==>
1527 d5dfae0a Iustin Pop
  let nl = makeSmallCluster node count
1528 d5dfae0a Iustin Pop
      (hnode, nl') = IntMap.deleteFindMax nl
1529 d5dfae0a Iustin Pop
      il = Container.empty
1530 d5dfae0a Iustin Pop
      allocnodes = Cluster.genAllocNodes defGroupList nl' 2 True
1531 d5dfae0a Iustin Pop
      i_templ = createInstance Types.unitMem Types.unitDsk Types.unitCpu
1532 d5dfae0a Iustin Pop
  in case allocnodes >>= \allocnodes' ->
1533 d5dfae0a Iustin Pop
    Cluster.iterateAlloc nl' il (Just 5) i_templ allocnodes' [] [] of
1534 96bc2003 Iustin Pop
       Types.Bad msg -> failTest $ "Failed to allocate: " ++ msg
1535 96bc2003 Iustin Pop
       Types.Ok (_, _, _, [], _) -> failTest "Failed to allocate: no instances"
1536 d5dfae0a Iustin Pop
       Types.Ok (_, xnl, il', _, _) ->
1537 d5dfae0a Iustin Pop
         let ynl = Container.add (Node.idx hnode) hnode xnl
1538 d5dfae0a Iustin Pop
             cv = Cluster.compCV ynl
1539 d5dfae0a Iustin Pop
             tbl = Cluster.Table ynl il' cv []
1540 6cff91f5 Iustin Pop
         in printTestCase "Failed to rebalance" $
1541 6cff91f5 Iustin Pop
            canBalance tbl True True False
1542 3fea6959 Iustin Pop
1543 525bfb36 Iustin Pop
-- | Checks consistency.
1544 2c4eb054 Iustin Pop
prop_Cluster_CheckConsistency :: Node.Node -> Instance.Instance -> Bool
1545 2c4eb054 Iustin Pop
prop_Cluster_CheckConsistency node inst =
1546 32b8d9c0 Iustin Pop
  let nl = makeSmallCluster node 3
1547 32b8d9c0 Iustin Pop
      [node1, node2, node3] = Container.elems nl
1548 10ef6b4e Iustin Pop
      node3' = node3 { Node.group = 1 }
1549 32b8d9c0 Iustin Pop
      nl' = Container.add (Node.idx node3') node3' nl
1550 32b8d9c0 Iustin Pop
      inst1 = Instance.setBoth inst (Node.idx node1) (Node.idx node2)
1551 32b8d9c0 Iustin Pop
      inst2 = Instance.setBoth inst (Node.idx node1) Node.noSecondary
1552 32b8d9c0 Iustin Pop
      inst3 = Instance.setBoth inst (Node.idx node1) (Node.idx node3)
1553 cb0c77ff Iustin Pop
      ccheck = Cluster.findSplitInstances nl' . Container.fromList
1554 32b8d9c0 Iustin Pop
  in null (ccheck [(0, inst1)]) &&
1555 32b8d9c0 Iustin Pop
     null (ccheck [(0, inst2)]) &&
1556 32b8d9c0 Iustin Pop
     (not . null $ ccheck [(0, inst3)])
1557 32b8d9c0 Iustin Pop
1558 525bfb36 Iustin Pop
-- | For now, we only test that we don't lose instances during the split.
1559 2c4eb054 Iustin Pop
prop_Cluster_SplitCluster :: Node.Node -> Instance.Instance -> Property
1560 2c4eb054 Iustin Pop
prop_Cluster_SplitCluster node inst =
1561 f4161783 Iustin Pop
  forAll (choose (0, 100)) $ \icnt ->
1562 f4161783 Iustin Pop
  let nl = makeSmallCluster node 2
1563 f4161783 Iustin Pop
      (nl', il') = foldl (\(ns, is) _ -> assignInstance ns is inst 0 1)
1564 f4161783 Iustin Pop
                   (nl, Container.empty) [1..icnt]
1565 f4161783 Iustin Pop
      gni = Cluster.splitCluster nl' il'
1566 f4161783 Iustin Pop
  in sum (map (Container.size . snd . snd) gni) == icnt &&
1567 f4161783 Iustin Pop
     all (\(guuid, (nl'', _)) -> all ((== guuid) . Node.group)
1568 f4161783 Iustin Pop
                                 (Container.elems nl'')) gni
1569 32b8d9c0 Iustin Pop
1570 00b70680 Iustin Pop
-- | Helper function to check if we can allocate an instance on a
1571 00b70680 Iustin Pop
-- given node list.
1572 00b70680 Iustin Pop
canAllocOn :: Node.List -> Int -> Instance.Instance -> Bool
1573 00b70680 Iustin Pop
canAllocOn nl reqnodes inst =
1574 00b70680 Iustin Pop
  case Cluster.genAllocNodes defGroupList nl reqnodes True >>=
1575 00b70680 Iustin Pop
       Cluster.tryAlloc nl (Container.empty) inst of
1576 00b70680 Iustin Pop
       Types.Bad _ -> False
1577 00b70680 Iustin Pop
       Types.Ok as ->
1578 00b70680 Iustin Pop
         case Cluster.asSolution as of
1579 00b70680 Iustin Pop
           Nothing -> False
1580 00b70680 Iustin Pop
           Just _ -> True
1581 00b70680 Iustin Pop
1582 00b70680 Iustin Pop
-- | Checks that allocation obeys minimum and maximum instance
1583 fce98abd Iustin Pop
-- policies. The unittest generates a random node, duplicates it /count/
1584 00b70680 Iustin Pop
-- times, and generates a random instance that can be allocated on
1585 00b70680 Iustin Pop
-- this mini-cluster; it then checks that after applying a policy that
1586 00b70680 Iustin Pop
-- the instance doesn't fits, the allocation fails.
1587 2c4eb054 Iustin Pop
prop_Cluster_AllocPolicy :: Node.Node -> Property
1588 2c4eb054 Iustin Pop
prop_Cluster_AllocPolicy node =
1589 00b70680 Iustin Pop
  -- rqn is the required nodes (1 or 2)
1590 00b70680 Iustin Pop
  forAll (choose (1, 2)) $ \rqn ->
1591 00b70680 Iustin Pop
  forAll (choose (5, 20)) $ \count ->
1592 00b70680 Iustin Pop
  forAll (arbitrary `suchThat` (canAllocOn (makeSmallCluster node count) rqn))
1593 00b70680 Iustin Pop
         $ \inst ->
1594 00b70680 Iustin Pop
  forAll (arbitrary `suchThat` (isFailure .
1595 00b70680 Iustin Pop
                                Instance.instMatchesPolicy inst)) $ \ipol ->
1596 00b70680 Iustin Pop
  let node' = Node.setPolicy ipol node
1597 00b70680 Iustin Pop
      nl = makeSmallCluster node' count
1598 00b70680 Iustin Pop
  in not $ canAllocOn nl rqn inst
1599 00b70680 Iustin Pop
1600 23fe06c2 Iustin Pop
testSuite "Cluster"
1601 2c4eb054 Iustin Pop
            [ 'prop_Cluster_Score_Zero
1602 2c4eb054 Iustin Pop
            , 'prop_Cluster_CStats_sane
1603 2c4eb054 Iustin Pop
            , 'prop_Cluster_Alloc_sane
1604 2c4eb054 Iustin Pop
            , 'prop_Cluster_CanTieredAlloc
1605 2c4eb054 Iustin Pop
            , 'prop_Cluster_AllocRelocate
1606 2c4eb054 Iustin Pop
            , 'prop_Cluster_AllocEvacuate
1607 2c4eb054 Iustin Pop
            , 'prop_Cluster_AllocChangeGroup
1608 2c4eb054 Iustin Pop
            , 'prop_Cluster_AllocBalance
1609 2c4eb054 Iustin Pop
            , 'prop_Cluster_CheckConsistency
1610 2c4eb054 Iustin Pop
            , 'prop_Cluster_SplitCluster
1611 2c4eb054 Iustin Pop
            , 'prop_Cluster_AllocPolicy
1612 d5dfae0a Iustin Pop
            ]
1613 88f25dd0 Iustin Pop
1614 525bfb36 Iustin Pop
-- ** OpCodes tests
1615 88f25dd0 Iustin Pop
1616 525bfb36 Iustin Pop
-- | Check that opcode serialization is idempotent.
1617 fce98abd Iustin Pop
prop_OpCodes_serialization :: OpCodes.OpCode -> Property
1618 88f25dd0 Iustin Pop
prop_OpCodes_serialization op =
1619 88f25dd0 Iustin Pop
  case J.readJSON (J.showJSON op) of
1620 96bc2003 Iustin Pop
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1621 72bb6b4e Iustin Pop
    J.Ok op' -> op ==? op'
1622 88f25dd0 Iustin Pop
1623 9990c068 Iustin Pop
-- | Check that Python and Haskell defined the same opcode list.
1624 9990c068 Iustin Pop
case_OpCodes_AllDefined :: HUnit.Assertion
1625 9990c068 Iustin Pop
case_OpCodes_AllDefined = do
1626 9990c068 Iustin Pop
  py_stdout <- runPython "from ganeti import opcodes\n\
1627 9990c068 Iustin Pop
                         \print '\\n'.join(opcodes.OP_MAPPING.keys())" "" >>=
1628 9990c068 Iustin Pop
               checkPythonResult
1629 9990c068 Iustin Pop
  let py_ops = sort $ lines py_stdout
1630 9990c068 Iustin Pop
      hs_ops = OpCodes.allOpIDs
1631 9990c068 Iustin Pop
      -- extra_py = py_ops \\ hs_ops
1632 9990c068 Iustin Pop
      extra_hs = hs_ops \\ py_ops
1633 9990c068 Iustin Pop
  -- FIXME: uncomment when we have parity
1634 9990c068 Iustin Pop
  -- HUnit.assertBool ("OpCodes missing from Haskell code:\n" ++
1635 9990c068 Iustin Pop
  --                  unlines extra_py) (null extra_py)
1636 9990c068 Iustin Pop
  HUnit.assertBool ("Extra OpCodes in the Haskell code code:\n" ++
1637 9990c068 Iustin Pop
                    unlines extra_hs) (null extra_hs)
1638 9990c068 Iustin Pop
1639 23fe06c2 Iustin Pop
testSuite "OpCodes"
1640 9990c068 Iustin Pop
            [ 'prop_OpCodes_serialization
1641 9990c068 Iustin Pop
            , 'case_OpCodes_AllDefined
1642 9990c068 Iustin Pop
            ]
1643 c088674b Iustin Pop
1644 525bfb36 Iustin Pop
-- ** Jobs tests
1645 525bfb36 Iustin Pop
1646 525bfb36 Iustin Pop
-- | Check that (queued) job\/opcode status serialization is idempotent.
1647 2c4eb054 Iustin Pop
prop_Jobs_OpStatus_serialization :: Jobs.OpStatus -> Property
1648 2c4eb054 Iustin Pop
prop_Jobs_OpStatus_serialization os =
1649 db079755 Iustin Pop
  case J.readJSON (J.showJSON os) of
1650 96bc2003 Iustin Pop
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1651 72bb6b4e Iustin Pop
    J.Ok os' -> os ==? os'
1652 db079755 Iustin Pop
1653 2c4eb054 Iustin Pop
prop_Jobs_JobStatus_serialization :: Jobs.JobStatus -> Property
1654 2c4eb054 Iustin Pop
prop_Jobs_JobStatus_serialization js =
1655 db079755 Iustin Pop
  case J.readJSON (J.showJSON js) of
1656 96bc2003 Iustin Pop
    J.Error e -> failTest $ "Cannot deserialise: " ++ e
1657 72bb6b4e Iustin Pop
    J.Ok js' -> js ==? js'
1658 db079755 Iustin Pop
1659 23fe06c2 Iustin Pop
testSuite "Jobs"
1660 2c4eb054 Iustin Pop
            [ 'prop_Jobs_OpStatus_serialization
1661 2c4eb054 Iustin Pop
            , 'prop_Jobs_JobStatus_serialization
1662 d5dfae0a Iustin Pop
            ]
1663 db079755 Iustin Pop
1664 525bfb36 Iustin Pop
-- ** Loader tests
1665 c088674b Iustin Pop
1666 fce98abd Iustin Pop
prop_Loader_lookupNode :: [(String, Int)] -> String -> String -> Property
1667 c088674b Iustin Pop
prop_Loader_lookupNode ktn inst node =
1668 72bb6b4e Iustin Pop
  Loader.lookupNode nl inst node ==? Data.Map.lookup node nl
1669 d5dfae0a Iustin Pop
    where nl = Data.Map.fromList ktn
1670 c088674b Iustin Pop
1671 fce98abd Iustin Pop
prop_Loader_lookupInstance :: [(String, Int)] -> String -> Property
1672 c088674b Iustin Pop
prop_Loader_lookupInstance kti inst =
1673 72bb6b4e Iustin Pop
  Loader.lookupInstance il inst ==? Data.Map.lookup inst il
1674 d5dfae0a Iustin Pop
    where il = Data.Map.fromList kti
1675 99b63608 Iustin Pop
1676 fce98abd Iustin Pop
prop_Loader_assignIndices :: Property
1677 3074ccaf Iustin Pop
prop_Loader_assignIndices =
1678 3074ccaf Iustin Pop
  -- generate nodes with unique names
1679 3074ccaf Iustin Pop
  forAll (arbitrary `suchThat`
1680 3074ccaf Iustin Pop
          (\nodes ->
1681 3074ccaf Iustin Pop
             let names = map Node.name nodes
1682 3074ccaf Iustin Pop
             in length names == length (nub names))) $ \nodes ->
1683 3074ccaf Iustin Pop
  let (nassoc, kt) =
1684 3074ccaf Iustin Pop
        Loader.assignIndices (map (\n -> (Node.name n, n)) nodes)
1685 3074ccaf Iustin Pop
  in Data.Map.size nassoc == length nodes &&
1686 3074ccaf Iustin Pop
     Container.size kt == length nodes &&
1687 3074ccaf Iustin Pop
     if not (null nodes)
1688 3074ccaf Iustin Pop
       then maximum (IntMap.keys kt) == length nodes - 1
1689 3074ccaf Iustin Pop
       else True
1690 c088674b Iustin Pop
1691 c088674b Iustin Pop
-- | Checks that the number of primary instances recorded on the nodes
1692 525bfb36 Iustin Pop
-- is zero.
1693 fce98abd Iustin Pop
prop_Loader_mergeData :: [Node.Node] -> Bool
1694 c088674b Iustin Pop
prop_Loader_mergeData ns =
1695 cb0c77ff Iustin Pop
  let na = Container.fromList $ map (\n -> (Node.idx n, n)) ns
1696 2d1708e0 Guido Trotter
  in case Loader.mergeData [] [] [] []
1697 f4f6eb0b Iustin Pop
         (Loader.emptyCluster {Loader.cdNodes = na}) of
1698 c088674b Iustin Pop
    Types.Bad _ -> False
1699 71375ef7 Iustin Pop
    Types.Ok (Loader.ClusterData _ nl il _ _) ->
1700 c088674b Iustin Pop
      let nodes = Container.elems nl
1701 c088674b Iustin Pop
          instances = Container.elems il
1702 c088674b Iustin Pop
      in (sum . map (length . Node.pList)) nodes == 0 &&
1703 4a007641 Iustin Pop
         null instances
1704 c088674b Iustin Pop
1705 efe98965 Guido Trotter
-- | Check that compareNameComponent on equal strings works.
1706 efe98965 Guido Trotter
prop_Loader_compareNameComponent_equal :: String -> Bool
1707 efe98965 Guido Trotter
prop_Loader_compareNameComponent_equal s =
1708 2fc5653f Iustin Pop
  BasicTypes.compareNameComponent s s ==
1709 2fc5653f Iustin Pop
    BasicTypes.LookupResult BasicTypes.ExactMatch s
1710 efe98965 Guido Trotter
1711 efe98965 Guido Trotter
-- | Check that compareNameComponent on prefix strings works.
1712 efe98965 Guido Trotter
prop_Loader_compareNameComponent_prefix :: NonEmptyList Char -> String -> Bool
1713 efe98965 Guido Trotter
prop_Loader_compareNameComponent_prefix (NonEmpty s1) s2 =
1714 2fc5653f Iustin Pop
  BasicTypes.compareNameComponent (s1 ++ "." ++ s2) s1 ==
1715 2fc5653f Iustin Pop
    BasicTypes.LookupResult BasicTypes.PartialMatch s1
1716 efe98965 Guido Trotter
1717 23fe06c2 Iustin Pop
testSuite "Loader"
1718 d5dfae0a Iustin Pop
            [ 'prop_Loader_lookupNode
1719 d5dfae0a Iustin Pop
            , 'prop_Loader_lookupInstance
1720 d5dfae0a Iustin Pop
            , 'prop_Loader_assignIndices
1721 d5dfae0a Iustin Pop
            , 'prop_Loader_mergeData
1722 d5dfae0a Iustin Pop
            , 'prop_Loader_compareNameComponent_equal
1723 d5dfae0a Iustin Pop
            , 'prop_Loader_compareNameComponent_prefix
1724 d5dfae0a Iustin Pop
            ]
1725 3c002a13 Iustin Pop
1726 3c002a13 Iustin Pop
-- ** Types tests
1727 3c002a13 Iustin Pop
1728 fce98abd Iustin Pop
prop_Types_AllocPolicy_serialisation :: Types.AllocPolicy -> Property
1729 0047d4e2 Iustin Pop
prop_Types_AllocPolicy_serialisation apol =
1730 d5dfae0a Iustin Pop
  case J.readJSON (J.showJSON apol) of
1731 aa1d552d Iustin Pop
    J.Ok p -> p ==? apol
1732 96bc2003 Iustin Pop
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1733 0047d4e2 Iustin Pop
1734 fce98abd Iustin Pop
prop_Types_DiskTemplate_serialisation :: Types.DiskTemplate -> Property
1735 0047d4e2 Iustin Pop
prop_Types_DiskTemplate_serialisation dt =
1736 d5dfae0a Iustin Pop
  case J.readJSON (J.showJSON dt) of
1737 aa1d552d Iustin Pop
    J.Ok p -> p ==? dt
1738 96bc2003 Iustin Pop
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1739 0047d4e2 Iustin Pop
1740 fce98abd Iustin Pop
prop_Types_ISpec_serialisation :: Types.ISpec -> Property
1741 aa1d552d Iustin Pop
prop_Types_ISpec_serialisation ispec =
1742 aa1d552d Iustin Pop
  case J.readJSON (J.showJSON ispec) of
1743 aa1d552d Iustin Pop
    J.Ok p -> p ==? ispec
1744 96bc2003 Iustin Pop
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1745 aa1d552d Iustin Pop
1746 fce98abd Iustin Pop
prop_Types_IPolicy_serialisation :: Types.IPolicy -> Property
1747 aa1d552d Iustin Pop
prop_Types_IPolicy_serialisation ipol =
1748 aa1d552d Iustin Pop
  case J.readJSON (J.showJSON ipol) of
1749 aa1d552d Iustin Pop
    J.Ok p -> p ==? ipol
1750 96bc2003 Iustin Pop
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1751 aa1d552d Iustin Pop
1752 fce98abd Iustin Pop
prop_Types_EvacMode_serialisation :: Types.EvacMode -> Property
1753 aa1d552d Iustin Pop
prop_Types_EvacMode_serialisation em =
1754 aa1d552d Iustin Pop
  case J.readJSON (J.showJSON em) of
1755 aa1d552d Iustin Pop
    J.Ok p -> p ==? em
1756 96bc2003 Iustin Pop
    J.Error s -> failTest $ "Failed to deserialise: " ++ s
1757 aa1d552d Iustin Pop
1758 fce98abd Iustin Pop
prop_Types_opToResult :: Types.OpResult Int -> Bool
1759 0047d4e2 Iustin Pop
prop_Types_opToResult op =
1760 d5dfae0a Iustin Pop
  case op of
1761 d5dfae0a Iustin Pop
    Types.OpFail _ -> Types.isBad r
1762 d5dfae0a Iustin Pop
    Types.OpGood v -> case r of
1763 d5dfae0a Iustin Pop
                        Types.Bad _ -> False
1764 d5dfae0a Iustin Pop
                        Types.Ok v' -> v == v'
1765 d5dfae0a Iustin Pop
  where r = Types.opToResult op
1766 0047d4e2 Iustin Pop
1767 fce98abd Iustin Pop
prop_Types_eitherToResult :: Either String Int -> Bool
1768 0047d4e2 Iustin Pop
prop_Types_eitherToResult ei =
1769 d5dfae0a Iustin Pop
  case ei of
1770 d5dfae0a Iustin Pop
    Left _ -> Types.isBad r
1771 d5dfae0a Iustin Pop
    Right v -> case r of
1772 d5dfae0a Iustin Pop
                 Types.Bad _ -> False
1773 d5dfae0a Iustin Pop
                 Types.Ok v' -> v == v'
1774 0047d4e2 Iustin Pop
    where r = Types.eitherToResult ei
1775 3c002a13 Iustin Pop
1776 23fe06c2 Iustin Pop
testSuite "Types"
1777 d5dfae0a Iustin Pop
            [ 'prop_Types_AllocPolicy_serialisation
1778 d5dfae0a Iustin Pop
            , 'prop_Types_DiskTemplate_serialisation
1779 aa1d552d Iustin Pop
            , 'prop_Types_ISpec_serialisation
1780 aa1d552d Iustin Pop
            , 'prop_Types_IPolicy_serialisation
1781 aa1d552d Iustin Pop
            , 'prop_Types_EvacMode_serialisation
1782 d5dfae0a Iustin Pop
            , 'prop_Types_opToResult
1783 d5dfae0a Iustin Pop
            , 'prop_Types_eitherToResult
1784 d5dfae0a Iustin Pop
            ]
1785 8b5a517a Iustin Pop
1786 8b5a517a Iustin Pop
-- ** CLI tests
1787 8b5a517a Iustin Pop
1788 8b5a517a Iustin Pop
-- | Test correct parsing.
1789 fce98abd Iustin Pop
prop_CLI_parseISpec :: String -> Int -> Int -> Int -> Property
1790 8b5a517a Iustin Pop
prop_CLI_parseISpec descr dsk mem cpu =
1791 fce98abd Iustin Pop
  let str = printf "%d,%d,%d" dsk mem cpu::String
1792 8b5a517a Iustin Pop
  in CLI.parseISpecString descr str ==? Types.Ok (Types.RSpec cpu mem dsk)
1793 8b5a517a Iustin Pop
1794 8b5a517a Iustin Pop
-- | Test parsing failure due to wrong section count.
1795 fce98abd Iustin Pop
prop_CLI_parseISpecFail :: String -> Property
1796 8b5a517a Iustin Pop
prop_CLI_parseISpecFail descr =
1797 8b5a517a Iustin Pop
  forAll (choose (0,100) `suchThat` ((/=) 3)) $ \nelems ->
1798 8b5a517a Iustin Pop
  forAll (replicateM nelems arbitrary) $ \values ->
1799 8b5a517a Iustin Pop
  let str = intercalate "," $ map show (values::[Int])
1800 8b5a517a Iustin Pop
  in case CLI.parseISpecString descr str of
1801 8b5a517a Iustin Pop
       Types.Ok v -> failTest $ "Expected failure, got " ++ show v
1802 8b5a517a Iustin Pop
       _ -> property True
1803 8b5a517a Iustin Pop
1804 a7ea861a Iustin Pop
-- | Test parseYesNo.
1805 fce98abd Iustin Pop
prop_CLI_parseYesNo :: Bool -> Bool -> [Char] -> Property
1806 a7ea861a Iustin Pop
prop_CLI_parseYesNo def testval val =
1807 a7ea861a Iustin Pop
  forAll (elements [val, "yes", "no"]) $ \actual_val ->
1808 a7ea861a Iustin Pop
  if testval
1809 a7ea861a Iustin Pop
    then CLI.parseYesNo def Nothing ==? Types.Ok def
1810 a7ea861a Iustin Pop
    else let result = CLI.parseYesNo def (Just actual_val)
1811 a7ea861a Iustin Pop
         in if actual_val `elem` ["yes", "no"]
1812 a7ea861a Iustin Pop
              then result ==? Types.Ok (actual_val == "yes")
1813 a7ea861a Iustin Pop
              else property $ Types.isBad result
1814 a7ea861a Iustin Pop
1815 89298c04 Iustin Pop
-- | Helper to check for correct parsing of string arg.
1816 fce98abd Iustin Pop
checkStringArg :: [Char]
1817 fce98abd Iustin Pop
               -> (GetOpt.OptDescr (CLI.Options -> Types.Result CLI.Options),
1818 fce98abd Iustin Pop
                   CLI.Options -> Maybe [Char])
1819 fce98abd Iustin Pop
               -> Property
1820 89298c04 Iustin Pop
checkStringArg val (opt, fn) =
1821 89298c04 Iustin Pop
  let GetOpt.Option _ longs _ _ = opt
1822 89298c04 Iustin Pop
  in case longs of
1823 89298c04 Iustin Pop
       [] -> failTest "no long options?"
1824 89298c04 Iustin Pop
       cmdarg:_ ->
1825 89298c04 Iustin Pop
         case CLI.parseOptsInner ["--" ++ cmdarg ++ "=" ++ val] "prog" [opt] of
1826 89298c04 Iustin Pop
           Left e -> failTest $ "Failed to parse option: " ++ show e
1827 89298c04 Iustin Pop
           Right (options, _) -> fn options ==? Just val
1828 89298c04 Iustin Pop
1829 89298c04 Iustin Pop
-- | Test a few string arguments.
1830 fce98abd Iustin Pop
prop_CLI_StringArg :: [Char] -> Property
1831 89298c04 Iustin Pop
prop_CLI_StringArg argument =
1832 89298c04 Iustin Pop
  let args = [ (CLI.oDataFile,      CLI.optDataFile)
1833 89298c04 Iustin Pop
             , (CLI.oDynuFile,      CLI.optDynuFile)
1834 89298c04 Iustin Pop
             , (CLI.oSaveCluster,   CLI.optSaveCluster)
1835 89298c04 Iustin Pop
             , (CLI.oReplay,        CLI.optReplay)
1836 89298c04 Iustin Pop
             , (CLI.oPrintCommands, CLI.optShowCmds)
1837 89298c04 Iustin Pop
             , (CLI.oLuxiSocket,    CLI.optLuxi)
1838 89298c04 Iustin Pop
             ]
1839 89298c04 Iustin Pop
  in conjoin $ map (checkStringArg argument) args
1840 89298c04 Iustin Pop
1841 a292b4e0 Iustin Pop
-- | Helper to test that a given option is accepted OK with quick exit.
1842 fce98abd Iustin Pop
checkEarlyExit :: String -> [CLI.OptType] -> String -> Property
1843 a292b4e0 Iustin Pop
checkEarlyExit name options param =
1844 a292b4e0 Iustin Pop
  case CLI.parseOptsInner [param] name options of
1845 a292b4e0 Iustin Pop
    Left (code, _) -> if code == 0
1846 a292b4e0 Iustin Pop
                          then property True
1847 a292b4e0 Iustin Pop
                          else failTest $ "Program " ++ name ++
1848 a292b4e0 Iustin Pop
                                 " returns invalid code " ++ show code ++
1849 a292b4e0 Iustin Pop
                                 " for option " ++ param
1850 a292b4e0 Iustin Pop
    _ -> failTest $ "Program " ++ name ++ " doesn't consider option " ++
1851 a292b4e0 Iustin Pop
         param ++ " as early exit one"
1852 a292b4e0 Iustin Pop
1853 a292b4e0 Iustin Pop
-- | Test that all binaries support some common options. There is
1854 a292b4e0 Iustin Pop
-- nothing actually random about this test...
1855 fce98abd Iustin Pop
prop_CLI_stdopts :: Property
1856 a292b4e0 Iustin Pop
prop_CLI_stdopts =
1857 a292b4e0 Iustin Pop
  let params = ["-h", "--help", "-V", "--version"]
1858 a292b4e0 Iustin Pop
      opts = map (\(name, (_, o)) -> (name, o)) Program.personalities
1859 a292b4e0 Iustin Pop
      -- apply checkEarlyExit across the cartesian product of params and opts
1860 a292b4e0 Iustin Pop
  in conjoin [checkEarlyExit n o p | p <- params, (n, o) <- opts]
1861 a292b4e0 Iustin Pop
1862 8b5a517a Iustin Pop
testSuite "CLI"
1863 8b5a517a Iustin Pop
          [ 'prop_CLI_parseISpec
1864 8b5a517a Iustin Pop
          , 'prop_CLI_parseISpecFail
1865 a7ea861a Iustin Pop
          , 'prop_CLI_parseYesNo
1866 89298c04 Iustin Pop
          , 'prop_CLI_StringArg
1867 a292b4e0 Iustin Pop
          , 'prop_CLI_stdopts
1868 8b5a517a Iustin Pop
          ]
1869 3ad57194 Iustin Pop
1870 3ad57194 Iustin Pop
-- * JSON tests
1871 3ad57194 Iustin Pop
1872 3ad57194 Iustin Pop
prop_JSON_toArray :: [Int] -> Property
1873 3ad57194 Iustin Pop
prop_JSON_toArray intarr =
1874 3ad57194 Iustin Pop
  let arr = map J.showJSON intarr in
1875 3ad57194 Iustin Pop
  case JSON.toArray (J.JSArray arr) of
1876 3ad57194 Iustin Pop
    Types.Ok arr' -> arr ==? arr'
1877 3ad57194 Iustin Pop
    Types.Bad err -> failTest $ "Failed to parse array: " ++ err
1878 3ad57194 Iustin Pop
1879 3ad57194 Iustin Pop
prop_JSON_toArrayFail :: Int -> String -> Bool -> Property
1880 3ad57194 Iustin Pop
prop_JSON_toArrayFail i s b =
1881 3ad57194 Iustin Pop
  -- poor man's instance Arbitrary JSValue
1882 3ad57194 Iustin Pop
  forAll (elements [J.showJSON i, J.showJSON s, J.showJSON b]) $ \item ->
1883 3ad57194 Iustin Pop
  case JSON.toArray item of
1884 3ad57194 Iustin Pop
    Types.Bad _ -> property True
1885 3ad57194 Iustin Pop
    Types.Ok result -> failTest $ "Unexpected parse, got " ++ show result
1886 3ad57194 Iustin Pop
1887 3ad57194 Iustin Pop
testSuite "JSON"
1888 3ad57194 Iustin Pop
          [ 'prop_JSON_toArray
1889 3ad57194 Iustin Pop
          , 'prop_JSON_toArrayFail
1890 3ad57194 Iustin Pop
          ]
1891 cdd495ae Iustin Pop
1892 cdd495ae Iustin Pop
-- * Luxi tests
1893 cdd495ae Iustin Pop
1894 be747966 Iustin Pop
instance Arbitrary Luxi.TagObject where
1895 be747966 Iustin Pop
  arbitrary = elements [minBound..maxBound]
1896 be747966 Iustin Pop
1897 cdd495ae Iustin Pop
instance Arbitrary Luxi.LuxiReq where
1898 cdd495ae Iustin Pop
  arbitrary = elements [minBound..maxBound]
1899 cdd495ae Iustin Pop
1900 cdd495ae Iustin Pop
instance Arbitrary Luxi.LuxiOp where
1901 cdd495ae Iustin Pop
  arbitrary = do
1902 cdd495ae Iustin Pop
    lreq <- arbitrary
1903 cdd495ae Iustin Pop
    case lreq of
1904 9a94c848 Iustin Pop
      Luxi.ReqQuery -> Luxi.Query <$> arbitrary <*> getFields <*> genFilter
1905 cdd495ae Iustin Pop
      Luxi.ReqQueryNodes -> Luxi.QueryNodes <$> (listOf getFQDN) <*>
1906 cdd495ae Iustin Pop
                            getFields <*> arbitrary
1907 cdd495ae Iustin Pop
      Luxi.ReqQueryGroups -> Luxi.QueryGroups <$> arbitrary <*>
1908 cdd495ae Iustin Pop
                             arbitrary <*> arbitrary
1909 cdd495ae Iustin Pop
      Luxi.ReqQueryInstances -> Luxi.QueryInstances <$> (listOf getFQDN) <*>
1910 cdd495ae Iustin Pop
                                getFields <*> arbitrary
1911 cdd495ae Iustin Pop
      Luxi.ReqQueryJobs -> Luxi.QueryJobs <$> arbitrary <*> getFields
1912 cdd495ae Iustin Pop
      Luxi.ReqQueryExports -> Luxi.QueryExports <$>
1913 cdd495ae Iustin Pop
                              (listOf getFQDN) <*> arbitrary
1914 cdd495ae Iustin Pop
      Luxi.ReqQueryConfigValues -> Luxi.QueryConfigValues <$> getFields
1915 cdd495ae Iustin Pop
      Luxi.ReqQueryClusterInfo -> pure Luxi.QueryClusterInfo
1916 be747966 Iustin Pop
      Luxi.ReqQueryTags -> Luxi.QueryTags <$> arbitrary <*> getFQDN
1917 cdd495ae Iustin Pop
      Luxi.ReqSubmitJob -> Luxi.SubmitJob <$> (resize maxOpCodes arbitrary)
1918 cdd495ae Iustin Pop
      Luxi.ReqSubmitManyJobs -> Luxi.SubmitManyJobs <$>
1919 cdd495ae Iustin Pop
                                (resize maxOpCodes arbitrary)
1920 cdd495ae Iustin Pop
      Luxi.ReqWaitForJobChange -> Luxi.WaitForJobChange <$> arbitrary <*>
1921 cdd495ae Iustin Pop
                                  getFields <*> pure J.JSNull <*>
1922 cdd495ae Iustin Pop
                                  pure J.JSNull <*> arbitrary
1923 cdd495ae Iustin Pop
      Luxi.ReqArchiveJob -> Luxi.ArchiveJob <$> arbitrary
1924 cdd495ae Iustin Pop
      Luxi.ReqAutoArchiveJobs -> Luxi.AutoArchiveJobs <$> arbitrary <*>
1925 cdd495ae Iustin Pop
                                 arbitrary
1926 cdd495ae Iustin Pop
      Luxi.ReqCancelJob -> Luxi.CancelJob <$> arbitrary
1927 cdd495ae Iustin Pop
      Luxi.ReqSetDrainFlag -> Luxi.SetDrainFlag <$> arbitrary
1928 cdd495ae Iustin Pop
      Luxi.ReqSetWatcherPause -> Luxi.SetWatcherPause <$> arbitrary
1929 cdd495ae Iustin Pop
1930 cdd495ae Iustin Pop
-- | Simple check that encoding/decoding of LuxiOp works.
1931 cdd495ae Iustin Pop
prop_Luxi_CallEncoding :: Luxi.LuxiOp -> Property
1932 cdd495ae Iustin Pop
prop_Luxi_CallEncoding op =
1933 cdd495ae Iustin Pop
  (Luxi.validateCall (Luxi.buildCall op) >>= Luxi.decodeCall) ==? Types.Ok op
1934 cdd495ae Iustin Pop
1935 13f2321c Iustin Pop
-- | Helper to a get a temporary file name.
1936 13f2321c Iustin Pop
getTempFileName :: IO FilePath
1937 13f2321c Iustin Pop
getTempFileName = do
1938 13f2321c Iustin Pop
  tempdir <- getTemporaryDirectory
1939 13f2321c Iustin Pop
  (fpath, handle) <- openTempFile tempdir "luxitest"
1940 13f2321c Iustin Pop
  _ <- hClose handle
1941 13f2321c Iustin Pop
  removeFile fpath
1942 13f2321c Iustin Pop
  return fpath
1943 13f2321c Iustin Pop
1944 13f2321c Iustin Pop
-- | Server ping-pong helper.
1945 13f2321c Iustin Pop
luxiServerPong :: Luxi.Client -> IO ()
1946 13f2321c Iustin Pop
luxiServerPong c = do
1947 a03b2e1c Iustin Pop
  msg <- Luxi.recvMsgExt c
1948 13f2321c Iustin Pop
  case msg of
1949 a03b2e1c Iustin Pop
    Luxi.RecvOk m -> Luxi.sendMsg c m >> luxiServerPong c
1950 a03b2e1c Iustin Pop
    _ -> return ()
1951 13f2321c Iustin Pop
1952 13f2321c Iustin Pop
-- | Client ping-pong helper.
1953 13f2321c Iustin Pop
luxiClientPong :: Luxi.Client -> [String] -> IO [String]
1954 13f2321c Iustin Pop
luxiClientPong c =
1955 13f2321c Iustin Pop
  mapM (\m -> Luxi.sendMsg c m >> Luxi.recvMsg c)
1956 13f2321c Iustin Pop
1957 13f2321c Iustin Pop
-- | Monadic check that, given a server socket, we can connect via a
1958 13f2321c Iustin Pop
-- client to it, and that we can send a list of arbitrary messages and
1959 13f2321c Iustin Pop
-- get back what we sent.
1960 13f2321c Iustin Pop
prop_Luxi_ClientServer :: [[DNSChar]] -> Property
1961 13f2321c Iustin Pop
prop_Luxi_ClientServer dnschars = monadicIO $ do
1962 13f2321c Iustin Pop
  let msgs = map (map dnsGetChar) dnschars
1963 13f2321c Iustin Pop
  fpath <- run $ getTempFileName
1964 13f2321c Iustin Pop
  -- we need to create the server first, otherwise (if we do it in the
1965 13f2321c Iustin Pop
  -- forked thread) the client could try to connect to it before it's
1966 13f2321c Iustin Pop
  -- ready
1967 13f2321c Iustin Pop
  server <- run $ Luxi.getServer fpath
1968 13f2321c Iustin Pop
  -- fork the server responder
1969 2cdaf225 Iustin Pop
  _ <- run . forkIO $
1970 13f2321c Iustin Pop
    bracket
1971 13f2321c Iustin Pop
      (Luxi.acceptClient server)
1972 a23643ee Iustin Pop
      (\c -> Luxi.closeClient c >> Luxi.closeServer fpath server)
1973 13f2321c Iustin Pop
      luxiServerPong
1974 13f2321c Iustin Pop
  replies <- run $
1975 13f2321c Iustin Pop
    bracket
1976 13f2321c Iustin Pop
      (Luxi.getClient fpath)
1977 13f2321c Iustin Pop
      Luxi.closeClient
1978 13f2321c Iustin Pop
      (\c -> luxiClientPong c msgs)
1979 13f2321c Iustin Pop
  assert $ replies == msgs
1980 13f2321c Iustin Pop
1981 2c4eb054 Iustin Pop
testSuite "Luxi"
1982 cdd495ae Iustin Pop
          [ 'prop_Luxi_CallEncoding
1983 13f2321c Iustin Pop
          , 'prop_Luxi_ClientServer
1984 cdd495ae Iustin Pop
          ]
1985 c5b4a186 Iustin Pop
1986 c5b4a186 Iustin Pop
-- * Ssconf tests
1987 c5b4a186 Iustin Pop
1988 c5b4a186 Iustin Pop
instance Arbitrary Ssconf.SSKey where
1989 c5b4a186 Iustin Pop
  arbitrary = elements [minBound..maxBound]
1990 c5b4a186 Iustin Pop
1991 fce98abd Iustin Pop
prop_Ssconf_filename :: Ssconf.SSKey -> Property
1992 c5b4a186 Iustin Pop
prop_Ssconf_filename key =
1993 c5b4a186 Iustin Pop
  printTestCase "Key doesn't start with correct prefix" $
1994 c5b4a186 Iustin Pop
    Ssconf.sSFilePrefix `isPrefixOf` Ssconf.keyToFilename (Just "") key
1995 c5b4a186 Iustin Pop
1996 c5b4a186 Iustin Pop
testSuite "Ssconf"
1997 c5b4a186 Iustin Pop
  [ 'prop_Ssconf_filename
1998 c5b4a186 Iustin Pop
  ]
1999 66f74cae Agata Murawska
2000 66f74cae Agata Murawska
-- * Rpc tests
2001 66f74cae Agata Murawska
2002 66f74cae Agata Murawska
-- | Monadic check that, for an offline node and a call that does not
2003 66f74cae Agata Murawska
-- offline nodes, we get a OfflineNodeError response.
2004 66f74cae Agata Murawska
-- FIXME: We need a way of generalizing this, running it for
2005 66f74cae Agata Murawska
-- every call manually will soon get problematic
2006 66f74cae Agata Murawska
prop_Rpc_noffl_request_allinstinfo :: Rpc.RpcCallAllInstancesInfo -> Property
2007 66f74cae Agata Murawska
prop_Rpc_noffl_request_allinstinfo call =
2008 66f74cae Agata Murawska
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
2009 66f74cae Agata Murawska
      res <- run $ Rpc.executeRpcCall [node] call
2010 66f74cae Agata Murawska
      stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
2011 66f74cae Agata Murawska
2012 66f74cae Agata Murawska
prop_Rpc_noffl_request_instlist :: Rpc.RpcCallInstanceList -> Property
2013 66f74cae Agata Murawska
prop_Rpc_noffl_request_instlist call =
2014 66f74cae Agata Murawska
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
2015 66f74cae Agata Murawska
      res <- run $ Rpc.executeRpcCall [node] call
2016 66f74cae Agata Murawska
      stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
2017 66f74cae Agata Murawska
2018 66f74cae Agata Murawska
prop_Rpc_noffl_request_nodeinfo :: Rpc.RpcCallNodeInfo -> Property
2019 66f74cae Agata Murawska
prop_Rpc_noffl_request_nodeinfo call =
2020 66f74cae Agata Murawska
  forAll (arbitrary `suchThat` Objects.nodeOffline) $ \node -> monadicIO $ do
2021 66f74cae Agata Murawska
      res <- run $ Rpc.executeRpcCall [node] call
2022 66f74cae Agata Murawska
      stop $ res ==? [(node, Left (Rpc.OfflineNodeError node))]
2023 66f74cae Agata Murawska
2024 66f74cae Agata Murawska
testSuite "Rpc"
2025 66f74cae Agata Murawska
  [ 'prop_Rpc_noffl_request_allinstinfo
2026 66f74cae Agata Murawska
  , 'prop_Rpc_noffl_request_instlist
2027 66f74cae Agata Murawska
  , 'prop_Rpc_noffl_request_nodeinfo
2028 66f74cae Agata Murawska
  ]
2029 e8a25d62 Iustin Pop
2030 dc6a0f82 Iustin Pop
-- * Qlang tests
2031 e8a25d62 Iustin Pop
2032 e8a25d62 Iustin Pop
-- | Tests that serialisation/deserialisation of filters is
2033 e8a25d62 Iustin Pop
-- idempotent.
2034 dc6a0f82 Iustin Pop
prop_Qlang_Serialisation :: Property
2035 dc6a0f82 Iustin Pop
prop_Qlang_Serialisation =
2036 e8a25d62 Iustin Pop
  forAll genFilter $ \flt ->
2037 e8a25d62 Iustin Pop
  J.readJSON (J.showJSON flt) ==? J.Ok flt
2038 e8a25d62 Iustin Pop
2039 dc6a0f82 Iustin Pop
testSuite "Qlang"
2040 dc6a0f82 Iustin Pop
  [ 'prop_Qlang_Serialisation
2041 e8a25d62 Iustin Pop
  ]