Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Program / Hspace.hs @ d66aa238

History | View | Annotate | Download (16.7 kB)

1
{-| Cluster space sizing
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2009, 2010, 2011, 2012 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 Ganeti.HTools.Program.Hspace
27
  (main
28
  , options
29
  , arguments
30
  ) where
31

    
32
import Control.Monad
33
import Data.Char (toUpper, toLower)
34
import Data.Function (on)
35
import Data.List
36
import Data.Maybe (fromMaybe)
37
import Data.Ord (comparing)
38
import System.IO
39

    
40
import Text.Printf (printf, hPrintf)
41

    
42
import qualified Ganeti.HTools.Container as Container
43
import qualified Ganeti.HTools.Cluster as Cluster
44
import qualified Ganeti.HTools.Node as Node
45
import qualified Ganeti.HTools.Instance as Instance
46

    
47
import Ganeti.BasicTypes
48
import Ganeti.Common
49
import Ganeti.HTools.Types
50
import Ganeti.HTools.CLI
51
import Ganeti.HTools.ExtLoader
52
import Ganeti.HTools.Loader
53
import Ganeti.Utils
54

    
55
-- | Options list and functions.
56
options :: IO [OptType]
57
options =
58
  return
59
    [ oPrintNodes
60
    , oDataFile
61
    , oDiskTemplate
62
    , oSpindleUse
63
    , oNodeSim
64
    , oRapiMaster
65
    , oLuxiSocket
66
    , oIAllocSrc
67
    , oVerbose
68
    , oQuiet
69
    , oOfflineNode
70
    , oMachineReadable
71
    , oMaxCpu
72
    , oMaxSolLength
73
    , oMinDisk
74
    , oStdSpec
75
    , oTieredSpec
76
    , oSaveCluster
77
    ]
78

    
79
-- | The list of arguments supported by the program.
80
arguments :: [ArgCompletion]
81
arguments = []
82

    
83
-- | The allocation phase we're in (initial, after tiered allocs, or
84
-- after regular allocation).
85
data Phase = PInitial
86
           | PFinal
87
           | PTiered
88

    
89
-- | The kind of instance spec we print.
90
data SpecType = SpecNormal
91
              | SpecTiered
92

    
93
-- | Prefix for machine readable names
94
htsPrefix :: String
95
htsPrefix = "HTS"
96

    
97
-- | What we prefix a spec with.
98
specPrefix :: SpecType -> String
99
specPrefix SpecNormal = "SPEC"
100
specPrefix SpecTiered = "TSPEC_INI"
101

    
102
-- | The description of a spec.
103
specDescription :: SpecType -> String
104
specDescription SpecNormal = "Standard (fixed-size)"
105
specDescription SpecTiered = "Tiered (initial size)"
106

    
107
-- | Efficiency generic function.
108
effFn :: (Cluster.CStats -> Integer)
109
      -> (Cluster.CStats -> Double)
110
      -> Cluster.CStats -> Double
111
effFn fi ft cs = fromIntegral (fi cs) / ft cs
112

    
113
-- | Memory efficiency.
114
memEff :: Cluster.CStats -> Double
115
memEff = effFn Cluster.csImem Cluster.csTmem
116

    
117
-- | Disk efficiency.
118
dskEff :: Cluster.CStats -> Double
119
dskEff = effFn Cluster.csIdsk Cluster.csTdsk
120

    
121
-- | Cpu efficiency.
122
cpuEff :: Cluster.CStats -> Double
123
cpuEff = effFn Cluster.csIcpu (fromIntegral . Cluster.csVcpu)
124

    
125
-- | Holds data for converting a 'Cluster.CStats' structure into
126
-- detailed statistics.
127
statsData :: [(String, Cluster.CStats -> String)]
128
statsData = [ ("SCORE", printf "%.8f" . Cluster.csScore)
129
            , ("INST_CNT", printf "%d" . Cluster.csNinst)
130
            , ("MEM_FREE", printf "%d" . Cluster.csFmem)
131
            , ("MEM_AVAIL", printf "%d" . Cluster.csAmem)
132
            , ("MEM_RESVD",
133
               \cs -> printf "%d" (Cluster.csFmem cs - Cluster.csAmem cs))
134
            , ("MEM_INST", printf "%d" . Cluster.csImem)
135
            , ("MEM_OVERHEAD",
136
               \cs -> printf "%d" (Cluster.csXmem cs + Cluster.csNmem cs))
137
            , ("MEM_EFF", printf "%.8f" . memEff)
138
            , ("DSK_FREE", printf "%d" . Cluster.csFdsk)
139
            , ("DSK_AVAIL", printf "%d". Cluster.csAdsk)
140
            , ("DSK_RESVD",
141
               \cs -> printf "%d" (Cluster.csFdsk cs - Cluster.csAdsk cs))
142
            , ("DSK_INST", printf "%d" . Cluster.csIdsk)
143
            , ("DSK_EFF", printf "%.8f" . dskEff)
144
            , ("CPU_INST", printf "%d" . Cluster.csIcpu)
145
            , ("CPU_EFF", printf "%.8f" . cpuEff)
146
            , ("MNODE_MEM_AVAIL", printf "%d" . Cluster.csMmem)
147
            , ("MNODE_DSK_AVAIL", printf "%d" . Cluster.csMdsk)
148
            ]
149

    
150
-- | List holding 'RSpec' formatting information.
151
specData :: [(String, RSpec -> String)]
152
specData = [ ("MEM", printf "%d" . rspecMem)
153
           , ("DSK", printf "%d" . rspecDsk)
154
           , ("CPU", printf "%d" . rspecCpu)
155
           ]
156

    
157
-- | List holding 'Cluster.CStats' formatting information.
158
clusterData :: [(String, Cluster.CStats -> String)]
159
clusterData = [ ("MEM", printf "%.0f" . Cluster.csTmem)
160
              , ("DSK", printf "%.0f" . Cluster.csTdsk)
161
              , ("CPU", printf "%.0f" . Cluster.csTcpu)
162
              , ("VCPU", printf "%d" . Cluster.csVcpu)
163
              ]
164

    
165
-- | Function to print stats for a given phase.
166
printStats :: Phase -> Cluster.CStats -> [(String, String)]
167
printStats ph cs =
168
  map (\(s, fn) -> (printf "%s_%s" kind s, fn cs)) statsData
169
  where kind = case ph of
170
                 PInitial -> "INI"
171
                 PFinal -> "FIN"
172
                 PTiered -> "TRL"
173

    
174
-- | Print failure reason and scores
175
printFRScores :: Node.List -> Node.List -> [(FailMode, Int)] -> IO ()
176
printFRScores ini_nl fin_nl sreason = do
177
  printf "  - most likely failure reason: %s\n" $ failureReason sreason::IO ()
178
  printClusterScores ini_nl fin_nl
179
  printClusterEff (Cluster.totalResources fin_nl)
180

    
181
-- | Print final stats and related metrics.
182
printResults :: Bool -> Node.List -> Node.List -> Int -> Int
183
             -> [(FailMode, Int)] -> IO ()
184
printResults True _ fin_nl num_instances allocs sreason = do
185
  let fin_stats = Cluster.totalResources fin_nl
186
      fin_instances = num_instances + allocs
187

    
188
  exitWhen (num_instances + allocs /= Cluster.csNinst fin_stats) $
189
           printf "internal inconsistency, allocated (%d)\
190
                  \ != counted (%d)\n" (num_instances + allocs)
191
           (Cluster.csNinst fin_stats)
192

    
193
  printKeysHTS $ printStats PFinal fin_stats
194
  printKeysHTS [ ("ALLOC_USAGE", printf "%.8f"
195
                                   ((fromIntegral num_instances::Double) /
196
                                   fromIntegral fin_instances))
197
               , ("ALLOC_INSTANCES", printf "%d" allocs)
198
               , ("ALLOC_FAIL_REASON", map toUpper . show . fst $ head sreason)
199
               ]
200
  printKeysHTS $ map (\(x, y) -> (printf "ALLOC_%s_CNT" (show x),
201
                                  printf "%d" y)) sreason
202

    
203
printResults False ini_nl fin_nl _ allocs sreason = do
204
  putStrLn "Normal (fixed-size) allocation results:"
205
  printf "  - %3d instances allocated\n" allocs :: IO ()
206
  printFRScores ini_nl fin_nl sreason
207

    
208
-- | Prints the final @OK@ marker in machine readable output.
209
printFinalHTS :: Bool -> IO ()
210
printFinalHTS = printFinal htsPrefix
211

    
212
-- | Compute the tiered spec counts from a list of allocated
213
-- instances.
214
tieredSpecMap :: [Instance.Instance]
215
              -> [(RSpec, Int)]
216
tieredSpecMap trl_ixes =
217
  let fin_trl_ixes = reverse trl_ixes
218
      ix_byspec = groupBy ((==) `on` Instance.specOf) fin_trl_ixes
219
      spec_map = map (\ixs -> (Instance.specOf $ head ixs, length ixs))
220
                 ix_byspec
221
  in spec_map
222

    
223
-- | Formats a spec map to strings.
224
formatSpecMap :: [(RSpec, Int)] -> [String]
225
formatSpecMap =
226
  map (\(spec, cnt) -> printf "%d,%d,%d=%d" (rspecMem spec)
227
                       (rspecDsk spec) (rspecCpu spec) cnt)
228

    
229
-- | Formats \"key-metrics\" values.
230
formatRSpec :: String -> AllocInfo -> [(String, String)]
231
formatRSpec s r =
232
  [ ("KM_" ++ s ++ "_CPU", show $ allocInfoVCpus r)
233
  , ("KM_" ++ s ++ "_NPU", show $ allocInfoNCpus r)
234
  , ("KM_" ++ s ++ "_MEM", show $ allocInfoMem r)
235
  , ("KM_" ++ s ++ "_DSK", show $ allocInfoDisk r)
236
  ]
237

    
238
-- | Shows allocations stats.
239
printAllocationStats :: Node.List -> Node.List -> IO ()
240
printAllocationStats ini_nl fin_nl = do
241
  let ini_stats = Cluster.totalResources ini_nl
242
      fin_stats = Cluster.totalResources fin_nl
243
      (rini, ralo, runa) = Cluster.computeAllocationDelta ini_stats fin_stats
244
  printKeysHTS $ formatRSpec "USED" rini
245
  printKeysHTS $ formatRSpec "POOL" ralo
246
  printKeysHTS $ formatRSpec "UNAV" runa
247

    
248
-- | Format a list of key\/values as a shell fragment.
249
printKeysHTS :: [(String, String)] -> IO ()
250
printKeysHTS = printKeys htsPrefix
251

    
252
-- | Converts instance data to a list of strings.
253
printInstance :: Node.List -> Instance.Instance -> [String]
254
printInstance nl i = [ Instance.name i
255
                     , Container.nameOf nl $ Instance.pNode i
256
                     , let sdx = Instance.sNode i
257
                       in if sdx == Node.noSecondary then ""
258
                          else Container.nameOf nl sdx
259
                     , show (Instance.mem i)
260
                     , show (Instance.dsk i)
261
                     , show (Instance.vcpus i)
262
                     ]
263

    
264
-- | Optionally print the allocation map.
265
printAllocationMap :: Int -> String
266
                   -> Node.List -> [Instance.Instance] -> IO ()
267
printAllocationMap verbose msg nl ixes =
268
  when (verbose > 1) $ do
269
    hPutStrLn stderr (msg ++ " map")
270
    hPutStr stderr . unlines . map ((:) ' ' .  unwords) $
271
            formatTable (map (printInstance nl) (reverse ixes))
272
                        -- This is the numberic-or-not field
273
                        -- specification; the first three fields are
274
                        -- strings, whereas the rest are numeric
275
                       [False, False, False, True, True, True]
276

    
277
-- | Formats nicely a list of resources.
278
formatResources :: a -> [(String, a->String)] -> String
279
formatResources res =
280
    intercalate ", " . map (\(a, fn) -> a ++ " " ++ fn res)
281

    
282
-- | Print the cluster resources.
283
printCluster :: Bool -> Cluster.CStats -> Int -> IO ()
284
printCluster True ini_stats node_count = do
285
  printKeysHTS $ map (\(a, fn) -> ("CLUSTER_" ++ a, fn ini_stats)) clusterData
286
  printKeysHTS [("CLUSTER_NODES", printf "%d" node_count)]
287
  printKeysHTS $ printStats PInitial ini_stats
288

    
289
printCluster False ini_stats node_count = do
290
  printf "The cluster has %d nodes and the following resources:\n  %s.\n"
291
         node_count (formatResources ini_stats clusterData)::IO ()
292
  printf "There are %s initial instances on the cluster.\n"
293
             (if inst_count > 0 then show inst_count else "no" )
294
      where inst_count = Cluster.csNinst ini_stats
295

    
296
-- | Prints the normal instance spec.
297
printISpec :: Bool -> RSpec -> SpecType -> DiskTemplate -> IO ()
298
printISpec True ispec spec disk_template = do
299
  printKeysHTS $ map (\(a, fn) -> (prefix ++ "_" ++ a, fn ispec)) specData
300
  printKeysHTS [ (prefix ++ "_RQN", printf "%d" req_nodes) ]
301
  printKeysHTS [ (prefix ++ "_DISK_TEMPLATE",
302
                  diskTemplateToRaw disk_template) ]
303
      where req_nodes = Instance.requiredNodes disk_template
304
            prefix = specPrefix spec
305

    
306
printISpec False ispec spec disk_template =
307
  printf "%s instance spec is:\n  %s, using disk\
308
         \ template '%s'.\n"
309
         (specDescription spec)
310
         (formatResources ispec specData) (diskTemplateToRaw disk_template)
311

    
312
-- | Prints the tiered results.
313
printTiered :: Bool -> [(RSpec, Int)]
314
            -> Node.List -> Node.List -> [(FailMode, Int)] -> IO ()
315
printTiered True spec_map nl trl_nl _ = do
316
  printKeysHTS $ printStats PTiered (Cluster.totalResources trl_nl)
317
  printKeysHTS [("TSPEC", unwords (formatSpecMap spec_map))]
318
  printAllocationStats nl trl_nl
319

    
320
printTiered False spec_map ini_nl fin_nl sreason = do
321
  _ <- printf "Tiered allocation results:\n"
322
  if null spec_map
323
    then putStrLn "  - no instances allocated"
324
    else mapM_ (\(ispec, cnt) ->
325
                  printf "  - %3d instances of spec %s\n" cnt
326
                           (formatResources ispec specData)) spec_map
327
  printFRScores ini_nl fin_nl sreason
328

    
329
-- | Displays the initial/final cluster scores.
330
printClusterScores :: Node.List -> Node.List -> IO ()
331
printClusterScores ini_nl fin_nl = do
332
  printf "  - initial cluster score: %.8f\n" $ Cluster.compCV ini_nl::IO ()
333
  printf "  -   final cluster score: %.8f\n" $ Cluster.compCV fin_nl
334

    
335
-- | Displays the cluster efficiency.
336
printClusterEff :: Cluster.CStats -> IO ()
337
printClusterEff cs =
338
  mapM_ (\(s, fn) ->
339
           printf "  - %s usage efficiency: %5.2f%%\n" s (fn cs * 100))
340
          [("memory", memEff),
341
           ("  disk", dskEff),
342
           ("  vcpu", cpuEff)]
343

    
344
-- | Computes the most likely failure reason.
345
failureReason :: [(FailMode, Int)] -> String
346
failureReason = show . fst . head
347

    
348
-- | Sorts the failure reasons.
349
sortReasons :: [(FailMode, Int)] -> [(FailMode, Int)]
350
sortReasons = reverse . sortBy (comparing snd)
351

    
352
-- | Runs an allocation algorithm and saves cluster state.
353
runAllocation :: ClusterData                -- ^ Cluster data
354
              -> Maybe Cluster.AllocResult  -- ^ Optional stop-allocation
355
              -> Result Cluster.AllocResult -- ^ Allocation result
356
              -> RSpec                      -- ^ Requested instance spec
357
              -> DiskTemplate               -- ^ Requested disk template
358
              -> SpecType                   -- ^ Allocation type
359
              -> Options                    -- ^ CLI options
360
              -> IO (FailStats, Node.List, Int, [(RSpec, Int)])
361
runAllocation cdata stop_allocation actual_result spec dt mode opts = do
362
  (reasons, new_nl, new_il, new_ixes, _) <-
363
      case stop_allocation of
364
        Just result_noalloc -> return result_noalloc
365
        Nothing -> exitIfBad "failure during allocation" actual_result
366

    
367
  let name = head . words . specDescription $ mode
368
      descr = name ++ " allocation"
369
      ldescr = "after " ++ map toLower descr
370

    
371
  printISpec (optMachineReadable opts) spec mode dt
372

    
373
  printAllocationMap (optVerbose opts) descr new_nl new_ixes
374

    
375
  maybePrintNodes (optShowNodes opts) descr (Cluster.printNodes new_nl)
376

    
377
  maybeSaveData (optSaveCluster opts) (map toLower name) ldescr
378
                    (cdata { cdNodes = new_nl, cdInstances = new_il})
379

    
380
  return (sortReasons reasons, new_nl, length new_ixes, tieredSpecMap new_ixes)
381

    
382
-- | Create an instance from a given spec.
383
instFromSpec :: RSpec -> DiskTemplate -> Int -> Instance.Instance
384
instFromSpec spx =
385
  Instance.create "new" (rspecMem spx) (rspecDsk spx)
386
    (rspecCpu spx) Running [] True (-1) (-1)
387

    
388
-- | Main function.
389
main :: Options -> [String] -> IO ()
390
main opts args = do
391
  exitUnless (null args) "This program doesn't take any arguments."
392

    
393
  let verbose = optVerbose opts
394
      machine_r = optMachineReadable opts
395

    
396
  orig_cdata@(ClusterData gl fixed_nl il _ ipol) <- loadExternalData opts
397
  nl <- setNodeStatus opts fixed_nl
398

    
399
  cluster_disk_template <-
400
    case iPolicyDiskTemplates ipol of
401
      first_templ:_ -> return first_templ
402
      _ -> exitErr "null list of disk templates received from cluster"
403

    
404
  let num_instances = Container.size il
405
      all_nodes = Container.elems fixed_nl
406
      cdata = orig_cdata { cdNodes = fixed_nl }
407
      disk_template = fromMaybe cluster_disk_template (optDiskTemplate opts)
408
      req_nodes = Instance.requiredNodes disk_template
409
      csf = commonSuffix fixed_nl il
410
      su = fromMaybe (iSpecSpindleUse $ iPolicyStdSpec ipol)
411
                     (optSpindleUse opts)
412

    
413
  when (not (null csf) && verbose > 1) $
414
       hPrintf stderr "Note: Stripping common suffix of '%s' from names\n" csf
415

    
416
  maybePrintNodes (optShowNodes opts) "Initial cluster" (Cluster.printNodes nl)
417

    
418
  when (verbose > 2) $
419
         hPrintf stderr "Initial coefficients: overall %.8f\n%s"
420
                 (Cluster.compCV nl) (Cluster.printStats "  " nl)
421

    
422
  printCluster machine_r (Cluster.totalResources nl) (length all_nodes)
423

    
424
  let stop_allocation = case Cluster.computeBadItems nl il of
425
                          ([], _) -> Nothing
426
                          _ -> Just ([(FailN1, 1)]::FailStats, nl, il, [], [])
427
      alloclimit = if optMaxLength opts == -1
428
                   then Nothing
429
                   else Just (optMaxLength opts)
430

    
431
  allocnodes <- exitIfBad "failure during allocation" $
432
                Cluster.genAllocNodes gl nl req_nodes True
433

    
434
  -- Run the tiered allocation
435

    
436
  let tspec = fromMaybe (rspecFromISpec (iPolicyMaxSpec ipol))
437
              (optTieredSpec opts)
438

    
439
  (treason, trl_nl, _, spec_map) <-
440
    runAllocation cdata stop_allocation
441
       (Cluster.tieredAlloc nl il alloclimit
442
        (instFromSpec tspec disk_template su) allocnodes [] [])
443
       tspec disk_template SpecTiered opts
444

    
445
  printTiered machine_r spec_map nl trl_nl treason
446

    
447
  -- Run the standard (avg-mode) allocation
448

    
449
  let ispec = fromMaybe (rspecFromISpec (iPolicyStdSpec ipol))
450
              (optStdSpec opts)
451

    
452
  (sreason, fin_nl, allocs, _) <-
453
      runAllocation cdata stop_allocation
454
            (Cluster.iterateAlloc nl il alloclimit
455
             (instFromSpec ispec disk_template su) allocnodes [] [])
456
            ispec disk_template SpecNormal opts
457

    
458
  printResults machine_r nl fin_nl num_instances allocs sreason
459

    
460
  -- Print final result
461

    
462
  printFinalHTS machine_r