Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Program / Hspace.hs @ 5b11f8db

History | View | Annotate | Download (16.5 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, toLower)
30
import Data.Function (on)
31
import Data.List
32
import Data.Maybe (fromMaybe)
33
import Data.Ord (comparing)
34
import System.IO
35

    
36
import Text.Printf (printf, hPrintf)
37

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

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

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

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

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

    
84
-- | Prefix for machine readable names
85
htsPrefix :: String
86
htsPrefix = "HTS"
87

    
88
-- | What we prefix a spec with.
89
specPrefix :: SpecType -> String
90
specPrefix SpecNormal = "SPEC"
91
specPrefix SpecTiered = "TSPEC_INI"
92

    
93
-- | The description of a spec.
94
specDescription :: SpecType -> String
95
specDescription SpecNormal = "Standard (fixed-size)"
96
specDescription SpecTiered = "Tiered (initial size)"
97

    
98
-- | Efficiency generic function.
99
effFn :: (Cluster.CStats -> Integer)
100
      -> (Cluster.CStats -> Double)
101
      -> Cluster.CStats -> Double
102
effFn fi ft cs = fromIntegral (fi cs) / ft cs
103

    
104
-- | Memory efficiency.
105
memEff :: Cluster.CStats -> Double
106
memEff = effFn Cluster.csImem Cluster.csTmem
107

    
108
-- | Disk efficiency.
109
dskEff :: Cluster.CStats -> Double
110
dskEff = effFn Cluster.csIdsk Cluster.csTdsk
111

    
112
-- | Cpu efficiency.
113
cpuEff :: Cluster.CStats -> Double
114
cpuEff = effFn Cluster.csIcpu (fromIntegral . Cluster.csVcpu)
115

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

    
141
-- | List holding 'RSpec' formatting information.
142
specData :: [(String, RSpec -> String)]
143
specData = [ ("MEM", printf "%d" . rspecMem)
144
           , ("DSK", printf "%d" . rspecDsk)
145
           , ("CPU", printf "%d" . rspecCpu)
146
           ]
147

    
148
-- | List holding 'Cluster.CStats' formatting information.
149
clusterData :: [(String, Cluster.CStats -> String)]
150
clusterData = [ ("MEM", printf "%.0f" . Cluster.csTmem)
151
              , ("DSK", printf "%.0f" . Cluster.csTdsk)
152
              , ("CPU", printf "%.0f" . Cluster.csTcpu)
153
              , ("VCPU", printf "%d" . Cluster.csVcpu)
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 failure reason and scores
166
printFRScores :: Node.List -> Node.List -> [(FailMode, Int)] -> IO ()
167
printFRScores ini_nl fin_nl sreason = do
168
  printf "  - most likely failure reason: %s\n" $ failureReason sreason::IO ()
169
  printClusterScores ini_nl fin_nl
170
  printClusterEff (Cluster.totalResources fin_nl)
171

    
172
-- | Print final stats and related metrics.
173
printResults :: Bool -> Node.List -> Node.List -> Int -> Int
174
             -> [(FailMode, Int)] -> IO ()
175
printResults True _ fin_nl num_instances allocs sreason = do
176
  let fin_stats = Cluster.totalResources fin_nl
177
      fin_instances = num_instances + allocs
178

    
179
  exitWhen (num_instances + allocs /= Cluster.csNinst fin_stats) $
180
           printf "internal inconsistency, allocated (%d)\
181
                  \ != counted (%d)\n" (num_instances + allocs)
182
           (Cluster.csNinst fin_stats)
183

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

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

    
199
-- | Prints the final @OK@ marker in machine readable output.
200
printFinalHTS :: Bool -> IO ()
201
printFinalHTS = printFinal htsPrefix
202

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

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

    
220
-- | Formats \"key-metrics\" values.
221
formatRSpec :: String -> AllocInfo -> [(String, String)]
222
formatRSpec s r =
223
  [ ("KM_" ++ s ++ "_CPU", show $ allocInfoVCpus r)
224
  , ("KM_" ++ s ++ "_NPU", show $ allocInfoNCpus r)
225
  , ("KM_" ++ s ++ "_MEM", show $ allocInfoMem r)
226
  , ("KM_" ++ s ++ "_DSK", show $ allocInfoDisk r)
227
  ]
228

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

    
239
-- | Format a list of key\/values as a shell fragment.
240
printKeysHTS :: [(String, String)] -> IO ()
241
printKeysHTS = printKeys htsPrefix
242

    
243
-- | Converts instance data to a list of strings.
244
printInstance :: Node.List -> Instance.Instance -> [String]
245
printInstance nl i = [ Instance.name i
246
                     , Container.nameOf nl $ Instance.pNode i
247
                     , let sdx = Instance.sNode i
248
                       in if sdx == Node.noSecondary then ""
249
                          else Container.nameOf nl sdx
250
                     , show (Instance.mem i)
251
                     , show (Instance.dsk i)
252
                     , show (Instance.vcpus i)
253
                     ]
254

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

    
268
-- | Formats nicely a list of resources.
269
formatResources :: a -> [(String, a->String)] -> String
270
formatResources res =
271
    intercalate ", " . map (\(a, fn) -> a ++ " " ++ fn res)
272

    
273
-- | Print the cluster resources.
274
printCluster :: Bool -> Cluster.CStats -> Int -> IO ()
275
printCluster True ini_stats node_count = do
276
  printKeysHTS $ map (\(a, fn) -> ("CLUSTER_" ++ a, fn ini_stats)) clusterData
277
  printKeysHTS [("CLUSTER_NODES", printf "%d" node_count)]
278
  printKeysHTS $ printStats PInitial ini_stats
279

    
280
printCluster False ini_stats node_count = do
281
  printf "The cluster has %d nodes and the following resources:\n  %s.\n"
282
         node_count (formatResources ini_stats clusterData)::IO ()
283
  printf "There are %s initial instances on the cluster.\n"
284
             (if inst_count > 0 then show inst_count else "no" )
285
      where inst_count = Cluster.csNinst ini_stats
286

    
287
-- | Prints the normal instance spec.
288
printISpec :: Bool -> RSpec -> SpecType -> DiskTemplate -> IO ()
289
printISpec True ispec spec disk_template = do
290
  printKeysHTS $ map (\(a, fn) -> (prefix ++ "_" ++ a, fn ispec)) specData
291
  printKeysHTS [ (prefix ++ "_RQN", printf "%d" req_nodes) ]
292
  printKeysHTS [ (prefix ++ "_DISK_TEMPLATE",
293
                  diskTemplateToRaw disk_template) ]
294
      where req_nodes = Instance.requiredNodes disk_template
295
            prefix = specPrefix spec
296

    
297
printISpec False ispec spec disk_template =
298
  printf "%s instance spec is:\n  %s, using disk\
299
         \ template '%s'.\n"
300
         (specDescription spec)
301
         (formatResources ispec specData) (diskTemplateToRaw disk_template)
302

    
303
-- | Prints the tiered results.
304
printTiered :: Bool -> [(RSpec, Int)]
305
            -> Node.List -> Node.List -> [(FailMode, Int)] -> IO ()
306
printTiered True spec_map nl trl_nl _ = do
307
  printKeysHTS $ printStats PTiered (Cluster.totalResources trl_nl)
308
  printKeysHTS [("TSPEC", unwords (formatSpecMap spec_map))]
309
  printAllocationStats nl trl_nl
310

    
311
printTiered False spec_map ini_nl fin_nl sreason = do
312
  _ <- printf "Tiered allocation results:\n"
313
  if null spec_map
314
    then putStrLn "  - no instances allocated"
315
    else mapM_ (\(ispec, cnt) ->
316
                  printf "  - %3d instances of spec %s\n" cnt
317
                           (formatResources ispec specData)) spec_map
318
  printFRScores ini_nl fin_nl sreason
319

    
320
-- | Displays the initial/final cluster scores.
321
printClusterScores :: Node.List -> Node.List -> IO ()
322
printClusterScores ini_nl fin_nl = do
323
  printf "  - initial cluster score: %.8f\n" $ Cluster.compCV ini_nl::IO ()
324
  printf "  -   final cluster score: %.8f\n" $ Cluster.compCV fin_nl
325

    
326
-- | Displays the cluster efficiency.
327
printClusterEff :: Cluster.CStats -> IO ()
328
printClusterEff cs =
329
  mapM_ (\(s, fn) ->
330
           printf "  - %s usage efficiency: %5.2f%%\n" s (fn cs * 100))
331
          [("memory", memEff),
332
           ("  disk", dskEff),
333
           ("  vcpu", cpuEff)]
334

    
335
-- | Computes the most likely failure reason.
336
failureReason :: [(FailMode, Int)] -> String
337
failureReason = show . fst . head
338

    
339
-- | Sorts the failure reasons.
340
sortReasons :: [(FailMode, Int)] -> [(FailMode, Int)]
341
sortReasons = reverse . sortBy (comparing snd)
342

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

    
358
  let name = head . words . specDescription $ mode
359
      descr = name ++ " allocation"
360
      ldescr = "after " ++ map toLower descr
361

    
362
  printISpec (optMachineReadable opts) spec mode dt
363

    
364
  printAllocationMap (optVerbose opts) descr new_nl new_ixes
365

    
366
  maybePrintNodes (optShowNodes opts) descr (Cluster.printNodes new_nl)
367

    
368
  maybeSaveData (optSaveCluster opts) (map toLower name) ldescr
369
                    (cdata { cdNodes = new_nl, cdInstances = new_il})
370

    
371
  return (sortReasons reasons, new_nl, length new_ixes, tieredSpecMap new_ixes)
372

    
373
-- | Create an instance from a given spec.
374
instFromSpec :: RSpec -> DiskTemplate -> Int -> Instance.Instance
375
instFromSpec spx =
376
  Instance.create "new" (rspecMem spx) (rspecDsk spx)
377
    (rspecCpu spx) Running [] True (-1) (-1)
378

    
379
-- | Main function.
380
main :: Options -> [String] -> IO ()
381
main opts args = do
382
  exitUnless (null args) "this program doesn't take any arguments"
383

    
384
  let verbose = optVerbose opts
385
      machine_r = optMachineReadable opts
386

    
387
  orig_cdata@(ClusterData gl fixed_nl il _ ipol) <- loadExternalData opts
388
  nl <- setNodeStatus opts fixed_nl
389

    
390
  cluster_disk_template <-
391
    case iPolicyDiskTemplates ipol of
392
      first_templ:_ -> return first_templ
393
      _ -> exitErr "null list of disk templates received from cluster"
394

    
395
  let num_instances = Container.size il
396
      all_nodes = Container.elems fixed_nl
397
      cdata = orig_cdata { cdNodes = fixed_nl }
398
      disk_template = fromMaybe cluster_disk_template (optDiskTemplate opts)
399
      req_nodes = Instance.requiredNodes disk_template
400
      csf = commonSuffix fixed_nl il
401
      su = fromMaybe (iSpecSpindleUse $ iPolicyStdSpec ipol)
402
                     (optSpindleUse opts)
403

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

    
407
  maybePrintNodes (optShowNodes opts) "Initial cluster" (Cluster.printNodes nl)
408

    
409
  when (verbose > 2) $
410
         hPrintf stderr "Initial coefficients: overall %.8f\n%s"
411
                 (Cluster.compCV nl) (Cluster.printStats "  " nl)
412

    
413
  printCluster machine_r (Cluster.totalResources nl) (length all_nodes)
414

    
415
  let stop_allocation = case Cluster.computeBadItems nl il of
416
                          ([], _) -> Nothing
417
                          _ -> Just ([(FailN1, 1)]::FailStats, nl, il, [], [])
418
      alloclimit = if optMaxLength opts == -1
419
                   then Nothing
420
                   else Just (optMaxLength opts)
421

    
422
  allocnodes <- exitIfBad "failure during allocation" $
423
                Cluster.genAllocNodes gl nl req_nodes True
424

    
425
  -- Run the tiered allocation
426

    
427
  let tspec = fromMaybe (rspecFromISpec (iPolicyMaxSpec ipol))
428
              (optTieredSpec opts)
429

    
430
  (treason, trl_nl, _, spec_map) <-
431
    runAllocation cdata stop_allocation
432
       (Cluster.tieredAlloc nl il alloclimit
433
        (instFromSpec tspec disk_template su) allocnodes [] [])
434
       tspec disk_template SpecTiered opts
435

    
436
  printTiered machine_r spec_map nl trl_nl treason
437

    
438
  -- Run the standard (avg-mode) allocation
439

    
440
  let ispec = fromMaybe (rspecFromISpec (iPolicyStdSpec ipol))
441
              (optStdSpec opts)
442

    
443
  (sreason, fin_nl, allocs, _) <-
444
      runAllocation cdata stop_allocation
445
            (Cluster.iterateAlloc nl il alloclimit
446
             (instFromSpec ispec disk_template su) allocnodes [] [])
447
            ispec disk_template SpecNormal opts
448

    
449
  printResults machine_r nl fin_nl num_instances allocs sreason
450

    
451
  -- Print final result
452

    
453
  printFinalHTS machine_r