Statistics
| Branch: | Tag: | Revision:

root / hspace.hs @ b2278348

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