Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / CLI.hs @ 4c9fdf69

History | View | Annotate | Download (24.1 kB)

1 209b3711 Iustin Pop
{-| Implementation of command-line functions.
2 209b3711 Iustin Pop
3 525bfb36 Iustin Pop
This module holds the common command-line related functions for the
4 26d62e4c Iustin Pop
binaries, separated into this module since "Ganeti.Utils" is
5 525bfb36 Iustin Pop
used in many other places and this is more IO oriented.
6 209b3711 Iustin Pop
7 209b3711 Iustin Pop
-}
8 209b3711 Iustin Pop
9 e2fa2baf Iustin Pop
{-
10 e2fa2baf Iustin Pop
11 e247747c Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
12 e2fa2baf Iustin Pop
13 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
14 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
15 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
16 e2fa2baf Iustin Pop
(at your option) any later version.
17 e2fa2baf Iustin Pop
18 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
19 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
20 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
21 e2fa2baf Iustin Pop
General Public License for more details.
22 e2fa2baf Iustin Pop
23 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
24 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
25 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
26 e2fa2baf Iustin Pop
02110-1301, USA.
27 e2fa2baf Iustin Pop
28 e2fa2baf Iustin Pop
-}
29 e2fa2baf Iustin Pop
30 209b3711 Iustin Pop
module Ganeti.HTools.CLI
31 cd08cfa4 Iustin Pop
  ( Options(..)
32 cd08cfa4 Iustin Pop
  , OptType
33 51000365 Iustin Pop
  , defaultOptions
34 51000365 Iustin Pop
  , Ganeti.HTools.CLI.parseOpts
35 51c3d88f Iustin Pop
  , parseOptsInner
36 a7ea861a Iustin Pop
  , parseYesNo
37 8b5a517a Iustin Pop
  , parseISpecString
38 cd08cfa4 Iustin Pop
  , shTemplate
39 cd08cfa4 Iustin Pop
  , maybePrintNodes
40 cd08cfa4 Iustin Pop
  , maybePrintInsts
41 cd08cfa4 Iustin Pop
  , maybeShowWarnings
42 79eef90b Agata Murawska
  , printKeys
43 79eef90b Agata Murawska
  , printFinal
44 cd08cfa4 Iustin Pop
  , setNodeStatus
45 cd08cfa4 Iustin Pop
  -- * The options
46 cd08cfa4 Iustin Pop
  , oDataFile
47 cd08cfa4 Iustin Pop
  , oDiskMoves
48 cd08cfa4 Iustin Pop
  , oDiskTemplate
49 f0753837 René Nussbaumer
  , oSpindleUse
50 cd08cfa4 Iustin Pop
  , oDynuFile
51 cd08cfa4 Iustin Pop
  , oEvacMode
52 cd08cfa4 Iustin Pop
  , oExInst
53 cd08cfa4 Iustin Pop
  , oExTags
54 cd08cfa4 Iustin Pop
  , oExecJobs
55 7dbe4c72 Klaus Aehlig
  , oForce
56 a12b230c Klaus Aehlig
  , oFullEvacuation
57 cd08cfa4 Iustin Pop
  , oGroup
58 9899796b René Nussbaumer
  , oIAllocSrc
59 23247a73 Klaus Aehlig
  , oIgnoreNonRedundant
60 cd08cfa4 Iustin Pop
  , oInstMoves
61 8af72964 Dato Simó
  , oJobDelay
62 29a30533 Iustin Pop
  , genOLuxiSocket
63 cd08cfa4 Iustin Pop
  , oLuxiSocket
64 cd08cfa4 Iustin Pop
  , oMachineReadable
65 cd08cfa4 Iustin Pop
  , oMaxCpu
66 cd08cfa4 Iustin Pop
  , oMaxSolLength
67 cd08cfa4 Iustin Pop
  , oMinDisk
68 cd08cfa4 Iustin Pop
  , oMinGain
69 cd08cfa4 Iustin Pop
  , oMinGainLim
70 cd08cfa4 Iustin Pop
  , oMinScore
71 cd08cfa4 Iustin Pop
  , oNoHeaders
72 22e513e7 Agata Murawska
  , oNoSimulation
73 cd08cfa4 Iustin Pop
  , oNodeSim
74 313fdabc Klaus Aehlig
  , oNodeTags
75 8d38fb72 Klaus Aehlig
  , oOfflineMaintenance
76 cd08cfa4 Iustin Pop
  , oOfflineNode
77 2207220d Klaus Aehlig
  , oOneStepOnly
78 cd08cfa4 Iustin Pop
  , oOutputDir
79 cd08cfa4 Iustin Pop
  , oPrintCommands
80 cd08cfa4 Iustin Pop
  , oPrintInsts
81 30ce253e Klaus Aehlig
  , oPrintMoves
82 cd08cfa4 Iustin Pop
  , oPrintNodes
83 cd08cfa4 Iustin Pop
  , oQuiet
84 cd08cfa4 Iustin Pop
  , oRapiMaster
85 cd08cfa4 Iustin Pop
  , oSaveCluster
86 cd08cfa4 Iustin Pop
  , oSelInst
87 cd08cfa4 Iustin Pop
  , oShowHelp
88 cd08cfa4 Iustin Pop
  , oShowVer
89 097ad7ee Iustin Pop
  , oShowComp
90 89363f98 Klaus Aehlig
  , oSkipNonRedundant
91 294bb337 Iustin Pop
  , oStdSpec
92 cd08cfa4 Iustin Pop
  , oTieredSpec
93 cd08cfa4 Iustin Pop
  , oVerbose
94 e247747c Iustin Pop
  , oPriority
95 42834645 Iustin Pop
  , genericOpts
96 cd08cfa4 Iustin Pop
  ) where
97 209b3711 Iustin Pop
98 cc532bdd Iustin Pop
import Control.Monad
99 79eef90b Agata Murawska
import Data.Char (toUpper)
100 e8f89bb6 Iustin Pop
import Data.Maybe (fromMaybe)
101 209b3711 Iustin Pop
import System.Console.GetOpt
102 209b3711 Iustin Pop
import System.IO
103 88a10df5 Iustin Pop
import Text.Printf (printf)
104 209b3711 Iustin Pop
105 5296ee23 Iustin Pop
import qualified Ganeti.HTools.Container as Container
106 5296ee23 Iustin Pop
import qualified Ganeti.HTools.Node as Node
107 9eeb0aa5 Michael Hanselmann
import qualified Ganeti.Path as Path
108 92e32d76 Iustin Pop
import Ganeti.HTools.Types
109 2fc5653f Iustin Pop
import Ganeti.BasicTypes
110 51000365 Iustin Pop
import Ganeti.Common as Common
111 e247747c Iustin Pop
import Ganeti.Types
112 26d62e4c Iustin Pop
import Ganeti.Utils
113 fae371cc Iustin Pop
114 525bfb36 Iustin Pop
-- * Data types
115 525bfb36 Iustin Pop
116 0427285d Iustin Pop
-- | Command line options structure.
117 0427285d Iustin Pop
data Options = Options
118 cd08cfa4 Iustin Pop
  { optDataFile    :: Maybe FilePath -- ^ Path to the cluster data file
119 cd08cfa4 Iustin Pop
  , optDiskMoves   :: Bool           -- ^ Allow disk moves
120 cd08cfa4 Iustin Pop
  , optInstMoves   :: Bool           -- ^ Allow instance moves
121 9fdd3d0f Iustin Pop
  , optDiskTemplate :: Maybe DiskTemplate  -- ^ Override for the disk template
122 f0753837 René Nussbaumer
  , optSpindleUse  :: Maybe Int      -- ^ Override for the spindle usage
123 cd08cfa4 Iustin Pop
  , optDynuFile    :: Maybe FilePath -- ^ Optional file with dynamic use data
124 cd08cfa4 Iustin Pop
  , optEvacMode    :: Bool           -- ^ Enable evacuation mode
125 cd08cfa4 Iustin Pop
  , optExInst      :: [String]       -- ^ Instances to be excluded
126 cd08cfa4 Iustin Pop
  , optExTags      :: Maybe [String] -- ^ Tags to use for exclusion
127 cd08cfa4 Iustin Pop
  , optExecJobs    :: Bool           -- ^ Execute the commands via Luxi
128 7dbe4c72 Klaus Aehlig
  , optForce       :: Bool           -- ^ Force the execution
129 a12b230c Klaus Aehlig
  , optFullEvacuation :: Bool        -- ^ Fully evacuate nodes to be rebooted
130 cd08cfa4 Iustin Pop
  , optGroup       :: Maybe GroupID  -- ^ The UUID of the group to process
131 9899796b René Nussbaumer
  , optIAllocSrc   :: Maybe FilePath -- ^ The iallocation spec
132 23247a73 Klaus Aehlig
  , optIgnoreNonRedundant :: Bool    -- ^ Ignore non-redundant instances
133 cd08cfa4 Iustin Pop
  , optSelInst     :: [String]       -- ^ Instances to be excluded
134 cd08cfa4 Iustin Pop
  , optLuxi        :: Maybe FilePath -- ^ Collect data from Luxi
135 8af72964 Dato Simó
  , optJobDelay    :: Double         -- ^ Delay before executing first job
136 cd08cfa4 Iustin Pop
  , optMachineReadable :: Bool       -- ^ Output machine-readable format
137 cd08cfa4 Iustin Pop
  , optMaster      :: String         -- ^ Collect data from RAPI
138 cd08cfa4 Iustin Pop
  , optMaxLength   :: Int            -- ^ Stop after this many steps
139 284e9822 Iustin Pop
  , optMcpu        :: Maybe Double   -- ^ Override max cpu ratio for nodes
140 cd08cfa4 Iustin Pop
  , optMdsk        :: Double         -- ^ Max disk usage ratio for nodes
141 cd08cfa4 Iustin Pop
  , optMinGain     :: Score          -- ^ Min gain we aim for in a step
142 cd08cfa4 Iustin Pop
  , optMinGainLim  :: Score          -- ^ Limit below which we apply mingain
143 cd08cfa4 Iustin Pop
  , optMinScore    :: Score          -- ^ The minimum score we aim for
144 cd08cfa4 Iustin Pop
  , optNoHeaders   :: Bool           -- ^ Do not show a header line
145 22e513e7 Agata Murawska
  , optNoSimulation :: Bool          -- ^ Skip the rebalancing dry-run
146 cd08cfa4 Iustin Pop
  , optNodeSim     :: [String]       -- ^ Cluster simulation mode
147 313fdabc Klaus Aehlig
  , optNodeTags    :: Maybe [String] -- ^ List of node tags to restrict to 
148 cd08cfa4 Iustin Pop
  , optOffline     :: [String]       -- ^ Names of offline nodes
149 8d38fb72 Klaus Aehlig
  , optOfflineMaintenance :: Bool    -- ^ Pretend all instances are offline
150 2207220d Klaus Aehlig
  , optOneStepOnly :: Bool           -- ^ Only do the first step
151 cd08cfa4 Iustin Pop
  , optOutPath     :: FilePath       -- ^ Path to the output directory
152 30ce253e Klaus Aehlig
  , optPrintMoves  :: Bool           -- ^ Whether to show the instance moves
153 cd08cfa4 Iustin Pop
  , optSaveCluster :: Maybe FilePath -- ^ Save cluster state to this file
154 cd08cfa4 Iustin Pop
  , optShowCmds    :: Maybe FilePath -- ^ Whether to show the command list
155 cd08cfa4 Iustin Pop
  , optShowHelp    :: Bool           -- ^ Just show the help
156 097ad7ee Iustin Pop
  , optShowComp    :: Bool           -- ^ Just show the completion info
157 cd08cfa4 Iustin Pop
  , optShowInsts   :: Bool           -- ^ Whether to show the instance map
158 cd08cfa4 Iustin Pop
  , optShowNodes   :: Maybe [String] -- ^ Whether to show node status
159 cd08cfa4 Iustin Pop
  , optShowVer     :: Bool           -- ^ Just show the program version
160 89363f98 Klaus Aehlig
  , optSkipNonRedundant :: Bool      -- ^ Skip nodes with non-redundant instance
161 be468da0 Iustin Pop
  , optStdSpec     :: Maybe RSpec    -- ^ Requested standard specs
162 ee4ffc8a Iustin Pop
  , optTestCount   :: Maybe Int      -- ^ Optional test count override
163 cd08cfa4 Iustin Pop
  , optTieredSpec  :: Maybe RSpec    -- ^ Requested specs for tiered mode
164 cd08cfa4 Iustin Pop
  , optReplay      :: Maybe String   -- ^ Unittests: RNG state
165 cd08cfa4 Iustin Pop
  , optVerbose     :: Int            -- ^ Verbosity level
166 e247747c Iustin Pop
  , optPriority    :: Maybe OpSubmitPriority -- ^ OpCode submit priority
167 cd08cfa4 Iustin Pop
  } deriving Show
168 0427285d Iustin Pop
169 0427285d Iustin Pop
-- | Default values for the command line options.
170 0427285d Iustin Pop
defaultOptions :: Options
171 0427285d Iustin Pop
defaultOptions  = Options
172 cd08cfa4 Iustin Pop
  { optDataFile    = Nothing
173 cd08cfa4 Iustin Pop
  , optDiskMoves   = True
174 cd08cfa4 Iustin Pop
  , optInstMoves   = True
175 9fdd3d0f Iustin Pop
  , optDiskTemplate = Nothing
176 f0753837 René Nussbaumer
  , optSpindleUse  = Nothing
177 cd08cfa4 Iustin Pop
  , optDynuFile    = Nothing
178 cd08cfa4 Iustin Pop
  , optEvacMode    = False
179 cd08cfa4 Iustin Pop
  , optExInst      = []
180 cd08cfa4 Iustin Pop
  , optExTags      = Nothing
181 cd08cfa4 Iustin Pop
  , optExecJobs    = False
182 7dbe4c72 Klaus Aehlig
  , optForce       = False
183 a12b230c Klaus Aehlig
  , optFullEvacuation = False
184 cd08cfa4 Iustin Pop
  , optGroup       = Nothing
185 9899796b René Nussbaumer
  , optIAllocSrc   = Nothing
186 23247a73 Klaus Aehlig
  , optIgnoreNonRedundant = False
187 cd08cfa4 Iustin Pop
  , optSelInst     = []
188 cd08cfa4 Iustin Pop
  , optLuxi        = Nothing
189 8af72964 Dato Simó
  , optJobDelay    = 10
190 cd08cfa4 Iustin Pop
  , optMachineReadable = False
191 cd08cfa4 Iustin Pop
  , optMaster      = ""
192 cd08cfa4 Iustin Pop
  , optMaxLength   = -1
193 284e9822 Iustin Pop
  , optMcpu        = Nothing
194 cd08cfa4 Iustin Pop
  , optMdsk        = defReservedDiskRatio
195 cd08cfa4 Iustin Pop
  , optMinGain     = 1e-2
196 cd08cfa4 Iustin Pop
  , optMinGainLim  = 1e-1
197 cd08cfa4 Iustin Pop
  , optMinScore    = 1e-9
198 cd08cfa4 Iustin Pop
  , optNoHeaders   = False
199 22e513e7 Agata Murawska
  , optNoSimulation = False
200 cd08cfa4 Iustin Pop
  , optNodeSim     = []
201 313fdabc Klaus Aehlig
  , optNodeTags    = Nothing
202 89363f98 Klaus Aehlig
  , optSkipNonRedundant = False
203 cd08cfa4 Iustin Pop
  , optOffline     = []
204 8d38fb72 Klaus Aehlig
  , optOfflineMaintenance = False
205 2207220d Klaus Aehlig
  , optOneStepOnly = False
206 cd08cfa4 Iustin Pop
  , optOutPath     = "."
207 30ce253e Klaus Aehlig
  , optPrintMoves  = False
208 cd08cfa4 Iustin Pop
  , optSaveCluster = Nothing
209 cd08cfa4 Iustin Pop
  , optShowCmds    = Nothing
210 cd08cfa4 Iustin Pop
  , optShowHelp    = False
211 097ad7ee Iustin Pop
  , optShowComp    = False
212 cd08cfa4 Iustin Pop
  , optShowInsts   = False
213 cd08cfa4 Iustin Pop
  , optShowNodes   = Nothing
214 cd08cfa4 Iustin Pop
  , optShowVer     = False
215 be468da0 Iustin Pop
  , optStdSpec     = Nothing
216 ee4ffc8a Iustin Pop
  , optTestCount   = Nothing
217 cd08cfa4 Iustin Pop
  , optTieredSpec  = Nothing
218 cd08cfa4 Iustin Pop
  , optReplay      = Nothing
219 cd08cfa4 Iustin Pop
  , optVerbose     = 1
220 e247747c Iustin Pop
  , optPriority    = Nothing
221 cd08cfa4 Iustin Pop
  }
222 0427285d Iustin Pop
223 55abd2c7 Iustin Pop
-- | Abbreviation for the option type.
224 51000365 Iustin Pop
type OptType = GenericOptType Options
225 51000365 Iustin Pop
226 51000365 Iustin Pop
instance StandardOptions Options where
227 51000365 Iustin Pop
  helpRequested = optShowHelp
228 51000365 Iustin Pop
  verRequested  = optShowVer
229 097ad7ee Iustin Pop
  compRequested = optShowComp
230 5b11f8db Iustin Pop
  requestHelp o = o { optShowHelp = True }
231 5b11f8db Iustin Pop
  requestVer  o = o { optShowVer  = True }
232 097ad7ee Iustin Pop
  requestComp o = o { optShowComp = True }
233 0427285d Iustin Pop
234 7da760ca Iustin Pop
-- * Helper functions
235 7da760ca Iustin Pop
236 7da760ca Iustin Pop
parseISpecString :: String -> String -> Result RSpec
237 7da760ca Iustin Pop
parseISpecString descr inp = do
238 7da760ca Iustin Pop
  let sp = sepSplit ',' inp
239 8b5a517a Iustin Pop
      err = Bad ("Invalid " ++ descr ++ " specification: '" ++ inp ++
240 8b5a517a Iustin Pop
                 "', expected disk,ram,cpu")
241 914c6df4 Bernardo Dal Seno
  when (length sp < 3 || length sp > 4) err
242 7da760ca Iustin Pop
  prs <- mapM (\(fn, val) -> fn val) $
243 8b5a517a Iustin Pop
         zip [ annotateResult (descr ++ " specs disk") . parseUnit
244 8b5a517a Iustin Pop
             , annotateResult (descr ++ " specs memory") . parseUnit
245 7da760ca Iustin Pop
             , tryRead (descr ++ " specs cpus")
246 914c6df4 Bernardo Dal Seno
             , tryRead (descr ++ " specs spindles")
247 7da760ca Iustin Pop
             ] sp
248 7da760ca Iustin Pop
  case prs of
249 914c6df4 Bernardo Dal Seno
    {- Spindles are optional, so that they are not needed when exclusive storage
250 914c6df4 Bernardo Dal Seno
       is disabled. When exclusive storage is disabled, spindles are ignored,
251 914c6df4 Bernardo Dal Seno
       so the actual value doesn't matter. We use 1 as a default so that in
252 914c6df4 Bernardo Dal Seno
       case someone forgets and exclusive storage is enabled, we don't run into
253 914c6df4 Bernardo Dal Seno
       weird situations. -}
254 914c6df4 Bernardo Dal Seno
    [dsk, ram, cpu] -> return $ RSpec cpu ram dsk 1
255 914c6df4 Bernardo Dal Seno
    [dsk, ram, cpu, spn] -> return $ RSpec cpu ram dsk spn
256 8b5a517a Iustin Pop
    _ -> err
257 7da760ca Iustin Pop
258 ce207617 Iustin Pop
-- | Disk template choices.
259 ce207617 Iustin Pop
optComplDiskTemplate :: OptCompletion
260 ce207617 Iustin Pop
optComplDiskTemplate = OptComplChoices $
261 ce207617 Iustin Pop
                       map diskTemplateToRaw [minBound..maxBound]
262 ce207617 Iustin Pop
263 525bfb36 Iustin Pop
-- * Command line options
264 525bfb36 Iustin Pop
265 16c2369c Iustin Pop
oDataFile :: OptType
266 ce207617 Iustin Pop
oDataFile =
267 ce207617 Iustin Pop
  (Option "t" ["text-data"]
268 ce207617 Iustin Pop
   (ReqArg (\ f o -> Ok o { optDataFile = Just f }) "FILE")
269 ce207617 Iustin Pop
   "the cluster data FILE",
270 ce207617 Iustin Pop
   OptComplFile)
271 0427285d Iustin Pop
272 df18fdfe Iustin Pop
oDiskMoves :: OptType
273 ce207617 Iustin Pop
oDiskMoves =
274 ce207617 Iustin Pop
  (Option "" ["no-disk-moves"]
275 ce207617 Iustin Pop
   (NoArg (\ opts -> Ok opts { optDiskMoves = False}))
276 ce207617 Iustin Pop
   "disallow disk moves from the list of allowed instance changes,\
277 ce207617 Iustin Pop
   \ thus allowing only the 'cheap' failover/migrate operations",
278 ce207617 Iustin Pop
   OptComplNone)
279 b2278348 Iustin Pop
280 c4bb977b Iustin Pop
oDiskTemplate :: OptType
281 ce207617 Iustin Pop
oDiskTemplate =
282 ce207617 Iustin Pop
  (Option "" ["disk-template"]
283 ce207617 Iustin Pop
   (reqWithConversion diskTemplateFromRaw
284 ce207617 Iustin Pop
    (\dt opts -> Ok opts { optDiskTemplate = Just dt })
285 ce207617 Iustin Pop
    "TEMPLATE") "select the desired disk template",
286 ce207617 Iustin Pop
   optComplDiskTemplate)
287 c4bb977b Iustin Pop
288 f0753837 René Nussbaumer
oSpindleUse :: OptType
289 ce207617 Iustin Pop
oSpindleUse =
290 ce207617 Iustin Pop
  (Option "" ["spindle-use"]
291 ce207617 Iustin Pop
   (reqWithConversion (tryRead "parsing spindle-use")
292 ce207617 Iustin Pop
    (\su opts -> do
293 ce207617 Iustin Pop
       when (su < 0) $
294 ce207617 Iustin Pop
            fail "Invalid value of the spindle-use (expected >= 0)"
295 ce207617 Iustin Pop
       return $ opts { optSpindleUse = Just su })
296 ce207617 Iustin Pop
    "SPINDLES") "select how many virtual spindle instances use\
297 ce207617 Iustin Pop
                \ [default read from cluster]",
298 ecebe9f6 Iustin Pop
   OptComplFloat)
299 f0753837 René Nussbaumer
300 ddef0585 Guido Trotter
oSelInst :: OptType
301 ce207617 Iustin Pop
oSelInst =
302 ce207617 Iustin Pop
  (Option "" ["select-instances"]
303 ce207617 Iustin Pop
   (ReqArg (\ f opts -> Ok opts { optSelInst = sepSplit ',' f }) "INSTS")
304 ce207617 Iustin Pop
   "only select given instances for any moves",
305 ce207617 Iustin Pop
   OptComplManyInstances)
306 ddef0585 Guido Trotter
307 8fcfb767 Guido Trotter
oInstMoves :: OptType
308 ce207617 Iustin Pop
oInstMoves =
309 ce207617 Iustin Pop
  (Option "" ["no-instance-moves"]
310 ce207617 Iustin Pop
   (NoArg (\ opts -> Ok opts { optInstMoves = False}))
311 ce207617 Iustin Pop
   "disallow instance (primary node) moves from the list of allowed,\
312 ce207617 Iustin Pop
   \ instance changes, thus allowing only slower, but sometimes\
313 ce207617 Iustin Pop
   \ safer, drbd secondary changes",
314 ce207617 Iustin Pop
   OptComplNone)
315 8fcfb767 Guido Trotter
316 df18fdfe Iustin Pop
oDynuFile :: OptType
317 ce207617 Iustin Pop
oDynuFile =
318 ce207617 Iustin Pop
  (Option "U" ["dynu-file"]
319 ce207617 Iustin Pop
   (ReqArg (\ f opts -> Ok opts { optDynuFile = Just f }) "FILE")
320 ce207617 Iustin Pop
   "Import dynamic utilisation data from the given FILE",
321 ce207617 Iustin Pop
   OptComplFile)
322 0427285d Iustin Pop
323 f0f21ec4 Iustin Pop
oEvacMode :: OptType
324 ce207617 Iustin Pop
oEvacMode =
325 ce207617 Iustin Pop
  (Option "E" ["evac-mode"]
326 ce207617 Iustin Pop
   (NoArg (\opts -> Ok opts { optEvacMode = True }))
327 516c52f2 Dato Simó
   "enable evacuation mode, where the algorithm only moves\
328 ce207617 Iustin Pop
   \ instances away from offline and drained nodes",
329 ce207617 Iustin Pop
   OptComplNone)
330 f0f21ec4 Iustin Pop
331 10f396e1 Iustin Pop
oExInst :: OptType
332 ce207617 Iustin Pop
oExInst =
333 ce207617 Iustin Pop
  (Option "" ["exclude-instances"]
334 ce207617 Iustin Pop
   (ReqArg (\ f opts -> Ok opts { optExInst = sepSplit ',' f }) "INSTS")
335 ce207617 Iustin Pop
   "exclude given instances from any moves",
336 ce207617 Iustin Pop
   OptComplManyInstances)
337 10f396e1 Iustin Pop
338 df18fdfe Iustin Pop
oExTags :: OptType
339 ce207617 Iustin Pop
oExTags =
340 ce207617 Iustin Pop
  (Option "" ["exclusion-tags"]
341 ce207617 Iustin Pop
   (ReqArg (\ f opts -> Ok opts { optExTags = Just $ sepSplit ',' f })
342 ce207617 Iustin Pop
    "TAG,...") "Enable instance exclusion based on given tag prefix",
343 ce207617 Iustin Pop
   OptComplString)
344 0427285d Iustin Pop
345 0df5a1b4 Iustin Pop
oExecJobs :: OptType
346 ce207617 Iustin Pop
oExecJobs =
347 ce207617 Iustin Pop
  (Option "X" ["exec"]
348 ce207617 Iustin Pop
   (NoArg (\ opts -> Ok opts { optExecJobs = True}))
349 ce207617 Iustin Pop
   "execute the suggested moves via Luxi (only available when using\
350 ce207617 Iustin Pop
   \ it for data gathering)",
351 ce207617 Iustin Pop
   OptComplNone)
352 0df5a1b4 Iustin Pop
353 7dbe4c72 Klaus Aehlig
oForce :: OptType
354 7dbe4c72 Klaus Aehlig
oForce =
355 7dbe4c72 Klaus Aehlig
  (Option "f" ["force"]
356 7dbe4c72 Klaus Aehlig
   (NoArg (\ opts -> Ok opts {optForce = True}))
357 7dbe4c72 Klaus Aehlig
   "force the execution of this program, even if warnings would\
358 7dbe4c72 Klaus Aehlig
   \ otherwise prevent it",
359 7dbe4c72 Klaus Aehlig
   OptComplNone)
360 7dbe4c72 Klaus Aehlig
361 a12b230c Klaus Aehlig
oFullEvacuation :: OptType
362 a12b230c Klaus Aehlig
oFullEvacuation =
363 a12b230c Klaus Aehlig
  (Option "" ["full-evacuation"]
364 a12b230c Klaus Aehlig
   (NoArg (\ opts -> Ok opts { optFullEvacuation = True}))
365 a12b230c Klaus Aehlig
   "fully evacuate the nodes to be rebooted",
366 a12b230c Klaus Aehlig
   OptComplNone)
367 a12b230c Klaus Aehlig
368 a423b510 Iustin Pop
oGroup :: OptType
369 ce207617 Iustin Pop
oGroup =
370 ce207617 Iustin Pop
  (Option "G" ["group"]
371 ce207617 Iustin Pop
   (ReqArg (\ f o -> Ok o { optGroup = Just f }) "ID")
372 0ff01075 Guido Trotter
   "the target node group (name or UUID)",
373 ce207617 Iustin Pop
   OptComplOneGroup)
374 a423b510 Iustin Pop
375 9899796b René Nussbaumer
oIAllocSrc :: OptType
376 ce207617 Iustin Pop
oIAllocSrc =
377 ce207617 Iustin Pop
  (Option "I" ["ialloc-src"]
378 ce207617 Iustin Pop
   (ReqArg (\ f opts -> Ok opts { optIAllocSrc = Just f }) "FILE")
379 ce207617 Iustin Pop
   "Specify an iallocator spec as the cluster data source",
380 ce207617 Iustin Pop
   OptComplFile)
381 9899796b René Nussbaumer
382 23247a73 Klaus Aehlig
oIgnoreNonRedundant :: OptType
383 23247a73 Klaus Aehlig
oIgnoreNonRedundant =
384 23247a73 Klaus Aehlig
  (Option "" ["ignore-non-redundant"]
385 23247a73 Klaus Aehlig
   (NoArg (\ opts -> Ok opts { optIgnoreNonRedundant = True }))
386 23247a73 Klaus Aehlig
    "Pretend that there are no non-redundant instances in the cluster",
387 23247a73 Klaus Aehlig
    OptComplNone)
388 23247a73 Klaus Aehlig
389 8af72964 Dato Simó
oJobDelay :: OptType
390 8af72964 Dato Simó
oJobDelay =
391 8af72964 Dato Simó
  (Option "" ["job-delay"]
392 8af72964 Dato Simó
   (reqWithConversion (tryRead "job delay")
393 8af72964 Dato Simó
    (\d opts -> Ok opts { optJobDelay = d }) "SECONDS")
394 8af72964 Dato Simó
   "insert this much delay before the execution of repair jobs\
395 8af72964 Dato Simó
   \ to allow the tool to continue processing instances",
396 8af72964 Dato Simó
   OptComplFloat)
397 8af72964 Dato Simó
398 29a30533 Iustin Pop
genOLuxiSocket :: String -> OptType
399 29a30533 Iustin Pop
genOLuxiSocket defSocket =
400 ce207617 Iustin Pop
  (Option "L" ["luxi"]
401 ce207617 Iustin Pop
   (OptArg ((\ f opts -> Ok opts { optLuxi = Just f }) .
402 29a30533 Iustin Pop
            fromMaybe defSocket) "SOCKET")
403 29a30533 Iustin Pop
   ("collect data via Luxi, optionally using the given SOCKET path [" ++
404 29a30533 Iustin Pop
    defSocket ++ "]"),
405 ce207617 Iustin Pop
   OptComplFile)
406 0427285d Iustin Pop
407 29a30533 Iustin Pop
oLuxiSocket :: IO OptType
408 67e4fcf4 Iustin Pop
oLuxiSocket = liftM genOLuxiSocket Path.defaultLuxiSocket
409 29a30533 Iustin Pop
410 519edd9f Iustin Pop
oMachineReadable :: OptType
411 ce207617 Iustin Pop
oMachineReadable =
412 ce207617 Iustin Pop
  (Option "" ["machine-readable"]
413 ce207617 Iustin Pop
   (OptArg (\ f opts -> do
414 ce207617 Iustin Pop
              flag <- parseYesNo True f
415 ce207617 Iustin Pop
              return $ opts { optMachineReadable = flag }) "CHOICE")
416 ce207617 Iustin Pop
   "enable machine readable output (pass either 'yes' or 'no' to\
417 ce207617 Iustin Pop
   \ explicitly control the flag, or without an argument defaults to\
418 c472667f Klaus Aehlig
   \ yes)",
419 ce207617 Iustin Pop
   optComplYesNo)
420 519edd9f Iustin Pop
421 0427285d Iustin Pop
oMaxCpu :: OptType
422 ce207617 Iustin Pop
oMaxCpu =
423 ce207617 Iustin Pop
  (Option "" ["max-cpu"]
424 ce207617 Iustin Pop
   (reqWithConversion (tryRead "parsing max-cpu")
425 ce207617 Iustin Pop
    (\mcpu opts -> do
426 ce207617 Iustin Pop
       when (mcpu <= 0) $
427 ce207617 Iustin Pop
            fail "Invalid value of the max-cpu ratio, expected >0"
428 ce207617 Iustin Pop
       return $ opts { optMcpu = Just mcpu }) "RATIO")
429 ce207617 Iustin Pop
   "maximum virtual-to-physical cpu ratio for nodes (from 0\
430 ce207617 Iustin Pop
   \ upwards) [default read from cluster]",
431 ecebe9f6 Iustin Pop
   OptComplFloat)
432 0427285d Iustin Pop
433 df18fdfe Iustin Pop
oMaxSolLength :: OptType
434 ce207617 Iustin Pop
oMaxSolLength =
435 ce207617 Iustin Pop
  (Option "l" ["max-length"]
436 ce207617 Iustin Pop
   (reqWithConversion (tryRead "max solution length")
437 ce207617 Iustin Pop
    (\i opts -> Ok opts { optMaxLength = i }) "N")
438 516c52f2 Dato Simó
   "cap the solution at this many balancing or allocation\
439 516c52f2 Dato Simó
   \ rounds (useful for very unbalanced clusters or empty\
440 ce207617 Iustin Pop
   \ clusters)",
441 ecebe9f6 Iustin Pop
   OptComplInteger)
442 df18fdfe Iustin Pop
443 0427285d Iustin Pop
oMinDisk :: OptType
444 ce207617 Iustin Pop
oMinDisk =
445 ce207617 Iustin Pop
  (Option "" ["min-disk"]
446 ce207617 Iustin Pop
   (reqWithConversion (tryRead "min free disk space")
447 ce207617 Iustin Pop
    (\n opts -> Ok opts { optMdsk = n }) "RATIO")
448 ce207617 Iustin Pop
   "minimum free disk space for nodes (between 0 and 1) [0]",
449 ecebe9f6 Iustin Pop
   OptComplFloat)
450 0427285d Iustin Pop
451 4f807a57 Iustin Pop
oMinGain :: OptType
452 ce207617 Iustin Pop
oMinGain =
453 ce207617 Iustin Pop
  (Option "g" ["min-gain"]
454 ce207617 Iustin Pop
   (reqWithConversion (tryRead "min gain")
455 ce207617 Iustin Pop
    (\g opts -> Ok opts { optMinGain = g }) "DELTA")
456 ce207617 Iustin Pop
   "minimum gain to aim for in a balancing step before giving up",
457 ecebe9f6 Iustin Pop
   OptComplFloat)
458 4f807a57 Iustin Pop
459 4f807a57 Iustin Pop
oMinGainLim :: OptType
460 ce207617 Iustin Pop
oMinGainLim =
461 ce207617 Iustin Pop
  (Option "" ["min-gain-limit"]
462 ce207617 Iustin Pop
   (reqWithConversion (tryRead "min gain limit")
463 ce207617 Iustin Pop
    (\g opts -> Ok opts { optMinGainLim = g }) "SCORE")
464 ce207617 Iustin Pop
   "minimum cluster score for which we start checking the min-gain",
465 ecebe9f6 Iustin Pop
   OptComplFloat)
466 4f807a57 Iustin Pop
467 df18fdfe Iustin Pop
oMinScore :: OptType
468 ce207617 Iustin Pop
oMinScore =
469 ce207617 Iustin Pop
  (Option "e" ["min-score"]
470 ce207617 Iustin Pop
   (reqWithConversion (tryRead "min score")
471 ce207617 Iustin Pop
    (\e opts -> Ok opts { optMinScore = e }) "EPSILON")
472 ce207617 Iustin Pop
   "mininum score to aim for",
473 ecebe9f6 Iustin Pop
   OptComplFloat)
474 c0501c69 Iustin Pop
475 df18fdfe Iustin Pop
oNoHeaders :: OptType
476 ce207617 Iustin Pop
oNoHeaders =
477 ce207617 Iustin Pop
  (Option "" ["no-headers"]
478 ce207617 Iustin Pop
   (NoArg (\ opts -> Ok opts { optNoHeaders = True }))
479 ce207617 Iustin Pop
   "do not show a header line",
480 ce207617 Iustin Pop
   OptComplNone)
481 4f83a560 Iustin Pop
482 22e513e7 Agata Murawska
oNoSimulation :: OptType
483 ce207617 Iustin Pop
oNoSimulation =
484 ce207617 Iustin Pop
  (Option "" ["no-simulation"]
485 ce207617 Iustin Pop
   (NoArg (\opts -> Ok opts {optNoSimulation = True}))
486 ce207617 Iustin Pop
   "do not perform rebalancing simulation",
487 ce207617 Iustin Pop
   OptComplNone)
488 22e513e7 Agata Murawska
489 df18fdfe Iustin Pop
oNodeSim :: OptType
490 ce207617 Iustin Pop
oNodeSim =
491 ce207617 Iustin Pop
  (Option "" ["simulate"]
492 ce207617 Iustin Pop
   (ReqArg (\ f o -> Ok o { optNodeSim = f:optNodeSim o }) "SPEC")
493 ce207617 Iustin Pop
   "simulate an empty cluster, given as\
494 ce207617 Iustin Pop
   \ 'alloc_policy,num_nodes,disk,ram,cpu'",
495 ce207617 Iustin Pop
   OptComplString)
496 df18fdfe Iustin Pop
497 313fdabc Klaus Aehlig
oNodeTags :: OptType
498 313fdabc Klaus Aehlig
oNodeTags =
499 313fdabc Klaus Aehlig
  (Option "" ["node-tags"]
500 313fdabc Klaus Aehlig
   (ReqArg (\ f opts -> Ok opts { optNodeTags = Just $ sepSplit ',' f })
501 313fdabc Klaus Aehlig
    "TAG,...") "Restrict to nodes with the given tags",
502 313fdabc Klaus Aehlig
   OptComplString)
503 313fdabc Klaus Aehlig
     
504 8d38fb72 Klaus Aehlig
oOfflineMaintenance :: OptType
505 8d38fb72 Klaus Aehlig
oOfflineMaintenance =
506 8d38fb72 Klaus Aehlig
  (Option "" ["offline-maintenance"]
507 8d38fb72 Klaus Aehlig
   (NoArg (\ opts -> Ok opts {optOfflineMaintenance = True}))
508 8d38fb72 Klaus Aehlig
   "Schedule offline maintenance, i.e., pretend that all instance are\
509 8d38fb72 Klaus Aehlig
   \ offline.",
510 8d38fb72 Klaus Aehlig
   OptComplNone)
511 8d38fb72 Klaus Aehlig
512 df18fdfe Iustin Pop
oOfflineNode :: OptType
513 ce207617 Iustin Pop
oOfflineNode =
514 ce207617 Iustin Pop
  (Option "O" ["offline"]
515 ce207617 Iustin Pop
   (ReqArg (\ n o -> Ok o { optOffline = n:optOffline o }) "NODE")
516 ce207617 Iustin Pop
   "set node as offline",
517 ce207617 Iustin Pop
   OptComplOneNode)
518 df18fdfe Iustin Pop
519 2207220d Klaus Aehlig
oOneStepOnly :: OptType
520 2207220d Klaus Aehlig
oOneStepOnly =
521 2207220d Klaus Aehlig
  (Option "" ["one-step-only"]
522 2207220d Klaus Aehlig
   (NoArg (\ opts -> Ok opts {optOneStepOnly = True}))
523 2207220d Klaus Aehlig
   "Only do the first step",
524 2207220d Klaus Aehlig
   OptComplNone)
525 2207220d Klaus Aehlig
526 df18fdfe Iustin Pop
oOutputDir :: OptType
527 ce207617 Iustin Pop
oOutputDir =
528 ce207617 Iustin Pop
  (Option "d" ["output-dir"]
529 ce207617 Iustin Pop
   (ReqArg (\ d opts -> Ok opts { optOutPath = d }) "PATH")
530 ce207617 Iustin Pop
   "directory in which to write output files",
531 ce207617 Iustin Pop
   OptComplDir)
532 df18fdfe Iustin Pop
533 df18fdfe Iustin Pop
oPrintCommands :: OptType
534 ce207617 Iustin Pop
oPrintCommands =
535 ce207617 Iustin Pop
  (Option "C" ["print-commands"]
536 ce207617 Iustin Pop
   (OptArg ((\ f opts -> Ok opts { optShowCmds = Just f }) .
537 ce207617 Iustin Pop
            fromMaybe "-")
538 ce207617 Iustin Pop
    "FILE")
539 ce207617 Iustin Pop
   "print the ganeti command list for reaching the solution,\
540 ce207617 Iustin Pop
   \ if an argument is passed then write the commands to a\
541 ce207617 Iustin Pop
   \ file named as such",
542 ce207617 Iustin Pop
   OptComplNone)
543 df18fdfe Iustin Pop
544 df18fdfe Iustin Pop
oPrintInsts :: OptType
545 ce207617 Iustin Pop
oPrintInsts =
546 ce207617 Iustin Pop
  (Option "" ["print-instances"]
547 ce207617 Iustin Pop
   (NoArg (\ opts -> Ok opts { optShowInsts = True }))
548 ce207617 Iustin Pop
   "print the final instance map",
549 ce207617 Iustin Pop
   OptComplNone)
550 df18fdfe Iustin Pop
551 30ce253e Klaus Aehlig
oPrintMoves :: OptType
552 30ce253e Klaus Aehlig
oPrintMoves =
553 30ce253e Klaus Aehlig
  (Option "" ["print-moves"]
554 30ce253e Klaus Aehlig
   (NoArg (\ opts -> Ok opts { optPrintMoves = True }))
555 30ce253e Klaus Aehlig
   "print the moves of the instances",
556 30ce253e Klaus Aehlig
   OptComplNone)
557 30ce253e Klaus Aehlig
558 df18fdfe Iustin Pop
oPrintNodes :: OptType
559 ce207617 Iustin Pop
oPrintNodes =
560 ce207617 Iustin Pop
  (Option "p" ["print-nodes"]
561 ce207617 Iustin Pop
   (OptArg ((\ f opts ->
562 ce207617 Iustin Pop
               let (prefix, realf) = case f of
563 ce207617 Iustin Pop
                                       '+':rest -> (["+"], rest)
564 ce207617 Iustin Pop
                                       _ -> ([], f)
565 ce207617 Iustin Pop
                   splitted = prefix ++ sepSplit ',' realf
566 ce207617 Iustin Pop
               in Ok opts { optShowNodes = Just splitted }) .
567 ce207617 Iustin Pop
            fromMaybe []) "FIELDS")
568 ce207617 Iustin Pop
   "print the final node list",
569 ce207617 Iustin Pop
   OptComplNone)
570 df18fdfe Iustin Pop
571 df18fdfe Iustin Pop
oQuiet :: OptType
572 ce207617 Iustin Pop
oQuiet =
573 ce207617 Iustin Pop
  (Option "q" ["quiet"]
574 ce207617 Iustin Pop
   (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts - 1 }))
575 ce207617 Iustin Pop
   "decrease the verbosity level",
576 ce207617 Iustin Pop
   OptComplNone)
577 df18fdfe Iustin Pop
578 df18fdfe Iustin Pop
oRapiMaster :: OptType
579 ce207617 Iustin Pop
oRapiMaster =
580 ce207617 Iustin Pop
  (Option "m" ["master"]
581 ce207617 Iustin Pop
   (ReqArg (\ m opts -> Ok opts { optMaster = m }) "ADDRESS")
582 ce207617 Iustin Pop
   "collect data via RAPI at the given ADDRESS",
583 ce207617 Iustin Pop
   OptComplHost)
584 df18fdfe Iustin Pop
585 02da9d07 Iustin Pop
oSaveCluster :: OptType
586 ce207617 Iustin Pop
oSaveCluster =
587 ce207617 Iustin Pop
  (Option "S" ["save"]
588 ce207617 Iustin Pop
   (ReqArg (\ f opts -> Ok opts { optSaveCluster = Just f }) "FILE")
589 ce207617 Iustin Pop
   "Save cluster state at the end of the processing to FILE",
590 ce207617 Iustin Pop
   OptComplNone)
591 02da9d07 Iustin Pop
592 89363f98 Klaus Aehlig
oSkipNonRedundant :: OptType
593 89363f98 Klaus Aehlig
oSkipNonRedundant =
594 89363f98 Klaus Aehlig
  (Option "" ["skip-non-redundant"]
595 89363f98 Klaus Aehlig
   (NoArg (\ opts -> Ok opts { optSkipNonRedundant = True }))
596 89363f98 Klaus Aehlig
    "Skip nodes that host a non-redundant instance",
597 89363f98 Klaus Aehlig
    OptComplNone)
598 89363f98 Klaus Aehlig
599 294bb337 Iustin Pop
oStdSpec :: OptType
600 ce207617 Iustin Pop
oStdSpec =
601 ce207617 Iustin Pop
  (Option "" ["standard-alloc"]
602 ce207617 Iustin Pop
   (ReqArg (\ inp opts -> do
603 ce207617 Iustin Pop
              tspec <- parseISpecString "standard" inp
604 ce207617 Iustin Pop
              return $ opts { optStdSpec = Just tspec } )
605 ce207617 Iustin Pop
    "STDSPEC")
606 ce207617 Iustin Pop
   "enable standard specs allocation, given as 'disk,ram,cpu'",
607 ce207617 Iustin Pop
   OptComplString)
608 294bb337 Iustin Pop
609 1f9066c0 Iustin Pop
oTieredSpec :: OptType
610 ce207617 Iustin Pop
oTieredSpec =
611 ce207617 Iustin Pop
  (Option "" ["tiered-alloc"]
612 ce207617 Iustin Pop
   (ReqArg (\ inp opts -> do
613 ce207617 Iustin Pop
              tspec <- parseISpecString "tiered" inp
614 ce207617 Iustin Pop
              return $ opts { optTieredSpec = Just tspec } )
615 ce207617 Iustin Pop
    "TSPEC")
616 ce207617 Iustin Pop
   "enable tiered specs allocation, given as 'disk,ram,cpu'",
617 ce207617 Iustin Pop
   OptComplString)
618 1f9066c0 Iustin Pop
619 df18fdfe Iustin Pop
oVerbose :: OptType
620 ce207617 Iustin Pop
oVerbose =
621 ce207617 Iustin Pop
  (Option "v" ["verbose"]
622 ce207617 Iustin Pop
   (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts + 1 }))
623 ce207617 Iustin Pop
   "increase the verbosity level",
624 ce207617 Iustin Pop
   OptComplNone)
625 fae371cc Iustin Pop
626 e247747c Iustin Pop
oPriority :: OptType
627 e247747c Iustin Pop
oPriority =
628 e247747c Iustin Pop
  (Option "" ["priority"]
629 e247747c Iustin Pop
   (ReqArg (\ inp opts -> do
630 e247747c Iustin Pop
              prio <- parseSubmitPriority inp
631 e247747c Iustin Pop
              Ok opts { optPriority = Just prio }) "PRIO")
632 e247747c Iustin Pop
   "set the priority of submitted jobs",
633 e247747c Iustin Pop
    OptComplChoices (map fmtSubmitPriority [minBound..maxBound]))
634 e247747c Iustin Pop
635 42834645 Iustin Pop
-- | Generic options.
636 42834645 Iustin Pop
genericOpts :: [GenericOptType Options]
637 42834645 Iustin Pop
genericOpts =  [ oShowVer
638 42834645 Iustin Pop
               , oShowHelp
639 097ad7ee Iustin Pop
               , oShowComp
640 42834645 Iustin Pop
               ]
641 42834645 Iustin Pop
642 525bfb36 Iustin Pop
-- * Functions
643 525bfb36 Iustin Pop
644 51000365 Iustin Pop
-- | Wrapper over 'Common.parseOpts' with our custom options.
645 0427285d Iustin Pop
parseOpts :: [String]               -- ^ The command line arguments
646 0427285d Iustin Pop
          -> String                 -- ^ The program name
647 0427285d Iustin Pop
          -> [OptType]              -- ^ The supported command line options
648 22278fa7 Iustin Pop
          -> [ArgCompletion]        -- ^ The supported command line arguments
649 0427285d Iustin Pop
          -> IO (Options, [String]) -- ^ The resulting options and leftover
650 0427285d Iustin Pop
                                    -- arguments
651 51000365 Iustin Pop
parseOpts = Common.parseOpts defaultOptions
652 51000365 Iustin Pop
653 209b3711 Iustin Pop
654 9188aeef Iustin Pop
-- | A shell script template for autogenerated scripts.
655 e0eb63f0 Iustin Pop
shTemplate :: String
656 e0eb63f0 Iustin Pop
shTemplate =
657 cd08cfa4 Iustin Pop
  printf "#!/bin/sh\n\n\
658 cd08cfa4 Iustin Pop
         \# Auto-generated script for executing cluster rebalancing\n\n\
659 cd08cfa4 Iustin Pop
         \# To stop, touch the file /tmp/stop-htools\n\n\
660 cd08cfa4 Iustin Pop
         \set -e\n\n\
661 cd08cfa4 Iustin Pop
         \check() {\n\
662 cd08cfa4 Iustin Pop
         \  if [ -f /tmp/stop-htools ]; then\n\
663 cd08cfa4 Iustin Pop
         \    echo 'Stop requested, exiting'\n\
664 cd08cfa4 Iustin Pop
         \    exit 0\n\
665 cd08cfa4 Iustin Pop
         \  fi\n\
666 cd08cfa4 Iustin Pop
         \}\n\n"
667 417f6b50 Iustin Pop
668 417f6b50 Iustin Pop
-- | Optionally print the node list.
669 417f6b50 Iustin Pop
maybePrintNodes :: Maybe [String]       -- ^ The field list
670 417f6b50 Iustin Pop
                -> String               -- ^ Informational message
671 417f6b50 Iustin Pop
                -> ([String] -> String) -- ^ Function to generate the listing
672 417f6b50 Iustin Pop
                -> IO ()
673 417f6b50 Iustin Pop
maybePrintNodes Nothing _ _ = return ()
674 417f6b50 Iustin Pop
maybePrintNodes (Just fields) msg fn = do
675 417f6b50 Iustin Pop
  hPutStrLn stderr ""
676 417f6b50 Iustin Pop
  hPutStrLn stderr (msg ++ " status:")
677 417f6b50 Iustin Pop
  hPutStrLn stderr $ fn fields
678 33e44f0c Iustin Pop
679 33e44f0c Iustin Pop
-- | Optionally print the instance list.
680 33e44f0c Iustin Pop
maybePrintInsts :: Bool   -- ^ Whether to print the instance list
681 33e44f0c Iustin Pop
                -> String -- ^ Type of the instance map (e.g. initial)
682 33e44f0c Iustin Pop
                -> String -- ^ The instance data
683 33e44f0c Iustin Pop
                -> IO ()
684 33e44f0c Iustin Pop
maybePrintInsts do_print msg instdata =
685 33e44f0c Iustin Pop
  when do_print $ do
686 33e44f0c Iustin Pop
    hPutStrLn stderr ""
687 33e44f0c Iustin Pop
    hPutStrLn stderr $ msg ++ " instance map:"
688 33e44f0c Iustin Pop
    hPutStr stderr instdata
689 8cd36391 Iustin Pop
690 8cd36391 Iustin Pop
-- | Function to display warning messages from parsing the cluster
691 8cd36391 Iustin Pop
-- state.
692 8cd36391 Iustin Pop
maybeShowWarnings :: [String] -- ^ The warning messages
693 8cd36391 Iustin Pop
                  -> IO ()
694 8cd36391 Iustin Pop
maybeShowWarnings fix_msgs =
695 8cd36391 Iustin Pop
  unless (null fix_msgs) $ do
696 8cd36391 Iustin Pop
    hPutStrLn stderr "Warning: cluster has inconsistent data:"
697 8cd36391 Iustin Pop
    hPutStrLn stderr . unlines . map (printf "  - %s") $ fix_msgs
698 5296ee23 Iustin Pop
699 79eef90b Agata Murawska
-- | Format a list of key, value as a shell fragment.
700 e60fa4af Agata Murawska
printKeys :: String              -- ^ Prefix to printed variables
701 e60fa4af Agata Murawska
          -> [(String, String)]  -- ^ List of (key, value) pairs to be printed
702 e60fa4af Agata Murawska
          -> IO ()
703 51000365 Iustin Pop
printKeys prefix =
704 51000365 Iustin Pop
  mapM_ (\(k, v) ->
705 51000365 Iustin Pop
           printf "%s_%s=%s\n" prefix (map toUpper k) (ensureQuoted v))
706 79eef90b Agata Murawska
707 79eef90b Agata Murawska
-- | Prints the final @OK@ marker in machine readable output.
708 e60fa4af Agata Murawska
printFinal :: String    -- ^ Prefix to printed variable
709 51000365 Iustin Pop
           -> Bool      -- ^ Whether output should be machine readable;
710 51000365 Iustin Pop
                        -- note: if not, there is nothing to print
711 e60fa4af Agata Murawska
           -> IO ()
712 79eef90b Agata Murawska
printFinal prefix True =
713 79eef90b Agata Murawska
  -- this should be the final entry
714 79eef90b Agata Murawska
  printKeys prefix [("OK", "1")]
715 79eef90b Agata Murawska
716 79eef90b Agata Murawska
printFinal _ False = return ()
717 79eef90b Agata Murawska
718 284e9822 Iustin Pop
-- | Potentially set the node as offline based on passed offline list.
719 284e9822 Iustin Pop
setNodeOffline :: [Ndx] -> Node.Node -> Node.Node
720 284e9822 Iustin Pop
setNodeOffline offline_indices n =
721 284e9822 Iustin Pop
  if Node.idx n `elem` offline_indices
722 284e9822 Iustin Pop
    then Node.setOffline n True
723 284e9822 Iustin Pop
    else n
724 284e9822 Iustin Pop
725 5296ee23 Iustin Pop
-- | Set node properties based on command line options.
726 5296ee23 Iustin Pop
setNodeStatus :: Options -> Node.List -> IO Node.List
727 5296ee23 Iustin Pop
setNodeStatus opts fixed_nl = do
728 5296ee23 Iustin Pop
  let offline_passed = optOffline opts
729 5296ee23 Iustin Pop
      all_nodes = Container.elems fixed_nl
730 5296ee23 Iustin Pop
      offline_lkp = map (lookupName (map Node.name all_nodes)) offline_passed
731 5296ee23 Iustin Pop
      offline_wrong = filter (not . goodLookupResult) offline_lkp
732 5296ee23 Iustin Pop
      offline_names = map lrContent offline_lkp
733 5296ee23 Iustin Pop
      offline_indices = map Node.idx $
734 5296ee23 Iustin Pop
                        filter (\n -> Node.name n `elem` offline_names)
735 5296ee23 Iustin Pop
                               all_nodes
736 5296ee23 Iustin Pop
      m_cpu = optMcpu opts
737 5296ee23 Iustin Pop
      m_dsk = optMdsk opts
738 5296ee23 Iustin Pop
739 5b11f8db Iustin Pop
  unless (null offline_wrong) .
740 88a10df5 Iustin Pop
         exitErr $ printf "wrong node name(s) set as offline: %s\n"
741 88a10df5 Iustin Pop
                   (commaJoin (map lrContent offline_wrong))
742 284e9822 Iustin Pop
  let setMCpuFn = case m_cpu of
743 284e9822 Iustin Pop
                    Nothing -> id
744 284e9822 Iustin Pop
                    Just new_mcpu -> flip Node.setMcpu new_mcpu
745 284e9822 Iustin Pop
  let nm = Container.map (setNodeOffline offline_indices .
746 284e9822 Iustin Pop
                          flip Node.setMdsk m_dsk .
747 284e9822 Iustin Pop
                          setMCpuFn) fixed_nl
748 284e9822 Iustin Pop
  return nm