X-Git-Url: https://code.grnet.gr/git/ganeti-local/blobdiff_plain/dc384cf064e529f2af240e10da763962889970ce..dce9bbb32b95f9a352933e483138e1789fc8635d:/htools/Ganeti/HTools/ExtLoader.hs diff --git a/htools/Ganeti/HTools/ExtLoader.hs b/htools/Ganeti/HTools/ExtLoader.hs index 0412c1b..f5db7f5 100644 --- a/htools/Ganeti/HTools/ExtLoader.hs +++ b/htools/Ganeti/HTools/ExtLoader.hs @@ -1,6 +1,4 @@ -{-# LANGUAGE CPP #-} - -{-| External data loader +{-| External data loader. This module holds the external data loading, and thus is the only one depending (via the specialized Text\/Rapi\/Luxi modules) on the actual @@ -10,7 +8,7 @@ libraries implementing the low-level protocols. {- -Copyright (C) 2009, 2010 Google Inc. +Copyright (C) 2009, 2010, 2011 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,22 +28,20 @@ Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA -} module Ganeti.HTools.ExtLoader - ( loadExternalData - , commonSuffix - , maybeSaveData - ) where + ( loadExternalData + , commonSuffix + , maybeSaveData + ) where +import Control.Monad import Data.Maybe (isJust, fromJust) -import Monad import System.FilePath import System.IO -import System -import Text.Printf (printf, hPrintf) +import System.Exit +import Text.Printf (hPrintf) import qualified Ganeti.HTools.Luxi as Luxi -#ifndef NO_CURL import qualified Ganeti.HTools.Rapi as Rapi -#endif import qualified Ganeti.HTools.Simu as Simu import qualified Ganeti.HTools.Text as Text import Ganeti.HTools.Loader (mergeData, checkData, ClusterData(..) @@ -55,23 +51,24 @@ import Ganeti.HTools.Types import Ganeti.HTools.CLI import Ganeti.HTools.Utils (sepSplit, tryRead) --- | Error beautifier +-- | Error beautifier. wrapIO :: IO (Result a) -> IO (Result a) wrapIO = flip catch (return . Bad . show) +-- | Parses a user-supplied utilisation string. parseUtilisation :: String -> Result (String, DynUtil) parseUtilisation line = - let columns = sepSplit ' ' line - in case columns 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 + 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 @@ -89,6 +86,7 @@ loadExternalData opts = do exTags = case optExTags opts of Nothing -> [] Just etl -> map (++ ":") etl + selInsts = optSelInst opts exInsts = optExInst opts when (length allSet > 1) $ @@ -97,43 +95,33 @@ loadExternalData opts = do " files options should be given.") exitWith $ ExitFailure 1 - util_contents <- (case optDynuFile opts of - Just path -> readFile path - Nothing -> return "") + util_contents <- maybe (return "") readFile (optDynuFile opts) let util_data = mapM parseUtilisation $ lines util_contents - util_data' <- (case util_data of - Ok x -> return x - Bad y -> do - hPutStrLn stderr ("Error: can't parse utilisation" ++ - " data: " ++ show y) - exitWith $ ExitFailure 1) + util_data' <- case util_data of + Ok x -> return x + Bad y -> do + hPutStrLn stderr ("Error: can't parse utilisation" ++ + " data: " ++ show y) + exitWith $ ExitFailure 1 input_data <- - case () of - _ | setRapi -> -#ifdef NO_CURL - return $ Bad "RAPI/curl backend disabled at compile time" -#else - wrapIO $ Rapi.loadData mhost -#endif - | setLuxi -> wrapIO $ Luxi.loadData $ fromJust lsock - | setSim -> Simu.loadData simdata - | setFile -> wrapIO $ Text.loadData $ fromJust tfile - | otherwise -> return $ Bad "No backend selected! Exiting." - - let ldresult = input_data >>= mergeData util_data' exTags exInsts + case () of + _ | setRapi -> wrapIO $ Rapi.loadData mhost + | setLuxi -> wrapIO $ Luxi.loadData $ fromJust lsock + | setSim -> Simu.loadData simdata + | setFile -> wrapIO $ Text.loadData $ fromJust tfile + | otherwise -> return $ Bad "No backend selected! Exiting." + + let ldresult = input_data >>= mergeData util_data' exTags selInsts exInsts cdata <- - (case ldresult of - Ok x -> return x - Bad s -> do - hPrintf stderr "Error: failed to load data. Details:\n%s\n" s - :: IO () - exitWith $ ExitFailure 1 - ) + case ldresult of + Ok x -> return x + Bad s -> do + hPrintf stderr + "Error: failed to load data, aborting. Details:\n%s\n" s:: IO () + exitWith $ ExitFailure 1 let (fix_msgs, nl) = checkData (cdNodes cdata) (cdInstances cdata) - unless (null fix_msgs || optVerbose opts == 0) $ do - hPutStrLn stderr "Warning: cluster has inconsistent data:" - hPutStrLn stderr . unlines . map (printf " - %s") $ fix_msgs + unless (optVerbose opts == 0) $ maybeShowWarnings fix_msgs return cdata {cdNodes = nl}