[Pkg-ganeti-devel] [ganeti] 52/165: Move htools' mond querying to a backend

Apollon Oikonomopoulos apoikos at moszumanska.debian.org
Tue Aug 11 13:53:12 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 a21c33c797bda38bb80bb542fa8ec0b80ea76dcd
Author: Klaus Aehlig <aehlig at google.com>
Date:   Wed Feb 18 12:49:35 2015 +0100

    Move htools' mond querying to a backend
    
    htools has the ability to query its monitoring daemons.
    As this is a backend of its own right, move it to a separate
    module, to keep the ExtLoader, which is about combining
    data, clean.
    
    Signed-off-by: Klaus Aehlig <aehlig at google.com>
    Reviewed-by: Petr Pudlak <pudlak at google.com>
---
 Makefile.am                                        |   3 +-
 .../HTools/{ExtLoader.hs => Backend/MonD.hs}       | 130 ++-------------
 src/Ganeti/HTools/ExtLoader.hs                     | 179 +--------------------
 src/Ganeti/HTools/Program/Hail.hs                  |   6 +-
 .../HTools/{ExtLoader.hs => Backend/MonD.hs}       |  14 +-
 test/hs/htest.hs                                   |   4 +-
 6 files changed, 39 insertions(+), 297 deletions(-)

diff --git a/Makefile.am b/Makefile.am
index 37bc895..6fe3a3a 100644
--- a/Makefile.am
+++ b/Makefile.am
@@ -886,6 +886,7 @@ HS_LIB_SRCS = \
 	src/Ganeti/HTools/AlgorithmParams.hs \
 	src/Ganeti/HTools/Backend/IAlloc.hs \
 	src/Ganeti/HTools/Backend/Luxi.hs \
+	src/Ganeti/HTools/Backend/MonD.hs \
 	src/Ganeti/HTools/Backend/Rapi.hs \
 	src/Ganeti/HTools/Backend/Simu.hs \
 	src/Ganeti/HTools/Backend/Text.hs \
@@ -1048,12 +1049,12 @@ HS_TEST_SRCS = \
 	test/hs/Test/Ganeti/Constants.hs \
 	test/hs/Test/Ganeti/Daemon.hs \
 	test/hs/Test/Ganeti/Errors.hs \
+	test/hs/Test/Ganeti/HTools/Backend/MonD.hs \
 	test/hs/Test/Ganeti/HTools/Backend/Simu.hs \
 	test/hs/Test/Ganeti/HTools/Backend/Text.hs \
 	test/hs/Test/Ganeti/HTools/CLI.hs \
 	test/hs/Test/Ganeti/HTools/Cluster.hs \
 	test/hs/Test/Ganeti/HTools/Container.hs \
-	test/hs/Test/Ganeti/HTools/ExtLoader.hs \
 	test/hs/Test/Ganeti/HTools/Graph.hs \
 	test/hs/Test/Ganeti/HTools/Instance.hs \
 	test/hs/Test/Ganeti/HTools/Loader.hs \
diff --git a/src/Ganeti/HTools/ExtLoader.hs b/src/Ganeti/HTools/Backend/MonD.hs
similarity index 62%
copy from src/Ganeti/HTools/ExtLoader.hs
copy to src/Ganeti/HTools/Backend/MonD.hs
index acb5b5e..e9974f4 100644
--- a/src/Ganeti/HTools/ExtLoader.hs
+++ b/src/Ganeti/HTools/Backend/MonD.hs
@@ -1,16 +1,15 @@
 {-# LANGUAGE BangPatterns #-}
 
-{-| External data loader.
+{-| Monitoring daemon backend
 
-This module holds the external data loading, and thus is the only one
-depending (via the specialized Text\/Rapi\/Luxi modules) on the actual
-libraries implementing the low-level protocols.
+This module holds implements the querying of the monitoring daemons
+for dynamic utilisation data.
 
 -}
 
 {-
 
-Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
+Copyright (C) 2015 Google Inc.
 All rights reserved.
 
 Redistribution and use in source and binary forms, with or without
@@ -38,130 +37,35 @@ SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
 
 -}
 
-module Ganeti.HTools.ExtLoader
-  ( loadExternalData
-  , commonSuffix
-  , maybeSaveData
-  , queryAllMonDDCs
+
+module Ganeti.HTools.Backend.MonD
+  ( queryAllMonDDCs
   , pMonDData
   ) where
 
 import Control.Monad
-import Control.Exception
-import Data.Maybe (isJust, fromJust, catMaybes)
+import qualified Data.List as L
+import qualified Data.Map as Map
+import Data.Maybe (catMaybes)
 import Network.Curl
-import System.FilePath
-import System.IO
-import System.Time (getClockTime)
-import Text.Printf (hPrintf)
-
 import qualified Text.JSON as J
-import qualified Data.Map as Map
-import qualified Data.List as L
 
+import Ganeti.BasicTypes
 import qualified Ganeti.Constants as C
+import Ganeti.Cpu.Types
 import qualified Ganeti.DataCollectors.CPUload as CPUload
+import Ganeti.DataCollectors.Types ( DCReport, DCCategory
+                                   , dcReportData, dcReportName
+                                   , getCategoryName )
 import qualified Ganeti.HTools.Container as Container
-import qualified Ganeti.HTools.Backend.Luxi as Luxi
-import qualified Ganeti.HTools.Backend.Rapi as Rapi
-import qualified Ganeti.HTools.Backend.Simu as Simu
-import qualified Ganeti.HTools.Backend.Text as Text
-import qualified Ganeti.HTools.Backend.IAlloc as IAlloc
 import qualified Ganeti.HTools.Node as Node
 import qualified Ganeti.HTools.Instance as Instance
-import Ganeti.HTools.Loader (mergeData, checkData, ClusterData(..)
-                            , commonSuffix, clearDynU)
-
-import Ganeti.BasicTypes
-import Ganeti.Cpu.Types
-import Ganeti.DataCollectors.Types hiding (DataCollector(..))
+import Ganeti.HTools.Loader (ClusterData(..))
 import Ganeti.HTools.Types
 import Ganeti.HTools.CLI
 import Ganeti.JSON
 import Ganeti.Logging (logWarning)
-import Ganeti.Utils (sepSplit, tryRead, exitIfBad, exitWhen)
-
--- | Error beautifier.
-wrapIO :: IO (Result a) -> IO (Result a)
-wrapIO = handle (\e -> return . Bad . show $ (e::IOException))
-
--- | Parses a user-supplied utilisation string.
-parseUtilisation :: String -> Result (String, DynUtil)
-parseUtilisation line =
-  case sepSplit ' ' line of
-    [name, cpu, mem, dsk, net] ->
-      do
-        rcpu <- tryRead name cpu
-        rmem <- tryRead name mem
-        rdsk <- tryRead name dsk
-        rnet <- tryRead name net
-        let du = DynUtil { cpuWeight = rcpu, memWeight = rmem
-                         , dskWeight = rdsk, netWeight = rnet }
-        return (name, du)
-    _ -> Bad $ "Cannot parse line " ++ line
-
--- | External tool data loader from a variety of sources.
-loadExternalData :: Options
-                 -> IO ClusterData
-loadExternalData opts = do
-  let mhost = optMaster opts
-      lsock = optLuxi opts
-      tfile = optDataFile opts
-      simdata = optNodeSim opts
-      iallocsrc = optIAllocSrc opts
-      setRapi = mhost /= ""
-      setLuxi = isJust lsock
-      setSim = (not . null) simdata
-      setFile = isJust tfile
-      setIAllocSrc = isJust iallocsrc
-      allSet = filter id [setRapi, setLuxi, setFile]
-      exTags = case optExTags opts of
-                 Nothing -> []
-                 Just etl -> map (++ ":") etl
-      selInsts = optSelInst opts
-      exInsts = optExInst opts
-
-  exitWhen (length allSet > 1) "Only one of the rapi, luxi, and data\
-                               \ files options should be given."
-
-  util_contents <- maybe (return "") readFile (optDynuFile opts)
-  util_data <- exitIfBad "can't parse utilisation data" .
-               mapM parseUtilisation $ lines util_contents
-  input_data <-
-    case () of
-      _ | setRapi -> wrapIO $ Rapi.loadData mhost
-        | setLuxi -> wrapIO . Luxi.loadData $ fromJust lsock
-        | setSim -> Simu.loadData simdata
-        | setFile -> wrapIO . Text.loadData $ fromJust tfile
-        | setIAllocSrc -> wrapIO . IAlloc.loadData $ fromJust iallocsrc
-        | otherwise -> return $ Bad "No backend selected! Exiting."
-  now <- getClockTime
-
-  let ignoreDynU = optIgnoreDynu opts
-      eff_u = if ignoreDynU then [] else util_data
-      ldresult = input_data >>= (if ignoreDynU then clearDynU else return)
-                            >>= mergeData eff_u exTags selInsts exInsts now
-  cdata <- exitIfBad "failed to load data, aborting" ldresult
-  cdata' <- if optMonD opts then queryAllMonDDCs cdata opts else return cdata
-  let (fix_msgs, nl) = checkData (cdNodes cdata') (cdInstances cdata')
-
-  unless (optVerbose opts == 0) $ maybeShowWarnings fix_msgs
-
-  return cdata' {cdNodes = nl}
-
--- | Function to save the cluster data to a file.
-maybeSaveData :: Maybe FilePath -- ^ The file prefix to save to
-              -> String         -- ^ The suffix (extension) to add
-              -> String         -- ^ Informational message
-              -> ClusterData    -- ^ The cluster data
-              -> IO ()
-maybeSaveData Nothing _ _ _ = return ()
-maybeSaveData (Just path) ext msg cdata = do
-  let adata = Text.serializeCluster cdata
-      out_path = path <.> ext
-  writeFile out_path adata
-  hPrintf stderr "The cluster state %s has been written to file '%s'\n"
-          msg out_path
+import Ganeti.Utils (exitIfBad)
 
 -- | Type describing a data collector basic information.
 data DataCollector = DataCollector
diff --git a/src/Ganeti/HTools/ExtLoader.hs b/src/Ganeti/HTools/ExtLoader.hs
index acb5b5e..cdc81eb 100644
--- a/src/Ganeti/HTools/ExtLoader.hs
+++ b/src/Ganeti/HTools/ExtLoader.hs
@@ -1,5 +1,3 @@
-{-# LANGUAGE BangPatterns #-}
-
 {-| External data loader.
 
 This module holds the external data loading, and thus is the only one
@@ -42,43 +40,27 @@ module Ganeti.HTools.ExtLoader
   ( loadExternalData
   , commonSuffix
   , maybeSaveData
-  , queryAllMonDDCs
-  , pMonDData
   ) where
 
 import Control.Monad
 import Control.Exception
-import Data.Maybe (isJust, fromJust, catMaybes)
-import Network.Curl
+import Data.Maybe (isJust, fromJust)
 import System.FilePath
 import System.IO
 import System.Time (getClockTime)
 import Text.Printf (hPrintf)
 
-import qualified Text.JSON as J
-import qualified Data.Map as Map
-import qualified Data.List as L
-
-import qualified Ganeti.Constants as C
-import qualified Ganeti.DataCollectors.CPUload as CPUload
-import qualified Ganeti.HTools.Container as Container
+import Ganeti.BasicTypes
 import qualified Ganeti.HTools.Backend.Luxi as Luxi
 import qualified Ganeti.HTools.Backend.Rapi as Rapi
 import qualified Ganeti.HTools.Backend.Simu as Simu
 import qualified Ganeti.HTools.Backend.Text as Text
 import qualified Ganeti.HTools.Backend.IAlloc as IAlloc
-import qualified Ganeti.HTools.Node as Node
-import qualified Ganeti.HTools.Instance as Instance
+import qualified Ganeti.HTools.Backend.MonD as MonD
+import Ganeti.HTools.CLI
 import Ganeti.HTools.Loader (mergeData, checkData, ClusterData(..)
                             , commonSuffix, clearDynU)
-
-import Ganeti.BasicTypes
-import Ganeti.Cpu.Types
-import Ganeti.DataCollectors.Types hiding (DataCollector(..))
 import Ganeti.HTools.Types
-import Ganeti.HTools.CLI
-import Ganeti.JSON
-import Ganeti.Logging (logWarning)
 import Ganeti.Utils (sepSplit, tryRead, exitIfBad, exitWhen)
 
 -- | Error beautifier.
@@ -142,7 +124,9 @@ loadExternalData opts = do
       ldresult = input_data >>= (if ignoreDynU then clearDynU else return)
                             >>= mergeData eff_u exTags selInsts exInsts now
   cdata <- exitIfBad "failed to load data, aborting" ldresult
-  cdata' <- if optMonD opts then queryAllMonDDCs cdata opts else return cdata
+  cdata' <- if optMonD opts
+              then MonD.queryAllMonDDCs cdata opts
+              else return cdata
   let (fix_msgs, nl) = checkData (cdNodes cdata') (cdInstances cdata')
 
   unless (optVerbose opts == 0) $ maybeShowWarnings fix_msgs
@@ -162,152 +146,3 @@ maybeSaveData (Just path) ext msg cdata = do
   writeFile out_path adata
   hPrintf stderr "The cluster state %s has been written to file '%s'\n"
           msg out_path
-
--- | Type describing a data collector basic information.
-data DataCollector = DataCollector
-  { dName     :: String           -- ^ Name of the data collector
-  , dCategory :: Maybe DCCategory -- ^ The name of the category
-  }
-
--- | The actual data types for MonD's Data Collectors.
-data Report = CPUavgloadReport CPUavgload
-
--- | The list of Data Collectors used by hail and hbal.
-collectors :: Options -> [DataCollector]
-collectors opts =
-  if optIgnoreDynu opts
-    then []
-    else [ DataCollector CPUload.dcName CPUload.dcCategory ]
-
--- | MonDs Data parsed by a mock file. Representing (node name, list of reports
--- produced by MonDs Data Collectors).
-type MonDData = (String, [DCReport])
-
--- | A map storing MonDs data.
-type MapMonDData = Map.Map String [DCReport]
-
--- | Parse MonD data file contents.
-pMonDData :: String -> Result [MonDData]
-pMonDData input =
-  loadJSArray "Parsing MonD's answer" input >>=
-  mapM (pMonDN . J.fromJSObject)
-
--- | Parse a node's JSON record.
-pMonDN :: JSRecord -> Result MonDData
-pMonDN a = do
-  node <- tryFromObj "Parsing node's name" a "node"
-  reports <- tryFromObj "Parsing node's reports" a "reports"
-  return (node, reports)
-
--- | Query all MonDs for all Data Collector.
-queryAllMonDDCs :: ClusterData -> Options -> IO ClusterData
-queryAllMonDDCs cdata opts = do
-  map_mDD <-
-    case optMonDFile opts of
-      Nothing -> return Nothing
-      Just fp -> do
-        monDData_contents <- readFile fp
-        monDData <- exitIfBad "can't parse MonD data"
-                    . pMonDData $ monDData_contents
-        return . Just $ Map.fromList monDData
-  let (ClusterData _ nl il _ _) = cdata
-  (nl', il') <- foldM (queryAllMonDs map_mDD) (nl, il) (collectors opts)
-  return $ cdata {cdNodes = nl', cdInstances = il'}
-
--- | Query all MonDs for a single Data Collector.
-queryAllMonDs :: Maybe MapMonDData -> (Node.List, Instance.List)
-                 -> DataCollector -> IO (Node.List, Instance.List)
-queryAllMonDs m (nl, il) dc = do
-  elems <- mapM (queryAMonD m dc) (Container.elems nl)
-  let elems' = catMaybes elems
-  if length elems == length elems'
-    then
-      let il' = foldl updateUtilData il elems'
-          nl' = zip (Container.keys nl) elems'
-      in return (Container.fromList nl', il')
-    else do
-      logWarning $ "Didn't receive an answer by all MonDs, " ++ dName dc
-                   ++ "'s data will be ignored."
-      return (nl,il)
-
--- | Query a specified MonD for a Data Collector.
-fromCurl :: DataCollector -> Node.Node -> IO (Maybe DCReport)
-fromCurl dc node = do
-  (code, !body) <-  curlGetString (prepareUrl dc node) []
-  case code of
-    CurlOK ->
-      case J.decodeStrict body :: J.Result DCReport of
-        J.Ok r -> return $ Just r
-        J.Error _ -> return Nothing
-    _ -> do
-      logWarning $ "Failed to contact node's " ++ Node.name node
-                   ++ " MonD for DC " ++ dName dc
-      return Nothing
-
--- | Return the data from correct combination of a Data Collector
--- and a DCReport.
-mkReport :: DataCollector -> Maybe DCReport -> Maybe Report
-mkReport dc dcr =
-  case dcr of
-    Nothing -> Nothing
-    Just dcr' ->
-      case () of
-           _ | CPUload.dcName == dName dc ->
-                 case fromJVal (dcReportData dcr') :: Result CPUavgload of
-                   Ok cav -> Just $ CPUavgloadReport cav
-                   Bad _ -> Nothing
-             | otherwise -> Nothing
-
--- | Get data report for the specified Data Collector and Node from the map.
-fromFile :: DataCollector -> Node.Node -> MapMonDData -> Maybe DCReport
-fromFile dc node m =
-  let matchDCName dcr = dName dc == dcReportName dcr
-  in maybe Nothing (L.find matchDCName) $ Map.lookup (Node.name node) m
-
--- | Query a MonD for a single Data Collector.
-queryAMonD :: Maybe MapMonDData -> DataCollector -> Node.Node
-              -> IO (Maybe Node.Node)
-queryAMonD m dc node = do
-  dcReport <-
-    case m of
-      Nothing -> fromCurl dc node
-      Just m' -> return $ fromFile dc node m'
-  case mkReport dc dcReport of
-    Nothing -> return Nothing
-    Just report ->
-      case report of
-        CPUavgloadReport cav ->
-          let ct = cavCpuTotal cav
-              du = Node.utilLoad node
-              du' = du {cpuWeight = ct}
-          in return $ Just node {Node.utilLoad = du'}
-
--- | Update utilization data.
-updateUtilData :: Instance.List -> Node.Node -> Instance.List
-updateUtilData il node =
-  let ct = cpuWeight (Node.utilLoad node)
-      n_uCpu = Node.uCpu node
-      upd inst =
-        if Node.idx node == Instance.pNode inst
-          then
-            let i_vcpus = Instance.vcpus inst
-                i_util = ct / fromIntegral n_uCpu * fromIntegral i_vcpus
-                i_du = Instance.util inst
-                i_du' = i_du {cpuWeight = i_util}
-            in inst {Instance.util = i_du'}
-          else inst
-  in Container.map upd il
-
--- | Prepare url to query a single collector.
-prepareUrl :: DataCollector -> Node.Node -> URLString
-prepareUrl dc node =
-  Node.name node ++ ":" ++ show C.defaultMondPort ++ "/"
-  ++ show C.mondLatestApiVersion ++ "/report/" ++
-  getDCCName (dCategory dc) ++ "/" ++ dName dc
-
--- | Get Category Name.
-getDCCName :: Maybe DCCategory -> String
-getDCCName dcc =
-  case dcc of
-    Nothing -> "default"
-    Just c -> getCategoryName c
diff --git a/src/Ganeti/HTools/Program/Hail.hs b/src/Ganeti/HTools/Program/Hail.hs
index 640f12b..a405760 100644
--- a/src/Ganeti/HTools/Program/Hail.hs
+++ b/src/Ganeti/HTools/Program/Hail.hs
@@ -49,9 +49,9 @@ import qualified Ganeti.HTools.Dedicated as Dedicated
 import Ganeti.Common
 import Ganeti.HTools.CLI
 import Ganeti.HTools.Backend.IAlloc
+import qualified Ganeti.HTools.Backend.MonD as MonD
 import Ganeti.HTools.Loader (Request(..), ClusterData(..), isAllocationRequest)
-import Ganeti.HTools.ExtLoader (maybeSaveData, loadExternalData
-                               , queryAllMonDDCs)
+import Ganeti.HTools.ExtLoader (maybeSaveData, loadExternalData)
 import Ganeti.Utils
 
 -- | Options list and functions.
@@ -87,7 +87,7 @@ wrapReadRequest opts args = do
     else do
       let Request rqt cdata = r1
       cdata' <-
-        if optMonD opts then queryAllMonDDCs cdata opts else return cdata
+        if optMonD opts then MonD.queryAllMonDDCs cdata opts else return cdata
       return $ Request rqt cdata'
 
 -- | Main function.
diff --git a/test/hs/Test/Ganeti/HTools/ExtLoader.hs b/test/hs/Test/Ganeti/HTools/Backend/MonD.hs
similarity index 95%
rename from test/hs/Test/Ganeti/HTools/ExtLoader.hs
rename to test/hs/Test/Ganeti/HTools/Backend/MonD.hs
index 31a6ccf..78051d8 100644
--- a/test/hs/Test/Ganeti/HTools/ExtLoader.hs
+++ b/test/hs/Test/Ganeti/HTools/Backend/MonD.hs
@@ -1,10 +1,12 @@
 {-# LANGUAGE TemplateHaskell #-}
 
-{-| Unittests for the MonD data parse function -}
+{-| Unittests for htools' ganeti-mond backend
+
+-}
 
 {-
 
-Copyright (C) 2013 Google Inc.
+Copyright (C) 2015 Google Inc.
 All rights reserved.
 
 Redistribution and use in source and binary forms, with or without
@@ -32,8 +34,8 @@ SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
 
 -}
 
-module Test.Ganeti.HTools.ExtLoader
-  ( testHTools_ExtLoader
+module Test.Ganeti.HTools.Backend.MonD
+  (testHTools_Backend_MonD
   ) where
 
 import qualified Test.HUnit as HUnit
@@ -44,7 +46,7 @@ import qualified Ganeti.DataCollectors.CPUload as CPUload
 
 import Ganeti.Cpu.Types (CPUavgload(..))
 import Ganeti.DataCollectors.Types (DCReport(..))
-import Ganeti.HTools.ExtLoader
+import Ganeti.HTools.Backend.MonD
 import Ganeti.JSON
 import Test.Ganeti.TestCommon
 import Test.Ganeti.TestHelper
@@ -123,6 +125,6 @@ compareCPUavgload a b =
      && length (cavCpus a) == length (cavCpus b)
      && and (zipWith relError (cavCpus a) (cavCpus b))
 
-testSuite "HTools/ExtLoader"
+testSuite "HTools/Backend/MonD"
           [ 'case_parseMonDData
           ]
diff --git a/test/hs/htest.hs b/test/hs/htest.hs
index b244e0f..6168077 100644
--- a/test/hs/htest.hs
+++ b/test/hs/htest.hs
@@ -49,12 +49,12 @@ import Test.Ganeti.Confd.Utils
 import Test.Ganeti.Confd.Types
 import Test.Ganeti.Daemon
 import Test.Ganeti.Errors
+import Test.Ganeti.HTools.Backend.MonD
 import Test.Ganeti.HTools.Backend.Simu
 import Test.Ganeti.HTools.Backend.Text
 import Test.Ganeti.HTools.CLI
 import Test.Ganeti.HTools.Cluster
 import Test.Ganeti.HTools.Container
-import Test.Ganeti.HTools.ExtLoader
 import Test.Ganeti.HTools.Graph
 import Test.Ganeti.HTools.Instance
 import Test.Ganeti.HTools.Loader
@@ -124,12 +124,12 @@ allTests =
   , testBlock_Drbd_Parser
   , testBlock_Drbd_Types
   , testErrors
+  , testHTools_Backend_MonD
   , testHTools_Backend_Simu
   , testHTools_Backend_Text
   , testHTools_CLI
   , testHTools_Cluster
   , testHTools_Container
-  , testHTools_ExtLoader
   , testHTools_Graph
   , testHTools_Instance
   , testHTools_Loader

-- 
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