Statistics
| Branch: | Tag: | Revision:

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

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