Unit tests for htools and exclusive storage
authorBernardo Dal Seno <bdalseno@google.com>
Wed, 5 Jun 2013 20:53:10 +0000 (22:53 +0200)
committerBernardo Dal Seno <bdalseno@google.com>
Fri, 7 Jun 2013 13:11:09 +0000 (15:11 +0200)
The existing tests are run also on nodes with exclusive storage enabled. The
values for spindles and exclusive storage are set in a consistent way, for
both nodes and instances.

Signed-off-by: Bernardo Dal Seno <bdalseno@google.com>
Reviewed-by: Klaus Aehlig <aehlig@google.com>

src/Ganeti/HTools/Types.hs
test/hs/Test/Ganeti/HTools/Cluster.hs
test/hs/Test/Ganeti/HTools/Instance.hs
test/hs/Test/Ganeti/HTools/Node.hs
test/hs/Test/Ganeti/TestCommon.hs
test/hs/Test/Ganeti/TestHTools.hs

index af533dc..84b1041 100644 (file)
@@ -53,6 +53,7 @@ module Ganeti.HTools.Types
   , unitMem
   , unitCpu
   , unitDsk
+  , unitSpindle
   , unknownField
   , Placement
   , IMove(..)
@@ -317,6 +318,10 @@ unitDsk = 256
 unitCpu :: Int
 unitCpu = 1
 
+-- | Base spindles unit.
+unitSpindle :: Int
+unitSpindle = 1
+
 -- | Reason for an operation's falure.
 data FailMode = FailMem  -- ^ Failed due to not enough RAM
               | FailDisk -- ^ Failed due to not enough disk
index bb11ac9..b51093b 100644 (file)
@@ -106,7 +106,8 @@ prop_Score_Zero :: Node.Node -> Property
 prop_Score_Zero node =
   forAll (choose (1, 1024)) $ \count ->
     (not (Node.offline node) && not (Node.failN1 node) && (count > 0) &&
-     (Node.tDsk node > 0) && (Node.tMem node > 0)) ==>
+     (Node.tDsk node > 0) && (Node.tMem node > 0) &&
+     (Node.tSpindles node > 0)) ==>
   let fn = Node.buildPeers node Container.empty
       nlst = replicate count fn
       score = Cluster.compCVNodes nlst
index 0d65dd2..6ac9699 100644 (file)
@@ -7,7 +7,7 @@
 
 {-
 
-Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
+Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
 
 This program is free software; you can redistribute it and/or modify
 it under the terms of the GNU General Public License as published by
@@ -30,12 +30,12 @@ module Test.Ganeti.HTools.Instance
   ( testHTools_Instance
   , genInstanceSmallerThanNode
   , genInstanceMaybeBiggerThanNode
-  , genInstanceSmallerThan
   , genInstanceOnNodeList
   , genInstanceList
   , Instance.Instance(..)
   ) where
 
+import Control.Monad (liftM)
 import Test.QuickCheck hiding (Result)
 
 import Test.Ganeti.TestHelper
@@ -52,8 +52,9 @@ import qualified Ganeti.HTools.Types as Types
 -- * Arbitrary instances
 
 -- | Generates a random instance with maximum disk/mem/cpu values.
-genInstanceSmallerThan :: Int -> Int -> Int -> Gen Instance.Instance
-genInstanceSmallerThan lim_mem lim_dsk lim_cpu = do
+genInstanceSmallerThan :: Int -> Int -> Int -> Maybe Int ->
+                          Gen Instance.Instance
+genInstanceSmallerThan lim_mem lim_dsk lim_cpu lim_spin = do
   name <- genFQDN
   mem <- choose (0, lim_mem)
   dsk <- choose (0, lim_dsk)
@@ -62,7 +63,9 @@ genInstanceSmallerThan lim_mem lim_dsk lim_cpu = do
   sn <- arbitrary
   vcpus <- choose (0, lim_cpu)
   dt <- arbitrary
-  spindles <- arbitrary
+  spindles <- case lim_spin of
+    Nothing -> genMaybe $ choose (0, maxSpindles)
+    Just ls -> liftM Just $ choose (0, ls)
   let disk = Instance.Disk dsk spindles
   return $ Instance.create
     name mem dsk [disk] vcpus run_st [] True pn sn dt 1 []
@@ -73,6 +76,9 @@ genInstanceSmallerThanNode node =
   genInstanceSmallerThan (Node.availMem node `div` 2)
                          (Node.availDisk node `div` 2)
                          (Node.availCpu node `div` 2)
+                         (if Node.exclStorage node
+                          then Just $ Node.fSpindles node `div` 2
+                          else Nothing)
 
 -- | Generates an instance possibly bigger than a node.
 genInstanceMaybeBiggerThanNode :: Node.Node -> Gen Instance.Instance
@@ -80,6 +86,10 @@ genInstanceMaybeBiggerThanNode node =
   genInstanceSmallerThan (Node.availMem  node + Types.unitMem * 2)
                          (Node.availDisk node + Types.unitDsk * 3)
                          (Node.availCpu  node + Types.unitCpu * 4)
+                         (if Node.exclStorage node
+                          then Just $ Node.fSpindles node +
+                               Types.unitSpindle * 5
+                          else Nothing)
 
 -- | Generates an instance with nodes on a node list.
 -- The following rules are respected:
@@ -106,7 +116,7 @@ genInstanceList igen = fmap (snd . Loader.assignIndices) names_instances
 
 -- let's generate a random instance
 instance Arbitrary Instance.Instance where
-  arbitrary = genInstanceSmallerThan maxMem maxDsk maxCpu
+  arbitrary = genInstanceSmallerThan maxMem maxDsk maxCpu Nothing
 
 -- * Test cases
 
index 3a79a6a..bcf4e1e 100644 (file)
@@ -69,18 +69,20 @@ genNode :: Maybe Int -- ^ Minimum node size in terms of units
                      -- just by the max... constants)
         -> Gen Node.Node
 genNode min_multiplier max_multiplier = do
-  let (base_mem, base_dsk, base_cpu) =
+  let (base_mem, base_dsk, base_cpu, base_spindles) =
         case min_multiplier of
           Just mm -> (mm * Types.unitMem,
                       mm * Types.unitDsk,
-                      mm * Types.unitCpu)
-          Nothing -> (0, 0, 0)
-      (top_mem, top_dsk, top_cpu)  =
+                      mm * Types.unitCpu,
+                      mm)
+          Nothing -> (0, 0, 0, 0)
+      (top_mem, top_dsk, top_cpu, top_spindles)  =
         case max_multiplier of
           Just mm -> (mm * Types.unitMem,
                       mm * Types.unitDsk,
-                      mm * Types.unitCpu)
-          Nothing -> (maxMem, maxDsk, maxCpu)
+                      mm * Types.unitCpu,
+                      mm)
+          Nothing -> (maxMem, maxDsk, maxCpu, maxSpindles)
   name  <- genFQDN
   mem_t <- choose (base_mem, top_mem)
   mem_f <- choose (base_mem, mem_t)
@@ -89,8 +91,10 @@ genNode min_multiplier max_multiplier = do
   dsk_f <- choose (base_dsk, dsk_t)
   cpu_t <- choose (base_cpu, top_cpu)
   offl  <- arbitrary
+  spindles <- choose (base_spindles, top_spindles)
   let n = Node.create name (fromIntegral mem_t) mem_n mem_f
-          (fromIntegral dsk_t) dsk_f (fromIntegral cpu_t) offl 1 0 0 False
+          (fromIntegral dsk_t) dsk_f (fromIntegral cpu_t) offl spindles
+          0 0 False
       n' = Node.setPolicy nullIPolicy n
   return $ Node.buildPeers n' Container.empty
 
@@ -101,7 +105,21 @@ genOnlineNode =
                               not (Node.failN1 n) &&
                               Node.availDisk n > 0 &&
                               Node.availMem n > 0 &&
-                              Node.availCpu n > 0)
+                              Node.availCpu n > 0 &&
+                              Node.tSpindles n > 0)
+
+-- | Generate a node with exclusive storage enabled.
+genExclStorNode :: Gen Node.Node
+genExclStorNode = do
+  n <- genOnlineNode
+  fs <- choose (Types.unitSpindle, Node.tSpindles n)
+  return n { Node.exclStorage = True
+           , Node.fSpindles = fs
+           }
+
+-- | Generate a node with exclusive storage possibly enabled.
+genMaybeExclStorNode :: Gen Node.Node
+genMaybeExclStorNode = oneof [genOnlineNode, genExclStorNode]
 
 -- and a random node
 instance Arbitrary Node.Node where
@@ -170,7 +188,7 @@ prop_setFmemExact node =
 -- memory does not raise an N+1 error
 prop_addPri_NoN1Fail :: Property
 prop_addPri_NoN1Fail =
-  forAll genOnlineNode $ \node ->
+  forAll genMaybeExclStorNode $ \node ->
   forAll (genInstanceSmallerThanNode node) $ \inst ->
   let inst' = inst { Instance.mem = Node.fMem node - Node.rMem node }
   in (Node.addPri node inst' /=? Bad Types.FailN1)
@@ -201,7 +219,7 @@ prop_addPriFD node inst =
 prop_addPriFC :: Property
 prop_addPriFC =
   forAll (choose (1, maxCpu)) $ \extra ->
-  forAll genOnlineNode $ \node ->
+  forAll genMaybeExclStorNode $ \node ->
   forAll (arbitrary `suchThat` Instance.notOffline) $ \inst ->
   let inst' = setInstanceSmallerThanNode node inst
       inst'' = inst' { Instance.vcpus = Node.availCpu node + extra }
@@ -223,7 +241,7 @@ prop_addSec node inst pdx =
 -- extra mem/cpu can always be added.
 prop_addOfflinePri :: NonNegative Int -> NonNegative Int -> Property
 prop_addOfflinePri (NonNegative extra_mem) (NonNegative extra_cpu) =
-  forAll genOnlineNode $ \node ->
+  forAll genMaybeExclStorNode $ \node ->
   forAll (genInstanceSmallerThanNode node) $ \inst ->
   let inst' = inst { Instance.runSt = Types.StatusOffline
                    , Instance.mem = Node.availMem node + extra_mem
@@ -237,7 +255,7 @@ prop_addOfflinePri (NonNegative extra_mem) (NonNegative extra_cpu) =
 prop_addOfflineSec :: NonNegative Int -> NonNegative Int
                    -> Types.Ndx -> Property
 prop_addOfflineSec (NonNegative extra_mem) (NonNegative extra_cpu) pdx =
-  forAll genOnlineNode $ \node ->
+  forAll genMaybeExclStorNode $ \node ->
   forAll (genInstanceSmallerThanNode node) $ \inst ->
   let inst' = inst { Instance.runSt = Types.StatusOffline
                    , Instance.mem = Node.availMem node + extra_mem
@@ -251,7 +269,8 @@ prop_addOfflineSec (NonNegative extra_mem) (NonNegative extra_cpu) pdx =
 prop_rMem :: Instance.Instance -> Property
 prop_rMem inst =
   not (Instance.isOffline inst) ==>
-  forAll (genOnlineNode `suchThat` ((> Types.unitMem) . Node.fMem)) $ \node ->
+  forAll (genMaybeExclStorNode `suchThat` ((> Types.unitMem) . Node.fMem)) $
+    \node ->
   -- ab = auto_balance, nb = non-auto_balance
   -- we use -1 as the primary node of the instance
   let inst' = inst { Instance.pNode = -1, Instance.autoBalance = True
@@ -324,7 +343,7 @@ prop_computeGroups nodes =
 -- Check idempotence of add/remove operations
 prop_addPri_idempotent :: Property
 prop_addPri_idempotent =
-  forAll genOnlineNode $ \node ->
+  forAll genMaybeExclStorNode $ \node ->
   forAll (genInstanceSmallerThanNode node) $ \inst ->
   case Node.addPri node inst of
     Ok node' -> Node.removePri node' inst ==? node
@@ -332,7 +351,7 @@ prop_addPri_idempotent =
 
 prop_addSec_idempotent :: Property
 prop_addSec_idempotent =
-  forAll genOnlineNode $ \node ->
+  forAll genMaybeExclStorNode $ \node ->
   forAll (genInstanceSmallerThanNode node) $ \inst ->
   let pdx = Node.idx node + 1
       inst' = Instance.setPri inst pdx
index 09785f9..7e1bc71 100644 (file)
@@ -27,6 +27,7 @@ module Test.Ganeti.TestCommon
   ( maxMem
   , maxDsk
   , maxCpu
+  , maxSpindles
   , maxVcpuRatio
   , maxSpindleRatio
   , maxNodes
@@ -98,6 +99,10 @@ maxDsk = 1024 * 1024 * 8
 maxCpu :: Int
 maxCpu = 1024
 
+-- | Max spindles (1024, somewhat random value).
+maxSpindles :: Int
+maxSpindles = 1024
+
 -- | Max vcpu ratio (random value).
 maxVcpuRatio :: Double
 maxVcpuRatio = 1024.0
index 8d13e58..2788aef 100644 (file)
@@ -119,7 +119,12 @@ makeSmallCluster node count =
 setInstanceSmallerThanNode :: Node.Node
                            -> Instance.Instance -> Instance.Instance
 setInstanceSmallerThanNode node inst =
-  inst { Instance.mem = Node.availMem node `div` 2
-       , Instance.dsk = Node.availDisk node `div` 2
-       , Instance.vcpus = Node.availCpu node `div` 2
-       }
+  let new_dsk = Node.availDisk node `div` 2
+  in inst { Instance.mem = Node.availMem node `div` 2
+          , Instance.dsk = new_dsk
+          , Instance.vcpus = Node.availCpu node `div` 2
+          , Instance.disks = [Instance.Disk new_dsk
+                              (if Node.exclStorage node
+                               then Just $ Node.fSpindles node `div` 2
+                               else Nothing)]
+          }