Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (51.5 kB)

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