Statistics
| Branch: | Tag: | Revision:

root / hspace.hs @ fca250e9

History | View | Annotate | Download (9.6 kB)

1 e10be8f2 Iustin Pop
{-| Cluster space sizing
2 e10be8f2 Iustin Pop
3 e10be8f2 Iustin Pop
-}
4 e10be8f2 Iustin Pop
5 e10be8f2 Iustin Pop
{-
6 e10be8f2 Iustin Pop
7 e10be8f2 Iustin Pop
Copyright (C) 2009 Google Inc.
8 e10be8f2 Iustin Pop
9 e10be8f2 Iustin Pop
This program is free software; you can redistribute it and/or modify
10 e10be8f2 Iustin Pop
it under the terms of the GNU General Public License as published by
11 e10be8f2 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 e10be8f2 Iustin Pop
(at your option) any later version.
13 e10be8f2 Iustin Pop
14 e10be8f2 Iustin Pop
This program is distributed in the hope that it will be useful, but
15 e10be8f2 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 e10be8f2 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 e10be8f2 Iustin Pop
General Public License for more details.
18 e10be8f2 Iustin Pop
19 e10be8f2 Iustin Pop
You should have received a copy of the GNU General Public License
20 e10be8f2 Iustin Pop
along with this program; if not, write to the Free Software
21 e10be8f2 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 e10be8f2 Iustin Pop
02110-1301, USA.
23 e10be8f2 Iustin Pop
24 e10be8f2 Iustin Pop
-}
25 e10be8f2 Iustin Pop
26 e10be8f2 Iustin Pop
module Main (main) where
27 e10be8f2 Iustin Pop
28 2bbf77cc Iustin Pop
import Data.Char (toUpper)
29 e10be8f2 Iustin Pop
import Data.List
30 e10be8f2 Iustin Pop
import Data.Function
31 e10be8f2 Iustin Pop
import Monad
32 e10be8f2 Iustin Pop
import System
33 e10be8f2 Iustin Pop
import System.IO
34 e10be8f2 Iustin Pop
import qualified System
35 e10be8f2 Iustin Pop
36 2795466b Iustin Pop
import Text.Printf (printf, hPrintf)
37 e10be8f2 Iustin Pop
38 e10be8f2 Iustin Pop
import qualified Ganeti.HTools.Container as Container
39 e10be8f2 Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
40 e10be8f2 Iustin Pop
import qualified Ganeti.HTools.Node as Node
41 e10be8f2 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
42 e10be8f2 Iustin Pop
43 e10be8f2 Iustin Pop
import Ganeti.HTools.Utils
44 f2280553 Iustin Pop
import Ganeti.HTools.Types
45 0427285d Iustin Pop
import Ganeti.HTools.CLI
46 e8f89bb6 Iustin Pop
import Ganeti.HTools.ExtLoader
47 e10be8f2 Iustin Pop
48 e10be8f2 Iustin Pop
-- | Options list and functions
49 0427285d Iustin Pop
options :: [OptType]
50 e10be8f2 Iustin Pop
options =
51 0427285d Iustin Pop
    [ oPrintNodes
52 0427285d Iustin Pop
    , oNodeFile
53 0427285d Iustin Pop
    , oInstFile
54 b2278348 Iustin Pop
    , oNodeSim
55 0427285d Iustin Pop
    , oRapiMaster
56 0427285d Iustin Pop
    , oLuxiSocket
57 0427285d Iustin Pop
    , oVerbose
58 0427285d Iustin Pop
    , oQuiet
59 0427285d Iustin Pop
    , oOfflineNode
60 0427285d Iustin Pop
    , oIMem
61 0427285d Iustin Pop
    , oIDisk
62 0427285d Iustin Pop
    , oIVcpus
63 0427285d Iustin Pop
    , oINodes
64 0427285d Iustin Pop
    , oMaxCpu
65 0427285d Iustin Pop
    , oMinDisk
66 0427285d Iustin Pop
    , oShowVer
67 0427285d Iustin Pop
    , oShowHelp
68 e10be8f2 Iustin Pop
    ]
69 e10be8f2 Iustin Pop
70 2bbf77cc Iustin Pop
data Phase = PInitial | PFinal
71 2bbf77cc Iustin Pop
72 2bbf77cc Iustin Pop
statsData :: [(String, Cluster.CStats -> String)]
73 2bbf77cc Iustin Pop
statsData = [ ("SCORE", printf "%.8f" . Cluster.cs_score)
74 2bbf77cc Iustin Pop
            , ("INST_CNT", printf "%d" . Cluster.cs_ninst)
75 2bbf77cc Iustin Pop
            , ("MEM_FREE", printf "%d" . Cluster.cs_fmem)
76 2bbf77cc Iustin Pop
            , ("MEM_AVAIL", printf "%d" . Cluster.cs_amem)
77 2bbf77cc Iustin Pop
            , ("MEM_RESVD",
78 2bbf77cc Iustin Pop
               \cs -> printf "%d" (Cluster.cs_fmem cs - Cluster.cs_amem cs))
79 2bbf77cc Iustin Pop
            , ("MEM_INST", printf "%d" . Cluster.cs_imem)
80 2bbf77cc Iustin Pop
            , ("MEM_OVERHEAD",
81 2bbf77cc Iustin Pop
               \cs -> printf "%d" (Cluster.cs_xmem cs + Cluster.cs_nmem cs))
82 2bbf77cc Iustin Pop
            , ("MEM_EFF",
83 2bbf77cc Iustin Pop
               \cs -> printf "%.8f" (fromIntegral (Cluster.cs_imem cs) /
84 2bbf77cc Iustin Pop
                                     Cluster.cs_tmem cs))
85 2bbf77cc Iustin Pop
            , ("DSK_FREE", printf "%d" . Cluster.cs_fdsk)
86 2bbf77cc Iustin Pop
            , ("DSK_AVAIL", printf "%d ". Cluster.cs_adsk)
87 2bbf77cc Iustin Pop
            , ("DSK_RESVD",
88 2bbf77cc Iustin Pop
               \cs -> printf "%d" (Cluster.cs_fdsk cs - Cluster.cs_adsk cs))
89 2bbf77cc Iustin Pop
            , ("DSK_INST", printf "%d" . Cluster.cs_idsk)
90 2bbf77cc Iustin Pop
            , ("DSK_EFF",
91 2bbf77cc Iustin Pop
               \cs -> printf "%.8f" (fromIntegral (Cluster.cs_idsk cs) /
92 2bbf77cc Iustin Pop
                                    Cluster.cs_tdsk cs))
93 2bbf77cc Iustin Pop
            , ("CPU_INST", printf "%d" . Cluster.cs_icpu)
94 2bbf77cc Iustin Pop
            , ("CPU_EFF",
95 2bbf77cc Iustin Pop
               \cs -> printf "%.8f" (fromIntegral (Cluster.cs_icpu cs) /
96 2bbf77cc Iustin Pop
                                     Cluster.cs_tcpu cs))
97 2bbf77cc Iustin Pop
            , ("MNODE_MEM_AVAIL", printf "%d" . Cluster.cs_mmem)
98 2bbf77cc Iustin Pop
            , ("MNODE_DSK_AVAIL", printf "%d" . Cluster.cs_mdsk)
99 2bbf77cc Iustin Pop
            ]
100 2bbf77cc Iustin Pop
101 2bbf77cc Iustin Pop
specData :: [(String, Options -> String)]
102 2bbf77cc Iustin Pop
specData = [ ("MEM", printf "%d" . optIMem)
103 2bbf77cc Iustin Pop
           , ("DSK", printf "%d" . optIDsk)
104 2bbf77cc Iustin Pop
           , ("CPU", printf "%d" . optIVCPUs)
105 2bbf77cc Iustin Pop
           , ("RQN", printf "%d" . optINodes)
106 2bbf77cc Iustin Pop
           ]
107 2bbf77cc Iustin Pop
108 2bbf77cc Iustin Pop
clusterData :: [(String, Cluster.CStats -> String)]
109 2bbf77cc Iustin Pop
clusterData = [ ("MEM", printf "%.0f" . Cluster.cs_tmem)
110 2bbf77cc Iustin Pop
              , ("DSK", printf "%.0f" . Cluster.cs_tdsk)
111 2bbf77cc Iustin Pop
              , ("CPU", printf "%.0f" . Cluster.cs_tcpu)
112 2bbf77cc Iustin Pop
              ]
113 2bbf77cc Iustin Pop
114 58631b72 Iustin Pop
-- | Recursively place instances on the cluster until we're out of space
115 e10be8f2 Iustin Pop
iterateDepth :: Node.List
116 e10be8f2 Iustin Pop
             -> Instance.List
117 e10be8f2 Iustin Pop
             -> Instance.Instance
118 e10be8f2 Iustin Pop
             -> Int
119 9dcec001 Iustin Pop
             -> [Instance.Instance]
120 31e7ac17 Iustin Pop
             -> Result (FailStats, Node.List, [Instance.Instance])
121 9dcec001 Iustin Pop
iterateDepth nl il newinst nreq ixes =
122 9dcec001 Iustin Pop
      let depth = length ixes
123 9f6dcdea Iustin Pop
          newname = printf "new-%d" depth::String
124 9f6dcdea Iustin Pop
          newidx = length (Container.elems il) + depth
125 e10be8f2 Iustin Pop
          newi2 = Instance.setIdx (Instance.setName newinst newname) newidx
126 31e7ac17 Iustin Pop
      in case Cluster.tryAlloc nl il newi2 nreq of
127 31e7ac17 Iustin Pop
           Bad s -> Bad s
128 31e7ac17 Iustin Pop
           Ok (errs, _, sols3) ->
129 478df686 Iustin Pop
               case sols3 of
130 31e7ac17 Iustin Pop
                 Nothing -> Ok (Cluster.collapseFailures errs, nl, ixes)
131 478df686 Iustin Pop
                 Just (_, (xnl, xi, _)) ->
132 478df686 Iustin Pop
                     iterateDepth xnl il newinst nreq $! (xi:ixes)
133 e10be8f2 Iustin Pop
134 58631b72 Iustin Pop
-- | Function to print stats for a given phase
135 2bbf77cc Iustin Pop
printStats :: Phase -> Cluster.CStats -> [(String, String)]
136 2bbf77cc Iustin Pop
printStats ph cs =
137 2bbf77cc Iustin Pop
  map (\(s, fn) -> (printf "%s_%s" kind s, fn cs)) statsData
138 2bbf77cc Iustin Pop
  where kind = case ph of
139 2bbf77cc Iustin Pop
                 PInitial -> "INI"
140 2bbf77cc Iustin Pop
                 PFinal -> "FIN"
141 e10be8f2 Iustin Pop
142 dca7f396 Iustin Pop
-- | Print final stats and related metrics
143 dca7f396 Iustin Pop
printResults :: Node.List -> Int -> Int -> [(FailMode, Int)] -> IO ()
144 dca7f396 Iustin Pop
printResults fin_nl num_instances allocs sreason = do
145 dca7f396 Iustin Pop
  let fin_stats = Cluster.totalResources fin_nl
146 dca7f396 Iustin Pop
      fin_instances = num_instances + allocs
147 dca7f396 Iustin Pop
148 de4ac2c2 Iustin Pop
  when (num_instances + allocs /= Cluster.cs_ninst fin_stats) $
149 de4ac2c2 Iustin Pop
       do
150 de4ac2c2 Iustin Pop
         hPrintf stderr "ERROR: internal inconsistency, allocated (%d)\
151 de4ac2c2 Iustin Pop
                        \ != counted (%d)\n" (num_instances + allocs)
152 de4ac2c2 Iustin Pop
                                 (Cluster.cs_ninst fin_stats)
153 de4ac2c2 Iustin Pop
         exitWith $ ExitFailure 1
154 de4ac2c2 Iustin Pop
155 2bbf77cc Iustin Pop
  printKeys $ printStats PFinal fin_stats
156 2bbf77cc Iustin Pop
  printKeys [ ("ALLOC_USAGE", printf "%.8f"
157 2bbf77cc Iustin Pop
                                ((fromIntegral num_instances::Double) /
158 2bbf77cc Iustin Pop
                                 fromIntegral fin_instances))
159 31e7ac17 Iustin Pop
            , ("ALLOC_INSTANCES", printf "%d" allocs)
160 2bbf77cc Iustin Pop
            , ("ALLOC_FAIL_REASON", map toUpper . show . fst $ head sreason)
161 2bbf77cc Iustin Pop
            ]
162 2bbf77cc Iustin Pop
  printKeys $ map (\(x, y) -> (printf "ALLOC_%s_CNT" (show x),
163 2bbf77cc Iustin Pop
                               printf "%d" y)) sreason
164 2bbf77cc Iustin Pop
  -- this should be the final entry
165 2bbf77cc Iustin Pop
  printKeys [("OK", "1")]
166 2bbf77cc Iustin Pop
167 2bbf77cc Iustin Pop
-- | Format a list of key/values as a shell fragment
168 2bbf77cc Iustin Pop
printKeys :: [(String, String)] -> IO ()
169 2bbf77cc Iustin Pop
printKeys = mapM_ (\(k, v) -> printf "HTS_%s=%s\n" (map toUpper k) v)
170 dca7f396 Iustin Pop
171 e10be8f2 Iustin Pop
-- | Main function.
172 e10be8f2 Iustin Pop
main :: IO ()
173 e10be8f2 Iustin Pop
main = do
174 e10be8f2 Iustin Pop
  cmd_args <- System.getArgs
175 0427285d Iustin Pop
  (opts, args) <- parseOpts cmd_args "hspace" options
176 e10be8f2 Iustin Pop
177 e10be8f2 Iustin Pop
  unless (null args) $ do
178 e10be8f2 Iustin Pop
         hPutStrLn stderr "Error: this program doesn't take any arguments."
179 e10be8f2 Iustin Pop
         exitWith $ ExitFailure 1
180 e10be8f2 Iustin Pop
181 2795466b Iustin Pop
  let verbose = optVerbose opts
182 2795466b Iustin Pop
183 0427285d Iustin Pop
  (fixed_nl, il, csf) <- loadExternalData opts
184 2795466b Iustin Pop
185 2bbf77cc Iustin Pop
  printKeys $ map (\(a, fn) -> ("SPEC_" ++ a, fn opts)) specData
186 7e74e7db Iustin Pop
187 9dcec001 Iustin Pop
  let num_instances = length $ Container.elems il
188 e10be8f2 Iustin Pop
189 e10be8f2 Iustin Pop
  let offline_names = optOffline opts
190 e10be8f2 Iustin Pop
      all_nodes = Container.elems fixed_nl
191 e10be8f2 Iustin Pop
      all_names = map Node.name all_nodes
192 9f6dcdea Iustin Pop
      offline_wrong = filter (flip notElem all_names) offline_names
193 e10be8f2 Iustin Pop
      offline_indices = map Node.idx $
194 e10be8f2 Iustin Pop
                        filter (\n -> elem (Node.name n) offline_names)
195 e10be8f2 Iustin Pop
                               all_nodes
196 9abe9caf Iustin Pop
      req_nodes = optINodes opts
197 83a91400 Iustin Pop
      m_cpu = optMcpu opts
198 83a91400 Iustin Pop
      m_dsk = optMdsk opts
199 e10be8f2 Iustin Pop
200 e10be8f2 Iustin Pop
  when (length offline_wrong > 0) $ do
201 2795466b Iustin Pop
         hPrintf stderr "Error: Wrong node name(s) set as offline: %s\n"
202 2795466b Iustin Pop
                     (commaJoin offline_wrong)
203 e10be8f2 Iustin Pop
         exitWith $ ExitFailure 1
204 e10be8f2 Iustin Pop
205 9abe9caf Iustin Pop
  when (req_nodes /= 1 && req_nodes /= 2) $ do
206 2795466b Iustin Pop
         hPrintf stderr "Error: Invalid required nodes (%d)\n" req_nodes
207 9abe9caf Iustin Pop
         exitWith $ ExitFailure 1
208 9abe9caf Iustin Pop
209 83a91400 Iustin Pop
  let nm = Container.map (\n -> if elem (Node.idx n) offline_indices
210 e10be8f2 Iustin Pop
                                then Node.setOffline n True
211 e10be8f2 Iustin Pop
                                else n) fixed_nl
212 83a91400 Iustin Pop
      nl = Container.map (flip Node.setMdsk m_dsk . flip Node.setMcpu m_cpu)
213 83a91400 Iustin Pop
           nm
214 e10be8f2 Iustin Pop
215 9f6dcdea Iustin Pop
  when (length csf > 0 && verbose > 1) $
216 2bbf77cc Iustin Pop
       hPrintf stderr "Note: Stripping common suffix of '%s' from names\n" csf
217 e10be8f2 Iustin Pop
218 e10be8f2 Iustin Pop
  when (optShowNodes opts) $
219 e10be8f2 Iustin Pop
       do
220 2bbf77cc Iustin Pop
         hPutStrLn stderr "Initial cluster status:"
221 2bbf77cc Iustin Pop
         hPutStrLn stderr $ Cluster.printNodes nl
222 e10be8f2 Iustin Pop
223 e10be8f2 Iustin Pop
  let ini_cv = Cluster.compCV nl
224 621de5b7 Iustin Pop
      ini_stats = Cluster.totalResources nl
225 e10be8f2 Iustin Pop
226 2485487d Iustin Pop
  when (verbose > 2) $
227 2bbf77cc Iustin Pop
         hPrintf stderr "Initial coefficients: overall %.8f, %s\n"
228 2bbf77cc Iustin Pop
                 ini_cv (Cluster.printStats nl)
229 de4ac2c2 Iustin Pop
230 2bbf77cc Iustin Pop
  printKeys $ map (\(a, fn) -> ("CLUSTER_" ++ a, fn ini_stats)) clusterData
231 2bbf77cc Iustin Pop
  printKeys [("CLUSTER_NODES", printf "%d" (length all_nodes))]
232 2bbf77cc Iustin Pop
  printKeys $ printStats PInitial ini_stats
233 e10be8f2 Iustin Pop
234 dca7f396 Iustin Pop
  let bad_nodes = fst $ Cluster.computeBadItems nl il
235 dca7f396 Iustin Pop
  when (length bad_nodes > 0) $ do
236 dca7f396 Iustin Pop
         -- This is failn1 case, so we print the same final stats and
237 dca7f396 Iustin Pop
         -- exit early
238 dca7f396 Iustin Pop
         printResults nl num_instances 0 [(FailN1, 1)]
239 dca7f396 Iustin Pop
         exitWith ExitSuccess
240 dca7f396 Iustin Pop
241 9dcec001 Iustin Pop
  let nmlen = Container.maxNameLen nl
242 e10be8f2 Iustin Pop
      newinst = Instance.create "new" (optIMem opts) (optIDsk opts)
243 d752eb39 Iustin Pop
                (optIVCPUs opts) "ADMIN_down" (-1) (-1)
244 e10be8f2 Iustin Pop
245 31e7ac17 Iustin Pop
  let result = iterateDepth nl il newinst req_nodes []
246 31e7ac17 Iustin Pop
  (ereason, fin_nl, ixes) <- (case result of
247 31e7ac17 Iustin Pop
                                Bad s -> do
248 31e7ac17 Iustin Pop
                                  hPrintf stderr "Failure: %s\n" s
249 31e7ac17 Iustin Pop
                                  exitWith $ ExitFailure 1
250 31e7ac17 Iustin Pop
                                Ok x -> return x)
251 31e7ac17 Iustin Pop
  let allocs = length ixes
252 9dcec001 Iustin Pop
      fin_ixes = reverse ixes
253 9dcec001 Iustin Pop
      ix_namelen = maximum . map (length . Instance.name) $ fin_ixes
254 44763b51 Iustin Pop
      sreason = reverse $ sortBy (compare `on` snd) ereason
255 9dcec001 Iustin Pop
256 9f6dcdea Iustin Pop
  when (verbose > 1) $
257 2bbf77cc Iustin Pop
         hPutStr stderr . unlines $
258 2bbf77cc Iustin Pop
         map (\i -> printf "Inst: %*s %-*s %-*s"
259 2bbf77cc Iustin Pop
                    ix_namelen (Instance.name i)
260 2bbf77cc Iustin Pop
                    nmlen (Container.nameOf fin_nl $ Instance.pnode i)
261 2bbf77cc Iustin Pop
                    nmlen (let sdx = Instance.snode i
262 2bbf77cc Iustin Pop
                           in if sdx == Node.noSecondary then ""
263 2bbf77cc Iustin Pop
                              else Container.nameOf fin_nl sdx)
264 2bbf77cc Iustin Pop
             ) fin_ixes
265 e10be8f2 Iustin Pop
266 e10be8f2 Iustin Pop
  when (optShowNodes opts) $
267 e10be8f2 Iustin Pop
       do
268 2bbf77cc Iustin Pop
         hPutStrLn stderr ""
269 2bbf77cc Iustin Pop
         hPutStrLn stderr "Final cluster status:"
270 2bbf77cc Iustin Pop
         hPutStrLn stderr $ Cluster.printNodes fin_nl
271 2bbf77cc Iustin Pop
272 2bbf77cc Iustin Pop
  printResults fin_nl num_instances allocs sreason