Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (16.7 kB)

1 e10be8f2 Iustin Pop
{-| Cluster space sizing
2 e10be8f2 Iustin Pop
3 e10be8f2 Iustin Pop
-}
4 e10be8f2 Iustin Pop
5 e10be8f2 Iustin Pop
{-
6 e10be8f2 Iustin Pop
7 1f5635a9 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
8 e10be8f2 Iustin Pop
9 e10be8f2 Iustin Pop
This program is free software; you can redistribute it and/or modify
10 e10be8f2 Iustin Pop
it under the terms of the GNU General Public License as published by
11 e10be8f2 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 e10be8f2 Iustin Pop
(at your option) any later version.
13 e10be8f2 Iustin Pop
14 e10be8f2 Iustin Pop
This program is distributed in the hope that it will be useful, but
15 e10be8f2 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 e10be8f2 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 e10be8f2 Iustin Pop
General Public License for more details.
18 e10be8f2 Iustin Pop
19 e10be8f2 Iustin Pop
You should have received a copy of the GNU General Public License
20 e10be8f2 Iustin Pop
along with this program; if not, write to the Free Software
21 e10be8f2 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 e10be8f2 Iustin Pop
02110-1301, USA.
23 e10be8f2 Iustin Pop
24 e10be8f2 Iustin Pop
-}
25 e10be8f2 Iustin Pop
26 22278fa7 Iustin Pop
module Ganeti.HTools.Program.Hspace
27 22278fa7 Iustin Pop
  (main
28 22278fa7 Iustin Pop
  , options
29 22278fa7 Iustin Pop
  , arguments
30 22278fa7 Iustin Pop
  ) where
31 e10be8f2 Iustin Pop
32 cc532bdd Iustin Pop
import Control.Monad
33 79eef90b Agata Murawska
import Data.Char (toUpper, toLower)
34 756df409 Iustin Pop
import Data.Function (on)
35 e10be8f2 Iustin Pop
import Data.List
36 be468da0 Iustin Pop
import Data.Maybe (fromMaybe)
37 5182e970 Iustin Pop
import Data.Ord (comparing)
38 e10be8f2 Iustin Pop
import System.IO
39 e10be8f2 Iustin Pop
40 2795466b Iustin Pop
import Text.Printf (printf, hPrintf)
41 e10be8f2 Iustin Pop
42 e10be8f2 Iustin Pop
import qualified Ganeti.HTools.Container as Container
43 e10be8f2 Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
44 e10be8f2 Iustin Pop
import qualified Ganeti.HTools.Node as Node
45 e10be8f2 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
46 e10be8f2 Iustin Pop
47 01e52493 Iustin Pop
import Ganeti.BasicTypes
48 22278fa7 Iustin Pop
import Ganeti.Common
49 f2280553 Iustin Pop
import Ganeti.HTools.Types
50 0427285d Iustin Pop
import Ganeti.HTools.CLI
51 e8f89bb6 Iustin Pop
import Ganeti.HTools.ExtLoader
52 4938fa30 Guido Trotter
import Ganeti.HTools.Loader
53 26d62e4c Iustin Pop
import Ganeti.Utils
54 e10be8f2 Iustin Pop
55 179c0828 Iustin Pop
-- | Options list and functions.
56 d66aa238 Iustin Pop
options :: IO [OptType]
57 e10be8f2 Iustin Pop
options =
58 d66aa238 Iustin Pop
  return
59 d66aa238 Iustin Pop
    [ oPrintNodes
60 d66aa238 Iustin Pop
    , oDataFile
61 d66aa238 Iustin Pop
    , oDiskTemplate
62 d66aa238 Iustin Pop
    , oSpindleUse
63 d66aa238 Iustin Pop
    , oNodeSim
64 d66aa238 Iustin Pop
    , oRapiMaster
65 d66aa238 Iustin Pop
    , oLuxiSocket
66 d66aa238 Iustin Pop
    , oIAllocSrc
67 d66aa238 Iustin Pop
    , oVerbose
68 d66aa238 Iustin Pop
    , oQuiet
69 d66aa238 Iustin Pop
    , oOfflineNode
70 d66aa238 Iustin Pop
    , oMachineReadable
71 d66aa238 Iustin Pop
    , oMaxCpu
72 d66aa238 Iustin Pop
    , oMaxSolLength
73 d66aa238 Iustin Pop
    , oMinDisk
74 d66aa238 Iustin Pop
    , oStdSpec
75 d66aa238 Iustin Pop
    , oTieredSpec
76 d66aa238 Iustin Pop
    , oSaveCluster
77 d66aa238 Iustin Pop
    ]
78 e10be8f2 Iustin Pop
79 22278fa7 Iustin Pop
-- | The list of arguments supported by the program.
80 22278fa7 Iustin Pop
arguments :: [ArgCompletion]
81 22278fa7 Iustin Pop
arguments = []
82 22278fa7 Iustin Pop
83 fcebc9db Iustin Pop
-- | The allocation phase we're in (initial, after tiered allocs, or
84 fcebc9db Iustin Pop
-- after regular allocation).
85 fcebc9db Iustin Pop
data Phase = PInitial
86 fcebc9db Iustin Pop
           | PFinal
87 fcebc9db Iustin Pop
           | PTiered
88 2bbf77cc Iustin Pop
89 375969eb Iustin Pop
-- | The kind of instance spec we print.
90 375969eb Iustin Pop
data SpecType = SpecNormal
91 375969eb Iustin Pop
              | SpecTiered
92 375969eb Iustin Pop
93 79eef90b Agata Murawska
-- | Prefix for machine readable names
94 79eef90b Agata Murawska
htsPrefix :: String
95 79eef90b Agata Murawska
htsPrefix = "HTS"
96 79eef90b Agata Murawska
97 375969eb Iustin Pop
-- | What we prefix a spec with.
98 375969eb Iustin Pop
specPrefix :: SpecType -> String
99 375969eb Iustin Pop
specPrefix SpecNormal = "SPEC"
100 375969eb Iustin Pop
specPrefix SpecTiered = "TSPEC_INI"
101 375969eb Iustin Pop
102 375969eb Iustin Pop
-- | The description of a spec.
103 375969eb Iustin Pop
specDescription :: SpecType -> String
104 e86f7f65 Iustin Pop
specDescription SpecNormal = "Standard (fixed-size)"
105 375969eb Iustin Pop
specDescription SpecTiered = "Tiered (initial size)"
106 375969eb Iustin Pop
107 375969eb Iustin Pop
-- | Efficiency generic function.
108 375969eb Iustin Pop
effFn :: (Cluster.CStats -> Integer)
109 375969eb Iustin Pop
      -> (Cluster.CStats -> Double)
110 1b0a6356 Iustin Pop
      -> Cluster.CStats -> Double
111 375969eb Iustin Pop
effFn fi ft cs = fromIntegral (fi cs) / ft cs
112 375969eb Iustin Pop
113 375969eb Iustin Pop
-- | Memory efficiency.
114 375969eb Iustin Pop
memEff :: Cluster.CStats -> Double
115 375969eb Iustin Pop
memEff = effFn Cluster.csImem Cluster.csTmem
116 375969eb Iustin Pop
117 375969eb Iustin Pop
-- | Disk efficiency.
118 375969eb Iustin Pop
dskEff :: Cluster.CStats -> Double
119 375969eb Iustin Pop
dskEff = effFn Cluster.csIdsk Cluster.csTdsk
120 375969eb Iustin Pop
121 375969eb Iustin Pop
-- | Cpu efficiency.
122 375969eb Iustin Pop
cpuEff :: Cluster.CStats -> Double
123 375969eb Iustin Pop
cpuEff = effFn Cluster.csIcpu (fromIntegral . Cluster.csVcpu)
124 375969eb Iustin Pop
125 179c0828 Iustin Pop
-- | Holds data for converting a 'Cluster.CStats' structure into
126 dd77da99 Helga Velroyen
-- detailed statistics.
127 2bbf77cc Iustin Pop
statsData :: [(String, Cluster.CStats -> String)]
128 f5b553da Iustin Pop
statsData = [ ("SCORE", printf "%.8f" . Cluster.csScore)
129 f5b553da Iustin Pop
            , ("INST_CNT", printf "%d" . Cluster.csNinst)
130 f5b553da Iustin Pop
            , ("MEM_FREE", printf "%d" . Cluster.csFmem)
131 f5b553da Iustin Pop
            , ("MEM_AVAIL", printf "%d" . Cluster.csAmem)
132 2bbf77cc Iustin Pop
            , ("MEM_RESVD",
133 f5b553da Iustin Pop
               \cs -> printf "%d" (Cluster.csFmem cs - Cluster.csAmem cs))
134 f5b553da Iustin Pop
            , ("MEM_INST", printf "%d" . Cluster.csImem)
135 2bbf77cc Iustin Pop
            , ("MEM_OVERHEAD",
136 f5b553da Iustin Pop
               \cs -> printf "%d" (Cluster.csXmem cs + Cluster.csNmem cs))
137 375969eb Iustin Pop
            , ("MEM_EFF", printf "%.8f" . memEff)
138 f5b553da Iustin Pop
            , ("DSK_FREE", printf "%d" . Cluster.csFdsk)
139 9739b6b8 Iustin Pop
            , ("DSK_AVAIL", printf "%d". Cluster.csAdsk)
140 2bbf77cc Iustin Pop
            , ("DSK_RESVD",
141 f5b553da Iustin Pop
               \cs -> printf "%d" (Cluster.csFdsk cs - Cluster.csAdsk cs))
142 f5b553da Iustin Pop
            , ("DSK_INST", printf "%d" . Cluster.csIdsk)
143 375969eb Iustin Pop
            , ("DSK_EFF", printf "%.8f" . dskEff)
144 f5b553da Iustin Pop
            , ("CPU_INST", printf "%d" . Cluster.csIcpu)
145 375969eb Iustin Pop
            , ("CPU_EFF", printf "%.8f" . cpuEff)
146 f5b553da Iustin Pop
            , ("MNODE_MEM_AVAIL", printf "%d" . Cluster.csMmem)
147 f5b553da Iustin Pop
            , ("MNODE_DSK_AVAIL", printf "%d" . Cluster.csMdsk)
148 2bbf77cc Iustin Pop
            ]
149 2bbf77cc Iustin Pop
150 179c0828 Iustin Pop
-- | List holding 'RSpec' formatting information.
151 1f9066c0 Iustin Pop
specData :: [(String, RSpec -> String)]
152 1f9066c0 Iustin Pop
specData = [ ("MEM", printf "%d" . rspecMem)
153 1f9066c0 Iustin Pop
           , ("DSK", printf "%d" . rspecDsk)
154 1f9066c0 Iustin Pop
           , ("CPU", printf "%d" . rspecCpu)
155 2bbf77cc Iustin Pop
           ]
156 2bbf77cc Iustin Pop
157 179c0828 Iustin Pop
-- | List holding 'Cluster.CStats' formatting information.
158 2bbf77cc Iustin Pop
clusterData :: [(String, Cluster.CStats -> String)]
159 f5b553da Iustin Pop
clusterData = [ ("MEM", printf "%.0f" . Cluster.csTmem)
160 f5b553da Iustin Pop
              , ("DSK", printf "%.0f" . Cluster.csTdsk)
161 f5b553da Iustin Pop
              , ("CPU", printf "%.0f" . Cluster.csTcpu)
162 bd3286e9 Iustin Pop
              , ("VCPU", printf "%d" . Cluster.csVcpu)
163 2bbf77cc Iustin Pop
              ]
164 2bbf77cc Iustin Pop
165 179c0828 Iustin Pop
-- | Function to print stats for a given phase.
166 2bbf77cc Iustin Pop
printStats :: Phase -> Cluster.CStats -> [(String, String)]
167 2bbf77cc Iustin Pop
printStats ph cs =
168 2bbf77cc Iustin Pop
  map (\(s, fn) -> (printf "%s_%s" kind s, fn cs)) statsData
169 2bbf77cc Iustin Pop
  where kind = case ph of
170 2bbf77cc Iustin Pop
                 PInitial -> "INI"
171 2bbf77cc Iustin Pop
                 PFinal -> "FIN"
172 fcebc9db Iustin Pop
                 PTiered -> "TRL"
173 e10be8f2 Iustin Pop
174 2f9198be Iustin Pop
-- | Print failure reason and scores
175 2f9198be Iustin Pop
printFRScores :: Node.List -> Node.List -> [(FailMode, Int)] -> IO ()
176 2f9198be Iustin Pop
printFRScores ini_nl fin_nl sreason = do
177 2f9198be Iustin Pop
  printf "  - most likely failure reason: %s\n" $ failureReason sreason::IO ()
178 2f9198be Iustin Pop
  printClusterScores ini_nl fin_nl
179 2f9198be Iustin Pop
  printClusterEff (Cluster.totalResources fin_nl)
180 2f9198be Iustin Pop
181 375969eb Iustin Pop
-- | Print final stats and related metrics.
182 375969eb Iustin Pop
printResults :: Bool -> Node.List -> Node.List -> Int -> Int
183 375969eb Iustin Pop
             -> [(FailMode, Int)] -> IO ()
184 375969eb Iustin Pop
printResults True _ fin_nl num_instances allocs sreason = do
185 dca7f396 Iustin Pop
  let fin_stats = Cluster.totalResources fin_nl
186 dca7f396 Iustin Pop
      fin_instances = num_instances + allocs
187 dca7f396 Iustin Pop
188 88a10df5 Iustin Pop
  exitWhen (num_instances + allocs /= Cluster.csNinst fin_stats) $
189 88a10df5 Iustin Pop
           printf "internal inconsistency, allocated (%d)\
190 88a10df5 Iustin Pop
                  \ != counted (%d)\n" (num_instances + allocs)
191 88a10df5 Iustin Pop
           (Cluster.csNinst fin_stats)
192 de4ac2c2 Iustin Pop
193 79eef90b Agata Murawska
  printKeysHTS $ printStats PFinal fin_stats
194 79eef90b Agata Murawska
  printKeysHTS [ ("ALLOC_USAGE", printf "%.8f"
195 e60fa4af Agata Murawska
                                   ((fromIntegral num_instances::Double) /
196 e60fa4af Agata Murawska
                                   fromIntegral fin_instances))
197 e60fa4af Agata Murawska
               , ("ALLOC_INSTANCES", printf "%d" allocs)
198 e60fa4af Agata Murawska
               , ("ALLOC_FAIL_REASON", map toUpper . show . fst $ head sreason)
199 e60fa4af Agata Murawska
               ]
200 79eef90b Agata Murawska
  printKeysHTS $ map (\(x, y) -> (printf "ALLOC_%s_CNT" (show x),
201 e60fa4af Agata Murawska
                                  printf "%d" y)) sreason
202 375969eb Iustin Pop
203 375969eb Iustin Pop
printResults False ini_nl fin_nl _ allocs sreason = do
204 375969eb Iustin Pop
  putStrLn "Normal (fixed-size) allocation results:"
205 375969eb Iustin Pop
  printf "  - %3d instances allocated\n" allocs :: IO ()
206 2f9198be Iustin Pop
  printFRScores ini_nl fin_nl sreason
207 375969eb Iustin Pop
208 375969eb Iustin Pop
-- | Prints the final @OK@ marker in machine readable output.
209 79eef90b Agata Murawska
printFinalHTS :: Bool -> IO ()
210 79eef90b Agata Murawska
printFinalHTS = printFinal htsPrefix
211 375969eb Iustin Pop
212 756df409 Iustin Pop
-- | Compute the tiered spec counts from a list of allocated
213 756df409 Iustin Pop
-- instances.
214 756df409 Iustin Pop
tieredSpecMap :: [Instance.Instance]
215 756df409 Iustin Pop
              -> [(RSpec, Int)]
216 756df409 Iustin Pop
tieredSpecMap trl_ixes =
217 3c3690aa Iustin Pop
  let fin_trl_ixes = reverse trl_ixes
218 3c3690aa Iustin Pop
      ix_byspec = groupBy ((==) `on` Instance.specOf) fin_trl_ixes
219 3c3690aa Iustin Pop
      spec_map = map (\ixs -> (Instance.specOf $ head ixs, length ixs))
220 3c3690aa Iustin Pop
                 ix_byspec
221 3c3690aa Iustin Pop
  in spec_map
222 756df409 Iustin Pop
223 756df409 Iustin Pop
-- | Formats a spec map to strings.
224 756df409 Iustin Pop
formatSpecMap :: [(RSpec, Int)] -> [String]
225 756df409 Iustin Pop
formatSpecMap =
226 3c3690aa Iustin Pop
  map (\(spec, cnt) -> printf "%d,%d,%d=%d" (rspecMem spec)
227 3c3690aa Iustin Pop
                       (rspecDsk spec) (rspecCpu spec) cnt)
228 756df409 Iustin Pop
229 179c0828 Iustin Pop
-- | Formats \"key-metrics\" values.
230 80d7d8a1 Iustin Pop
formatRSpec :: String -> AllocInfo -> [(String, String)]
231 80d7d8a1 Iustin Pop
formatRSpec s r =
232 80d7d8a1 Iustin Pop
  [ ("KM_" ++ s ++ "_CPU", show $ allocInfoVCpus r)
233 80d7d8a1 Iustin Pop
  , ("KM_" ++ s ++ "_NPU", show $ allocInfoNCpus r)
234 80d7d8a1 Iustin Pop
  , ("KM_" ++ s ++ "_MEM", show $ allocInfoMem r)
235 80d7d8a1 Iustin Pop
  , ("KM_" ++ s ++ "_DSK", show $ allocInfoDisk r)
236 3c3690aa Iustin Pop
  ]
237 bd3286e9 Iustin Pop
238 179c0828 Iustin Pop
-- | Shows allocations stats.
239 5f3b040a Iustin Pop
printAllocationStats :: Node.List -> Node.List -> IO ()
240 5f3b040a Iustin Pop
printAllocationStats ini_nl fin_nl = do
241 bd3286e9 Iustin Pop
  let ini_stats = Cluster.totalResources ini_nl
242 bd3286e9 Iustin Pop
      fin_stats = Cluster.totalResources fin_nl
243 bd3286e9 Iustin Pop
      (rini, ralo, runa) = Cluster.computeAllocationDelta ini_stats fin_stats
244 79eef90b Agata Murawska
  printKeysHTS $ formatRSpec "USED" rini
245 79eef90b Agata Murawska
  printKeysHTS $ formatRSpec "POOL" ralo
246 79eef90b Agata Murawska
  printKeysHTS $ formatRSpec "UNAV" runa
247 9739b6b8 Iustin Pop
248 179c0828 Iustin Pop
-- | Format a list of key\/values as a shell fragment.
249 79eef90b Agata Murawska
printKeysHTS :: [(String, String)] -> IO ()
250 79eef90b Agata Murawska
printKeysHTS = printKeys htsPrefix
251 dca7f396 Iustin Pop
252 179c0828 Iustin Pop
-- | Converts instance data to a list of strings.
253 366a7c89 Iustin Pop
printInstance :: Node.List -> Instance.Instance -> [String]
254 366a7c89 Iustin Pop
printInstance nl i = [ Instance.name i
255 5182e970 Iustin Pop
                     , Container.nameOf nl $ Instance.pNode i
256 5182e970 Iustin Pop
                     , let sdx = Instance.sNode i
257 5182e970 Iustin Pop
                       in if sdx == Node.noSecondary then ""
258 5182e970 Iustin Pop
                          else Container.nameOf nl sdx
259 366a7c89 Iustin Pop
                     , show (Instance.mem i)
260 366a7c89 Iustin Pop
                     , show (Instance.dsk i)
261 366a7c89 Iustin Pop
                     , show (Instance.vcpus i)
262 366a7c89 Iustin Pop
                     ]
263 366a7c89 Iustin Pop
264 179c0828 Iustin Pop
-- | Optionally print the allocation map.
265 6eaa7bb8 Iustin Pop
printAllocationMap :: Int -> String
266 6eaa7bb8 Iustin Pop
                   -> Node.List -> [Instance.Instance] -> IO ()
267 6eaa7bb8 Iustin Pop
printAllocationMap verbose msg nl ixes =
268 6eaa7bb8 Iustin Pop
  when (verbose > 1) $ do
269 e86f7f65 Iustin Pop
    hPutStrLn stderr (msg ++ " map")
270 3603605a Iustin Pop
    hPutStr stderr . unlines . map ((:) ' ' .  unwords) $
271 6eaa7bb8 Iustin Pop
            formatTable (map (printInstance nl) (reverse ixes))
272 6eaa7bb8 Iustin Pop
                        -- This is the numberic-or-not field
273 6eaa7bb8 Iustin Pop
                        -- specification; the first three fields are
274 6eaa7bb8 Iustin Pop
                        -- strings, whereas the rest are numeric
275 6eaa7bb8 Iustin Pop
                       [False, False, False, True, True, True]
276 6eaa7bb8 Iustin Pop
277 375969eb Iustin Pop
-- | Formats nicely a list of resources.
278 1b0a6356 Iustin Pop
formatResources :: a -> [(String, a->String)] -> String
279 375969eb Iustin Pop
formatResources res =
280 375969eb Iustin Pop
    intercalate ", " . map (\(a, fn) -> a ++ " " ++ fn res)
281 375969eb Iustin Pop
282 375969eb Iustin Pop
-- | Print the cluster resources.
283 375969eb Iustin Pop
printCluster :: Bool -> Cluster.CStats -> Int -> IO ()
284 375969eb Iustin Pop
printCluster True ini_stats node_count = do
285 79eef90b Agata Murawska
  printKeysHTS $ map (\(a, fn) -> ("CLUSTER_" ++ a, fn ini_stats)) clusterData
286 79eef90b Agata Murawska
  printKeysHTS [("CLUSTER_NODES", printf "%d" node_count)]
287 79eef90b Agata Murawska
  printKeysHTS $ printStats PInitial ini_stats
288 375969eb Iustin Pop
289 375969eb Iustin Pop
printCluster False ini_stats node_count = do
290 375969eb Iustin Pop
  printf "The cluster has %d nodes and the following resources:\n  %s.\n"
291 375969eb Iustin Pop
         node_count (formatResources ini_stats clusterData)::IO ()
292 375969eb Iustin Pop
  printf "There are %s initial instances on the cluster.\n"
293 375969eb Iustin Pop
             (if inst_count > 0 then show inst_count else "no" )
294 375969eb Iustin Pop
      where inst_count = Cluster.csNinst ini_stats
295 375969eb Iustin Pop
296 375969eb Iustin Pop
-- | Prints the normal instance spec.
297 375969eb Iustin Pop
printISpec :: Bool -> RSpec -> SpecType -> DiskTemplate -> IO ()
298 375969eb Iustin Pop
printISpec True ispec spec disk_template = do
299 79eef90b Agata Murawska
  printKeysHTS $ map (\(a, fn) -> (prefix ++ "_" ++ a, fn ispec)) specData
300 79eef90b Agata Murawska
  printKeysHTS [ (prefix ++ "_RQN", printf "%d" req_nodes) ]
301 79eef90b Agata Murawska
  printKeysHTS [ (prefix ++ "_DISK_TEMPLATE",
302 e60fa4af Agata Murawska
                  diskTemplateToRaw disk_template) ]
303 375969eb Iustin Pop
      where req_nodes = Instance.requiredNodes disk_template
304 375969eb Iustin Pop
            prefix = specPrefix spec
305 375969eb Iustin Pop
306 1b0a6356 Iustin Pop
printISpec False ispec spec disk_template =
307 375969eb Iustin Pop
  printf "%s instance spec is:\n  %s, using disk\
308 375969eb Iustin Pop
         \ template '%s'.\n"
309 375969eb Iustin Pop
         (specDescription spec)
310 5f828ce4 Agata Murawska
         (formatResources ispec specData) (diskTemplateToRaw disk_template)
311 375969eb Iustin Pop
312 375969eb Iustin Pop
-- | Prints the tiered results.
313 5f3b040a Iustin Pop
printTiered :: Bool -> [(RSpec, Int)]
314 375969eb Iustin Pop
            -> Node.List -> Node.List -> [(FailMode, Int)] -> IO ()
315 5f3b040a Iustin Pop
printTiered True spec_map nl trl_nl _ = do
316 79eef90b Agata Murawska
  printKeysHTS $ printStats PTiered (Cluster.totalResources trl_nl)
317 79eef90b Agata Murawska
  printKeysHTS [("TSPEC", unwords (formatSpecMap spec_map))]
318 5f3b040a Iustin Pop
  printAllocationStats nl trl_nl
319 375969eb Iustin Pop
320 5f3b040a Iustin Pop
printTiered False spec_map ini_nl fin_nl sreason = do
321 375969eb Iustin Pop
  _ <- printf "Tiered allocation results:\n"
322 1f5635a9 Iustin Pop
  if null spec_map
323 1f5635a9 Iustin Pop
    then putStrLn "  - no instances allocated"
324 1f5635a9 Iustin Pop
    else mapM_ (\(ispec, cnt) ->
325 1f5635a9 Iustin Pop
                  printf "  - %3d instances of spec %s\n" cnt
326 1f5635a9 Iustin Pop
                           (formatResources ispec specData)) spec_map
327 2f9198be Iustin Pop
  printFRScores ini_nl fin_nl sreason
328 375969eb Iustin Pop
329 179c0828 Iustin Pop
-- | Displays the initial/final cluster scores.
330 375969eb Iustin Pop
printClusterScores :: Node.List -> Node.List -> IO ()
331 375969eb Iustin Pop
printClusterScores ini_nl fin_nl = do
332 375969eb Iustin Pop
  printf "  - initial cluster score: %.8f\n" $ Cluster.compCV ini_nl::IO ()
333 375969eb Iustin Pop
  printf "  -   final cluster score: %.8f\n" $ Cluster.compCV fin_nl
334 375969eb Iustin Pop
335 179c0828 Iustin Pop
-- | Displays the cluster efficiency.
336 375969eb Iustin Pop
printClusterEff :: Cluster.CStats -> IO ()
337 375969eb Iustin Pop
printClusterEff cs =
338 3c3690aa Iustin Pop
  mapM_ (\(s, fn) ->
339 3c3690aa Iustin Pop
           printf "  - %s usage efficiency: %5.2f%%\n" s (fn cs * 100))
340 375969eb Iustin Pop
          [("memory", memEff),
341 375969eb Iustin Pop
           ("  disk", dskEff),
342 375969eb Iustin Pop
           ("  vcpu", cpuEff)]
343 375969eb Iustin Pop
344 375969eb Iustin Pop
-- | Computes the most likely failure reason.
345 375969eb Iustin Pop
failureReason :: [(FailMode, Int)] -> String
346 375969eb Iustin Pop
failureReason = show . fst . head
347 375969eb Iustin Pop
348 375969eb Iustin Pop
-- | Sorts the failure reasons.
349 375969eb Iustin Pop
sortReasons :: [(FailMode, Int)] -> [(FailMode, Int)]
350 375969eb Iustin Pop
sortReasons = reverse . sortBy (comparing snd)
351 375969eb Iustin Pop
352 e86f7f65 Iustin Pop
-- | Runs an allocation algorithm and saves cluster state.
353 e86f7f65 Iustin Pop
runAllocation :: ClusterData                -- ^ Cluster data
354 e86f7f65 Iustin Pop
              -> Maybe Cluster.AllocResult  -- ^ Optional stop-allocation
355 e86f7f65 Iustin Pop
              -> Result Cluster.AllocResult -- ^ Allocation result
356 e86f7f65 Iustin Pop
              -> RSpec                      -- ^ Requested instance spec
357 9fdd3d0f Iustin Pop
              -> DiskTemplate               -- ^ Requested disk template
358 e86f7f65 Iustin Pop
              -> SpecType                   -- ^ Allocation type
359 e86f7f65 Iustin Pop
              -> Options                    -- ^ CLI options
360 e86f7f65 Iustin Pop
              -> IO (FailStats, Node.List, Int, [(RSpec, Int)])
361 9fdd3d0f Iustin Pop
runAllocation cdata stop_allocation actual_result spec dt mode opts = do
362 e86f7f65 Iustin Pop
  (reasons, new_nl, new_il, new_ixes, _) <-
363 e86f7f65 Iustin Pop
      case stop_allocation of
364 e86f7f65 Iustin Pop
        Just result_noalloc -> return result_noalloc
365 88a10df5 Iustin Pop
        Nothing -> exitIfBad "failure during allocation" actual_result
366 e86f7f65 Iustin Pop
367 e86f7f65 Iustin Pop
  let name = head . words . specDescription $ mode
368 e86f7f65 Iustin Pop
      descr = name ++ " allocation"
369 e86f7f65 Iustin Pop
      ldescr = "after " ++ map toLower descr
370 e86f7f65 Iustin Pop
371 9fdd3d0f Iustin Pop
  printISpec (optMachineReadable opts) spec mode dt
372 e86f7f65 Iustin Pop
373 e86f7f65 Iustin Pop
  printAllocationMap (optVerbose opts) descr new_nl new_ixes
374 e86f7f65 Iustin Pop
375 e86f7f65 Iustin Pop
  maybePrintNodes (optShowNodes opts) descr (Cluster.printNodes new_nl)
376 e86f7f65 Iustin Pop
377 e86f7f65 Iustin Pop
  maybeSaveData (optSaveCluster opts) (map toLower name) ldescr
378 e86f7f65 Iustin Pop
                    (cdata { cdNodes = new_nl, cdInstances = new_il})
379 e86f7f65 Iustin Pop
380 e86f7f65 Iustin Pop
  return (sortReasons reasons, new_nl, length new_ixes, tieredSpecMap new_ixes)
381 e86f7f65 Iustin Pop
382 8564fb47 Iustin Pop
-- | Create an instance from a given spec.
383 f0753837 René Nussbaumer
instFromSpec :: RSpec -> DiskTemplate -> Int -> Instance.Instance
384 5b11f8db Iustin Pop
instFromSpec spx =
385 8564fb47 Iustin Pop
  Instance.create "new" (rspecMem spx) (rspecDsk spx)
386 5b11f8db Iustin Pop
    (rspecCpu spx) Running [] True (-1) (-1)
387 8564fb47 Iustin Pop
388 e10be8f2 Iustin Pop
-- | Main function.
389 21839f47 Iustin Pop
main :: Options -> [String] -> IO ()
390 21839f47 Iustin Pop
main opts args = do
391 707cd3d7 Helga Velroyen
  exitUnless (null args) "This program doesn't take any arguments."
392 e10be8f2 Iustin Pop
393 2795466b Iustin Pop
  let verbose = optVerbose opts
394 375969eb Iustin Pop
      machine_r = optMachineReadable opts
395 2795466b Iustin Pop
396 be468da0 Iustin Pop
  orig_cdata@(ClusterData gl fixed_nl il _ ipol) <- loadExternalData opts
397 e86f7f65 Iustin Pop
  nl <- setNodeStatus opts fixed_nl
398 2795466b Iustin Pop
399 9fdd3d0f Iustin Pop
  cluster_disk_template <-
400 9fdd3d0f Iustin Pop
    case iPolicyDiskTemplates ipol of
401 9fdd3d0f Iustin Pop
      first_templ:_ -> return first_templ
402 88a10df5 Iustin Pop
      _ -> exitErr "null list of disk templates received from cluster"
403 9fdd3d0f Iustin Pop
404 5296ee23 Iustin Pop
  let num_instances = Container.size il
405 e10be8f2 Iustin Pop
      all_nodes = Container.elems fixed_nl
406 71375ef7 Iustin Pop
      cdata = orig_cdata { cdNodes = fixed_nl }
407 9fdd3d0f Iustin Pop
      disk_template = fromMaybe cluster_disk_template (optDiskTemplate opts)
408 9fdd3d0f Iustin Pop
      req_nodes = Instance.requiredNodes disk_template
409 3e4480e0 Iustin Pop
      csf = commonSuffix fixed_nl il
410 f0753837 René Nussbaumer
      su = fromMaybe (iSpecSpindleUse $ iPolicyStdSpec ipol)
411 f0753837 René Nussbaumer
                     (optSpindleUse opts)
412 e10be8f2 Iustin Pop
413 5296ee23 Iustin Pop
  when (not (null csf) && verbose > 1) $
414 2bbf77cc Iustin Pop
       hPrintf stderr "Note: Stripping common suffix of '%s' from names\n" csf
415 e10be8f2 Iustin Pop
416 e86f7f65 Iustin Pop
  maybePrintNodes (optShowNodes opts) "Initial cluster" (Cluster.printNodes nl)
417 e10be8f2 Iustin Pop
418 2485487d Iustin Pop
  when (verbose > 2) $
419 2922d2c5 René Nussbaumer
         hPrintf stderr "Initial coefficients: overall %.8f\n%s"
420 2922d2c5 René Nussbaumer
                 (Cluster.compCV nl) (Cluster.printStats "  " nl)
421 de4ac2c2 Iustin Pop
422 e86f7f65 Iustin Pop
  printCluster machine_r (Cluster.totalResources nl) (length all_nodes)
423 375969eb Iustin Pop
424 e86f7f65 Iustin Pop
  let stop_allocation = case Cluster.computeBadItems nl il of
425 e86f7f65 Iustin Pop
                          ([], _) -> Nothing
426 e86f7f65 Iustin Pop
                          _ -> Just ([(FailN1, 1)]::FailStats, nl, il, [], [])
427 e86f7f65 Iustin Pop
      alloclimit = if optMaxLength opts == -1
428 e86f7f65 Iustin Pop
                   then Nothing
429 e86f7f65 Iustin Pop
                   else Just (optMaxLength opts)
430 dca7f396 Iustin Pop
431 88a10df5 Iustin Pop
  allocnodes <- exitIfBad "failure during allocation" $
432 88a10df5 Iustin Pop
                Cluster.genAllocNodes gl nl req_nodes True
433 41b5c85a Iustin Pop
434 be468da0 Iustin Pop
  -- Run the tiered allocation
435 fcebc9db Iustin Pop
436 be468da0 Iustin Pop
  let tspec = fromMaybe (rspecFromISpec (iPolicyMaxSpec ipol))
437 be468da0 Iustin Pop
              (optTieredSpec opts)
438 fcebc9db Iustin Pop
439 be468da0 Iustin Pop
  (treason, trl_nl, _, spec_map) <-
440 be468da0 Iustin Pop
    runAllocation cdata stop_allocation
441 be468da0 Iustin Pop
       (Cluster.tieredAlloc nl il alloclimit
442 f0753837 René Nussbaumer
        (instFromSpec tspec disk_template su) allocnodes [] [])
443 9fdd3d0f Iustin Pop
       tspec disk_template SpecTiered opts
444 be468da0 Iustin Pop
445 5f3b040a Iustin Pop
  printTiered machine_r spec_map nl trl_nl treason
446 fcebc9db Iustin Pop
447 fcebc9db Iustin Pop
  -- Run the standard (avg-mode) allocation
448 e10be8f2 Iustin Pop
449 be468da0 Iustin Pop
  let ispec = fromMaybe (rspecFromISpec (iPolicyStdSpec ipol))
450 be468da0 Iustin Pop
              (optStdSpec opts)
451 be468da0 Iustin Pop
452 e86f7f65 Iustin Pop
  (sreason, fin_nl, allocs, _) <-
453 e86f7f65 Iustin Pop
      runAllocation cdata stop_allocation
454 8564fb47 Iustin Pop
            (Cluster.iterateAlloc nl il alloclimit
455 f0753837 René Nussbaumer
             (instFromSpec ispec disk_template su) allocnodes [] [])
456 9fdd3d0f Iustin Pop
            ispec disk_template SpecNormal opts
457 3e9501d0 Iustin Pop
458 375969eb Iustin Pop
  printResults machine_r nl fin_nl num_instances allocs sreason
459 375969eb Iustin Pop
460 be468da0 Iustin Pop
  -- Print final result
461 be468da0 Iustin Pop
462 79eef90b Agata Murawska
  printFinalHTS machine_r