Introduce a new type for allocation results
[ganeti-local] / hspace.hs
1 {-| Cluster space sizing
2
3 -}
4
5 {-
6
7 Copyright (C) 2009 Google Inc.
8
9 This program is free software; you can redistribute it and/or modify
10 it under the terms of the GNU General Public License as published by
11 the Free Software Foundation; either version 2 of the License, or
12 (at your option) any later version.
13
14 This program is distributed in the hope that it will be useful, but
15 WITHOUT ANY WARRANTY; without even the implied warranty of
16 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 General Public License for more details.
18
19 You should have received a copy of the GNU General Public License
20 along with this program; if not, write to the Free Software
21 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 02110-1301, USA.
23
24 -}
25
26 module Main (main) where
27
28 import Data.List
29 import Data.Function
30 import Monad
31 import System
32 import System.IO
33 import System.Console.GetOpt
34 import qualified System
35
36 import Text.Printf (printf)
37
38 import qualified Ganeti.HTools.Container as Container
39 import qualified Ganeti.HTools.Cluster as Cluster
40 import qualified Ganeti.HTools.Node as Node
41 import qualified Ganeti.HTools.Instance as Instance
42 import qualified Ganeti.HTools.CLI as CLI
43
44 import Ganeti.HTools.Utils
45 import Ganeti.HTools.Types
46
47 -- | Command line options structure.
48 data Options = Options
49     { optShowNodes :: Bool           -- ^ Whether to show node status
50     , optNodef     :: FilePath       -- ^ Path to the nodes file
51     , optNodeSet   :: Bool           -- ^ The nodes have been set by options
52     , optInstf     :: FilePath       -- ^ Path to the instances file
53     , optInstSet   :: Bool           -- ^ The insts have been set by options
54     , optMaster    :: String         -- ^ Collect data from RAPI
55     , optVerbose   :: Int            -- ^ Verbosity level
56     , optOffline   :: [String]       -- ^ Names of offline nodes
57     , optIMem      :: Int            -- ^ Instance memory
58     , optIDsk      :: Int            -- ^ Instance disk
59     , optIVCPUs    :: Int            -- ^ Instance VCPUs
60     , optINodes    :: Int            -- ^ Nodes required for an instance
61     , optMcpu      :: Double         -- ^ Max cpu ratio for nodes
62     , optMdsk      :: Double         -- ^ Max disk usage ratio for nodes
63     , optShowVer   :: Bool           -- ^ Just show the program version
64     , optShowHelp  :: Bool           -- ^ Just show the help
65     } deriving Show
66
67 instance CLI.CLIOptions Options where
68     showVersion = optShowVer
69     showHelp    = optShowHelp
70
71 instance CLI.EToolOptions Options where
72     nodeFile   = optNodef
73     nodeSet    = optNodeSet
74     instFile   = optInstf
75     instSet    = optInstSet
76     masterName = optMaster
77     silent a   = (optVerbose a) == 0
78
79 -- | Default values for the command line options.
80 defaultOptions :: Options
81 defaultOptions  = Options
82  { optShowNodes = False
83  , optNodef     = "nodes"
84  , optNodeSet   = False
85  , optInstf     = "instances"
86  , optInstSet   = False
87  , optMaster    = ""
88  , optVerbose   = 1
89  , optOffline   = []
90  , optIMem      = 4096
91  , optIDsk      = 102400
92  , optIVCPUs    = 1
93  , optINodes    = 2
94  , optMcpu      = -1
95  , optMdsk      = -1
96  , optShowVer   = False
97  , optShowHelp  = False
98  }
99
100 -- | Options list and functions
101 options :: [OptDescr (Options -> Options)]
102 options =
103     [ Option ['p']     ["print-nodes"]
104       (NoArg (\ opts -> opts { optShowNodes = True }))
105       "print the final node list"
106     , Option ['n']     ["nodes"]
107       (ReqArg (\ f opts -> opts { optNodef = f, optNodeSet = True }) "FILE")
108       "the node list FILE"
109     , Option ['i']     ["instances"]
110       (ReqArg (\ f opts -> opts { optInstf =  f, optInstSet = True }) "FILE")
111       "the instance list FILE"
112     , Option ['m']     ["master"]
113       (ReqArg (\ m opts -> opts { optMaster = m }) "ADDRESS")
114       "collect data via RAPI at the given ADDRESS"
115     , Option ['v']     ["verbose"]
116       (NoArg (\ opts -> opts { optVerbose = (optVerbose opts) + 1 }))
117       "increase the verbosity level"
118     , Option ['q']     ["quiet"]
119       (NoArg (\ opts -> opts { optVerbose = (optVerbose opts) - 1 }))
120       "decrease the verbosity level"
121     , Option ['O']     ["offline"]
122       (ReqArg (\ n opts -> opts { optOffline = n:optOffline opts }) "NODE")
123       "set node as offline"
124     , Option []        ["memory"]
125       (ReqArg (\ m opts -> opts { optIMem = read m }) "MEMORY")
126       "memory size for instances"
127     , Option []        ["disk"]
128       (ReqArg (\ d opts -> opts { optIDsk = read d }) "DISK")
129       "disk size for instances"
130     , Option []        ["vcpus"]
131       (ReqArg (\ p opts -> opts { optIVCPUs = read p }) "NUM")
132       "number of virtual cpus for instances"
133     , Option []        ["req-nodes"]
134       (ReqArg (\ n opts -> opts { optINodes = read n }) "NODES")
135       "number of nodes for the new instances (1=plain, 2=mirrored)"
136     , Option []        ["max-cpu"]
137       (ReqArg (\ n opts -> opts { optMcpu = read n }) "RATIO")
138       "maximum virtual-to-physical cpu ratio for nodes"
139     , Option []        ["min-disk"]
140       (ReqArg (\ n opts -> opts { optMdsk = read n }) "RATIO")
141       "minimum free disk space for nodes (between 0 and 1)"
142     , Option ['V']     ["version"]
143       (NoArg (\ opts -> opts { optShowVer = True}))
144       "show the version of the program"
145     , Option ['h']     ["help"]
146       (NoArg (\ opts -> opts { optShowHelp = True}))
147       "show help"
148     ]
149
150 filterFails :: Cluster.AllocSolution
151             -> OpResult [(Node.List, Instance.Instance, [Node.Node])]
152 filterFails sols =
153     let sols' = concat . map (\ (onl, i, nn) ->
154                                   case onl of
155                                     OpFail _ -> []
156                                     OpGood gnl -> [(gnl, i, nn)]
157                              ) $ sols
158     in
159       if null sols' then
160           OpFail FailN1
161       else
162           return sols'
163
164 processResults :: [(Node.List, Instance.Instance, [Node.Node])]
165                -> (Node.List, Instance.Instance, [Node.Node])
166 processResults sols =
167     let sols' = map (\e@(nl', _, _) -> (Cluster.compCV  nl', e)) sols
168         sols'' = sortBy (compare `on` fst) sols'
169     in snd $ head sols''
170
171 iterateDepth :: Node.List
172              -> Instance.List
173              -> Instance.Instance
174              -> Int
175              -> [Instance.Instance]
176              -> (Node.List, [Instance.Instance])
177 iterateDepth nl il newinst nreq ixes =
178       let depth = length ixes
179           newname = (printf "new-%d" depth)::String
180           newidx = (length $ Container.elems il) + depth
181           newi2 = Instance.setIdx (Instance.setName newinst newname) newidx
182           sols = (Cluster.tryAlloc nl il newi2 nreq)::
183                  OpResult Cluster.AllocSolution
184           orig = (nl, ixes)
185       in case sols of
186            OpFail _ -> orig
187            OpGood sols' ->
188                let
189                    sols'' = filterFails sols'
190                in case sols'' of
191                     OpFail _ -> orig
192                     OpGood sols''' ->
193                         let (xnl, xi, _) = processResults sols'''
194                         in iterateDepth xnl il newinst nreq (xi:ixes)
195
196 printStats :: String -> Cluster.CStats -> IO ()
197 printStats kind cs = do
198   printf "%s free RAM: %d\n" kind (Cluster.cs_fmem cs)
199   printf "%s allocatable RAM: %d\n" kind (Cluster.cs_amem cs)
200   printf "%s reserved RAM: %d\n" kind ((Cluster.cs_fmem cs) -
201                                        (Cluster.cs_amem cs))
202   printf "%s free disk: %d\n" kind (Cluster.cs_fdsk cs)
203   printf "%s allocatable disk: %d\n" kind (Cluster.cs_adsk cs)
204   printf "%s reserved disk: %d\n" kind ((Cluster.cs_fdsk cs) -
205                                         (Cluster.cs_adsk cs))
206   printf "%s max node allocatable RAM: %d\n" kind (Cluster.cs_mmem cs)
207   printf "%s max node allocatable disk: %d\n" kind (Cluster.cs_mdsk cs)
208
209 -- | Main function.
210 main :: IO ()
211 main = do
212   cmd_args <- System.getArgs
213   (opts, args) <- CLI.parseOpts cmd_args "hspace" options defaultOptions
214
215   unless (null args) $ do
216          hPutStrLn stderr "Error: this program doesn't take any arguments."
217          exitWith $ ExitFailure 1
218
219   let verbose = optVerbose opts
220
221   (fixed_nl, il, csf) <- CLI.loadExternalData opts
222   let num_instances = length $ Container.elems il
223
224   let offline_names = optOffline opts
225       all_nodes = Container.elems fixed_nl
226       all_names = map Node.name all_nodes
227       offline_wrong = filter (\n -> not $ elem n all_names) offline_names
228       offline_indices = map Node.idx $
229                         filter (\n -> elem (Node.name n) offline_names)
230                                all_nodes
231       req_nodes = optINodes opts
232       m_cpu = optMcpu opts
233       m_dsk = optMdsk opts
234
235   when (length offline_wrong > 0) $ do
236          printf "Error: Wrong node name(s) set as offline: %s\n"
237                 (commaJoin offline_wrong)
238          exitWith $ ExitFailure 1
239
240   when (req_nodes /= 1 && req_nodes /= 2) $ do
241          printf "Error: Invalid required nodes (%d)\n" req_nodes
242          exitWith $ ExitFailure 1
243
244   let nm = Container.map (\n -> if elem (Node.idx n) offline_indices
245                                 then Node.setOffline n True
246                                 else n) fixed_nl
247       nl = Container.map (flip Node.setMdsk m_dsk . flip Node.setMcpu m_cpu)
248            nm
249
250   when (length csf > 0 && verbose > 1) $ do
251          printf "Note: Stripping common suffix of '%s' from names\n" csf
252
253   let bad_nodes = fst $ Cluster.computeBadItems nl il
254   when (length bad_nodes > 0) $ do
255          putStrLn "Error: Cluster not N+1, no space to allocate."
256          exitWith $ ExitFailure 1
257
258   when (optShowNodes opts) $
259        do
260          putStrLn "Initial cluster status:"
261          putStrLn $ Cluster.printNodes nl
262
263   let ini_cv = Cluster.compCV nl
264       ini_stats = Cluster.totalResources nl
265
266   (if verbose > 2 then
267        printf "Initial coefficients: overall %.8f, %s\n"
268        ini_cv (Cluster.printStats nl)
269    else
270        printf "Initial score: %.8f\n" ini_cv)
271   printf "Initial instances: %d\n" num_instances
272   printStats "Initial" ini_stats
273
274   let nmlen = Container.maxNameLen nl
275       newinst = Instance.create "new" (optIMem opts) (optIDsk opts)
276                 (optIVCPUs opts) "ADMIN_down" (-1) (-1)
277
278   let (fin_nl, ixes) = iterateDepth nl il newinst req_nodes []
279       allocs = length ixes
280       fin_instances = num_instances + allocs
281       fin_ixes = reverse ixes
282       ix_namelen = maximum . map (length . Instance.name) $ fin_ixes
283       fin_stats = Cluster.totalResources fin_nl
284
285   printf "Final score: %.8f\n" (Cluster.compCV fin_nl)
286   printf "Final instances: %d\n" (num_instances + allocs)
287   printStats "Final" fin_stats
288   printf "Usage: %.5f\n" (((fromIntegral num_instances)::Double) /
289                           (fromIntegral fin_instances))
290   printf "Allocations: %d\n" allocs
291   when (verbose > 1) $ do
292          putStr . unlines . map (\i -> printf "Inst: %*s %-*s %-*s"
293                      ix_namelen (Instance.name i)
294                      nmlen (Container.nameOf fin_nl $ Instance.pnode i)
295                      nmlen (let sdx = Instance.snode i
296                             in if sdx == Node.noSecondary then ""
297                                else Container.nameOf fin_nl sdx))
298          $ fin_ixes
299
300   when (optShowNodes opts) $
301        do
302          putStrLn ""
303          putStrLn "Final cluster status:"
304          putStrLn $ Cluster.printNodes fin_nl