Statistics
| Branch: | Tag: | Revision:

root / hspace.hs @ 9739b6b8

History | View | Annotate | Download (12.3 kB)

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, isAlphaNum)
29
import Data.List
30
import Data.Function
31
import Data.Maybe (isJust, fromJust)
32
import Monad
33
import System
34
import System.IO
35
import qualified System
36

    
37
import Text.Printf (printf, hPrintf)
38

    
39
import qualified Ganeti.HTools.Container as Container
40
import qualified Ganeti.HTools.Cluster as Cluster
41
import qualified Ganeti.HTools.Node as Node
42
import qualified Ganeti.HTools.Instance as Instance
43

    
44
import Ganeti.HTools.Utils
45
import Ganeti.HTools.Types
46
import Ganeti.HTools.CLI
47
import Ganeti.HTools.ExtLoader
48

    
49
-- | Options list and functions
50
options :: [OptType]
51
options =
52
    [ oPrintNodes
53
    , oNodeFile
54
    , oInstFile
55
    , oNodeSim
56
    , oRapiMaster
57
    , oLuxiSocket
58
    , oVerbose
59
    , oQuiet
60
    , oOfflineNode
61
    , oIMem
62
    , oIDisk
63
    , oIVcpus
64
    , oINodes
65
    , oMaxCpu
66
    , oMinDisk
67
    , oTieredSpec
68
    , oShowVer
69
    , oShowHelp
70
    ]
71

    
72
-- | The allocation phase we're in (initial, after tiered allocs, or
73
-- after regular allocation).
74
data Phase = PInitial
75
           | PFinal
76
           | PTiered
77

    
78
statsData :: [(String, Cluster.CStats -> String)]
79
statsData = [ ("SCORE", printf "%.8f" . Cluster.csScore)
80
            , ("INST_CNT", printf "%d" . Cluster.csNinst)
81
            , ("MEM_FREE", printf "%d" . Cluster.csFmem)
82
            , ("MEM_AVAIL", printf "%d" . Cluster.csAmem)
83
            , ("MEM_RESVD",
84
               \cs -> printf "%d" (Cluster.csFmem cs - Cluster.csAmem cs))
85
            , ("MEM_INST", printf "%d" . Cluster.csImem)
86
            , ("MEM_OVERHEAD",
87
               \cs -> printf "%d" (Cluster.csXmem cs + Cluster.csNmem cs))
88
            , ("MEM_EFF",
89
               \cs -> printf "%.8f" (fromIntegral (Cluster.csImem cs) /
90
                                     Cluster.csTmem cs))
91
            , ("DSK_FREE", printf "%d" . Cluster.csFdsk)
92
            , ("DSK_AVAIL", printf "%d". Cluster.csAdsk)
93
            , ("DSK_RESVD",
94
               \cs -> printf "%d" (Cluster.csFdsk cs - Cluster.csAdsk cs))
95
            , ("DSK_INST", printf "%d" . Cluster.csIdsk)
96
            , ("DSK_EFF",
97
               \cs -> printf "%.8f" (fromIntegral (Cluster.csIdsk cs) /
98
                                    Cluster.csTdsk cs))
99
            , ("CPU_INST", printf "%d" . Cluster.csIcpu)
100
            , ("CPU_EFF",
101
               \cs -> printf "%.8f" (fromIntegral (Cluster.csIcpu cs) /
102
                                     Cluster.csTcpu cs))
103
            , ("MNODE_MEM_AVAIL", printf "%d" . Cluster.csMmem)
104
            , ("MNODE_DSK_AVAIL", printf "%d" . Cluster.csMdsk)
105
            ]
106

    
107
specData :: [(String, RSpec -> String)]
108
specData = [ ("MEM", printf "%d" . rspecMem)
109
           , ("DSK", printf "%d" . rspecDsk)
110
           , ("CPU", printf "%d" . rspecCpu)
111
           ]
112

    
113
clusterData :: [(String, Cluster.CStats -> String)]
114
clusterData = [ ("MEM", printf "%.0f" . Cluster.csTmem)
115
              , ("DSK", printf "%.0f" . Cluster.csTdsk)
116
              , ("CPU", printf "%.0f" . Cluster.csTcpu)
117
              ]
118

    
119
-- | Recursively place instances on the cluster until we're out of space
120
iterateDepth :: Node.List
121
             -> Instance.List
122
             -> Instance.Instance
123
             -> Int
124
             -> [Instance.Instance]
125
             -> Result (FailStats, Node.List, [Instance.Instance])
126
iterateDepth nl il newinst nreq ixes =
127
      let depth = length ixes
128
          newname = printf "new-%d" depth::String
129
          newidx = length (Container.elems il) + depth
130
          newi2 = Instance.setIdx (Instance.setName newinst newname) newidx
131
      in case Cluster.tryAlloc nl il newi2 nreq of
132
           Bad s -> Bad s
133
           Ok (errs, _, sols3) ->
134
               case sols3 of
135
                 Nothing -> Ok (Cluster.collapseFailures errs, nl, ixes)
136
                 Just (_, (xnl, xi, _)) ->
137
                     iterateDepth xnl il newinst nreq $! (xi:ixes)
138

    
139
tieredAlloc :: Node.List
140
            -> Instance.List
141
            -> Instance.Instance
142
            -> Int
143
            -> [Instance.Instance]
144
            -> Result (FailStats, Node.List, [Instance.Instance])
145
tieredAlloc nl il newinst nreq ixes =
146
    case iterateDepth nl il newinst nreq ixes of
147
      Bad s -> Bad s
148
      Ok (errs, nl', ixes') ->
149
          case Instance.shrinkByType newinst . fst . last $
150
               sortBy (compare `on` snd) errs of
151
            Bad _ -> Ok (errs, nl', ixes')
152
            Ok newinst' ->
153
                tieredAlloc nl' il newinst' nreq ixes'
154

    
155

    
156
-- | Function to print stats for a given phase
157
printStats :: Phase -> Cluster.CStats -> [(String, String)]
158
printStats ph cs =
159
  map (\(s, fn) -> (printf "%s_%s" kind s, fn cs)) statsData
160
  where kind = case ph of
161
                 PInitial -> "INI"
162
                 PFinal -> "FIN"
163
                 PTiered -> "TRL"
164

    
165
-- | Print final stats and related metrics
166
printResults :: Node.List -> Int -> Int -> [(FailMode, Int)] -> IO ()
167
printResults fin_nl num_instances allocs sreason = do
168
  let fin_stats = Cluster.totalResources fin_nl
169
      fin_instances = num_instances + allocs
170

    
171
  when (num_instances + allocs /= Cluster.csNinst fin_stats) $
172
       do
173
         hPrintf stderr "ERROR: internal inconsistency, allocated (%d)\
174
                        \ != counted (%d)\n" (num_instances + allocs)
175
                                 (Cluster.csNinst fin_stats)
176
         exitWith $ ExitFailure 1
177

    
178
  printKeys $ printStats PFinal fin_stats
179
  printKeys [ ("ALLOC_USAGE", printf "%.8f"
180
                                ((fromIntegral num_instances::Double) /
181
                                 fromIntegral fin_instances))
182
            , ("ALLOC_INSTANCES", printf "%d" allocs)
183
            , ("ALLOC_FAIL_REASON", map toUpper . show . fst $ head sreason)
184
            ]
185
  printKeys $ map (\(x, y) -> (printf "ALLOC_%s_CNT" (show x),
186
                               printf "%d" y)) sreason
187
  -- this should be the final entry
188
  printKeys [("OK", "1")]
189

    
190
-- | Ensure a value is quoted if needed
191
ensureQuoted :: String -> String
192
ensureQuoted v = if not (all (\c -> (isAlphaNum c || c == '.')) v)
193
                 then '\'':v ++ "'"
194
                 else v
195

    
196
-- | Format a list of key/values as a shell fragment
197
printKeys :: [(String, String)] -> IO ()
198
printKeys = mapM_ (\(k, v) ->
199
                   printf "HTS_%s=%s\n" (map toUpper k) (ensureQuoted v))
200

    
201
printInstance :: Node.List -> Instance.Instance -> [String]
202
printInstance nl i = [ Instance.name i
203
                     , (Container.nameOf nl $ Instance.pNode i)
204
                     , (let sdx = Instance.sNode i
205
                        in if sdx == Node.noSecondary then ""
206
                           else Container.nameOf nl sdx)
207
                     , show (Instance.mem i)
208
                     , show (Instance.dsk i)
209
                     , show (Instance.vcpus i)
210
                     ]
211

    
212
-- | Main function.
213
main :: IO ()
214
main = do
215
  cmd_args <- System.getArgs
216
  (opts, args) <- parseOpts cmd_args "hspace" options
217

    
218
  unless (null args) $ do
219
         hPutStrLn stderr "Error: this program doesn't take any arguments."
220
         exitWith $ ExitFailure 1
221

    
222
  let verbose = optVerbose opts
223
      ispec = optISpec opts
224
      shownodes = optShowNodes opts
225

    
226
  (fixed_nl, il, csf) <- loadExternalData opts
227

    
228
  printKeys $ map (\(a, fn) -> ("SPEC_" ++ a, fn ispec)) specData
229
  printKeys [ ("SPEC_RQN", printf "%d" (optINodes opts)) ]
230

    
231
  let num_instances = length $ Container.elems il
232

    
233
  let offline_names = optOffline opts
234
      all_nodes = Container.elems fixed_nl
235
      all_names = map Node.name all_nodes
236
      offline_wrong = filter (flip notElem all_names) offline_names
237
      offline_indices = map Node.idx $
238
                        filter (\n -> elem (Node.name n) offline_names)
239
                               all_nodes
240
      req_nodes = optINodes opts
241
      m_cpu = optMcpu opts
242
      m_dsk = optMdsk opts
243

    
244
  when (length offline_wrong > 0) $ do
245
         hPrintf stderr "Error: Wrong node name(s) set as offline: %s\n"
246
                     (commaJoin offline_wrong)
247
         exitWith $ ExitFailure 1
248

    
249
  when (req_nodes /= 1 && req_nodes /= 2) $ do
250
         hPrintf stderr "Error: Invalid required nodes (%d)\n" req_nodes
251
         exitWith $ ExitFailure 1
252

    
253
  let nm = Container.map (\n -> if elem (Node.idx n) offline_indices
254
                                then Node.setOffline n True
255
                                else n) fixed_nl
256
      nl = Container.map (flip Node.setMdsk m_dsk . flip Node.setMcpu m_cpu)
257
           nm
258

    
259
  when (length csf > 0 && verbose > 1) $
260
       hPrintf stderr "Note: Stripping common suffix of '%s' from names\n" csf
261

    
262
  when (isJust shownodes) $
263
       do
264
         hPutStrLn stderr "Initial cluster status:"
265
         hPutStrLn stderr $ Cluster.printNodes nl (fromJust shownodes)
266

    
267
  let ini_cv = Cluster.compCV nl
268
      ini_stats = Cluster.totalResources nl
269

    
270
  when (verbose > 2) $
271
         hPrintf stderr "Initial coefficients: overall %.8f, %s\n"
272
                 ini_cv (Cluster.printStats nl)
273

    
274
  printKeys $ map (\(a, fn) -> ("CLUSTER_" ++ a, fn ini_stats)) clusterData
275
  printKeys [("CLUSTER_NODES", printf "%d" (length all_nodes))]
276
  printKeys $ printStats PInitial ini_stats
277

    
278
  let bad_nodes = fst $ Cluster.computeBadItems nl il
279
  when (length bad_nodes > 0) $ do
280
         -- This is failn1 case, so we print the same final stats and
281
         -- exit early
282
         printResults nl num_instances 0 [(FailN1, 1)]
283
         exitWith ExitSuccess
284

    
285
  -- utility functions
286
  let iofspec spx = Instance.create "new" (rspecMem spx) (rspecDsk spx)
287
                    (rspecCpu spx) "ADMIN_down" (-1) (-1)
288
      exitifbad val = (case val of
289
                         Bad s -> do
290
                           hPrintf stderr "Failure: %s\n" s
291
                           exitWith $ ExitFailure 1
292
                         Ok x -> return x)
293

    
294

    
295
  let reqinst = iofspec ispec
296

    
297
  -- Run the tiered allocation, if enabled
298

    
299
  (case optTieredSpec opts of
300
     Nothing -> return ()
301
     Just tspec -> do
302
       let tresu = tieredAlloc nl il (iofspec tspec) req_nodes []
303
       (_, trl_nl, trl_ixes) <- exitifbad tresu
304
       let fin_trl_ixes = reverse trl_ixes
305
           ix_byspec = groupBy ((==) `on` Instance.specOf) fin_trl_ixes
306
           spec_map = map (\ixs -> (Instance.specOf $ head ixs, length ixs))
307
                      ix_byspec::[(RSpec, Int)]
308
           spec_map' = map (\(spec, cnt) ->
309
                                printf "%d,%d,%d=%d" (rspecMem spec)
310
                                       (rspecDsk spec) (rspecCpu spec) cnt)
311
                       spec_map::[String]
312

    
313
       when (verbose > 1) $ do
314
         hPutStrLn stderr "Tiered allocation map"
315
         hPutStr stderr . unlines . map ((:) ' ' .  intercalate " ") $
316
                 formatTable (map (printInstance trl_nl) fin_trl_ixes)
317
                                 [False, False, False, True, True, True]
318

    
319
       when (isJust shownodes) $ do
320
         hPutStrLn stderr ""
321
         hPutStrLn stderr "Tiered allocation status:"
322
         hPutStrLn stderr $ Cluster.printNodes trl_nl (fromJust shownodes)
323

    
324
       printKeys $ printStats PTiered (Cluster.totalResources trl_nl)
325
       printKeys [("TSPEC", intercalate " " spec_map')])
326

    
327
  -- Run the standard (avg-mode) allocation
328

    
329
  let result = iterateDepth nl il reqinst req_nodes []
330
  (ereason, fin_nl, ixes) <- exitifbad result
331

    
332
  let allocs = length ixes
333
      fin_ixes = reverse ixes
334
      sreason = reverse $ sortBy (compare `on` snd) ereason
335

    
336
  when (verbose > 1) $ do
337
         hPutStrLn stderr "Instance map"
338
         hPutStr stderr . unlines . map ((:) ' ' .  intercalate " ") $
339
                 formatTable (map (printInstance fin_nl) fin_ixes)
340
                                 [False, False, False, True, True, True]
341
  when (isJust shownodes) $
342
       do
343
         hPutStrLn stderr ""
344
         hPutStrLn stderr "Final cluster status:"
345
         hPutStrLn stderr $ Cluster.printNodes fin_nl (fromJust shownodes)
346

    
347
  printResults fin_nl num_instances allocs sreason