Statistics
| Branch: | Tag: | Revision:

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

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