[Pkg-ganeti-devel] [ganeti] 103/165: Move cluster metrics to a separate module

Apollon Oikonomopoulos apoikos at moszumanska.debian.org
Tue Aug 11 13:53:18 UTC 2015


This is an automated email from the git hooks/post-receive script.

apoikos pushed a commit to branch master
in repository ganeti.

commit a528597c7a302967da84860228fe8b22af476756
Author: Klaus Aehlig <aehlig at google.com>
Date:   Tue Apr 14 15:11:41 2015 +0200

    Move cluster metrics to a separate module
    
    This is a code move. In this way, operations that need the cluster metrics
    (like simulating node evacuation, e.g., in order to determine global N+1
    redundancy) can use it, without having to depend on Ganeti.HTools.Cluster.
    In particular, they can provide functionality that eventually will be used
    by Ganeti.HTools.Cluster functions without having to go into that already
    overcrowded module. Making that module smaller, and hence more manageable,
    is a nice side effect.
    
    Signed-off-by: Klaus Aehlig <aehlig at google.com>
    Reviewed-by: Petr Pudlak <pudlak at google.com>
---
 Makefile.am                           |   1 +
 src/Ganeti/HTools/Cluster.hs          | 176 +--------------------------
 src/Ganeti/HTools/Cluster/Metrics.hs  | 221 ++++++++++++++++++++++++++++++++++
 src/Ganeti/HTools/Program/Hbal.hs     |   9 +-
 src/Ganeti/HTools/Program/Hcheck.hs   |   7 +-
 src/Ganeti/HTools/Program/Hinfo.hs    |   7 +-
 src/Ganeti/HTools/Program/Hscan.hs    |   3 +-
 src/Ganeti/HTools/Program/Hspace.hs   |   7 +-
 src/Ganeti/HTools/Program/Hsqueeze.hs |   3 +-
 test/hs/Test/Ganeti/HTools/Cluster.hs |   7 +-
 10 files changed, 251 insertions(+), 190 deletions(-)

diff --git a/Makefile.am b/Makefile.am
index 08f696a..2e119b2 100644
--- a/Makefile.am
+++ b/Makefile.am
@@ -905,6 +905,7 @@ HS_LIB_SRCS = \
 	src/Ganeti/HTools/Backend/Text.hs \
 	src/Ganeti/HTools/CLI.hs \
 	src/Ganeti/HTools/Cluster.hs \
+	src/Ganeti/HTools/Cluster/Metrics.hs \
 	src/Ganeti/HTools/Cluster/Moves.hs \
 	src/Ganeti/HTools/Container.hs \
 	src/Ganeti/HTools/Dedicated.hs \
diff --git a/src/Ganeti/HTools/Cluster.hs b/src/Ganeti/HTools/Cluster.hs
index 71ebba7..63e39de 100644
--- a/src/Ganeti/HTools/Cluster.hs
+++ b/src/Ganeti/HTools/Cluster.hs
@@ -74,11 +74,6 @@ module Ganeti.HTools.Cluster
   -- * Balacing functions
   , doNextBalance
   , tryBalance
-  , compCV
-  , optimalCVScore
-  , compCVNodes
-  , compDetailedCV
-  , printStats
   , iMoveToJob
   -- * IAllocator functions
   , genAllocNodes
@@ -102,7 +97,7 @@ module Ganeti.HTools.Cluster
 
 import Control.Applicative ((<$>), liftA2)
 import Control.Arrow ((&&&))
-import Control.Monad (unless, guard)
+import Control.Monad (unless)
 import qualified Data.IntSet as IntSet
 import Data.List
 import Data.Maybe (fromJust, fromMaybe, isJust, isNothing)
@@ -113,11 +108,13 @@ import Ganeti.BasicTypes
 import qualified Ganeti.Constants as C
 import Ganeti.HTools.AlgorithmParams (AlgorithmOptions(..), defaultOptions)
 import qualified Ganeti.HTools.Container as Container
+import Ganeti.HTools.Cluster.Metrics ( compCV, compCVfromStats, compCVNodes
+                                     , compClusterStatistics
+                                     , updateClusterStatisticsTwice)
 import Ganeti.HTools.Cluster.Moves (setInstanceLocationScore, applyMoveEx)
 import qualified Ganeti.HTools.Instance as Instance
 import qualified Ganeti.HTools.Nic as Nic
 import qualified Ganeti.HTools.Node as Node
-import qualified Ganeti.HTools.PeerMap as P
 import qualified Ganeti.HTools.Group as Group
 import Ganeti.HTools.Types
 import Ganeti.Compat
@@ -346,157 +343,6 @@ computeAllocationDelta cini cfin =
                        }
   in (rini, rfin, runa)
 
--- | Coefficient for the total reserved memory in the cluster metric. We
--- use a (local) constant here, as it is also used in the computation of
--- the best possible cluster score.
-reservedMemRtotalCoeff :: Double
-reservedMemRtotalCoeff = 0.25
-
--- | The names and weights of the individual elements in the CV list, together
--- with their statistical accumulation function and a bit to decide whether it
--- is a statistics for online nodes.
-detailedCVInfoExt :: [((Double, String), ([Double] -> Statistics, Bool))]
-detailedCVInfoExt = [ ((0.5,  "free_mem_cv"), (getStdDevStatistics, True))
-                    , ((0.5,  "free_disk_cv"), (getStdDevStatistics, True))
-                    , ((1,  "n1_cnt"), (getSumStatistics, True))
-                    , ((1,  "reserved_mem_cv"), (getStdDevStatistics, True))
-                    , ((4,  "offline_all_cnt"), (getSumStatistics, False))
-                    , ((16, "offline_pri_cnt"), (getSumStatistics, False))
-                    , ( (0.5,  "vcpu_ratio_cv")
-                      , (getStdDevStatistics, True))
-                    , ((1,  "cpu_load_cv"), (getStdDevStatistics, True))
-                    , ((1,  "mem_load_cv"), (getStdDevStatistics, True))
-                    , ((1,  "disk_load_cv"), (getStdDevStatistics, True))
-                    , ((1,  "net_load_cv"), (getStdDevStatistics, True))
-                    , ((2,  "pri_tags_score"), (getSumStatistics, True))
-                    , ((0.5,  "spindles_cv"), (getStdDevStatistics, True))
-                    , ((0.5,  "free_mem_cv_forth"), (getStdDevStatistics, True))
-                    , ( (0.5,  "free_disk_cv_forth")
-                      , (getStdDevStatistics, True))
-                    , ( (0.5,  "vcpu_ratio_cv_forth")
-                      , (getStdDevStatistics, True))
-                    , ((0.5,  "spindles_cv_forth"), (getStdDevStatistics, True))
-                    , ((1,  "location_score"), (getSumStatistics, True))
-                    , ( (reservedMemRtotalCoeff,  "reserved_mem_rtotal")
-                      , (getSumStatistics, True))
-                    ]
-
--- | Compute the lower bound of the cluster score, i.e., the sum of the minimal
--- values for all cluster score values that are not 0 on a perfectly balanced
--- cluster.
-optimalCVScore :: Node.List -> Double
-optimalCVScore nodelist = fromMaybe 0 $ do
-  let nodes = Container.elems nodelist
-  guard $ length nodes > 1
-  let nodeMems = map Node.tMem nodes
-      totalMem = sum nodeMems
-      totalMemOneLessNode = totalMem - maximum nodeMems
-  guard $ totalMemOneLessNode > 0
-  let totalDrbdMem = fromIntegral . sum $ map (P.sumElems . Node.peers) nodes
-      optimalUsage = totalDrbdMem / totalMem
-      optimalUsageOneLessNode = totalDrbdMem / totalMemOneLessNode
-      relativeReserved = optimalUsageOneLessNode - optimalUsage
-  return $ reservedMemRtotalCoeff * relativeReserved
-
--- | The names and weights of the individual elements in the CV list.
-detailedCVInfo :: [(Double, String)]
-detailedCVInfo = map fst detailedCVInfoExt
-
--- | Holds the weights used by 'compCVNodes' for each metric.
-detailedCVWeights :: [Double]
-detailedCVWeights = map fst detailedCVInfo
-
--- | The aggregation functions for the weights
-detailedCVAggregation :: [([Double] -> Statistics, Bool)]
-detailedCVAggregation = map snd detailedCVInfoExt
-
--- | The bit vector describing which parts of the statistics are
--- for online nodes.
-detailedCVOnlineStatus :: [Bool]
-detailedCVOnlineStatus = map snd detailedCVAggregation
-
--- | Compute statistical measures of a single node.
-compDetailedCVNode :: Node.Node -> [Double]
-compDetailedCVNode node =
-  let mem = Node.pMem node
-      memF = Node.pMemForth node
-      dsk = Node.pDsk node
-      dskF = Node.pDskForth node
-      n1 = fromIntegral
-           $ if Node.failN1 node
-               then length (Node.sList node) + length (Node.pList node)
-               else 0
-      res = Node.pRem node
-      ipri = fromIntegral . length $ Node.pList node
-      isec = fromIntegral . length $ Node.sList node
-      ioff = ipri + isec
-      cpu = Node.pCpuEff node
-      cpuF = Node.pCpuEffForth node
-      DynUtil c1 m1 d1 nn1 = Node.utilLoad node
-      DynUtil c2 m2 d2 nn2 = Node.utilPool node
-      (c_load, m_load, d_load, n_load) = (c1/c2, m1/m2, d1/d2, nn1/nn2)
-      pri_tags = fromIntegral $ Node.conflictingPrimaries node
-      spindles = Node.instSpindles node / Node.hiSpindles node
-      spindlesF = Node.instSpindlesForth node / Node.hiSpindles node
-      location_score = fromIntegral $ Node.locationScore node
-  in [ mem, dsk, n1, res, ioff, ipri, cpu
-     , c_load, m_load, d_load, n_load
-     , pri_tags, spindles
-     , memF, dskF, cpuF, spindlesF
-     , location_score
-     , res
-     ]
-
--- | Compute the statistics of a cluster.
-compClusterStatistics :: [Node.Node] -> [Statistics]
-compClusterStatistics all_nodes =
-  let (offline, nodes) = partition Node.offline all_nodes
-      offline_values = transpose (map compDetailedCVNode offline)
-                       ++ repeat []
-      -- transpose of an empty list is empty and not k times the empty list, as
-      -- would be the transpose of a 0 x k matrix
-      online_values = transpose $ map compDetailedCVNode nodes
-      aggregate (f, True) (onNodes, _) = f onNodes
-      aggregate (f, False) (_, offNodes) = f offNodes
-  in zipWith aggregate detailedCVAggregation
-       $ zip online_values offline_values
-
--- | Update a cluster statistics by replacing the contribution of one
--- node by that of another.
-updateClusterStatistics :: [Statistics]
-                           -> (Node.Node, Node.Node) -> [Statistics]
-updateClusterStatistics stats (old, new) =
-  let update = zip (compDetailedCVNode old) (compDetailedCVNode new)
-      online = not $ Node.offline old
-      updateStat forOnline stat upd = if forOnline == online
-                                        then updateStatistics stat upd
-                                        else stat
-  in zipWith3 updateStat detailedCVOnlineStatus stats update
-
--- | Update a cluster statistics twice.
-updateClusterStatisticsTwice :: [Statistics]
-                                -> (Node.Node, Node.Node)
-                                -> (Node.Node, Node.Node)
-                                -> [Statistics]
-updateClusterStatisticsTwice s a =
-  updateClusterStatistics (updateClusterStatistics s a)
-
--- | Compute cluster statistics
-compDetailedCV :: [Node.Node] -> [Double]
-compDetailedCV = map getStatisticValue . compClusterStatistics
-
--- | Compute the cluster score from its statistics
-compCVfromStats :: [Statistics] -> Double
-compCVfromStats = sum . zipWith (*) detailedCVWeights . map getStatisticValue
-
--- | Compute the /total/ variance.
-compCVNodes :: [Node.Node] -> Double
-compCVNodes = sum . zipWith (*) detailedCVWeights . compDetailedCV
-
--- | Wrapper over 'compCVNodes' for callers that have a 'Node.List'.
-compCV :: Node.List -> Double
-compCV = compCVNodes . Container.elems
-
 -- | Compute online nodes from a 'Node.List'.
 getOnline :: Node.List -> [Node.Node]
 getOnline = filter (not . Node.offline) . Container.elems
@@ -1622,20 +1468,6 @@ printInsts nl il =
       isnum = False:False:False:False:False:repeat True
   in printTable "" header (map helper sil) isnum
 
--- | Shows statistics for a given node list.
-printStats :: String -> Node.List -> String
-printStats lp nl =
-  let dcvs = compDetailedCV $ Container.elems nl
-      (weights, names) = unzip detailedCVInfo
-      hd = zip3 (weights ++ repeat 1) (names ++ repeat "unknown") dcvs
-      header = [ "Field", "Value", "Weight" ]
-      formatted = map (\(w, h, val) ->
-                         [ h
-                         , printf "%.8f" val
-                         , printf "x%.2f" w
-                         ]) hd
-  in printTable lp header formatted $ False:repeat True
-
 -- | Convert a placement into a list of OpCodes (basically a job).
 iMoveToJob :: Node.List        -- ^ The node list; only used for node
                                -- names, so any version is good
diff --git a/src/Ganeti/HTools/Cluster/Metrics.hs b/src/Ganeti/HTools/Cluster/Metrics.hs
new file mode 100644
index 0000000..2d909ad
--- /dev/null
+++ b/src/Ganeti/HTools/Cluster/Metrics.hs
@@ -0,0 +1,221 @@
+{-| Implementation of the cluster metric
+
+-}
+
+{-
+
+Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
+All rights reserved.
+
+Redistribution and use in source and binary forms, with or without
+modification, are permitted provided that the following conditions are
+met:
+
+1. Redistributions of source code must retain the above copyright notice,
+this list of conditions and the following disclaimer.
+
+2. Redistributions in binary form must reproduce the above copyright
+notice, this list of conditions and the following disclaimer in the
+documentation and/or other materials provided with the distribution.
+
+THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS
+IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
+TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
+PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR
+CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL,
+EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO,
+PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR
+PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF
+LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING
+NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS
+SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
+
+-}
+
+module Ganeti.HTools.Cluster.Metrics
+  ( compCV
+  , compCVfromStats
+  , compCVNodes
+  , compClusterStatistics
+  , updateClusterStatisticsTwice
+  , optimalCVScore
+  , printStats
+  ) where
+
+import Control.Monad (guard)
+import Data.List (partition, transpose)
+import Data.Maybe (fromMaybe)
+import Text.Printf (printf)
+
+import qualified Ganeti.HTools.Container as Container
+import qualified Ganeti.HTools.Node as Node
+import qualified Ganeti.HTools.PeerMap as P
+import Ganeti.HTools.Types
+import Ganeti.Utils (printTable)
+import Ganeti.Utils.Statistics
+
+-- | Coefficient for the total reserved memory in the cluster metric. We
+-- use a (local) constant here, as it is also used in the computation of
+-- the best possible cluster score.
+reservedMemRtotalCoeff :: Double
+reservedMemRtotalCoeff = 0.25
+
+-- | The names and weights of the individual elements in the CV list, together
+-- with their statistical accumulation function and a bit to decide whether it
+-- is a statistics for online nodes.
+detailedCVInfoExt :: [((Double, String), ([Double] -> Statistics, Bool))]
+detailedCVInfoExt = [ ((0.5,  "free_mem_cv"), (getStdDevStatistics, True))
+                    , ((0.5,  "free_disk_cv"), (getStdDevStatistics, True))
+                    , ((1,  "n1_cnt"), (getSumStatistics, True))
+                    , ((1,  "reserved_mem_cv"), (getStdDevStatistics, True))
+                    , ((4,  "offline_all_cnt"), (getSumStatistics, False))
+                    , ((16, "offline_pri_cnt"), (getSumStatistics, False))
+                    , ( (0.5,  "vcpu_ratio_cv")
+                      , (getStdDevStatistics, True))
+                    , ((1,  "cpu_load_cv"), (getStdDevStatistics, True))
+                    , ((1,  "mem_load_cv"), (getStdDevStatistics, True))
+                    , ((1,  "disk_load_cv"), (getStdDevStatistics, True))
+                    , ((1,  "net_load_cv"), (getStdDevStatistics, True))
+                    , ((2,  "pri_tags_score"), (getSumStatistics, True))
+                    , ((0.5,  "spindles_cv"), (getStdDevStatistics, True))
+                    , ((0.5,  "free_mem_cv_forth"), (getStdDevStatistics, True))
+                    , ( (0.5,  "free_disk_cv_forth")
+                      , (getStdDevStatistics, True))
+                    , ( (0.5,  "vcpu_ratio_cv_forth")
+                      , (getStdDevStatistics, True))
+                    , ((0.5,  "spindles_cv_forth"), (getStdDevStatistics, True))
+                    , ((1,  "location_score"), (getSumStatistics, True))
+                    , ( (reservedMemRtotalCoeff,  "reserved_mem_rtotal")
+                      , (getSumStatistics, True))
+                    ]
+
+-- | Compute the lower bound of the cluster score, i.e., the sum of the minimal
+-- values for all cluster score values that are not 0 on a perfectly balanced
+-- cluster.
+optimalCVScore :: Node.List -> Double
+optimalCVScore nodelist = fromMaybe 0 $ do
+  let nodes = Container.elems nodelist
+  guard $ length nodes > 1
+  let nodeMems = map Node.tMem nodes
+      totalMem = sum nodeMems
+      totalMemOneLessNode = totalMem - maximum nodeMems
+  guard $ totalMemOneLessNode > 0
+  let totalDrbdMem = fromIntegral . sum $ map (P.sumElems . Node.peers) nodes
+      optimalUsage = totalDrbdMem / totalMem
+      optimalUsageOneLessNode = totalDrbdMem / totalMemOneLessNode
+      relativeReserved = optimalUsageOneLessNode - optimalUsage
+  return $ reservedMemRtotalCoeff * relativeReserved
+
+-- | The names and weights of the individual elements in the CV list.
+detailedCVInfo :: [(Double, String)]
+detailedCVInfo = map fst detailedCVInfoExt
+
+-- | Holds the weights used by 'compCVNodes' for each metric.
+detailedCVWeights :: [Double]
+detailedCVWeights = map fst detailedCVInfo
+
+-- | The aggregation functions for the weights
+detailedCVAggregation :: [([Double] -> Statistics, Bool)]
+detailedCVAggregation = map snd detailedCVInfoExt
+
+-- | The bit vector describing which parts of the statistics are
+-- for online nodes.
+detailedCVOnlineStatus :: [Bool]
+detailedCVOnlineStatus = map snd detailedCVAggregation
+
+-- | Compute statistical measures of a single node.
+compDetailedCVNode :: Node.Node -> [Double]
+compDetailedCVNode node =
+  let mem = Node.pMem node
+      memF = Node.pMemForth node
+      dsk = Node.pDsk node
+      dskF = Node.pDskForth node
+      n1 = fromIntegral
+           $ if Node.failN1 node
+               then length (Node.sList node) + length (Node.pList node)
+               else 0
+      res = Node.pRem node
+      ipri = fromIntegral . length $ Node.pList node
+      isec = fromIntegral . length $ Node.sList node
+      ioff = ipri + isec
+      cpu = Node.pCpuEff node
+      cpuF = Node.pCpuEffForth node
+      DynUtil c1 m1 d1 nn1 = Node.utilLoad node
+      DynUtil c2 m2 d2 nn2 = Node.utilPool node
+      (c_load, m_load, d_load, n_load) = (c1/c2, m1/m2, d1/d2, nn1/nn2)
+      pri_tags = fromIntegral $ Node.conflictingPrimaries node
+      spindles = Node.instSpindles node / Node.hiSpindles node
+      spindlesF = Node.instSpindlesForth node / Node.hiSpindles node
+      location_score = fromIntegral $ Node.locationScore node
+  in [ mem, dsk, n1, res, ioff, ipri, cpu
+     , c_load, m_load, d_load, n_load
+     , pri_tags, spindles
+     , memF, dskF, cpuF, spindlesF
+     , location_score
+     , res
+     ]
+
+-- | Compute the statistics of a cluster.
+compClusterStatistics :: [Node.Node] -> [Statistics]
+compClusterStatistics all_nodes =
+  let (offline, nodes) = partition Node.offline all_nodes
+      offline_values = transpose (map compDetailedCVNode offline)
+                       ++ repeat []
+      -- transpose of an empty list is empty and not k times the empty list, as
+      -- would be the transpose of a 0 x k matrix
+      online_values = transpose $ map compDetailedCVNode nodes
+      aggregate (f, True) (onNodes, _) = f onNodes
+      aggregate (f, False) (_, offNodes) = f offNodes
+  in zipWith aggregate detailedCVAggregation
+       $ zip online_values offline_values
+
+-- | Update a cluster statistics by replacing the contribution of one
+-- node by that of another.
+updateClusterStatistics :: [Statistics]
+                           -> (Node.Node, Node.Node) -> [Statistics]
+updateClusterStatistics stats (old, new) =
+  let update = zip (compDetailedCVNode old) (compDetailedCVNode new)
+      online = not $ Node.offline old
+      updateStat forOnline stat upd = if forOnline == online
+                                        then updateStatistics stat upd
+                                        else stat
+  in zipWith3 updateStat detailedCVOnlineStatus stats update
+
+-- | Update a cluster statistics twice.
+updateClusterStatisticsTwice :: [Statistics]
+                                -> (Node.Node, Node.Node)
+                                -> (Node.Node, Node.Node)
+                                -> [Statistics]
+updateClusterStatisticsTwice s a =
+  updateClusterStatistics (updateClusterStatistics s a)
+
+-- | Compute cluster statistics
+compDetailedCV :: [Node.Node] -> [Double]
+compDetailedCV = map getStatisticValue . compClusterStatistics
+
+-- | Compute the cluster score from its statistics
+compCVfromStats :: [Statistics] -> Double
+compCVfromStats = sum . zipWith (*) detailedCVWeights . map getStatisticValue
+
+-- | Compute the /total/ variance.
+compCVNodes :: [Node.Node] -> Double
+compCVNodes = sum . zipWith (*) detailedCVWeights . compDetailedCV
+
+-- | Wrapper over 'compCVNodes' for callers that have a 'Node.List'.
+compCV :: Node.List -> Double
+compCV = compCVNodes . Container.elems
+
+-- | Shows statistics for a given node list.
+printStats :: String -> Node.List -> String
+printStats lp nl =
+  let dcvs = compDetailedCV $ Container.elems nl
+      (weights, names) = unzip detailedCVInfo
+      hd = zip3 (weights ++ repeat 1) (names ++ repeat "unknown") dcvs
+      header = [ "Field", "Value", "Weight" ]
+      formatted = map (\(w, h, val) ->
+                         [ h
+                         , printf "%.8f" val
+                         , printf "x%.2f" w
+                         ]) hd
+  in printTable lp header formatted $ False:repeat True
+
diff --git a/src/Ganeti/HTools/Program/Hbal.hs b/src/Ganeti/HTools/Program/Hbal.hs
index 6137962..b875aaf 100644
--- a/src/Ganeti/HTools/Program/Hbal.hs
+++ b/src/Ganeti/HTools/Program/Hbal.hs
@@ -52,6 +52,7 @@ import Text.Printf (printf)
 import Ganeti.HTools.AlgorithmParams (AlgorithmOptions(..), fromCLIOptions)
 import qualified Ganeti.HTools.Container as Container
 import qualified Ganeti.HTools.Cluster as Cluster
+import qualified Ganeti.HTools.Cluster.Metrics as Metrics
 import qualified Ganeti.HTools.Group as Group
 import qualified Ganeti.HTools.Node as Node
 import qualified Ganeti.HTools.Instance as Instance
@@ -329,14 +330,14 @@ main opts args = do
 
   maybePrintNodes shownodes "Initial cluster" (Cluster.printNodes nl)
 
-  let ini_cv = Cluster.compCV nl
-      opt_cv = Cluster.optimalCVScore nl
+  let ini_cv = Metrics.compCV nl
+      opt_cv = Metrics.optimalCVScore nl
       ini_tbl = Cluster.Table nl il ini_cv []
       min_cv = optMinScore opts
 
   if verbose > 2
     then printf "Initial coefficients: overall %.8f\n%s"
-           ini_cv (Cluster.printStats "  " nl)::IO ()
+           ini_cv (Metrics.printStats "  " nl)::IO ()
     else printf "Initial score: %.8f\n" ini_cv
 
   checkNeedRebalance opts ini_cv opt_cv
@@ -354,7 +355,7 @@ main opts args = do
                   _ | null fin_plc -> printf "No solution found\n"
                     | verbose > 2 ->
                         printf "Final coefficients:   overall %.8f\n%s"
-                        fin_cv (Cluster.printStats "  " fin_nl)
+                        fin_cv (Metrics.printStats "  " fin_nl)
                     | otherwise ->
                         printf "Cluster score improved from %.8f to %.8f\n"
                         ini_cv fin_cv ::String
diff --git a/src/Ganeti/HTools/Program/Hcheck.hs b/src/Ganeti/HTools/Program/Hcheck.hs
index be2af8c..d0d1e1e 100644
--- a/src/Ganeti/HTools/Program/Hcheck.hs
+++ b/src/Ganeti/HTools/Program/Hcheck.hs
@@ -46,6 +46,7 @@ import Text.Printf (printf)
 import Ganeti.HTools.AlgorithmParams (fromCLIOptions)
 import qualified Ganeti.HTools.Container as Container
 import qualified Ganeti.HTools.Cluster as Cluster
+import qualified Ganeti.HTools.Cluster.Metrics as Metrics
 import qualified Ganeti.HTools.Group as Group
 import qualified Ganeti.HTools.Node as Node
 import qualified Ganeti.HTools.Instance as Instance
@@ -253,7 +254,7 @@ perGroupChecks gl (gidx, (nl, il)) =
                      (map Node.conflictingPrimaries (Container.elems nl))
       offline_pri = sum . map length $ map Node.pList offnl
       offline_sec = length $ map Node.sList offnl
-      score = Cluster.compCV nl
+      score = Metrics.compCV nl
       groupstats = [ n1violated
                    , conflicttags
                    , offline_pri
@@ -279,9 +280,9 @@ executeSimulation opts ini_tbl min_cv gidx nl il = do
 -- | Simulate group rebalance if group's score is not good
 maybeSimulateGroupRebalance :: Options -> GroupInfo -> IO GroupInfo
 maybeSimulateGroupRebalance opts (gidx, (nl, il)) = do
-  let ini_cv = Cluster.compCV nl
+  let ini_cv = Metrics.compCV nl
       ini_tbl = Cluster.Table nl il ini_cv []
-      min_cv = optMinScore opts + Cluster.optimalCVScore nl
+      min_cv = optMinScore opts + Metrics.optimalCVScore nl
   if ini_cv < min_cv
     then return (gidx, (nl, il))
     else executeSimulation opts ini_tbl min_cv gidx nl il
diff --git a/src/Ganeti/HTools/Program/Hinfo.hs b/src/Ganeti/HTools/Program/Hinfo.hs
index 05e0d7b..1098687 100644
--- a/src/Ganeti/HTools/Program/Hinfo.hs
+++ b/src/Ganeti/HTools/Program/Hinfo.hs
@@ -46,6 +46,7 @@ import Text.Printf (printf)
 
 import qualified Ganeti.HTools.Container as Container
 import qualified Ganeti.HTools.Cluster as Cluster
+import qualified Ganeti.HTools.Cluster.Metrics as Metrics
 import qualified Ganeti.HTools.Node as Node
 import qualified Ganeti.HTools.Group as Group
 import qualified Ganeti.HTools.Instance as Instance
@@ -101,7 +102,7 @@ calcGroupInfo g nl il =
       bn_size                    = length bad_nodes
       bi_size                    = length bad_instances
       n1h                        = bn_size == 0
-      score                      = Cluster.compCV nl
+      score                      = Metrics.compCV nl
   in GroupInfo (Group.name g) nl_size il_size bn_size bi_size n1h score
 
 -- | Helper to format one group row result.
@@ -192,5 +193,5 @@ main opts args = do
 
   maybePrintNodes shownodes "Cluster" (Cluster.printNodes nlf)
 
-  printf "Cluster coefficients:\n%s" (Cluster.printStats "  " nlf)::IO ()
-  printf "Cluster score: %.8f\n" (Cluster.compCV nlf)
+  printf "Cluster coefficients:\n%s" (Metrics.printStats "  " nlf)::IO ()
+  printf "Cluster score: %.8f\n" (Metrics.compCV nlf)
diff --git a/src/Ganeti/HTools/Program/Hscan.hs b/src/Ganeti/HTools/Program/Hscan.hs
index 057f005..1fb6a55 100644
--- a/src/Ganeti/HTools/Program/Hscan.hs
+++ b/src/Ganeti/HTools/Program/Hscan.hs
@@ -50,6 +50,7 @@ import Text.Printf (printf)
 import Ganeti.BasicTypes
 import qualified Ganeti.HTools.Container as Container
 import qualified Ganeti.HTools.Cluster as Cluster
+import qualified Ganeti.HTools.Cluster.Metrics as Metrics
 import qualified Ganeti.HTools.Node as Node
 import qualified Ganeti.HTools.Instance as Instance
 import qualified Ganeti.HTools.Backend.Rapi as Rapi
@@ -82,7 +83,7 @@ printCluster :: Node.List -> Instance.List
              -> String
 printCluster nl il =
   let (bad_nodes, bad_instances) = Cluster.computeBadItems nl il
-      ccv = Cluster.compCV nl
+      ccv = Metrics.compCV nl
       nodes = Container.elems nl
       insts = Container.elems il
       t_ram = sum . map Node.tMem $ nodes
diff --git a/src/Ganeti/HTools/Program/Hspace.hs b/src/Ganeti/HTools/Program/Hspace.hs
index 9db1441..b9899be 100644
--- a/src/Ganeti/HTools/Program/Hspace.hs
+++ b/src/Ganeti/HTools/Program/Hspace.hs
@@ -52,6 +52,7 @@ import Text.Printf (printf, hPrintf)
 import qualified Ganeti.HTools.AlgorithmParams as Alg
 import qualified Ganeti.HTools.Container as Container
 import qualified Ganeti.HTools.Cluster as Cluster
+import qualified Ganeti.HTools.Cluster.Metrics as Metrics
 import qualified Ganeti.HTools.Group as Group
 import qualified Ganeti.HTools.Node as Node
 import qualified Ganeti.HTools.Instance as Instance
@@ -379,8 +380,8 @@ printTiered False spec_map ini_nl fin_nl sreason = do
 -- | Displays the initial/final cluster scores.
 printClusterScores :: Node.List -> Node.List -> IO ()
 printClusterScores ini_nl fin_nl = do
-  printf "  - initial cluster score: %.8f\n" $ Cluster.compCV ini_nl::IO ()
-  printf "  -   final cluster score: %.8f\n" $ Cluster.compCV fin_nl
+  printf "  - initial cluster score: %.8f\n" $ Metrics.compCV ini_nl::IO ()
+  printf "  -   final cluster score: %.8f\n" $ Metrics.compCV fin_nl
 
 -- | Displays the cluster efficiency.
 printClusterEff :: Cluster.CStats -> Bool -> IO ()
@@ -493,7 +494,7 @@ main opts args = do
 
   when (verbose > 2) $
          hPrintf stderr "Initial coefficients: overall %.8f\n%s"
-                 (Cluster.compCV nl) (Cluster.printStats "  " nl)
+                 (Metrics.compCV nl) (Metrics.printStats "  " nl)
 
   printCluster machine_r (Cluster.totalResources nl) (length all_nodes)
     (Node.haveExclStorage nl)
diff --git a/src/Ganeti/HTools/Program/Hsqueeze.hs b/src/Ganeti/HTools/Program/Hsqueeze.hs
index db6c473..0a29b77 100644
--- a/src/Ganeti/HTools/Program/Hsqueeze.hs
+++ b/src/Ganeti/HTools/Program/Hsqueeze.hs
@@ -53,6 +53,7 @@ import qualified Ganeti.HTools.AlgorithmParams as Alg
 import Ganeti.HTools.CLI
 import qualified Ganeti.HTools.Container as Container
 import qualified Ganeti.HTools.Cluster as Cluster
+import qualified Ganeti.HTools.Cluster.Metrics as Metrics
 import Ganeti.HTools.ExtLoader
 import qualified Ganeti.HTools.Instance as Instance
 import Ganeti.HTools.Loader
@@ -131,7 +132,7 @@ allNodesCapacityFor inst (nl, _) =
 balance :: (Node.List, Instance.List) 
            -> ((Node.List, Instance.List), [MoveJob])
 balance (nl, il) =
-  let ini_cv = Cluster.compCV nl
+  let ini_cv = Metrics.compCV nl
       ini_tbl = Cluster.Table nl il ini_cv []
       balanceStep = Cluster.tryBalance
                       (Alg.defaultOptions { Alg.algMinGain = 0.0
diff --git a/test/hs/Test/Ganeti/HTools/Cluster.hs b/test/hs/Test/Ganeti/HTools/Cluster.hs
index 5cfc901..2829dea 100644
--- a/test/hs/Test/Ganeti/HTools/Cluster.hs
+++ b/test/hs/Test/Ganeti/HTools/Cluster.hs
@@ -54,6 +54,7 @@ import Ganeti.BasicTypes
 import qualified Ganeti.HTools.AlgorithmParams as Alg
 import qualified Ganeti.HTools.Backend.IAlloc as IAlloc
 import qualified Ganeti.HTools.Cluster as Cluster
+import qualified Ganeti.HTools.Cluster.Metrics as Metrics
 import qualified Ganeti.HTools.Container as Container
 import qualified Ganeti.HTools.Group as Group
 import qualified Ganeti.HTools.Instance as Instance
@@ -128,7 +129,7 @@ prop_Score_Zero node =
      (Node.tSpindles node > 0) && (Node.tCpu node > 0)) ==>
   let fn = Node.buildPeers node Container.empty
       nlst = replicate count fn
-      score = Cluster.compCVNodes nlst
+      score = Metrics.compCVNodes nlst
   -- we can't say == 0 here as the floating point errors accumulate;
   -- this should be much lower than the default score in CLI.hs
   in score <= 1e-12
@@ -166,7 +167,7 @@ prop_Alloc_sane inst =
              in counterexample "Cluster can be balanced after allocation"
                   (not (canBalance tbl True True False)) .&&.
                 counterexample "Solution score differs from actual node list"
-                  (abs (Cluster.compCV xnl - cv) < 1e-12)
+                  (abs (Metrics.compCV xnl - cv) < 1e-12)
 
 -- | Checks that on a 2-5 node cluster, we can allocate a random
 -- instance spec via tiered allocation (whatever the original instance
@@ -325,7 +326,7 @@ prop_AllocBalance =
        Ok (_, _, _, [], _) -> failTest "Failed to allocate: no instances"
        Ok (_, xnl, il', _, _) ->
          let ynl = Container.add (Node.idx hnode) hnode xnl
-             cv = Cluster.compCV ynl
+             cv = Metrics.compCV ynl
              tbl = Cluster.Table ynl il' cv []
          in counterexample "Failed to rebalance" $
             canBalance tbl True True False

-- 
Alioth's /usr/local/bin/git-commit-notice on /srv/git.debian.org/git/pkg-ganeti/ganeti.git



More information about the Pkg-ganeti-devel mailing list