Split the exernal data loader out of CLI.hs
[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     , oShowVer
67     , oShowHelp
68     ]
69
70 data Phase = PInitial | PFinal
71
72 statsData :: [(String, Cluster.CStats -> String)]
73 statsData = [ ("SCORE", printf "%.8f" . Cluster.cs_score)
74             , ("INST_CNT", printf "%d" . Cluster.cs_ninst)
75             , ("MEM_FREE", printf "%d" . Cluster.cs_fmem)
76             , ("MEM_AVAIL", printf "%d" . Cluster.cs_amem)
77             , ("MEM_RESVD",
78                \cs -> printf "%d" (Cluster.cs_fmem cs - Cluster.cs_amem cs))
79             , ("MEM_INST", printf "%d" . Cluster.cs_imem)
80             , ("MEM_OVERHEAD",
81                \cs -> printf "%d" (Cluster.cs_xmem cs + Cluster.cs_nmem cs))
82             , ("MEM_EFF",
83                \cs -> printf "%.8f" (fromIntegral (Cluster.cs_imem cs) /
84                                      Cluster.cs_tmem cs))
85             , ("DSK_FREE", printf "%d" . Cluster.cs_fdsk)
86             , ("DSK_AVAIL", printf "%d ". Cluster.cs_adsk)
87             , ("DSK_RESVD",
88                \cs -> printf "%d" (Cluster.cs_fdsk cs - Cluster.cs_adsk cs))
89             , ("DSK_INST", printf "%d" . Cluster.cs_idsk)
90             , ("DSK_EFF",
91                \cs -> printf "%.8f" (fromIntegral (Cluster.cs_idsk cs) /
92                                     Cluster.cs_tdsk cs))
93             , ("CPU_INST", printf "%d" . Cluster.cs_icpu)
94             , ("CPU_EFF",
95                \cs -> printf "%.8f" (fromIntegral (Cluster.cs_icpu cs) /
96                                      Cluster.cs_tcpu cs))
97             , ("MNODE_MEM_AVAIL", printf "%d" . Cluster.cs_mmem)
98             , ("MNODE_DSK_AVAIL", printf "%d" . Cluster.cs_mdsk)
99             ]
100
101 specData :: [(String, Options -> String)]
102 specData = [ ("MEM", printf "%d" . optIMem)
103            , ("DSK", printf "%d" . optIDsk)
104            , ("CPU", printf "%d" . optIVCPUs)
105            , ("RQN", printf "%d" . optINodes)
106            ]
107
108 clusterData :: [(String, Cluster.CStats -> String)]
109 clusterData = [ ("MEM", printf "%.0f" . Cluster.cs_tmem)
110               , ("DSK", printf "%.0f" . Cluster.cs_tdsk)
111               , ("CPU", printf "%.0f" . Cluster.cs_tcpu)
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.cs_ninst fin_stats) $
149        do
150          hPrintf stderr "ERROR: internal inconsistency, allocated (%d)\
151                         \ != counted (%d)\n" (num_instances + allocs)
152                                  (Cluster.cs_ninst 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
183   (fixed_nl, il, csf) <- loadExternalData opts
184
185   printKeys $ map (\(a, fn) -> ("SPEC_" ++ a, fn opts)) specData
186
187   let num_instances = length $ Container.elems il
188
189   let offline_names = optOffline opts
190       all_nodes = Container.elems fixed_nl
191       all_names = map Node.name all_nodes
192       offline_wrong = filter (flip notElem all_names) offline_names
193       offline_indices = map Node.idx $
194                         filter (\n -> elem (Node.name n) offline_names)
195                                all_nodes
196       req_nodes = optINodes opts
197       m_cpu = optMcpu opts
198       m_dsk = optMdsk opts
199
200   when (length offline_wrong > 0) $ do
201          hPrintf stderr "Error: Wrong node name(s) set as offline: %s\n"
202                      (commaJoin offline_wrong)
203          exitWith $ ExitFailure 1
204
205   when (req_nodes /= 1 && req_nodes /= 2) $ do
206          hPrintf stderr "Error: Invalid required nodes (%d)\n" req_nodes
207          exitWith $ ExitFailure 1
208
209   let nm = Container.map (\n -> if elem (Node.idx n) offline_indices
210                                 then Node.setOffline n True
211                                 else n) fixed_nl
212       nl = Container.map (flip Node.setMdsk m_dsk . flip Node.setMcpu m_cpu)
213            nm
214
215   when (length csf > 0 && verbose > 1) $
216        hPrintf stderr "Note: Stripping common suffix of '%s' from names\n" csf
217
218   when (optShowNodes opts) $
219        do
220          hPutStrLn stderr "Initial cluster status:"
221          hPutStrLn stderr $ Cluster.printNodes nl
222
223   let ini_cv = Cluster.compCV nl
224       ini_stats = Cluster.totalResources nl
225
226   when (verbose > 2) $
227          hPrintf stderr "Initial coefficients: overall %.8f, %s\n"
228                  ini_cv (Cluster.printStats nl)
229
230   printKeys $ map (\(a, fn) -> ("CLUSTER_" ++ a, fn ini_stats)) clusterData
231   printKeys [("CLUSTER_NODES", printf "%d" (length all_nodes))]
232   printKeys $ printStats PInitial ini_stats
233
234   let bad_nodes = fst $ Cluster.computeBadItems nl il
235   when (length bad_nodes > 0) $ do
236          -- This is failn1 case, so we print the same final stats and
237          -- exit early
238          printResults nl num_instances 0 [(FailN1, 1)]
239          exitWith ExitSuccess
240
241   let nmlen = Container.maxNameLen nl
242       newinst = Instance.create "new" (optIMem opts) (optIDsk opts)
243                 (optIVCPUs opts) "ADMIN_down" (-1) (-1)
244
245   let result = iterateDepth nl il newinst req_nodes []
246   (ereason, fin_nl, ixes) <- (case result of
247                                 Bad s -> do
248                                   hPrintf stderr "Failure: %s\n" s
249                                   exitWith $ ExitFailure 1
250                                 Ok x -> return x)
251   let allocs = length ixes
252       fin_ixes = reverse ixes
253       ix_namelen = maximum . map (length . Instance.name) $ fin_ixes
254       sreason = reverse $ sortBy (compare `on` snd) ereason
255
256   when (verbose > 1) $
257          hPutStr stderr . unlines $
258          map (\i -> printf "Inst: %*s %-*s %-*s"
259                     ix_namelen (Instance.name i)
260                     nmlen (Container.nameOf fin_nl $ Instance.pnode i)
261                     nmlen (let sdx = Instance.snode i
262                            in if sdx == Node.noSecondary then ""
263                               else Container.nameOf fin_nl sdx)
264              ) fin_ixes
265
266   when (optShowNodes opts) $
267        do
268          hPutStrLn stderr ""
269          hPutStrLn stderr "Final cluster status:"
270          hPutStrLn stderr $ Cluster.printNodes fin_nl
271
272   printResults fin_nl num_instances allocs sreason