Statistics
| Branch: | Tag: | Revision:

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

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