Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Program / Hspace.hs @ 72bb6b4e

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