Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Program / Hspace.hs @ 885759da

History | View | Annotate | Download (19.4 kB)

1
{-| Cluster space sizing
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2009, 2010, 2011, 2012, 2013 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 = do
58
  luxi <- oLuxiSocket
59
  return
60
    [ oPrintNodes
61
    , oDataFile
62
    , oDiskTemplate
63
    , oSpindleUse
64
    , oNodeSim
65
    , oRapiMaster
66
    , luxi
67
    , oIAllocSrc
68
    , oVerbose
69
    , oQuiet
70
    , oOfflineNode
71
    , oMachineReadable
72
    , oMaxCpu
73
    , oMaxSolLength
74
    , oMinDisk
75
    , oStdSpec
76
    , oTieredSpec
77
    , oSaveCluster
78
    ]
79

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

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

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

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

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

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

    
108
-- | The \"name\" of a 'SpecType'.
109
specName :: SpecType -> String
110
specName SpecNormal = "Standard"
111
specName SpecTiered = "Tiered"
112

    
113
-- | Efficiency generic function.
114
effFn :: (Cluster.CStats -> Integer)
115
      -> (Cluster.CStats -> Double)
116
      -> Cluster.CStats -> Double
117
effFn fi ft cs = fromIntegral (fi cs) / ft cs
118

    
119
-- | Memory efficiency.
120
memEff :: Cluster.CStats -> Double
121
memEff = effFn Cluster.csImem Cluster.csTmem
122

    
123
-- | Disk efficiency.
124
dskEff :: Cluster.CStats -> Double
125
dskEff = effFn Cluster.csIdsk Cluster.csTdsk
126

    
127
-- | Cpu efficiency.
128
cpuEff :: Cluster.CStats -> Double
129
cpuEff = effFn Cluster.csIcpu (fromIntegral . Cluster.csVcpu)
130

    
131
-- | Spindles efficiency.
132
spnEff :: Cluster.CStats -> Double
133
spnEff = effFn Cluster.csIspn Cluster.csTspn
134

    
135
-- | Holds data for converting a 'Cluster.CStats' structure into
136
-- detailed statistics.
137
statsData :: [(String, Cluster.CStats -> String)]
138
statsData = [ ("SCORE", printf "%.8f" . Cluster.csScore)
139
            , ("INST_CNT", printf "%d" . Cluster.csNinst)
140
            , ("MEM_FREE", printf "%d" . Cluster.csFmem)
141
            , ("MEM_AVAIL", printf "%d" . Cluster.csAmem)
142
            , ("MEM_RESVD",
143
               \cs -> printf "%d" (Cluster.csFmem cs - Cluster.csAmem cs))
144
            , ("MEM_INST", printf "%d" . Cluster.csImem)
145
            , ("MEM_OVERHEAD",
146
               \cs -> printf "%d" (Cluster.csXmem cs + Cluster.csNmem cs))
147
            , ("MEM_EFF", printf "%.8f" . memEff)
148
            , ("DSK_FREE", printf "%d" . Cluster.csFdsk)
149
            , ("DSK_AVAIL", printf "%d". Cluster.csAdsk)
150
            , ("DSK_RESVD",
151
               \cs -> printf "%d" (Cluster.csFdsk cs - Cluster.csAdsk cs))
152
            , ("DSK_INST", printf "%d" . Cluster.csIdsk)
153
            , ("DSK_EFF", printf "%.8f" . dskEff)
154
            , ("SPN_FREE", printf "%d" . Cluster.csFspn)
155
            , ("SPN_INST", printf "%d" . Cluster.csIspn)
156
            , ("SPN_EFF", printf "%.8f" . spnEff)
157
            , ("CPU_INST", printf "%d" . Cluster.csIcpu)
158
            , ("CPU_EFF", printf "%.8f" . cpuEff)
159
            , ("MNODE_MEM_AVAIL", printf "%d" . Cluster.csMmem)
160
            , ("MNODE_DSK_AVAIL", printf "%d" . Cluster.csMdsk)
161
            ]
162

    
163
-- | List holding 'RSpec' formatting information.
164
specData :: [(String, RSpec -> String)]
165
specData = [ ("MEM", printf "%d" . rspecMem)
166
           , ("DSK", printf "%d" . rspecDsk)
167
           , ("CPU", printf "%d" . rspecCpu)
168
           ]
169

    
170
-- | 'RSpec' formatting information including spindles.
171
specDataSpn :: [(String, RSpec -> String)]
172
specDataSpn = specData ++ [("SPN", printf "%d" . rspecSpn)]
173

    
174
-- | List holding 'Cluster.CStats' formatting information.
175
clusterData :: [(String, Cluster.CStats -> String)]
176
clusterData = [ ("MEM", printf "%.0f" . Cluster.csTmem)
177
              , ("DSK", printf "%.0f" . Cluster.csTdsk)
178
              , ("CPU", printf "%.0f" . Cluster.csTcpu)
179
              , ("VCPU", printf "%d" . Cluster.csVcpu)
180
              ]
181

    
182
-- | 'Cluster.CStats' formatting information including spindles
183
clusterDataSpn :: [(String, Cluster.CStats -> String)]
184
clusterDataSpn = clusterData ++ [("SPN", printf "%.0f" . Cluster.csTspn)]
185

    
186
-- | Function to print stats for a given phase.
187
printStats :: Phase -> Cluster.CStats -> [(String, String)]
188
printStats ph cs =
189
  map (\(s, fn) -> (printf "%s_%s" kind s, fn cs)) statsData
190
  where kind = case ph of
191
                 PInitial -> "INI"
192
                 PFinal -> "FIN"
193
                 PTiered -> "TRL"
194

    
195
-- | Print failure reason and scores
196
printFRScores :: Node.List -> Node.List -> [(FailMode, Int)] -> IO ()
197
printFRScores ini_nl fin_nl sreason = do
198
  printf "  - most likely failure reason: %s\n" $ failureReason sreason::IO ()
199
  printClusterScores ini_nl fin_nl
200
  printClusterEff (Cluster.totalResources fin_nl) (Node.haveExclStorage fin_nl)
201

    
202
-- | Print final stats and related metrics.
203
printResults :: Bool -> Node.List -> Node.List -> Int -> Int
204
             -> [(FailMode, Int)] -> IO ()
205
printResults True _ fin_nl num_instances allocs sreason = do
206
  let fin_stats = Cluster.totalResources fin_nl
207
      fin_instances = num_instances + allocs
208

    
209
  exitWhen (num_instances + allocs /= Cluster.csNinst fin_stats) $
210
           printf "internal inconsistency, allocated (%d)\
211
                  \ != counted (%d)\n" (num_instances + allocs)
212
           (Cluster.csNinst fin_stats)
213

    
214
  main_reason <- exitIfEmpty "Internal error, no failure reasons?!" sreason
215

    
216
  printKeysHTS $ printStats PFinal fin_stats
217
  printKeysHTS [ ("ALLOC_USAGE", printf "%.8f"
218
                                   ((fromIntegral num_instances::Double) /
219
                                   fromIntegral fin_instances))
220
               , ("ALLOC_INSTANCES", printf "%d" allocs)
221
               , ("ALLOC_FAIL_REASON", map toUpper . show . fst $ main_reason)
222
               ]
223
  printKeysHTS $ map (\(x, y) -> (printf "ALLOC_%s_CNT" (show x),
224
                                  printf "%d" y)) sreason
225

    
226
printResults False ini_nl fin_nl _ allocs sreason = do
227
  putStrLn "Normal (fixed-size) allocation results:"
228
  printf "  - %3d instances allocated\n" allocs :: IO ()
229
  printFRScores ini_nl fin_nl sreason
230

    
231
-- | Prints the final @OK@ marker in machine readable output.
232
printFinalHTS :: Bool -> IO ()
233
printFinalHTS = printFinal htsPrefix
234

    
235
{-# ANN tieredSpecMap "HLint: ignore Use alternative" #-}
236
-- | Compute the tiered spec counts from a list of allocated
237
-- instances.
238
tieredSpecMap :: [Instance.Instance]
239
              -> [(RSpec, Int)]
240
tieredSpecMap trl_ixes =
241
  let fin_trl_ixes = reverse trl_ixes
242
      ix_byspec = groupBy ((==) `on` Instance.specOf) fin_trl_ixes
243
      -- head is "safe" here, as groupBy returns list of non-empty lists
244
      spec_map = map (\ixs -> (Instance.specOf $ head ixs, length ixs))
245
                 ix_byspec
246
  in spec_map
247

    
248
-- | Formats a spec map to strings.
249
formatSpecMap :: [(RSpec, Int)] -> [String]
250
formatSpecMap =
251
  map (\(spec, cnt) -> printf "%d,%d,%d,%d=%d" (rspecMem spec)
252
                       (rspecDsk spec) (rspecCpu spec) (rspecSpn spec) cnt)
253

    
254
-- | Formats \"key-metrics\" values.
255
formatRSpec :: String -> AllocInfo -> [(String, String)]
256
formatRSpec s r =
257
  [ ("KM_" ++ s ++ "_CPU", show $ allocInfoVCpus r)
258
  , ("KM_" ++ s ++ "_NPU", show $ allocInfoNCpus r)
259
  , ("KM_" ++ s ++ "_MEM", show $ allocInfoMem r)
260
  , ("KM_" ++ s ++ "_DSK", show $ allocInfoDisk r)
261
  , ("KM_" ++ s ++ "_SPN", show $ allocInfoSpn r)
262
  ]
263

    
264
-- | Shows allocations stats.
265
printAllocationStats :: Node.List -> Node.List -> IO ()
266
printAllocationStats ini_nl fin_nl = do
267
  let ini_stats = Cluster.totalResources ini_nl
268
      fin_stats = Cluster.totalResources fin_nl
269
      (rini, ralo, runa) = Cluster.computeAllocationDelta ini_stats fin_stats
270
  printKeysHTS $ formatRSpec "USED" rini
271
  printKeysHTS $ formatRSpec "POOL" ralo
272
  printKeysHTS $ formatRSpec "UNAV" runa
273

    
274
-- | Format a list of key\/values as a shell fragment.
275
printKeysHTS :: [(String, String)] -> IO ()
276
printKeysHTS = printKeys htsPrefix
277

    
278
-- | Converts instance data to a list of strings.
279
printInstance :: Node.List -> Instance.Instance -> [String]
280
printInstance nl i = [ Instance.name i
281
                     , Container.nameOf nl $ Instance.pNode i
282
                     , let sdx = Instance.sNode i
283
                       in if sdx == Node.noSecondary then ""
284
                          else Container.nameOf nl sdx
285
                     , show (Instance.mem i)
286
                     , show (Instance.dsk i)
287
                     , show (Instance.vcpus i)
288
                     , if Node.haveExclStorage nl
289
                       then case Instance.getTotalSpindles i of
290
                              Nothing -> "?"
291
                              Just sp -> show sp
292
                       else ""
293
                     ]
294

    
295
-- | Optionally print the allocation map.
296
printAllocationMap :: Int -> String
297
                   -> Node.List -> [Instance.Instance] -> IO ()
298
printAllocationMap verbose msg nl ixes =
299
  when (verbose > 1) $ do
300
    hPutStrLn stderr (msg ++ " map")
301
    hPutStr stderr . unlines . map ((:) ' ' .  unwords) $
302
            formatTable (map (printInstance nl) (reverse ixes))
303
                        -- This is the numberic-or-not field
304
                        -- specification; the first three fields are
305
                        -- strings, whereas the rest are numeric
306
                       [False, False, False, True, True, True, True]
307

    
308
-- | Formats nicely a list of resources.
309
formatResources :: a -> [(String, a->String)] -> String
310
formatResources res =
311
    intercalate ", " . map (\(a, fn) -> a ++ " " ++ fn res)
312

    
313
-- | Print the cluster resources.
314
printCluster :: Bool -> Cluster.CStats -> Int -> Bool -> IO ()
315
printCluster True ini_stats node_count _ = do
316
  printKeysHTS $ map (\(a, fn) -> ("CLUSTER_" ++ a, fn ini_stats))
317
    clusterDataSpn
318
  printKeysHTS [("CLUSTER_NODES", printf "%d" node_count)]
319
  printKeysHTS $ printStats PInitial ini_stats
320

    
321
printCluster False ini_stats node_count print_spn = do
322
  let cldata = if print_spn then clusterDataSpn else clusterData
323
  printf "The cluster has %d nodes and the following resources:\n  %s.\n"
324
         node_count (formatResources ini_stats cldata)::IO ()
325
  printf "There are %s initial instances on the cluster.\n"
326
             (if inst_count > 0 then show inst_count else "no" )
327
      where inst_count = Cluster.csNinst ini_stats
328

    
329
-- | Prints the normal instance spec.
330
printISpec :: Bool -> RSpec -> SpecType -> DiskTemplate -> Bool -> IO ()
331
printISpec True ispec spec disk_template _ = do
332
  printKeysHTS $ map (\(a, fn) -> (prefix ++ "_" ++ a, fn ispec)) specDataSpn
333
  printKeysHTS [ (prefix ++ "_RQN", printf "%d" req_nodes) ]
334
  printKeysHTS [ (prefix ++ "_DISK_TEMPLATE",
335
                  diskTemplateToRaw disk_template) ]
336
      where req_nodes = Instance.requiredNodes disk_template
337
            prefix = specPrefix spec
338

    
339
printISpec False ispec spec disk_template print_spn =
340
  let spdata = if print_spn then specDataSpn else specData
341
  in printf "%s instance spec is:\n  %s, using disk\
342
            \ template '%s'.\n"
343
            (specDescription spec)
344
            (formatResources ispec spdata) (diskTemplateToRaw disk_template)
345

    
346
-- | Prints the tiered results.
347
printTiered :: Bool -> [(RSpec, Int)]
348
            -> Node.List -> Node.List -> [(FailMode, Int)] -> IO ()
349
printTiered True spec_map nl trl_nl _ = do
350
  printKeysHTS $ printStats PTiered (Cluster.totalResources trl_nl)
351
  printKeysHTS [("TSPEC", unwords (formatSpecMap spec_map))]
352
  printAllocationStats nl trl_nl
353

    
354
printTiered False spec_map ini_nl fin_nl sreason = do
355
  _ <- printf "Tiered allocation results:\n"
356
  let spdata = if Node.haveExclStorage ini_nl then specDataSpn else specData
357
  if null spec_map
358
    then putStrLn "  - no instances allocated"
359
    else mapM_ (\(ispec, cnt) ->
360
                  printf "  - %3d instances of spec %s\n" cnt
361
                           (formatResources ispec spdata)) spec_map
362
  printFRScores ini_nl fin_nl sreason
363

    
364
-- | Displays the initial/final cluster scores.
365
printClusterScores :: Node.List -> Node.List -> IO ()
366
printClusterScores ini_nl fin_nl = do
367
  printf "  - initial cluster score: %.8f\n" $ Cluster.compCV ini_nl::IO ()
368
  printf "  -   final cluster score: %.8f\n" $ Cluster.compCV fin_nl
369

    
370
-- | Displays the cluster efficiency.
371
printClusterEff :: Cluster.CStats -> Bool -> IO ()
372
printClusterEff cs print_spn = do
373
  let format = [("memory", memEff),
374
                ("disk", dskEff),
375
                ("vcpu", cpuEff)] ++
376
               [("spindles", spnEff) | print_spn]
377
      len = maximum $ map (length . fst) format
378
  mapM_ (\(s, fn) ->
379
          printf "  - %*s usage efficiency: %5.2f%%\n" len s (fn cs * 100))
380
    format
381

    
382
-- | Computes the most likely failure reason.
383
failureReason :: [(FailMode, Int)] -> String
384
failureReason = show . fst . head
385

    
386
-- | Sorts the failure reasons.
387
sortReasons :: [(FailMode, Int)] -> [(FailMode, Int)]
388
sortReasons = sortBy (flip (comparing snd))
389

    
390
-- | Runs an allocation algorithm and saves cluster state.
391
runAllocation :: ClusterData                -- ^ Cluster data
392
              -> Maybe Cluster.AllocResult  -- ^ Optional stop-allocation
393
              -> Result Cluster.AllocResult -- ^ Allocation result
394
              -> RSpec                      -- ^ Requested instance spec
395
              -> DiskTemplate               -- ^ Requested disk template
396
              -> SpecType                   -- ^ Allocation type
397
              -> Options                    -- ^ CLI options
398
              -> IO (FailStats, Node.List, Int, [(RSpec, Int)])
399
runAllocation cdata stop_allocation actual_result spec dt mode opts = do
400
  (reasons, new_nl, new_il, new_ixes, _) <-
401
      case stop_allocation of
402
        Just result_noalloc -> return result_noalloc
403
        Nothing -> exitIfBad "failure during allocation" actual_result
404

    
405
  let name = specName mode
406
      descr = name ++ " allocation"
407
      ldescr = "after " ++ map toLower descr
408
      excstor = Node.haveExclStorage new_nl
409

    
410
  printISpec (optMachineReadable opts) spec mode dt excstor
411

    
412
  printAllocationMap (optVerbose opts) descr new_nl new_ixes
413

    
414
  maybePrintNodes (optShowNodes opts) descr (Cluster.printNodes new_nl)
415

    
416
  maybeSaveData (optSaveCluster opts) (map toLower name) ldescr
417
                    (cdata { cdNodes = new_nl, cdInstances = new_il})
418

    
419
  return (sortReasons reasons, new_nl, length new_ixes, tieredSpecMap new_ixes)
420

    
421
-- | Create an instance from a given spec.
422
-- For values not implied by the resorce specification (like distribution of
423
-- of the disk space to individual disks), sensible defaults are guessed (e.g.,
424
-- having a single disk).
425
instFromSpec :: RSpec -> DiskTemplate -> Int -> Instance.Instance
426
instFromSpec spx dt su =
427
  Instance.create "new" (rspecMem spx) (rspecDsk spx)
428
    [Instance.Disk (rspecDsk spx) (Just $ rspecSpn spx)]
429
    (rspecCpu spx) Running [] True (-1) (-1) dt su []
430

    
431
combineTiered :: Maybe Int -> Cluster.AllocNodes -> Cluster.AllocResult ->
432
           Instance.Instance -> Result Cluster.AllocResult
433
combineTiered limit allocnodes result inst = do
434
  let (_, nl, il, ixes, cstats) = result
435
      ixes_cnt = length ixes
436
      (stop, newlimit) = case limit of
437
        Nothing -> (False, Nothing)
438
        Just n -> (n <= ixes_cnt, Just (n - ixes_cnt))
439
  if stop
440
    then return result
441
    else Cluster.tieredAlloc nl il newlimit inst allocnodes ixes cstats
442

    
443
-- | Main function.
444
main :: Options -> [String] -> IO ()
445
main opts args = do
446
  exitUnless (null args) "This program doesn't take any arguments."
447

    
448
  let verbose = optVerbose opts
449
      machine_r = optMachineReadable opts
450

    
451
  orig_cdata@(ClusterData gl fixed_nl il _ ipol) <- loadExternalData opts
452
  nl <- setNodeStatus opts fixed_nl
453

    
454
  cluster_disk_template <-
455
    case iPolicyDiskTemplates ipol of
456
      first_templ:_ -> return first_templ
457
      _ -> exitErr "null list of disk templates received from cluster"
458

    
459
  let num_instances = Container.size il
460
      all_nodes = Container.elems fixed_nl
461
      cdata = orig_cdata { cdNodes = fixed_nl }
462
      disk_template = fromMaybe cluster_disk_template (optDiskTemplate opts)
463
      req_nodes = Instance.requiredNodes disk_template
464
      csf = commonSuffix fixed_nl il
465
      su = fromMaybe (iSpecSpindleUse $ iPolicyStdSpec ipol)
466
                     (optSpindleUse opts)
467

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

    
471
  maybePrintNodes (optShowNodes opts) "Initial cluster" (Cluster.printNodes nl)
472

    
473
  when (verbose > 2) $
474
         hPrintf stderr "Initial coefficients: overall %.8f\n%s"
475
                 (Cluster.compCV nl) (Cluster.printStats "  " nl)
476

    
477
  printCluster machine_r (Cluster.totalResources nl) (length all_nodes)
478
    (Node.haveExclStorage nl)
479

    
480
  let stop_allocation = case Cluster.computeBadItems nl il of
481
                          ([], _) -> Nothing
482
                          _ -> Just ([(FailN1, 1)]::FailStats, nl, il, [], [])
483
      alloclimit = if optMaxLength opts == -1
484
                   then Nothing
485
                   else Just (optMaxLength opts)
486

    
487
  allocnodes <- exitIfBad "failure during allocation" $
488
                Cluster.genAllocNodes gl nl req_nodes True
489

    
490
  -- Run the tiered allocation
491

    
492
  let minmaxes = iPolicyMinMaxISpecs ipol
493
      tspecs = case optTieredSpec opts of
494
                 Nothing -> map (rspecFromISpec . minMaxISpecsMaxSpec)
495
                            minmaxes
496
                 Just t -> [t]
497
      tinsts = map (\ts -> instFromSpec ts disk_template su) tspecs
498
  tspec <- case tspecs of
499
    [] -> exitErr "Empty list of specs received from the cluster"
500
    t:_ -> return t
501

    
502
  (treason, trl_nl, _, spec_map) <-
503
    runAllocation cdata stop_allocation
504
       (foldM (combineTiered alloclimit allocnodes) ([], nl, il, [], []) tinsts)
505
       tspec disk_template SpecTiered opts
506

    
507
  printTiered machine_r spec_map nl trl_nl treason
508

    
509
  -- Run the standard (avg-mode) allocation
510

    
511
  let ispec = fromMaybe (rspecFromISpec (iPolicyStdSpec ipol))
512
              (optStdSpec opts)
513

    
514
  (sreason, fin_nl, allocs, _) <-
515
      runAllocation cdata stop_allocation
516
            (Cluster.iterateAlloc nl il alloclimit
517
             (instFromSpec ispec disk_template su) allocnodes [] [])
518
            ispec disk_template SpecNormal opts
519

    
520
  printResults machine_r nl fin_nl num_instances allocs sreason
521

    
522
  -- Print final result
523

    
524
  printFinalHTS machine_r