hspace prints info about spindles
authorBernardo Dal Seno <bdalseno@google.com>
Thu, 6 Jun 2013 16:04:54 +0000 (18:04 +0200)
committerBernardo Dal Seno <bdalseno@google.com>
Fri, 7 Jun 2013 13:11:24 +0000 (15:11 +0200)
Statistics about spindles are tracked. In human-readable output, spindles
are printed only when used (i.e., exclusive storage is enabled). For
machine-oriented output, they are always there.

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

src/Ganeti/HTools/Cluster.hs
src/Ganeti/HTools/Node.hs
src/Ganeti/HTools/Program/Hspace.hs
src/Ganeti/HTools/Types.hs

index 582530b..6e615d7 100644 (file)
@@ -150,6 +150,7 @@ data Table = Table Node.List Instance.List Score [Placement]
 data CStats = CStats
   { csFmem :: Integer -- ^ Cluster free mem
   , csFdsk :: Integer -- ^ Cluster free disk
+  , csFspn :: Integer -- ^ Cluster free spindles
   , csAmem :: Integer -- ^ Cluster allocatable mem
   , csAdsk :: Integer -- ^ Cluster allocatable disk
   , csAcpu :: Integer -- ^ Cluster allocatable cpus
@@ -158,9 +159,11 @@ data CStats = CStats
   , csMcpu :: Integer -- ^ Max node allocatable cpu
   , csImem :: Integer -- ^ Instance used mem
   , csIdsk :: Integer -- ^ Instance used disk
+  , csIspn :: Integer -- ^ Instance used spindles
   , csIcpu :: Integer -- ^ Instance used cpu
   , csTmem :: Double  -- ^ Cluster total mem
   , csTdsk :: Double  -- ^ Cluster total disk
+  , csTspn :: Double  -- ^ Cluster total spindles
   , csTcpu :: Double  -- ^ Cluster total cpus
   , csVcpu :: Integer -- ^ Cluster total virtual cpus
   , csNcpu :: Double  -- ^ Equivalent to 'csIcpu' but in terms of
@@ -222,7 +225,7 @@ instanceNodes nl inst =
 
 -- | Zero-initializer for the CStats type.
 emptyCStats :: CStats
-emptyCStats = CStats 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0
+emptyCStats = CStats 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0
 
 -- | Update stats with data from a new node.
 updateCStats :: CStats -> Node.Node -> CStats
@@ -233,7 +236,8 @@ updateCStats cs node =
                csImem = x_imem, csIdsk = x_idsk, csIcpu = x_icpu,
                csTmem = x_tmem, csTdsk = x_tdsk, csTcpu = x_tcpu,
                csVcpu = x_vcpu, csNcpu = x_ncpu,
-               csXmem = x_xmem, csNmem = x_nmem, csNinst = x_ninst
+               csXmem = x_xmem, csNmem = x_nmem, csNinst = x_ninst,
+               csFspn = x_fspn, csIspn = x_ispn, csTspn = x_tspn
              }
         = cs
       inc_amem = Node.fMem node - Node.rMem node
@@ -243,12 +247,14 @@ updateCStats cs node =
                  - Node.xMem node - Node.fMem node
       inc_icpu = Node.uCpu node
       inc_idsk = truncate (Node.tDsk node) - Node.fDsk node
+      inc_ispn = Node.tSpindles node - Node.fSpindles node
       inc_vcpu = Node.hiCpu node
       inc_acpu = Node.availCpu node
       inc_ncpu = fromIntegral (Node.uCpu node) /
                  iPolicyVcpuRatio (Node.iPolicy node)
   in cs { csFmem = x_fmem + fromIntegral (Node.fMem node)
         , csFdsk = x_fdsk + fromIntegral (Node.fDsk node)
+        , csFspn = x_fspn + fromIntegral (Node.fSpindles node)
         , csAmem = x_amem + fromIntegral inc_amem'
         , csAdsk = x_adsk + fromIntegral inc_adsk
         , csAcpu = x_acpu + fromIntegral inc_acpu
@@ -257,9 +263,11 @@ updateCStats cs node =
         , csMcpu = max x_mcpu (fromIntegral inc_acpu)
         , csImem = x_imem + fromIntegral inc_imem
         , csIdsk = x_idsk + fromIntegral inc_idsk
+        , csIspn = x_ispn + fromIntegral inc_ispn
         , csIcpu = x_icpu + fromIntegral inc_icpu
         , csTmem = x_tmem + Node.tMem node
         , csTdsk = x_tdsk + Node.tDsk node
+        , csTspn = x_tspn + fromIntegral (Node.tSpindles node)
         , csTcpu = x_tcpu + Node.tCpu node
         , csVcpu = x_vcpu + fromIntegral inc_vcpu
         , csNcpu = x_ncpu + inc_ncpu
@@ -283,24 +291,28 @@ totalResources nl =
 computeAllocationDelta :: CStats -> CStats -> AllocStats
 computeAllocationDelta cini cfin =
   let CStats {csImem = i_imem, csIdsk = i_idsk, csIcpu = i_icpu,
-              csNcpu = i_ncpu } = cini
+              csNcpu = i_ncpu, csIspn = i_ispn } = cini
       CStats {csImem = f_imem, csIdsk = f_idsk, csIcpu = f_icpu,
               csTmem = t_mem, csTdsk = t_dsk, csVcpu = f_vcpu,
-              csNcpu = f_ncpu, csTcpu = f_tcpu } = cfin
+              csNcpu = f_ncpu, csTcpu = f_tcpu,
+              csIspn = f_ispn, csTspn = t_spn } = cfin
       rini = AllocInfo { allocInfoVCpus = fromIntegral i_icpu
                        , allocInfoNCpus = i_ncpu
                        , allocInfoMem   = fromIntegral i_imem
                        , allocInfoDisk  = fromIntegral i_idsk
+                       , allocInfoSpn   = fromIntegral i_ispn
                        }
       rfin = AllocInfo { allocInfoVCpus = fromIntegral (f_icpu - i_icpu)
                        , allocInfoNCpus = f_ncpu - i_ncpu
                        , allocInfoMem   = fromIntegral (f_imem - i_imem)
                        , allocInfoDisk  = fromIntegral (f_idsk - i_idsk)
+                       , allocInfoSpn   = fromIntegral (f_ispn - i_ispn)
                        }
       runa = AllocInfo { allocInfoVCpus = fromIntegral (f_vcpu - f_icpu)
                        , allocInfoNCpus = f_tcpu - f_ncpu
                        , allocInfoMem   = truncate t_mem - fromIntegral f_imem
                        , allocInfoDisk  = truncate t_dsk - fromIntegral f_idsk
+                       , allocInfoSpn   = truncate t_spn - fromIntegral f_ispn
                        }
   in (rini, rfin, runa)
 
index 095b6ef..ba7457d 100644 (file)
@@ -74,6 +74,7 @@ module Ganeti.HTools.Node
   , computeGroups
   , mkNodeGraph
   , mkRebootNodeGraph
+  , haveExclStorage
   ) where
 
 import Control.Monad (liftM, liftM2)
@@ -222,6 +223,11 @@ decIf :: (Num a) => Bool -> a -> a -> a
 decIf True  base delta = base - delta
 decIf False base _     = base
 
+-- | Is exclusive storage enabled on any node?
+haveExclStorage :: List -> Bool
+haveExclStorage nl =
+  any exclStorage $ Container.elems nl
+
 -- * Initialization functions
 
 -- | Create a new node.
index 157bf66..9f0561e 100644 (file)
@@ -128,6 +128,10 @@ dskEff = effFn Cluster.csIdsk Cluster.csTdsk
 cpuEff :: Cluster.CStats -> Double
 cpuEff = effFn Cluster.csIcpu (fromIntegral . Cluster.csVcpu)
 
+-- | Spindles efficiency.
+spnEff :: Cluster.CStats -> Double
+spnEff = effFn Cluster.csIspn Cluster.csTspn
+
 -- | Holds data for converting a 'Cluster.CStats' structure into
 -- detailed statistics.
 statsData :: [(String, Cluster.CStats -> String)]
@@ -147,6 +151,9 @@ statsData = [ ("SCORE", printf "%.8f" . Cluster.csScore)
                \cs -> printf "%d" (Cluster.csFdsk cs - Cluster.csAdsk cs))
             , ("DSK_INST", printf "%d" . Cluster.csIdsk)
             , ("DSK_EFF", printf "%.8f" . dskEff)
+            , ("SPN_FREE", printf "%d" . Cluster.csFspn)
+            , ("SPN_INST", printf "%d" . Cluster.csIspn)
+            , ("SPN_EFF", printf "%.8f" . spnEff)
             , ("CPU_INST", printf "%d" . Cluster.csIcpu)
             , ("CPU_EFF", printf "%.8f" . cpuEff)
             , ("MNODE_MEM_AVAIL", printf "%d" . Cluster.csMmem)
@@ -160,6 +167,10 @@ specData = [ ("MEM", printf "%d" . rspecMem)
            , ("CPU", printf "%d" . rspecCpu)
            ]
 
+-- | 'RSpec' formatting information including spindles.
+specDataSpn :: [(String, RSpec -> String)]
+specDataSpn = specData ++ [("SPN", printf "%d" . rspecSpn)]
+
 -- | List holding 'Cluster.CStats' formatting information.
 clusterData :: [(String, Cluster.CStats -> String)]
 clusterData = [ ("MEM", printf "%.0f" . Cluster.csTmem)
@@ -168,6 +179,10 @@ clusterData = [ ("MEM", printf "%.0f" . Cluster.csTmem)
               , ("VCPU", printf "%d" . Cluster.csVcpu)
               ]
 
+-- | 'Cluster.CStats' formatting information including spindles
+clusterDataSpn :: [(String, Cluster.CStats -> String)]
+clusterDataSpn = clusterData ++ [("SPN", printf "%.0f" . Cluster.csTspn)]
+
 -- | Function to print stats for a given phase.
 printStats :: Phase -> Cluster.CStats -> [(String, String)]
 printStats ph cs =
@@ -182,7 +197,7 @@ printFRScores :: Node.List -> Node.List -> [(FailMode, Int)] -> IO ()
 printFRScores ini_nl fin_nl sreason = do
   printf "  - most likely failure reason: %s\n" $ failureReason sreason::IO ()
   printClusterScores ini_nl fin_nl
-  printClusterEff (Cluster.totalResources fin_nl)
+  printClusterEff (Cluster.totalResources fin_nl) (Node.haveExclStorage fin_nl)
 
 -- | Print final stats and related metrics.
 printResults :: Bool -> Node.List -> Node.List -> Int -> Int
@@ -233,8 +248,8 @@ tieredSpecMap trl_ixes =
 -- | Formats a spec map to strings.
 formatSpecMap :: [(RSpec, Int)] -> [String]
 formatSpecMap =
-  map (\(spec, cnt) -> printf "%d,%d,%d=%d" (rspecMem spec)
-                       (rspecDsk spec) (rspecCpu spec) cnt)
+  map (\(spec, cnt) -> printf "%d,%d,%d,%d=%d" (rspecMem spec)
+                       (rspecDsk spec) (rspecCpu spec) (rspecSpn spec) cnt)
 
 -- | Formats \"key-metrics\" values.
 formatRSpec :: String -> AllocInfo -> [(String, String)]
@@ -243,6 +258,7 @@ formatRSpec s r =
   , ("KM_" ++ s ++ "_NPU", show $ allocInfoNCpus r)
   , ("KM_" ++ s ++ "_MEM", show $ allocInfoMem r)
   , ("KM_" ++ s ++ "_DSK", show $ allocInfoDisk r)
+  , ("KM_" ++ s ++ "_SPN", show $ allocInfoSpn r)
   ]
 
 -- | Shows allocations stats.
@@ -269,6 +285,11 @@ printInstance nl i = [ Instance.name i
                      , show (Instance.mem i)
                      , show (Instance.dsk i)
                      , show (Instance.vcpus i)
+                     , if Node.haveExclStorage nl
+                       then case Instance.getTotalSpindles i of
+                              Nothing -> "?"
+                              Just sp -> show sp
+                       else ""
                      ]
 
 -- | Optionally print the allocation map.
@@ -282,7 +303,7 @@ printAllocationMap verbose msg nl ixes =
                         -- This is the numberic-or-not field
                         -- specification; the first three fields are
                         -- strings, whereas the rest are numeric
-                       [False, False, False, True, True, True]
+                       [False, False, False, True, True, True, True]
 
 -- | Formats nicely a list of resources.
 formatResources :: a -> [(String, a->String)] -> String
@@ -290,34 +311,37 @@ formatResources res =
     intercalate ", " . map (\(a, fn) -> a ++ " " ++ fn res)
 
 -- | Print the cluster resources.
-printCluster :: Bool -> Cluster.CStats -> Int -> IO ()
-printCluster True ini_stats node_count = do
-  printKeysHTS $ map (\(a, fn) -> ("CLUSTER_" ++ a, fn ini_stats)) clusterData
+printCluster :: Bool -> Cluster.CStats -> Int -> Bool -> IO ()
+printCluster True ini_stats node_count _ = do
+  printKeysHTS $ map (\(a, fn) -> ("CLUSTER_" ++ a, fn ini_stats))
+    clusterDataSpn
   printKeysHTS [("CLUSTER_NODES", printf "%d" node_count)]
   printKeysHTS $ printStats PInitial ini_stats
 
-printCluster False ini_stats node_count = do
+printCluster False ini_stats node_count print_spn = do
+  let cldata = if print_spn then clusterDataSpn else clusterData
   printf "The cluster has %d nodes and the following resources:\n  %s.\n"
-         node_count (formatResources ini_stats clusterData)::IO ()
+         node_count (formatResources ini_stats cldata)::IO ()
   printf "There are %s initial instances on the cluster.\n"
              (if inst_count > 0 then show inst_count else "no" )
       where inst_count = Cluster.csNinst ini_stats
 
 -- | Prints the normal instance spec.
-printISpec :: Bool -> RSpec -> SpecType -> DiskTemplate -> IO ()
-printISpec True ispec spec disk_template = do
-  printKeysHTS $ map (\(a, fn) -> (prefix ++ "_" ++ a, fn ispec)) specData
+printISpec :: Bool -> RSpec -> SpecType -> DiskTemplate -> Bool -> IO ()
+printISpec True ispec spec disk_template _ = do
+  printKeysHTS $ map (\(a, fn) -> (prefix ++ "_" ++ a, fn ispec)) specDataSpn
   printKeysHTS [ (prefix ++ "_RQN", printf "%d" req_nodes) ]
   printKeysHTS [ (prefix ++ "_DISK_TEMPLATE",
                   diskTemplateToRaw disk_template) ]
       where req_nodes = Instance.requiredNodes disk_template
             prefix = specPrefix spec
 
-printISpec False ispec spec disk_template =
-  printf "%s instance spec is:\n  %s, using disk\
-         \ template '%s'.\n"
-         (specDescription spec)
-         (formatResources ispec specData) (diskTemplateToRaw disk_template)
+printISpec False ispec spec disk_template print_spn =
+  let spdata = if print_spn then specDataSpn else specData
+  in printf "%s instance spec is:\n  %s, using disk\
+            \ template '%s'.\n"
+            (specDescription spec)
+            (formatResources ispec spdata) (diskTemplateToRaw disk_template)
 
 -- | Prints the tiered results.
 printTiered :: Bool -> [(RSpec, Int)]
@@ -329,11 +353,12 @@ printTiered True spec_map nl trl_nl _ = do
 
 printTiered False spec_map ini_nl fin_nl sreason = do
   _ <- printf "Tiered allocation results:\n"
+  let spdata = if Node.haveExclStorage ini_nl then specDataSpn else specData
   if null spec_map
     then putStrLn "  - no instances allocated"
     else mapM_ (\(ispec, cnt) ->
                   printf "  - %3d instances of spec %s\n" cnt
-                           (formatResources ispec specData)) spec_map
+                           (formatResources ispec spdata)) spec_map
   printFRScores ini_nl fin_nl sreason
 
 -- | Displays the initial/final cluster scores.
@@ -343,13 +368,16 @@ printClusterScores ini_nl fin_nl = do
   printf "  -   final cluster score: %.8f\n" $ Cluster.compCV fin_nl
 
 -- | Displays the cluster efficiency.
-printClusterEff :: Cluster.CStats -> IO ()
-printClusterEff cs =
+printClusterEff :: Cluster.CStats -> Bool -> IO ()
+printClusterEff cs print_spn = do
+  let format = [("memory", memEff),
+                ("disk", dskEff),
+                ("vcpu", cpuEff)] ++
+               [("spindles", spnEff) | print_spn]
+      len = maximum $ map (length . fst) format
   mapM_ (\(s, fn) ->
-           printf "  - %s usage efficiency: %5.2f%%\n" s (fn cs * 100))
-          [("memory", memEff),
-           ("  disk", dskEff),
-           ("  vcpu", cpuEff)]
+          printf "  - %*s usage efficiency: %5.2f%%\n" len s (fn cs * 100))
+    format
 
 -- | Computes the most likely failure reason.
 failureReason :: [(FailMode, Int)] -> String
@@ -377,8 +405,9 @@ runAllocation cdata stop_allocation actual_result spec dt mode opts = do
   let name = specName mode
       descr = name ++ " allocation"
       ldescr = "after " ++ map toLower descr
+      excstor = Node.haveExclStorage new_nl
 
-  printISpec (optMachineReadable opts) spec mode dt
+  printISpec (optMachineReadable opts) spec mode dt excstor
 
   printAllocationMap (optVerbose opts) descr new_nl new_ixes
 
@@ -446,6 +475,7 @@ main opts args = do
                  (Cluster.compCV nl) (Cluster.printStats "  " nl)
 
   printCluster machine_r (Cluster.totalResources nl) (length all_nodes)
+    (Node.haveExclStorage nl)
 
   let stop_allocation = case Cluster.computeBadItems nl il of
                           ([], _) -> Nothing
index 44f0b8c..764c56c 100644 (file)
@@ -155,6 +155,7 @@ data AllocInfo = AllocInfo
   , allocInfoNCpus :: Double -- ^ Normalised CPUs
   , allocInfoMem   :: Int    -- ^ Memory
   , allocInfoDisk  :: Int    -- ^ Disk
+  , allocInfoSpn   :: Int    -- ^ Spindles
   } deriving (Show, Eq)
 
 -- | Currently used, possibly to allocate, unallocable.