Statistics
| Branch: | Tag: | Revision:

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

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