Rework the instance spec CLI options
[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.Char (toUpper)
29 import Data.List
30 import Data.Function
31 import Monad
32 import System
33 import System.IO
34 import qualified System
35
36 import Text.Printf (printf, hPrintf)
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
43 import Ganeti.HTools.Utils
44 import Ganeti.HTools.Types
45 import Ganeti.HTools.CLI
46 import Ganeti.HTools.ExtLoader
47
48 -- | Options list and functions
49 options :: [OptType]
50 options =
51     [ oPrintNodes
52     , oNodeFile
53     , oInstFile
54     , oNodeSim
55     , oRapiMaster
56     , oLuxiSocket
57     , oVerbose
58     , oQuiet
59     , oOfflineNode
60     , oIMem
61     , oIDisk
62     , oIVcpus
63     , oINodes
64     , oMaxCpu
65     , oMinDisk
66     , oTieredSpec
67     , oShowVer
68     , oShowHelp
69     ]
70
71 data Phase = PInitial | PFinal
72
73 statsData :: [(String, Cluster.CStats -> String)]
74 statsData = [ ("SCORE", printf "%.8f" . Cluster.csScore)
75             , ("INST_CNT", printf "%d" . Cluster.csNinst)
76             , ("MEM_FREE", printf "%d" . Cluster.csFmem)
77             , ("MEM_AVAIL", printf "%d" . Cluster.csAmem)
78             , ("MEM_RESVD",
79                \cs -> printf "%d" (Cluster.csFmem cs - Cluster.csAmem cs))
80             , ("MEM_INST", printf "%d" . Cluster.csImem)
81             , ("MEM_OVERHEAD",
82                \cs -> printf "%d" (Cluster.csXmem cs + Cluster.csNmem cs))
83             , ("MEM_EFF",
84                \cs -> printf "%.8f" (fromIntegral (Cluster.csImem cs) /
85                                      Cluster.csTmem cs))
86             , ("DSK_FREE", printf "%d" . Cluster.csFdsk)
87             , ("DSK_AVAIL", printf "%d ". Cluster.csAdsk)
88             , ("DSK_RESVD",
89                \cs -> printf "%d" (Cluster.csFdsk cs - Cluster.csAdsk cs))
90             , ("DSK_INST", printf "%d" . Cluster.csIdsk)
91             , ("DSK_EFF",
92                \cs -> printf "%.8f" (fromIntegral (Cluster.csIdsk cs) /
93                                     Cluster.csTdsk cs))
94             , ("CPU_INST", printf "%d" . Cluster.csIcpu)
95             , ("CPU_EFF",
96                \cs -> printf "%.8f" (fromIntegral (Cluster.csIcpu cs) /
97                                      Cluster.csTcpu cs))
98             , ("MNODE_MEM_AVAIL", printf "%d" . Cluster.csMmem)
99             , ("MNODE_DSK_AVAIL", printf "%d" . Cluster.csMdsk)
100             ]
101
102 specData :: [(String, RSpec -> String)]
103 specData = [ ("MEM", printf "%d" . rspecMem)
104            , ("DSK", printf "%d" . rspecDsk)
105            , ("CPU", printf "%d" . rspecCpu)
106            ]
107
108 clusterData :: [(String, Cluster.CStats -> String)]
109 clusterData = [ ("MEM", printf "%.0f" . Cluster.csTmem)
110               , ("DSK", printf "%.0f" . Cluster.csTdsk)
111               , ("CPU", printf "%.0f" . Cluster.csTcpu)
112               ]
113
114 -- | Recursively place instances on the cluster until we're out of space
115 iterateDepth :: Node.List
116              -> Instance.List
117              -> Instance.Instance
118              -> Int
119              -> [Instance.Instance]
120              -> Result (FailStats, Node.List, [Instance.Instance])
121 iterateDepth nl il newinst nreq ixes =
122       let depth = length ixes
123           newname = printf "new-%d" depth::String
124           newidx = length (Container.elems il) + depth
125           newi2 = Instance.setIdx (Instance.setName newinst newname) newidx
126       in case Cluster.tryAlloc nl il newi2 nreq of
127            Bad s -> Bad s
128            Ok (errs, _, sols3) ->
129                case sols3 of
130                  Nothing -> Ok (Cluster.collapseFailures errs, nl, ixes)
131                  Just (_, (xnl, xi, _)) ->
132                      iterateDepth xnl il newinst nreq $! (xi:ixes)
133
134 -- | Function to print stats for a given phase
135 printStats :: Phase -> Cluster.CStats -> [(String, String)]
136 printStats ph cs =
137   map (\(s, fn) -> (printf "%s_%s" kind s, fn cs)) statsData
138   where kind = case ph of
139                  PInitial -> "INI"
140                  PFinal -> "FIN"
141
142 -- | Print final stats and related metrics
143 printResults :: Node.List -> Int -> Int -> [(FailMode, Int)] -> IO ()
144 printResults fin_nl num_instances allocs sreason = do
145   let fin_stats = Cluster.totalResources fin_nl
146       fin_instances = num_instances + allocs
147
148   when (num_instances + allocs /= Cluster.csNinst fin_stats) $
149        do
150          hPrintf stderr "ERROR: internal inconsistency, allocated (%d)\
151                         \ != counted (%d)\n" (num_instances + allocs)
152                                  (Cluster.csNinst fin_stats)
153          exitWith $ ExitFailure 1
154
155   printKeys $ printStats PFinal fin_stats
156   printKeys [ ("ALLOC_USAGE", printf "%.8f"
157                                 ((fromIntegral num_instances::Double) /
158                                  fromIntegral fin_instances))
159             , ("ALLOC_INSTANCES", printf "%d" allocs)
160             , ("ALLOC_FAIL_REASON", map toUpper . show . fst $ head sreason)
161             ]
162   printKeys $ map (\(x, y) -> (printf "ALLOC_%s_CNT" (show x),
163                                printf "%d" y)) sreason
164   -- this should be the final entry
165   printKeys [("OK", "1")]
166
167 -- | Format a list of key/values as a shell fragment
168 printKeys :: [(String, String)] -> IO ()
169 printKeys = mapM_ (\(k, v) -> printf "HTS_%s=%s\n" (map toUpper k) v)
170
171 -- | Main function.
172 main :: IO ()
173 main = do
174   cmd_args <- System.getArgs
175   (opts, args) <- parseOpts cmd_args "hspace" options
176
177   unless (null args) $ do
178          hPutStrLn stderr "Error: this program doesn't take any arguments."
179          exitWith $ ExitFailure 1
180
181   let verbose = optVerbose opts
182       ispec = optISpec opts
183
184   (fixed_nl, il, csf) <- loadExternalData opts
185
186   printKeys $ map (\(a, fn) -> ("SPEC_" ++ a, fn ispec)) specData
187   printKeys [ ("SPEC_RQN", printf "%d" (optINodes opts)) ]
188
189   let num_instances = length $ Container.elems il
190
191   let offline_names = optOffline opts
192       all_nodes = Container.elems fixed_nl
193       all_names = map Node.name all_nodes
194       offline_wrong = filter (flip notElem all_names) offline_names
195       offline_indices = map Node.idx $
196                         filter (\n -> elem (Node.name n) offline_names)
197                                all_nodes
198       req_nodes = optINodes opts
199       m_cpu = optMcpu opts
200       m_dsk = optMdsk opts
201
202   when (length offline_wrong > 0) $ do
203          hPrintf stderr "Error: Wrong node name(s) set as offline: %s\n"
204                      (commaJoin offline_wrong)
205          exitWith $ ExitFailure 1
206
207   when (req_nodes /= 1 && req_nodes /= 2) $ do
208          hPrintf stderr "Error: Invalid required nodes (%d)\n" req_nodes
209          exitWith $ ExitFailure 1
210
211   let nm = Container.map (\n -> if elem (Node.idx n) offline_indices
212                                 then Node.setOffline n True
213                                 else n) fixed_nl
214       nl = Container.map (flip Node.setMdsk m_dsk . flip Node.setMcpu m_cpu)
215            nm
216
217   when (length csf > 0 && verbose > 1) $
218        hPrintf stderr "Note: Stripping common suffix of '%s' from names\n" csf
219
220   when (optShowNodes opts) $
221        do
222          hPutStrLn stderr "Initial cluster status:"
223          hPutStrLn stderr $ Cluster.printNodes nl
224
225   let ini_cv = Cluster.compCV nl
226       ini_stats = Cluster.totalResources nl
227
228   when (verbose > 2) $
229          hPrintf stderr "Initial coefficients: overall %.8f, %s\n"
230                  ini_cv (Cluster.printStats nl)
231
232   printKeys $ map (\(a, fn) -> ("CLUSTER_" ++ a, fn ini_stats)) clusterData
233   printKeys [("CLUSTER_NODES", printf "%d" (length all_nodes))]
234   printKeys $ printStats PInitial ini_stats
235
236   let bad_nodes = fst $ Cluster.computeBadItems nl il
237   when (length bad_nodes > 0) $ do
238          -- This is failn1 case, so we print the same final stats and
239          -- exit early
240          printResults nl num_instances 0 [(FailN1, 1)]
241          exitWith ExitSuccess
242
243   let nmlen = Container.maxNameLen nl
244       reqinst = Instance.create "new" (rspecMem ispec) (rspecDsk ispec)
245                 (rspecCpu ispec) "ADMIN_down" (-1) (-1)
246
247   let result = iterateDepth nl il reqinst req_nodes []
248   (ereason, fin_nl, ixes) <- (case result of
249                                 Bad s -> do
250                                   hPrintf stderr "Failure: %s\n" s
251                                   exitWith $ ExitFailure 1
252                                 Ok x -> return x)
253   let allocs = length ixes
254       fin_ixes = reverse ixes
255       ix_namelen = maximum . map (length . Instance.name) $ fin_ixes
256       sreason = reverse $ sortBy (compare `on` snd) ereason
257
258   when (verbose > 1) $
259          hPutStr stderr . unlines $
260          map (\i -> printf "Inst: %*s %-*s %-*s"
261                     ix_namelen (Instance.name i)
262                     nmlen (Container.nameOf fin_nl $ Instance.pNode i)
263                     nmlen (let sdx = Instance.sNode i
264                            in if sdx == Node.noSecondary then ""
265                               else Container.nameOf fin_nl sdx)
266              ) fin_ixes
267
268   when (optShowNodes opts) $
269        do
270          hPutStrLn stderr ""
271          hPutStrLn stderr "Final cluster status:"
272          hPutStrLn stderr $ Cluster.printNodes fin_nl
273
274   printResults fin_nl num_instances allocs sreason