Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (17 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 (main, options) where
27

    
28
import Control.Monad
29
import Data.Char (toUpper, isAlphaNum, toLower)
30
import Data.Function (on)
31
import Data.List
32
import Data.Maybe (fromMaybe)
33
import Data.Ord (comparing)
34
import System.Exit
35
import System.IO
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
import Ganeti.HTools.Loader
49

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

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

    
79
-- | The kind of instance spec we print.
80
data SpecType = SpecNormal
81
              | SpecTiered
82

    
83
-- | What we prefix a spec with.
84
specPrefix :: SpecType -> String
85
specPrefix SpecNormal = "SPEC"
86
specPrefix SpecTiered = "TSPEC_INI"
87

    
88
-- | The description of a spec.
89
specDescription :: SpecType -> String
90
specDescription SpecNormal = "Standard (fixed-size)"
91
specDescription SpecTiered = "Tiered (initial size)"
92

    
93
-- | Efficiency generic function.
94
effFn :: (Cluster.CStats -> Integer)
95
      -> (Cluster.CStats -> Double)
96
      -> Cluster.CStats -> Double
97
effFn fi ft cs = fromIntegral (fi cs) / ft cs
98

    
99
-- | Memory efficiency.
100
memEff :: Cluster.CStats -> Double
101
memEff = effFn Cluster.csImem Cluster.csTmem
102

    
103
-- | Disk efficiency.
104
dskEff :: Cluster.CStats -> Double
105
dskEff = effFn Cluster.csIdsk Cluster.csTdsk
106

    
107
-- | Cpu efficiency.
108
cpuEff :: Cluster.CStats -> Double
109
cpuEff = effFn Cluster.csIcpu (fromIntegral . Cluster.csVcpu)
110

    
111
-- | Holds data for converting a 'Cluster.CStats' structure into
112
-- detailed statictics.
113
statsData :: [(String, Cluster.CStats -> String)]
114
statsData = [ ("SCORE", printf "%.8f" . Cluster.csScore)
115
            , ("INST_CNT", printf "%d" . Cluster.csNinst)
116
            , ("MEM_FREE", printf "%d" . Cluster.csFmem)
117
            , ("MEM_AVAIL", printf "%d" . Cluster.csAmem)
118
            , ("MEM_RESVD",
119
               \cs -> printf "%d" (Cluster.csFmem cs - Cluster.csAmem cs))
120
            , ("MEM_INST", printf "%d" . Cluster.csImem)
121
            , ("MEM_OVERHEAD",
122
               \cs -> printf "%d" (Cluster.csXmem cs + Cluster.csNmem cs))
123
            , ("MEM_EFF", printf "%.8f" . memEff)
124
            , ("DSK_FREE", printf "%d" . Cluster.csFdsk)
125
            , ("DSK_AVAIL", printf "%d". Cluster.csAdsk)
126
            , ("DSK_RESVD",
127
               \cs -> printf "%d" (Cluster.csFdsk cs - Cluster.csAdsk cs))
128
            , ("DSK_INST", printf "%d" . Cluster.csIdsk)
129
            , ("DSK_EFF", printf "%.8f" . dskEff)
130
            , ("CPU_INST", printf "%d" . Cluster.csIcpu)
131
            , ("CPU_EFF", printf "%.8f" . cpuEff)
132
            , ("MNODE_MEM_AVAIL", printf "%d" . Cluster.csMmem)
133
            , ("MNODE_DSK_AVAIL", printf "%d" . Cluster.csMdsk)
134
            ]
135

    
136
-- | List holding 'RSpec' formatting information.
137
specData :: [(String, RSpec -> String)]
138
specData = [ ("MEM", printf "%d" . rspecMem)
139
           , ("DSK", printf "%d" . rspecDsk)
140
           , ("CPU", printf "%d" . rspecCpu)
141
           ]
142

    
143
-- | List holding 'Cluster.CStats' formatting information.
144
clusterData :: [(String, Cluster.CStats -> String)]
145
clusterData = [ ("MEM", printf "%.0f" . Cluster.csTmem)
146
              , ("DSK", printf "%.0f" . Cluster.csTdsk)
147
              , ("CPU", printf "%.0f" . Cluster.csTcpu)
148
              , ("VCPU", printf "%d" . Cluster.csVcpu)
149
              ]
150

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

    
160
-- | Print failure reason and scores
161
printFRScores :: Node.List -> Node.List -> [(FailMode, Int)] -> IO ()
162
printFRScores ini_nl fin_nl sreason = do
163
  printf "  - most likely failure reason: %s\n" $ failureReason sreason::IO ()
164
  printClusterScores ini_nl fin_nl
165
  printClusterEff (Cluster.totalResources fin_nl)
166

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

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

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

    
191
printResults False ini_nl fin_nl _ allocs sreason = do
192
  putStrLn "Normal (fixed-size) allocation results:"
193
  printf "  - %3d instances allocated\n" allocs :: IO ()
194
  printFRScores ini_nl fin_nl sreason
195

    
196
-- | Prints the final @OK@ marker in machine readable output.
197
printFinal :: Bool -> IO ()
198
printFinal True =
199
  -- this should be the final entry
200
  printKeys [("OK", "1")]
201

    
202
printFinal False = return ()
203

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

    
215
-- | Formats a spec map to strings.
216
formatSpecMap :: [(RSpec, Int)] -> [String]
217
formatSpecMap =
218
  map (\(spec, cnt) -> printf "%d,%d,%d=%d" (rspecMem spec)
219
                       (rspecDsk spec) (rspecCpu spec) cnt)
220

    
221
-- | Formats \"key-metrics\" values.
222
formatRSpec :: Double -> String -> RSpec -> [(String, String)]
223
formatRSpec m_cpu s r =
224
  [ ("KM_" ++ s ++ "_CPU", show $ rspecCpu r)
225
  , ("KM_" ++ s ++ "_NPU", show $ fromIntegral (rspecCpu r) / m_cpu)
226
  , ("KM_" ++ s ++ "_MEM", show $ rspecMem r)
227
  , ("KM_" ++ s ++ "_DSK", show $ rspecDsk r)
228
  ]
229

    
230
-- | Shows allocations stats.
231
printAllocationStats :: Double -> Node.List -> Node.List -> IO ()
232
printAllocationStats m_cpu ini_nl fin_nl = do
233
  let ini_stats = Cluster.totalResources ini_nl
234
      fin_stats = Cluster.totalResources fin_nl
235
      (rini, ralo, runa) = Cluster.computeAllocationDelta ini_stats fin_stats
236
  printKeys $ formatRSpec m_cpu  "USED" rini
237
  printKeys $ formatRSpec m_cpu "POOL"ralo
238
  printKeys $ formatRSpec m_cpu "UNAV" runa
239

    
240
-- | Ensure a value is quoted if needed.
241
ensureQuoted :: String -> String
242
ensureQuoted v = if not (all (\c -> isAlphaNum c || c == '.') v)
243
                 then '\'':v ++ "'"
244
                 else v
245

    
246
-- | Format a list of key\/values as a shell fragment.
247
printKeys :: [(String, String)] -> IO ()
248
printKeys = mapM_ (\(k, v) ->
249
                   printf "HTS_%s=%s\n" (map toUpper k) (ensureQuoted v))
250

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

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

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

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

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

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

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

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

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

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

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

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

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

    
351
-- | Aborts the program if we get a bad value.
352
exitIfBad :: Result a -> IO a
353
exitIfBad (Bad s) =
354
  hPrintf stderr "Failure: %s\n" s >> exitWith (ExitFailure 1)
355
exitIfBad (Ok v) = return v
356

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

    
372
  let name = head . words . specDescription $ mode
373
      descr = name ++ " allocation"
374
      ldescr = "after " ++ map toLower descr
375

    
376
  printISpec (optMachineReadable opts) spec mode dt
377

    
378
  printAllocationMap (optVerbose opts) descr new_nl new_ixes
379

    
380
  maybePrintNodes (optShowNodes opts) descr (Cluster.printNodes new_nl)
381

    
382
  maybeSaveData (optSaveCluster opts) (map toLower name) ldescr
383
                    (cdata { cdNodes = new_nl, cdInstances = new_il})
384

    
385
  return (sortReasons reasons, new_nl, length new_ixes, tieredSpecMap new_ixes)
386

    
387
-- | Create an instance from a given spec.
388
instFromSpec :: RSpec -> DiskTemplate -> Instance.Instance
389
instFromSpec spx disk_template =
390
  Instance.create "new" (rspecMem spx) (rspecDsk spx)
391
    (rspecCpu spx) Running [] True (-1) (-1) disk_template
392

    
393
-- | Main function.
394
main :: Options -> [String] -> IO ()
395
main opts args = do
396
  unless (null args) $ do
397
         hPutStrLn stderr "Error: this program doesn't take any arguments."
398
         exitWith $ ExitFailure 1
399

    
400
  let verbose = optVerbose opts
401
      machine_r = optMachineReadable opts
402

    
403
  orig_cdata@(ClusterData gl fixed_nl il _ ipol) <- loadExternalData opts
404
  nl <- setNodeStatus opts fixed_nl
405

    
406
  cluster_disk_template <-
407
    case iPolicyDiskTemplates ipol of
408
      first_templ:_ -> return first_templ
409
      _ -> do
410
         _ <- hPutStrLn stderr $ "Error: null list of disk templates\
411
                               \ received from cluster!"
412
         exitWith $ ExitFailure 1
413

    
414
  let num_instances = Container.size il
415
      all_nodes = Container.elems fixed_nl
416
      cdata = orig_cdata { cdNodes = fixed_nl }
417
      disk_template = fromMaybe cluster_disk_template (optDiskTemplate opts)
418
      req_nodes = Instance.requiredNodes disk_template
419
      csf = commonSuffix fixed_nl il
420

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

    
424
  maybePrintNodes (optShowNodes opts) "Initial cluster" (Cluster.printNodes nl)
425

    
426
  when (verbose > 2) $
427
         hPrintf stderr "Initial coefficients: overall %.8f, %s\n"
428
                 (Cluster.compCV nl) (Cluster.printStats nl)
429

    
430
  printCluster machine_r (Cluster.totalResources nl) (length all_nodes)
431

    
432
  let stop_allocation = case Cluster.computeBadItems nl il of
433
                          ([], _) -> Nothing
434
                          _ -> Just ([(FailN1, 1)]::FailStats, nl, il, [], [])
435
      alloclimit = if optMaxLength opts == -1
436
                   then Nothing
437
                   else Just (optMaxLength opts)
438

    
439
  allocnodes <- exitIfBad $ Cluster.genAllocNodes gl nl req_nodes True
440

    
441
  -- Run the tiered allocation
442

    
443
  let tspec = fromMaybe (rspecFromISpec (iPolicyMaxSpec ipol))
444
              (optTieredSpec opts)
445

    
446
  (treason, trl_nl, _, spec_map) <-
447
    runAllocation cdata stop_allocation
448
       (Cluster.tieredAlloc nl il alloclimit
449
        (instFromSpec tspec disk_template) allocnodes [] [])
450
       tspec disk_template SpecTiered opts
451

    
452
  printTiered machine_r spec_map (optMcpu opts) nl trl_nl treason
453

    
454
  -- Run the standard (avg-mode) allocation
455

    
456
  let ispec = fromMaybe (rspecFromISpec (iPolicyStdSpec ipol))
457
              (optStdSpec opts)
458

    
459
  (sreason, fin_nl, allocs, _) <-
460
      runAllocation cdata stop_allocation
461
            (Cluster.iterateAlloc nl il alloclimit
462
             (instFromSpec ispec disk_template) allocnodes [] [])
463
            ispec disk_template SpecNormal opts
464

    
465
  printResults machine_r nl fin_nl num_instances allocs sreason
466

    
467
  -- Print final result
468

    
469
  printFinal machine_r