Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Program / Hspace.hs @ 4b77c2a2

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