Add a simulated cluster data loader
[ganeti-local] / Ganeti / HTools / CLI.hs
1 {-| Implementation of command-line functions.
2
3 This module holds the common cli-related functions for the binaries,
4 separated into this module since Utils.hs is used in many other places
5 and this is more IO oriented.
6
7 -}
8
9 {-
10
11 Copyright (C) 2009 Google Inc.
12
13 This program is free software; you can redistribute it and/or modify
14 it under the terms of the GNU General Public License as published by
15 the Free Software Foundation; either version 2 of the License, or
16 (at your option) any later version.
17
18 This program is distributed in the hope that it will be useful, but
19 WITHOUT ANY WARRANTY; without even the implied warranty of
20 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
21 General Public License for more details.
22
23 You should have received a copy of the GNU General Public License
24 along with this program; if not, write to the Free Software
25 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
26 02110-1301, USA.
27
28 -}
29
30 module Ganeti.HTools.CLI
31     ( Options(..)
32     , OptType
33     , parseOpts
34     , parseEnv
35     , shTemplate
36     , loadExternalData
37     , defaultLuxiSocket
38     -- * The options
39     , oPrintNodes
40     , oPrintCommands
41     , oOneline
42     , oNoHeaders
43     , oOutputDir
44     , oNodeFile
45     , oInstFile
46     , oNodeSim
47     , oRapiMaster
48     , oLuxiSocket
49     , oMaxSolLength
50     , oVerbose
51     , oQuiet
52     , oOfflineNode
53     , oMinScore
54     , oIMem
55     , oIDisk
56     , oIVcpus
57     , oINodes
58     , oMaxCpu
59     , oMinDisk
60     , oShowVer
61     , oShowHelp
62     ) where
63
64 import Control.Exception
65 import Data.Maybe (isJust, fromJust, fromMaybe)
66 import qualified Data.Version
67 import Monad
68 import System.Console.GetOpt
69 import System.Posix.Env
70 import System.IO
71 import System.Info
72 import System
73 import Text.Printf (printf, hPrintf)
74
75 import qualified Ganeti.HTools.Version as Version(version)
76 import qualified Ganeti.HTools.Luxi as Luxi
77 import qualified Ganeti.HTools.Rapi as Rapi
78 import qualified Ganeti.HTools.Simu as Simu
79 import qualified Ganeti.HTools.Text as Text
80 import qualified Ganeti.HTools.Loader as Loader
81 import qualified Ganeti.HTools.Instance as Instance
82 import qualified Ganeti.HTools.Node as Node
83 import qualified Ganeti.HTools.Cluster as Cluster
84
85 import Ganeti.HTools.Types
86
87 -- | The default value for the luxi socket
88 defaultLuxiSocket :: FilePath
89 defaultLuxiSocket = "/var/run/ganeti/socket/ganeti-master"
90
91 -- | Command line options structure.
92 data Options = Options
93     { optShowNodes :: Bool           -- ^ Whether to show node status
94     , optShowCmds  :: Maybe FilePath -- ^ Whether to show the command list
95     , optOneline   :: Bool           -- ^ Switch output to a single line
96     , optOutPath   :: FilePath       -- ^ Path to the output directory
97     , optNoHeaders :: Bool           -- ^ Do not show a header line
98     , optNodeFile  :: FilePath       -- ^ Path to the nodes file
99     , optNodeSet   :: Bool           -- ^ The nodes have been set by options
100     , optInstFile  :: FilePath       -- ^ Path to the instances file
101     , optInstSet   :: Bool           -- ^ The insts have been set by options
102     , optNodeSim   :: Maybe String   -- ^ Cluster simulation mode
103     , optMaxLength :: Int            -- ^ Stop after this many steps
104     , optMaster    :: String         -- ^ Collect data from RAPI
105     , optLuxi      :: Maybe FilePath -- ^ Collect data from Luxi
106     , optOffline   :: [String]       -- ^ Names of offline nodes
107     , optIMem      :: Int            -- ^ Instance memory
108     , optIDsk      :: Int            -- ^ Instance disk
109     , optIVCPUs    :: Int            -- ^ Instance VCPUs
110     , optINodes    :: Int            -- ^ Nodes required for an instance
111     , optMinScore  :: Cluster.Score  -- ^ The minimum score we aim for
112     , optMcpu      :: Double         -- ^ Max cpu ratio for nodes
113     , optMdsk      :: Double         -- ^ Max disk usage ratio for nodes
114     , optVerbose   :: Int            -- ^ Verbosity level
115     , optShowVer   :: Bool           -- ^ Just show the program version
116     , optShowHelp  :: Bool           -- ^ Just show the help
117     } deriving Show
118
119 -- | Default values for the command line options.
120 defaultOptions :: Options
121 defaultOptions  = Options
122  { optShowNodes = False
123  , optShowCmds  = Nothing
124  , optOneline   = False
125  , optNoHeaders = False
126  , optOutPath   = "."
127  , optNodeFile  = "nodes"
128  , optNodeSet   = False
129  , optInstFile  = "instances"
130  , optInstSet   = False
131  , optNodeSim   = Nothing
132  , optMaxLength = -1
133  , optMaster    = ""
134  , optLuxi      = Nothing
135  , optOffline   = []
136  , optIMem      = 4096
137  , optIDsk      = 102400
138  , optIVCPUs    = 1
139  , optINodes    = 2
140  , optMinScore  = 1e-9
141  , optMcpu      = -1
142  , optMdsk      = -1
143  , optVerbose   = 1
144  , optShowVer   = False
145  , optShowHelp  = False
146  }
147
148 -- | Abrreviation for the option type
149 type OptType = OptDescr (Options -> Options)
150
151 oPrintNodes :: OptType
152 oPrintNodes = Option "p" ["print-nodes"]
153               (NoArg (\ opts -> opts { optShowNodes = True }))
154               "print the final node list"
155
156 oPrintCommands :: OptType
157 oPrintCommands = Option "C" ["print-commands"]
158                  (OptArg ((\ f opts -> opts { optShowCmds = Just f }) .
159                           fromMaybe "-")
160                   "FILE")
161                  "print the ganeti command list for reaching the solution,\
162                  \ if an argument is passed then write the commands to a\
163                  \ file named as such"
164
165 oOneline :: OptType
166 oOneline = Option "o" ["oneline"]
167            (NoArg (\ opts -> opts { optOneline = True }))
168            "print the ganeti command list for reaching the solution"
169
170 oNoHeaders :: OptType
171 oNoHeaders = Option "" ["no-headers"]
172              (NoArg (\ opts -> opts { optNoHeaders = True }))
173              "do not show a header line"
174
175 oOutputDir :: OptType
176 oOutputDir = Option "d" ["output-dir"]
177              (ReqArg (\ d opts -> opts { optOutPath = d }) "PATH")
178              "directory in which to write output files"
179
180 oNodeFile :: OptType
181 oNodeFile = Option "n" ["nodes"]
182             (ReqArg (\ f o -> o { optNodeFile = f, optNodeSet = True }) "FILE")
183             "the node list FILE"
184
185 oInstFile :: OptType
186 oInstFile = Option "i" ["instances"]
187             (ReqArg (\ f o -> o { optInstFile = f, optInstSet = True }) "FILE")
188             "the instance list FILE"
189
190 oNodeSim :: OptType
191 oNodeSim = Option "" ["simulate"]
192             (ReqArg (\ f o -> o { optNodeSim = Just f }) "SPEC")
193             "simulate an empty cluster, given as 'num_nodes,disk,memory,cpus'"
194
195 oRapiMaster :: OptType
196 oRapiMaster = Option "m" ["master"]
197               (ReqArg (\ m opts -> opts { optMaster = m }) "ADDRESS")
198               "collect data via RAPI at the given ADDRESS"
199
200 oLuxiSocket :: OptType
201 oLuxiSocket = Option "L" ["luxi"]
202               (OptArg ((\ f opts -> opts { optLuxi = Just f }) .
203                        fromMaybe defaultLuxiSocket) "SOCKET")
204               "collect data via Luxi, optionally using the given SOCKET path"
205
206 oVerbose :: OptType
207 oVerbose = Option "v" ["verbose"]
208            (NoArg (\ opts -> opts { optVerbose = optVerbose opts + 1 }))
209            "increase the verbosity level"
210
211 oQuiet :: OptType
212 oQuiet = Option "q" ["quiet"]
213          (NoArg (\ opts -> opts { optVerbose = optVerbose opts - 1 }))
214          "decrease the verbosity level"
215
216 oOfflineNode :: OptType
217 oOfflineNode = Option "O" ["offline"]
218                (ReqArg (\ n o -> o { optOffline = n:optOffline o }) "NODE")
219                "set node as offline"
220
221 oMaxSolLength :: OptType
222 oMaxSolLength = Option "l" ["max-length"]
223                 (ReqArg (\ i opts -> opts { optMaxLength =  read i::Int }) "N")
224                 "cap the solution at this many moves (useful for very\
225                 \ unbalanced clusters)"
226
227 oMinScore :: OptType
228 oMinScore = Option "e" ["min-score"]
229             (ReqArg (\ e opts -> opts { optMinScore = read e }) "EPSILON")
230             " mininum score to aim for"
231
232 oIMem :: OptType
233 oIMem = Option "" ["memory"]
234         (ReqArg (\ m opts -> opts { optIMem = read m }) "MEMORY")
235         "memory size for instances"
236
237 oIDisk :: OptType
238 oIDisk = Option "" ["disk"]
239          (ReqArg (\ d opts -> opts { optIDsk = read d }) "DISK")
240          "disk size for instances"
241
242 oIVcpus :: OptType
243 oIVcpus = Option "" ["vcpus"]
244           (ReqArg (\ p opts -> opts { optIVCPUs = read p }) "NUM")
245           "number of virtual cpus for instances"
246
247 oINodes :: OptType
248 oINodes = Option "" ["req-nodes"]
249           (ReqArg (\ n opts -> opts { optINodes = read n }) "NODES")
250           "number of nodes for the new instances (1=plain, 2=mirrored)"
251
252 oMaxCpu :: OptType
253 oMaxCpu = Option "" ["max-cpu"]
254           (ReqArg (\ n opts -> opts { optMcpu = read n }) "RATIO")
255           "maximum virtual-to-physical cpu ratio for nodes"
256
257 oMinDisk :: OptType
258 oMinDisk = Option "" ["min-disk"]
259            (ReqArg (\ n opts -> opts { optMdsk = read n }) "RATIO")
260            "minimum free disk space for nodes (between 0 and 1)"
261
262 oShowVer :: OptType
263 oShowVer = Option "V" ["version"]
264            (NoArg (\ opts -> opts { optShowVer = True}))
265            "show the version of the program"
266
267 oShowHelp :: OptType
268 oShowHelp = Option "h" ["help"]
269             (NoArg (\ opts -> opts { optShowHelp = True}))
270             "show help"
271
272 -- | Usage info
273 usageHelp :: String -> [OptType] -> String
274 usageHelp progname =
275     usageInfo (printf "%s %s\nUsage: %s [OPTION...]"
276                progname Version.version progname)
277
278 -- | Command line parser, using the 'options' structure.
279 parseOpts :: [String]               -- ^ The command line arguments
280           -> String                 -- ^ The program name
281           -> [OptType]              -- ^ The supported command line options
282           -> IO (Options, [String]) -- ^ The resulting options and leftover
283                                     -- arguments
284 parseOpts argv progname options =
285     case getOpt Permute options argv of
286       (o, n, []) ->
287           do
288             let resu@(po, _) = (foldl (flip id) defaultOptions o, n)
289             when (optShowHelp po) $ do
290               putStr $ usageHelp progname options
291               exitWith ExitSuccess
292             when (optShowVer po) $ do
293               printf "%s %s\ncompiled with %s %s\nrunning on %s %s\n"
294                      progname Version.version
295                      compilerName (Data.Version.showVersion compilerVersion)
296                      os arch
297               exitWith ExitSuccess
298             return resu
299       (_, _, errs) ->
300           ioError (userError (concat errs ++ usageHelp progname options))
301
302 -- | Parse the environment and return the node\/instance names.
303 --
304 -- This also hardcodes here the default node\/instance file names.
305 parseEnv :: () -> IO (String, String)
306 parseEnv () = do
307   a <- getEnvDefault "HTOOLS_NODES" "nodes"
308   b <- getEnvDefault "HTOOLS_INSTANCES" "instances"
309   return (a, b)
310
311 -- | A shell script template for autogenerated scripts.
312 shTemplate :: String
313 shTemplate =
314     printf "#!/bin/sh\n\n\
315            \# Auto-generated script for executing cluster rebalancing\n\n\
316            \# To stop, touch the file /tmp/stop-htools\n\n\
317            \set -e\n\n\
318            \check() {\n\
319            \  if [ -f /tmp/stop-htools ]; then\n\
320            \    echo 'Stop requested, exiting'\n\
321            \    exit 0\n\
322            \  fi\n\
323            \}\n\n"
324
325 -- | Error beautifier
326 wrapIO :: IO (Result a) -> IO (Result a)
327 wrapIO act =
328     handle (\e -> return $ Bad $ show e)
329     act
330
331 -- | External tool data loader from a variety of sources.
332 loadExternalData :: Options
333                  -> IO (Node.List, Instance.List, String)
334 loadExternalData opts = do
335   (env_node, env_inst) <- parseEnv ()
336   let nodef = if optNodeSet opts then optNodeFile opts
337               else env_node
338       instf = if optInstSet opts then optInstFile opts
339               else env_inst
340       mhost = optMaster opts
341       lsock = optLuxi opts
342       simdata = optNodeSim opts
343       setRapi = mhost /= ""
344       setLuxi = isJust lsock
345       setSim = isJust simdata
346       setFiles = optNodeSet opts || optInstSet opts
347       allSet = filter id [setRapi, setLuxi, setFiles]
348   when (length allSet > 1) $
349        do
350          hPutStrLn stderr "Error: Only one of the rapi, luxi, and data\
351                           \ files options should be given."
352          exitWith $ ExitFailure 1
353
354   input_data <-
355       case () of
356         _ | setRapi -> wrapIO $ Rapi.loadData mhost
357           | setLuxi -> wrapIO $ Luxi.loadData $ fromJust lsock
358           | setSim -> Simu.loadData $ fromJust simdata
359           | otherwise -> wrapIO $ Text.loadData nodef instf
360
361   let ldresult = input_data >>= Loader.mergeData
362   (loaded_nl, il, csf) <-
363       (case ldresult of
364          Ok x -> return x
365          Bad s -> do
366            hPrintf stderr "Error: failed to load data. Details:\n%s\n" s
367            exitWith $ ExitFailure 1
368       )
369   let (fix_msgs, fixed_nl) = Loader.checkData loaded_nl il
370
371   unless (null fix_msgs || optVerbose opts == 0) $ do
372          hPutStrLn stderr "Warning: cluster has inconsistent data:"
373          hPutStrLn stderr . unlines . map (printf "  - %s") $ fix_msgs
374
375   return (fixed_nl, il, csf)