Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Program / Hspace.hs @ 22278fa7

History | View | Annotate | Download (16.6 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.Common
48
import Ganeti.HTools.Types
49
import Ganeti.HTools.CLI
50
import Ganeti.HTools.ExtLoader
51
import Ganeti.HTools.Loader
52
import Ganeti.Utils
53

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

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

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

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

    
91
-- | Prefix for machine readable names
92
htsPrefix :: String
93
htsPrefix = "HTS"
94

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
369
  printISpec (optMachineReadable opts) spec mode dt
370

    
371
  printAllocationMap (optVerbose opts) descr new_nl new_ixes
372

    
373
  maybePrintNodes (optShowNodes opts) descr (Cluster.printNodes new_nl)
374

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

    
378
  return (sortReasons reasons, new_nl, length new_ixes, tieredSpecMap new_ixes)
379

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

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

    
391
  let verbose = optVerbose opts
392
      machine_r = optMachineReadable opts
393

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

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

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

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

    
414
  maybePrintNodes (optShowNodes opts) "Initial cluster" (Cluster.printNodes nl)
415

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

    
420
  printCluster machine_r (Cluster.totalResources nl) (length all_nodes)
421

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

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

    
432
  -- Run the tiered allocation
433

    
434
  let tspec = fromMaybe (rspecFromISpec (iPolicyMaxSpec ipol))
435
              (optTieredSpec opts)
436

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

    
443
  printTiered machine_r spec_map nl trl_nl treason
444

    
445
  -- Run the standard (avg-mode) allocation
446

    
447
  let ispec = fromMaybe (rspecFromISpec (iPolicyStdSpec ipol))
448
              (optStdSpec opts)
449

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

    
456
  printResults machine_r nl fin_nl num_instances allocs sreason
457

    
458
  -- Print final result
459

    
460
  printFinalHTS machine_r