module Ganeti.HTools.CLI
( Options(..)
, OptType
, defaultOptions
, Ganeti.HTools.CLI.parseOpts
, parseOptsInner
, parseYesNo
, parseISpecString
, shTemplate
, maybeSaveCommands
, maybePrintNodes
, maybePrintInsts
, maybeShowWarnings
, printKeys
, printFinal
, setNodeStatus
, oDataFile
, oDiskMoves
, oDiskTemplate
, oDryRun
, oSpindleUse
, oDynuFile
, oMonD
, oMonDDataFile
, oMonDXen
, oEvacMode
, oMonDExitMissing
, oFirstJobGroup
, oRestrictedMigrate
, oExInst
, oExTags
, oExecJobs
, oForce
, oFullEvacuation
, oGroup
, oIAllocSrc
, oIgnoreDyn
, oIgnoreNonRedundant
, oIgnoreSoftErrors
, oIndependentGroups
, oAcceptExisting
, oInstMoves
, oJobDelay
, genOLuxiSocket
, oLuxiSocket
, oMachineReadable
, oMaxCpu
, oMaxSolLength
, oMinDisk
, oMinGain
, oMinGainLim
, oMinResources
, oMinScore
, oNoHeaders
, oNoSimulation
, oNodeSim
, oNodeTags
, oOfflineMaintenance
, oOfflineNode
, oOneStepOnly
, oOutputDir
, oPrintCommands
, oPrintInsts
, oPrintMoves
, oPrintNodes
, oQuiet
, oRapiMaster
, oReason
, oRestrictToNodes
, oSaveCluster
, oSelInst
, oShowHelp
, oShowVer
, oShowComp
, oSkipNonRedundant
, oStdSpec
, oTargetResources
, oTieredSpec
, oVerbose
, oPriority
, oNoCapacityChecks
, genericOpts
) where
import Control.Monad
import Data.Char (toUpper)
import Data.Maybe (fromMaybe)
import System.Console.GetOpt
import System.IO
import Text.Printf (printf)
import qualified Ganeti.HTools.Container as Container
import qualified Ganeti.HTools.Node as Node
import qualified Ganeti.Path as Path
import Ganeti.HTools.Types
import Ganeti.BasicTypes
import Ganeti.Common as Common
import Ganeti.Types
import Ganeti.Utils
data Options = Options
{ optDataFile :: Maybe FilePath
, optDiskMoves :: Bool
, optInstMoves :: Bool
, optDiskTemplate :: Maybe DiskTemplate
, optSpindleUse :: Maybe Int
, optDynuFile :: Maybe FilePath
, optIgnoreDynu :: Bool
, optIgnoreSoftErrors :: Bool
, optIndependentGroups :: Bool
, optAcceptExisting :: Bool
, optMonD :: Bool
, optMonDFile :: Maybe FilePath
, optMonDXen :: Bool
, optMonDExitMissing :: Bool
, optEvacMode :: Bool
, optRestrictedMigrate :: Bool
, optExInst :: [String]
, optExTags :: Maybe [String]
, optExecJobs :: Bool
, optDryRun :: Bool
, optFirstJobGroup :: Bool
, optForce :: Bool
, optFullEvacuation :: Bool
, optGroup :: Maybe GroupID
, optIAllocSrc :: Maybe FilePath
, optIgnoreNonRedundant :: Bool
, optSelInst :: [String]
, optLuxi :: Maybe FilePath
, optJobDelay :: Double
, optMachineReadable :: Bool
, optMaster :: String
, optMaxLength :: Int
, optMcpu :: Maybe Double
, optMdsk :: Double
, optMinGain :: Score
, optMinGainLim :: Score
, optMinResources :: Double
, optMinScore :: Score
, optNoHeaders :: Bool
, optNoSimulation :: Bool
, optNodeSim :: [String]
, optNodeTags :: Maybe [String]
, optOffline :: [String]
, optRestrictToNodes :: Maybe [String]
, optOfflineMaintenance :: Bool
, optOneStepOnly :: Bool
, optOutPath :: FilePath
, optPrintMoves :: Bool
, optReason :: Maybe String
, optSaveCluster :: Maybe FilePath
, optShowCmds :: Maybe FilePath
, optShowHelp :: Bool
, optShowComp :: Bool
, optShowInsts :: Bool
, optShowNodes :: Maybe [String]
, optShowVer :: Bool
, optSkipNonRedundant :: Bool
, optStdSpec :: Maybe RSpec
, optTargetResources :: Double
, optTestCount :: Maybe Int
, optTieredSpec :: Maybe RSpec
, optReplay :: Maybe String
, optVerbose :: Int
, optPriority :: Maybe OpSubmitPriority
, optCapacity :: Bool
} deriving Show
defaultOptions :: Options
defaultOptions = Options
{ optDataFile = Nothing
, optDiskMoves = True
, optInstMoves = True
, optIndependentGroups = False
, optAcceptExisting = False
, optDiskTemplate = Nothing
, optSpindleUse = Nothing
, optIgnoreDynu = False
, optIgnoreSoftErrors = False
, optDynuFile = Nothing
, optMonD = False
, optMonDFile = Nothing
, optMonDXen = False
, optMonDExitMissing = False
, optEvacMode = False
, optRestrictedMigrate = False
, optExInst = []
, optExTags = Nothing
, optExecJobs = False
, optDryRun = False
, optFirstJobGroup = False
, optForce = False
, optFullEvacuation = False
, optGroup = Nothing
, optIAllocSrc = Nothing
, optIgnoreNonRedundant = False
, optSelInst = []
, optLuxi = Nothing
, optJobDelay = 10
, optMachineReadable = False
, optMaster = ""
, optMaxLength = 1
, optMcpu = Nothing
, optMdsk = defReservedDiskRatio
, optMinGain = 1e-2
, optMinGainLim = 1e-1
, optMinResources = 2.0
, optMinScore = 1e-9
, optNoHeaders = False
, optNoSimulation = False
, optNodeSim = []
, optNodeTags = Nothing
, optSkipNonRedundant = False
, optOffline = []
, optRestrictToNodes = Nothing
, optOfflineMaintenance = False
, optOneStepOnly = False
, optOutPath = "."
, optPrintMoves = False
, optReason = Nothing
, optSaveCluster = Nothing
, optShowCmds = Nothing
, optShowHelp = False
, optShowComp = False
, optShowInsts = False
, optShowNodes = Nothing
, optShowVer = False
, optStdSpec = Nothing
, optTargetResources = 2.0
, optTestCount = Nothing
, optTieredSpec = Nothing
, optReplay = Nothing
, optVerbose = 1
, optPriority = Nothing
, optCapacity = True
}
type OptType = GenericOptType Options
instance StandardOptions Options where
helpRequested = optShowHelp
verRequested = optShowVer
compRequested = optShowComp
requestHelp o = o { optShowHelp = True }
requestVer o = o { optShowVer = True }
requestComp o = o { optShowComp = True }
parseISpecString :: String -> String -> Result RSpec
parseISpecString descr inp = do
let sp = sepSplit ',' inp
err = Bad ("Invalid " ++ descr ++ " specification: '" ++ inp ++
"', expected disk,ram,cpu")
when (length sp < 3 || length sp > 4) err
prs <- mapM (\(fn, val) -> fn val) $
zip [ annotateResult (descr ++ " specs disk") . parseUnit
, annotateResult (descr ++ " specs memory") . parseUnit
, tryRead (descr ++ " specs cpus")
, tryRead (descr ++ " specs spindles")
] sp
case prs of
[dsk, ram, cpu] -> return $ RSpec cpu ram dsk 1
[dsk, ram, cpu, spn] -> return $ RSpec cpu ram dsk spn
_ -> err
optComplDiskTemplate :: OptCompletion
optComplDiskTemplate = OptComplChoices $
map diskTemplateToRaw [minBound..maxBound]
oDataFile :: OptType
oDataFile =
(Option "t" ["text-data"]
(ReqArg (\ f o -> Ok o { optDataFile = Just f }) "FILE")
"the cluster data FILE",
OptComplFile)
oDiskMoves :: OptType
oDiskMoves =
(Option "" ["no-disk-moves"]
(NoArg (\ opts -> Ok opts { optDiskMoves = False}))
"disallow disk moves from the list of allowed instance changes,\
\ thus allowing only the 'cheap' failover/migrate operations",
OptComplNone)
oMonD :: OptType
oMonD =
(Option "" ["mond"]
(OptArg (\ f opts -> do
flag <- parseYesNo True f
return $ opts { optMonD = flag }) "CHOICE")
"pass either 'yes' or 'no' to query all monDs",
optComplYesNo)
oMonDDataFile :: OptType
oMonDDataFile =
(Option "" ["mond-data"]
(ReqArg (\ f opts -> Ok opts { optMonDFile = Just f }) "FILE")
"Import data provided by MonDs from the given FILE",
OptComplFile)
oMonDXen :: OptType
oMonDXen =
(Option "" ["mond-xen"]
(NoArg (\ opts -> Ok opts { optMonDXen = True }))
"also consider xen-specific collectors in MonD queries",
OptComplNone)
oMonDExitMissing :: OptType
oMonDExitMissing =
(Option "" ["exit-on-missing-mond-data"]
(NoArg (\ opts -> Ok opts { optMonDExitMissing = True }))
"abort if the data available from the monitoring daemons is incomplete",
OptComplNone)
oDiskTemplate :: OptType
oDiskTemplate =
(Option "" ["disk-template"]
(reqWithConversion diskTemplateFromRaw
(\dt opts -> Ok opts { optDiskTemplate = Just dt })
"TEMPLATE") "select the desired disk template",
optComplDiskTemplate)
oSpindleUse :: OptType
oSpindleUse =
(Option "" ["spindle-use"]
(reqWithConversion (tryRead "parsing spindle-use")
(\su opts -> do
when (su < 0) $
fail "Invalid value of the spindle-use (expected >= 0)"
return $ opts { optSpindleUse = Just su })
"SPINDLES") "select how many virtual spindle instances use\
\ [default read from cluster]",
OptComplFloat)
oSelInst :: OptType
oSelInst =
(Option "" ["select-instances"]
(ReqArg (\ f opts -> Ok opts { optSelInst = sepSplit ',' f }) "INSTS")
"only select given instances for any moves",
OptComplManyInstances)
oInstMoves :: OptType
oInstMoves =
(Option "" ["no-instance-moves"]
(NoArg (\ opts -> Ok opts { optInstMoves = False}))
"disallow instance (primary node) moves from the list of allowed,\
\ instance changes, thus allowing only slower, but sometimes\
\ safer, drbd secondary changes",
OptComplNone)
oDynuFile :: OptType
oDynuFile =
(Option "U" ["dynu-file"]
(ReqArg (\ f opts -> Ok opts { optDynuFile = Just f }) "FILE")
"Import dynamic utilisation data from the given FILE",
OptComplFile)
oIgnoreDyn :: OptType
oIgnoreDyn =
(Option "" ["ignore-dynu"]
(NoArg (\ opts -> Ok opts {optIgnoreDynu = True}))
"Ignore any dynamic utilisation information",
OptComplNone)
oIgnoreSoftErrors :: OptType
oIgnoreSoftErrors =
(Option "" ["ignore-soft-errors"]
(NoArg (\ opts -> Ok opts {optIgnoreSoftErrors = True}))
"Ignore any soft restrictions in balancing",
OptComplNone)
oIndependentGroups :: OptType
oIndependentGroups =
(Option "" ["independent-groups"]
(NoArg (\ opts -> Ok opts {optIndependentGroups = True}))
"Consider groups independently",
OptComplNone)
oAcceptExisting :: OptType
oAcceptExisting =
(Option "" ["accept-existing-errors"]
(NoArg (\ opts -> Ok opts {optAcceptExisting = True}))
"Accept existing N+1 violations; just don't add new ones",
OptComplNone)
oEvacMode :: OptType
oEvacMode =
(Option "E" ["evac-mode"]
(NoArg (\opts -> Ok opts { optEvacMode = True }))
"enable evacuation mode, where the algorithm only moves\
\ instances away from offline and drained nodes",
OptComplNone)
oRestrictedMigrate :: OptType
oRestrictedMigrate =
(Option "" ["restricted-migration"]
(NoArg (\opts -> Ok opts { optRestrictedMigrate = True }))
"disallow replace-primary moves (aka frf-moves); in evacuation mode, this\
\ will ensure that the only migrations are off the drained nodes",
OptComplNone)
oExInst :: OptType
oExInst =
(Option "" ["exclude-instances"]
(ReqArg (\ f opts -> Ok opts { optExInst = sepSplit ',' f }) "INSTS")
"exclude given instances from any moves",
OptComplManyInstances)
oExTags :: OptType
oExTags =
(Option "" ["exclusion-tags"]
(ReqArg (\ f opts -> Ok opts { optExTags = Just $ sepSplit ',' f })
"TAG,...") "Enable instance exclusion based on given tag prefix",
OptComplString)
oExecJobs :: OptType
oExecJobs =
(Option "X" ["exec"]
(NoArg (\ opts -> Ok opts { optExecJobs = True}))
"execute the suggested moves via Luxi (only available when using\
\ it for data gathering)",
OptComplNone)
oDryRun :: OptType
oDryRun =
(Option "" ["dry-run"]
(NoArg (\ opts -> Ok opts { optDryRun = True}))
"do not execute any commands and just report what would be done",
OptComplNone)
oReason :: OptType
oReason =
(Option "" ["reason"]
(ReqArg (\ f opts -> Ok opts { optReason = Just f }) "REASON")
"The reason to pass to the submitted jobs",
OptComplNone)
oFirstJobGroup :: OptType
oFirstJobGroup =
(Option "" ["first-job-group"]
(NoArg (\ opts -> Ok opts {optFirstJobGroup = True}))
"only execute the first group of jobs",
OptComplNone)
oForce :: OptType
oForce =
(Option "f" ["force"]
(NoArg (\ opts -> Ok opts {optForce = True}))
"force the execution of this program, even if warnings would\
\ otherwise prevent it",
OptComplNone)
oFullEvacuation :: OptType
oFullEvacuation =
(Option "" ["full-evacuation"]
(NoArg (\ opts -> Ok opts { optFullEvacuation = True}))
"fully evacuate the nodes to be rebooted",
OptComplNone)
oGroup :: OptType
oGroup =
(Option "G" ["group"]
(ReqArg (\ f o -> Ok o { optGroup = Just f }) "ID")
"the target node group (name or UUID)",
OptComplOneGroup)
oIAllocSrc :: OptType
oIAllocSrc =
(Option "I" ["ialloc-src"]
(ReqArg (\ f opts -> Ok opts { optIAllocSrc = Just f }) "FILE")
"Specify an iallocator spec as the cluster data source",
OptComplFile)
oIgnoreNonRedundant :: OptType
oIgnoreNonRedundant =
(Option "" ["ignore-non-redundant"]
(NoArg (\ opts -> Ok opts { optIgnoreNonRedundant = True }))
"Pretend that there are no non-redundant instances in the cluster",
OptComplNone)
oJobDelay :: OptType
oJobDelay =
(Option "" ["job-delay"]
(reqWithConversion (tryRead "job delay")
(\d opts -> Ok opts { optJobDelay = d }) "SECONDS")
"insert this much delay before the execution of repair jobs\
\ to allow the tool to continue processing instances",
OptComplFloat)
genOLuxiSocket :: String -> OptType
genOLuxiSocket defSocket =
(Option "L" ["luxi"]
(OptArg ((\ f opts -> Ok opts { optLuxi = Just f }) .
fromMaybe defSocket) "SOCKET")
("collect data via Luxi, optionally using the given SOCKET path [" ++
defSocket ++ "]"),
OptComplFile)
oLuxiSocket :: IO OptType
oLuxiSocket = liftM genOLuxiSocket Path.defaultQuerySocket
oMachineReadable :: OptType
oMachineReadable =
(Option "" ["machine-readable"]
(OptArg (\ f opts -> do
flag <- parseYesNo True f
return $ opts { optMachineReadable = flag }) "CHOICE")
"enable machine readable output (pass either 'yes' or 'no' to\
\ explicitly control the flag, or without an argument defaults to\
\ yes)",
optComplYesNo)
oMaxCpu :: OptType
oMaxCpu =
(Option "" ["max-cpu"]
(reqWithConversion (tryRead "parsing max-cpu")
(\mcpu opts -> do
when (mcpu <= 0) $
fail "Invalid value of the max-cpu ratio, expected >0"
return $ opts { optMcpu = Just mcpu }) "RATIO")
"maximum virtual-to-physical cpu ratio for nodes (from 0\
\ upwards) [default read from cluster]",
OptComplFloat)
oMaxSolLength :: OptType
oMaxSolLength =
(Option "l" ["max-length"]
(reqWithConversion (tryRead "max solution length")
(\i opts -> Ok opts { optMaxLength = i }) "N")
"cap the solution at this many balancing or allocation\
\ rounds (useful for very unbalanced clusters or empty\
\ clusters)",
OptComplInteger)
oMinDisk :: OptType
oMinDisk =
(Option "" ["min-disk"]
(reqWithConversion (tryRead "min free disk space")
(\n opts -> Ok opts { optMdsk = n }) "RATIO")
"minimum free disk space for nodes (between 0 and 1) [0]",
OptComplFloat)
oMinGain :: OptType
oMinGain =
(Option "g" ["min-gain"]
(reqWithConversion (tryRead "min gain")
(\g opts -> Ok opts { optMinGain = g }) "DELTA")
"minimum gain to aim for in a balancing step before giving up",
OptComplFloat)
oMinGainLim :: OptType
oMinGainLim =
(Option "" ["min-gain-limit"]
(reqWithConversion (tryRead "min gain limit")
(\g opts -> Ok opts { optMinGainLim = g }) "SCORE")
"minimum cluster score for which we start checking the min-gain",
OptComplFloat)
oMinResources :: OptType
oMinResources =
(Option "" ["minimal-resources"]
(reqWithConversion (tryRead "minimal resources")
(\d opts -> Ok opts { optMinResources = d}) "FACTOR")
"minimal resources to be present on each in multiples of\
\ the standard allocation for not onlining standby nodes",
OptComplFloat)
oMinScore :: OptType
oMinScore =
(Option "e" ["min-score"]
(reqWithConversion (tryRead "min score")
(\e opts -> Ok opts { optMinScore = e }) "EPSILON")
"mininum excess to the N+1 limit to aim for",
OptComplFloat)
oNoHeaders :: OptType
oNoHeaders =
(Option "" ["no-headers"]
(NoArg (\ opts -> Ok opts { optNoHeaders = True }))
"do not show a header line",
OptComplNone)
oNoSimulation :: OptType
oNoSimulation =
(Option "" ["no-simulation"]
(NoArg (\opts -> Ok opts {optNoSimulation = True}))
"do not perform rebalancing simulation",
OptComplNone)
oNodeSim :: OptType
oNodeSim =
(Option "" ["simulate"]
(ReqArg (\ f o -> Ok o { optNodeSim = f:optNodeSim o }) "SPEC")
"simulate an empty cluster, given as\
\ 'alloc_policy,num_nodes,disk,ram,cpu'",
OptComplString)
oNodeTags :: OptType
oNodeTags =
(Option "" ["node-tags"]
(ReqArg (\ f opts -> Ok opts { optNodeTags = Just $ sepSplit ',' f })
"TAG,...") "Restrict to nodes with the given tags",
OptComplString)
oOfflineMaintenance :: OptType
oOfflineMaintenance =
(Option "" ["offline-maintenance"]
(NoArg (\ opts -> Ok opts {optOfflineMaintenance = True}))
"Schedule offline maintenance, i.e., pretend that all instance are\
\ offline.",
OptComplNone)
oOfflineNode :: OptType
oOfflineNode =
(Option "O" ["offline"]
(ReqArg (\ n o -> Ok o { optOffline = n:optOffline o }) "NODE")
"set node as offline",
OptComplOneNode)
oRestrictToNodes :: OptType
oRestrictToNodes =
(Option "" ["restrict-allocation-to"]
(ReqArg (\ ns o -> Ok o { optRestrictToNodes = Just $ sepSplit ',' ns })
"NODE,...") "Restrict allocations to the given set of nodes",
OptComplManyNodes)
oOneStepOnly :: OptType
oOneStepOnly =
(Option "" ["one-step-only"]
(NoArg (\ opts -> Ok opts {optOneStepOnly = True}))
"Only do the first step",
OptComplNone)
oOutputDir :: OptType
oOutputDir =
(Option "d" ["output-dir"]
(ReqArg (\ d opts -> Ok opts { optOutPath = d }) "PATH")
"directory in which to write output files",
OptComplDir)
oPrintCommands :: OptType
oPrintCommands =
(Option "C" ["print-commands"]
(OptArg ((\ f opts -> Ok opts { optShowCmds = Just f }) .
fromMaybe "-")
"FILE")
"print the ganeti command list for reaching the solution,\
\ if an argument is passed then write the commands to a\
\ file named as such",
OptComplNone)
oPrintInsts :: OptType
oPrintInsts =
(Option "" ["print-instances"]
(NoArg (\ opts -> Ok opts { optShowInsts = True }))
"print the final instance map",
OptComplNone)
oPrintMoves :: OptType
oPrintMoves =
(Option "" ["print-moves"]
(NoArg (\ opts -> Ok opts { optPrintMoves = True }))
"print the moves of the instances",
OptComplNone)
oPrintNodes :: OptType
oPrintNodes =
(Option "p" ["print-nodes"]
(OptArg ((\ f opts ->
let (prefix, realf) = case f of
'+':rest -> (["+"], rest)
_ -> ([], f)
splitted = prefix ++ sepSplit ',' realf
in Ok opts { optShowNodes = Just splitted }) .
fromMaybe []) "FIELDS")
"print the final node list",
OptComplNone)
oQuiet :: OptType
oQuiet =
(Option "q" ["quiet"]
(NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts 1 }))
"decrease the verbosity level",
OptComplNone)
oRapiMaster :: OptType
oRapiMaster =
(Option "m" ["master"]
(ReqArg (\ m opts -> Ok opts { optMaster = m }) "ADDRESS")
"collect data via RAPI at the given ADDRESS",
OptComplHost)
oSaveCluster :: OptType
oSaveCluster =
(Option "S" ["save"]
(ReqArg (\ f opts -> Ok opts { optSaveCluster = Just f }) "FILE")
"Save cluster state at the end of the processing to FILE",
OptComplNone)
oSkipNonRedundant :: OptType
oSkipNonRedundant =
(Option "" ["skip-non-redundant"]
(NoArg (\ opts -> Ok opts { optSkipNonRedundant = True }))
"Skip nodes that host a non-redundant instance",
OptComplNone)
oStdSpec :: OptType
oStdSpec =
(Option "" ["standard-alloc"]
(ReqArg (\ inp opts -> do
tspec <- parseISpecString "standard" inp
return $ opts { optStdSpec = Just tspec } )
"STDSPEC")
"enable standard specs allocation, given as 'disk,ram,cpu'",
OptComplString)
oTargetResources :: OptType
oTargetResources =
(Option "" ["target-resources"]
(reqWithConversion (tryRead "target resources")
(\d opts -> Ok opts { optTargetResources = d}) "FACTOR")
"target resources to be left on each node after squeezing in\
\ multiples of the standard allocation",
OptComplFloat)
oTieredSpec :: OptType
oTieredSpec =
(Option "" ["tiered-alloc"]
(ReqArg (\ inp opts -> do
tspec <- parseISpecString "tiered" inp
return $ opts { optTieredSpec = Just tspec } )
"TSPEC")
"enable tiered specs allocation, given as 'disk,ram,cpu'",
OptComplString)
oVerbose :: OptType
oVerbose =
(Option "v" ["verbose"]
(NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts + 1 }))
"increase the verbosity level",
OptComplNone)
oPriority :: OptType
oPriority =
(Option "" ["priority"]
(ReqArg (\ inp opts -> do
prio <- parseSubmitPriority inp
Ok opts { optPriority = Just prio }) "PRIO")
"set the priority of submitted jobs",
OptComplChoices (map fmtSubmitPriority [minBound..maxBound]))
oNoCapacityChecks :: OptType
oNoCapacityChecks =
(Option "" ["no-capacity-checks"]
(NoArg (\ opts -> Ok opts { optCapacity = False}))
"disable capacity checks (like global N+1 redundancy)",
OptComplNone)
genericOpts :: [GenericOptType Options]
genericOpts = [ oShowVer
, oShowHelp
, oShowComp
]
parseOpts :: [String]
-> String
-> [OptType]
-> [ArgCompletion]
-> IO (Options, [String])
parseOpts = Common.parseOpts defaultOptions
shTemplate :: String
shTemplate =
printf "#!/bin/sh\n\n\
\# Auto-generated script for executing cluster rebalancing\n\n\
\# To stop, touch the file /tmp/stop-htools\n\n\
\set -e\n\n\
\check() {\n\
\ if [ -f /tmp/stop-htools ]; then\n\
\ echo 'Stop requested, exiting'\n\
\ exit 0\n\
\ fi\n\
\}\n\n"
maybeSaveCommands :: String
-> Options
-> String
-> IO ()
maybeSaveCommands msg opts cmds =
case optShowCmds opts of
Nothing -> return ()
Just "-" -> do
putStrLn ""
putStrLn msg
putStr . unlines . map (" " ++) . filter (/= " check") . lines $ cmds
Just out_path -> do
writeFile out_path (shTemplate ++ cmds)
printf "The commands have been written to file '%s'\n" out_path
maybePrintNodes :: Maybe [String]
-> String
-> ([String] -> String)
-> IO ()
maybePrintNodes Nothing _ _ = return ()
maybePrintNodes (Just fields) msg fn = do
hPutStrLn stderr ""
hPutStrLn stderr (msg ++ " status:")
hPutStrLn stderr $ fn fields
maybePrintInsts :: Bool
-> String
-> String
-> IO ()
maybePrintInsts do_print msg instdata =
when do_print $ do
hPutStrLn stderr ""
hPutStrLn stderr $ msg ++ " instance map:"
hPutStr stderr instdata
maybeShowWarnings :: [String]
-> IO ()
maybeShowWarnings fix_msgs =
unless (null fix_msgs) $ do
hPutStrLn stderr "Warning: cluster has inconsistent data:"
hPutStrLn stderr . unlines . map (printf " - %s") $ fix_msgs
printKeys :: String
-> [(String, String)]
-> IO ()
printKeys prefix =
mapM_ (\(k, v) ->
printf "%s_%s=%s\n" prefix (map toUpper k) (ensureQuoted v))
printFinal :: String
-> Bool
-> IO ()
printFinal prefix True =
printKeys prefix [("OK", "1")]
printFinal _ False = return ()
setNodeOffline :: [Ndx] -> Node.Node -> Node.Node
setNodeOffline offline_indices n =
if Node.idx n `elem` offline_indices
then Node.setOffline n True
else n
setNodeStatus :: Options -> Node.List -> IO Node.List
setNodeStatus opts fixed_nl = do
let offline_passed = optOffline opts
all_nodes = Container.elems fixed_nl
offline_lkp = map (lookupName (map Node.name all_nodes)) offline_passed
offline_wrong = filter (not . goodLookupResult) offline_lkp
offline_names = map lrContent offline_lkp
offline_indices = map Node.idx $
filter (\n -> Node.name n `elem` offline_names)
all_nodes
m_cpu = optMcpu opts
m_dsk = optMdsk opts
unless (null offline_wrong) .
exitErr $ printf "wrong node name(s) set as offline: %s\n"
(commaJoin (map lrContent offline_wrong))
let setMCpuFn = case m_cpu of
Nothing -> id
Just new_mcpu -> flip Node.setMcpu new_mcpu
let nm = Container.map (setNodeOffline offline_indices .
flip Node.setMdsk m_dsk .
setMCpuFn) fixed_nl
return nm