Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Program / Hspace.hs @ 1b0a6356

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 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 0427285d Iustin Pop
    , oMinDisk
69 1f9066c0 Iustin Pop
    , oTieredSpec
70 3e9501d0 Iustin Pop
    , oSaveCluster
71 0427285d Iustin Pop
    , oShowVer
72 0427285d Iustin Pop
    , oShowHelp
73 e10be8f2 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 375969eb Iustin Pop
specDescription SpecNormal = "Normal (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 375969eb Iustin Pop
-- | Print final stats and related metrics.
163 375969eb Iustin Pop
printResults :: Bool -> Node.List -> Node.List -> Int -> Int
164 375969eb Iustin Pop
             -> [(FailMode, Int)] -> IO ()
165 375969eb Iustin Pop
printResults True _ fin_nl num_instances allocs sreason = do
166 dca7f396 Iustin Pop
  let fin_stats = Cluster.totalResources fin_nl
167 dca7f396 Iustin Pop
      fin_instances = num_instances + allocs
168 dca7f396 Iustin Pop
169 f5b553da Iustin Pop
  when (num_instances + allocs /= Cluster.csNinst fin_stats) $
170 de4ac2c2 Iustin Pop
       do
171 de4ac2c2 Iustin Pop
         hPrintf stderr "ERROR: internal inconsistency, allocated (%d)\
172 de4ac2c2 Iustin Pop
                        \ != counted (%d)\n" (num_instances + allocs)
173 c939b58e Iustin Pop
                                 (Cluster.csNinst fin_stats) :: IO ()
174 de4ac2c2 Iustin Pop
         exitWith $ ExitFailure 1
175 de4ac2c2 Iustin Pop
176 2bbf77cc Iustin Pop
  printKeys $ printStats PFinal fin_stats
177 2bbf77cc Iustin Pop
  printKeys [ ("ALLOC_USAGE", printf "%.8f"
178 2bbf77cc Iustin Pop
                                ((fromIntegral num_instances::Double) /
179 2bbf77cc Iustin Pop
                                 fromIntegral fin_instances))
180 31e7ac17 Iustin Pop
            , ("ALLOC_INSTANCES", printf "%d" allocs)
181 2bbf77cc Iustin Pop
            , ("ALLOC_FAIL_REASON", map toUpper . show . fst $ head sreason)
182 2bbf77cc Iustin Pop
            ]
183 2bbf77cc Iustin Pop
  printKeys $ map (\(x, y) -> (printf "ALLOC_%s_CNT" (show x),
184 2bbf77cc Iustin Pop
                               printf "%d" y)) sreason
185 375969eb Iustin Pop
186 375969eb Iustin Pop
printResults False ini_nl fin_nl _ allocs sreason = do
187 375969eb Iustin Pop
  putStrLn "Normal (fixed-size) allocation results:"
188 375969eb Iustin Pop
  printf "  - %3d instances allocated\n" allocs :: IO ()
189 375969eb Iustin Pop
  printf "  - most likely failure reason: %s\n" $ failureReason sreason::IO ()
190 375969eb Iustin Pop
  printClusterScores ini_nl fin_nl
191 375969eb Iustin Pop
  printClusterEff (Cluster.totalResources fin_nl)
192 375969eb Iustin Pop
193 375969eb Iustin Pop
-- | Prints the final @OK@ marker in machine readable output.
194 375969eb Iustin Pop
printFinal :: Bool -> IO ()
195 375969eb Iustin Pop
printFinal True =
196 2bbf77cc Iustin Pop
  -- this should be the final entry
197 2bbf77cc Iustin Pop
  printKeys [("OK", "1")]
198 2bbf77cc Iustin Pop
199 375969eb Iustin Pop
printFinal False = return ()
200 375969eb Iustin Pop
201 756df409 Iustin Pop
-- | Compute the tiered spec counts from a list of allocated
202 756df409 Iustin Pop
-- instances.
203 756df409 Iustin Pop
tieredSpecMap :: [Instance.Instance]
204 756df409 Iustin Pop
              -> [(RSpec, Int)]
205 756df409 Iustin Pop
tieredSpecMap trl_ixes =
206 756df409 Iustin Pop
    let fin_trl_ixes = reverse trl_ixes
207 756df409 Iustin Pop
        ix_byspec = groupBy ((==) `on` Instance.specOf) fin_trl_ixes
208 756df409 Iustin Pop
        spec_map = map (\ixs -> (Instance.specOf $ head ixs, length ixs))
209 756df409 Iustin Pop
                   ix_byspec
210 756df409 Iustin Pop
    in spec_map
211 756df409 Iustin Pop
212 756df409 Iustin Pop
-- | Formats a spec map to strings.
213 756df409 Iustin Pop
formatSpecMap :: [(RSpec, Int)] -> [String]
214 756df409 Iustin Pop
formatSpecMap =
215 756df409 Iustin Pop
    map (\(spec, cnt) -> printf "%d,%d,%d=%d" (rspecMem spec)
216 756df409 Iustin Pop
                         (rspecDsk spec) (rspecCpu spec) cnt)
217 756df409 Iustin Pop
218 179c0828 Iustin Pop
-- | Formats \"key-metrics\" values.
219 4886952e Iustin Pop
formatRSpec :: Double -> String -> RSpec -> [(String, String)]
220 4886952e Iustin Pop
formatRSpec m_cpu s r =
221 bd3286e9 Iustin Pop
    [ ("KM_" ++ s ++ "_CPU", show $ rspecCpu r)
222 4886952e Iustin Pop
    , ("KM_" ++ s ++ "_NPU", show $ fromIntegral (rspecCpu r) / m_cpu)
223 bd3286e9 Iustin Pop
    , ("KM_" ++ s ++ "_MEM", show $ rspecMem r)
224 bd3286e9 Iustin Pop
    , ("KM_" ++ s ++ "_DSK", show $ rspecDsk r)
225 bd3286e9 Iustin Pop
    ]
226 bd3286e9 Iustin Pop
227 179c0828 Iustin Pop
-- | Shows allocations stats.
228 4886952e Iustin Pop
printAllocationStats :: Double -> Node.List -> Node.List -> IO ()
229 4886952e Iustin Pop
printAllocationStats m_cpu ini_nl fin_nl = do
230 bd3286e9 Iustin Pop
  let ini_stats = Cluster.totalResources ini_nl
231 bd3286e9 Iustin Pop
      fin_stats = Cluster.totalResources fin_nl
232 bd3286e9 Iustin Pop
      (rini, ralo, runa) = Cluster.computeAllocationDelta ini_stats fin_stats
233 4886952e Iustin Pop
  printKeys $ formatRSpec m_cpu  "USED" rini
234 4886952e Iustin Pop
  printKeys $ formatRSpec m_cpu "POOL"ralo
235 4886952e Iustin Pop
  printKeys $ formatRSpec m_cpu "UNAV" runa
236 bd3286e9 Iustin Pop
237 179c0828 Iustin Pop
-- | Ensure a value is quoted if needed.
238 9739b6b8 Iustin Pop
ensureQuoted :: String -> String
239 cc532bdd Iustin Pop
ensureQuoted v = if not (all (\c -> isAlphaNum c || c == '.') v)
240 9739b6b8 Iustin Pop
                 then '\'':v ++ "'"
241 9739b6b8 Iustin Pop
                 else v
242 9739b6b8 Iustin Pop
243 179c0828 Iustin Pop
-- | Format a list of key\/values as a shell fragment.
244 2bbf77cc Iustin Pop
printKeys :: [(String, String)] -> IO ()
245 9739b6b8 Iustin Pop
printKeys = mapM_ (\(k, v) ->
246 9739b6b8 Iustin Pop
                   printf "HTS_%s=%s\n" (map toUpper k) (ensureQuoted v))
247 dca7f396 Iustin Pop
248 179c0828 Iustin Pop
-- | Converts instance data to a list of strings.
249 366a7c89 Iustin Pop
printInstance :: Node.List -> Instance.Instance -> [String]
250 366a7c89 Iustin Pop
printInstance nl i = [ Instance.name i
251 5182e970 Iustin Pop
                     , Container.nameOf nl $ Instance.pNode i
252 5182e970 Iustin Pop
                     , let sdx = Instance.sNode i
253 5182e970 Iustin Pop
                       in if sdx == Node.noSecondary then ""
254 5182e970 Iustin Pop
                          else Container.nameOf nl sdx
255 366a7c89 Iustin Pop
                     , show (Instance.mem i)
256 366a7c89 Iustin Pop
                     , show (Instance.dsk i)
257 366a7c89 Iustin Pop
                     , show (Instance.vcpus i)
258 366a7c89 Iustin Pop
                     ]
259 366a7c89 Iustin Pop
260 179c0828 Iustin Pop
-- | Optionally print the allocation map.
261 6eaa7bb8 Iustin Pop
printAllocationMap :: Int -> String
262 6eaa7bb8 Iustin Pop
                   -> Node.List -> [Instance.Instance] -> IO ()
263 6eaa7bb8 Iustin Pop
printAllocationMap verbose msg nl ixes =
264 6eaa7bb8 Iustin Pop
  when (verbose > 1) $ do
265 6eaa7bb8 Iustin Pop
    hPutStrLn stderr msg
266 6eaa7bb8 Iustin Pop
    hPutStr stderr . unlines . map ((:) ' ' .  intercalate " ") $
267 6eaa7bb8 Iustin Pop
            formatTable (map (printInstance nl) (reverse ixes))
268 6eaa7bb8 Iustin Pop
                        -- This is the numberic-or-not field
269 6eaa7bb8 Iustin Pop
                        -- specification; the first three fields are
270 6eaa7bb8 Iustin Pop
                        -- strings, whereas the rest are numeric
271 6eaa7bb8 Iustin Pop
                       [False, False, False, True, True, True]
272 6eaa7bb8 Iustin Pop
273 375969eb Iustin Pop
-- | Formats nicely a list of resources.
274 1b0a6356 Iustin Pop
formatResources :: a -> [(String, a->String)] -> String
275 375969eb Iustin Pop
formatResources res =
276 375969eb Iustin Pop
    intercalate ", " . map (\(a, fn) -> a ++ " " ++ fn res)
277 375969eb Iustin Pop
278 375969eb Iustin Pop
-- | Print the cluster resources.
279 375969eb Iustin Pop
printCluster :: Bool -> Cluster.CStats -> Int -> IO ()
280 375969eb Iustin Pop
printCluster True ini_stats node_count = do
281 375969eb Iustin Pop
  printKeys $ map (\(a, fn) -> ("CLUSTER_" ++ a, fn ini_stats)) clusterData
282 375969eb Iustin Pop
  printKeys [("CLUSTER_NODES", printf "%d" node_count)]
283 375969eb Iustin Pop
  printKeys $ printStats PInitial ini_stats
284 375969eb Iustin Pop
285 375969eb Iustin Pop
printCluster False ini_stats node_count = do
286 375969eb Iustin Pop
  printf "The cluster has %d nodes and the following resources:\n  %s.\n"
287 375969eb Iustin Pop
         node_count (formatResources ini_stats clusterData)::IO ()
288 375969eb Iustin Pop
  printf "There are %s initial instances on the cluster.\n"
289 375969eb Iustin Pop
             (if inst_count > 0 then show inst_count else "no" )
290 375969eb Iustin Pop
      where inst_count = Cluster.csNinst ini_stats
291 375969eb Iustin Pop
292 375969eb Iustin Pop
-- | Prints the normal instance spec.
293 375969eb Iustin Pop
printISpec :: Bool -> RSpec -> SpecType -> DiskTemplate -> IO ()
294 375969eb Iustin Pop
printISpec True ispec spec disk_template = do
295 375969eb Iustin Pop
  printKeys $ map (\(a, fn) -> (prefix ++ "_" ++ a, fn ispec)) specData
296 375969eb Iustin Pop
  printKeys [ (prefix ++ "_RQN", printf "%d" req_nodes) ]
297 375969eb Iustin Pop
  printKeys [ (prefix ++ "_DISK_TEMPLATE", dtToString disk_template) ]
298 375969eb Iustin Pop
      where req_nodes = Instance.requiredNodes disk_template
299 375969eb Iustin Pop
            prefix = specPrefix spec
300 375969eb Iustin Pop
301 1b0a6356 Iustin Pop
printISpec False ispec spec disk_template =
302 375969eb Iustin Pop
  printf "%s instance spec is:\n  %s, using disk\
303 375969eb Iustin Pop
         \ template '%s'.\n"
304 375969eb Iustin Pop
         (specDescription spec)
305 375969eb Iustin Pop
         (formatResources ispec specData) (dtToString disk_template)
306 375969eb Iustin Pop
307 375969eb Iustin Pop
-- | Prints the tiered results.
308 375969eb Iustin Pop
printTiered :: Bool -> [(RSpec, Int)] -> Double
309 375969eb Iustin Pop
            -> Node.List -> Node.List -> [(FailMode, Int)] -> IO ()
310 375969eb Iustin Pop
printTiered True spec_map m_cpu nl trl_nl _ = do
311 375969eb Iustin Pop
  printKeys $ printStats PTiered (Cluster.totalResources trl_nl)
312 375969eb Iustin Pop
  printKeys [("TSPEC", intercalate " " (formatSpecMap spec_map))]
313 375969eb Iustin Pop
  printAllocationStats m_cpu nl trl_nl
314 375969eb Iustin Pop
315 375969eb Iustin Pop
printTiered False spec_map _ ini_nl fin_nl sreason = do
316 375969eb Iustin Pop
  _ <- printf "Tiered allocation results:\n"
317 375969eb Iustin Pop
  mapM_ (\(ispec, cnt) ->
318 375969eb Iustin Pop
             printf "  - %3d instances of spec %s\n" cnt
319 375969eb Iustin Pop
                        (formatResources ispec specData)) spec_map
320 375969eb Iustin Pop
  printf "  - most likely failure reason: %s\n" $ failureReason sreason::IO ()
321 375969eb Iustin Pop
  printClusterScores ini_nl fin_nl
322 375969eb Iustin Pop
  printClusterEff (Cluster.totalResources fin_nl)
323 375969eb Iustin Pop
324 179c0828 Iustin Pop
-- | Displays the initial/final cluster scores.
325 375969eb Iustin Pop
printClusterScores :: Node.List -> Node.List -> IO ()
326 375969eb Iustin Pop
printClusterScores ini_nl fin_nl = do
327 375969eb Iustin Pop
  printf "  - initial cluster score: %.8f\n" $ Cluster.compCV ini_nl::IO ()
328 375969eb Iustin Pop
  printf "  -   final cluster score: %.8f\n" $ Cluster.compCV fin_nl
329 375969eb Iustin Pop
330 179c0828 Iustin Pop
-- | Displays the cluster efficiency.
331 375969eb Iustin Pop
printClusterEff :: Cluster.CStats -> IO ()
332 375969eb Iustin Pop
printClusterEff cs =
333 375969eb Iustin Pop
    mapM_ (\(s, fn) ->
334 375969eb Iustin Pop
               printf "  - %s usage efficiency: %5.2f%%\n" s (fn cs * 100))
335 375969eb Iustin Pop
          [("memory", memEff),
336 375969eb Iustin Pop
           ("  disk", dskEff),
337 375969eb Iustin Pop
           ("  vcpu", cpuEff)]
338 375969eb Iustin Pop
339 375969eb Iustin Pop
-- | Computes the most likely failure reason.
340 375969eb Iustin Pop
failureReason :: [(FailMode, Int)] -> String
341 375969eb Iustin Pop
failureReason = show . fst . head
342 375969eb Iustin Pop
343 375969eb Iustin Pop
-- | Sorts the failure reasons.
344 375969eb Iustin Pop
sortReasons :: [(FailMode, Int)] -> [(FailMode, Int)]
345 375969eb Iustin Pop
sortReasons = reverse . sortBy (comparing snd)
346 375969eb Iustin Pop
347 e10be8f2 Iustin Pop
-- | Main function.
348 e10be8f2 Iustin Pop
main :: IO ()
349 e10be8f2 Iustin Pop
main = do
350 e10be8f2 Iustin Pop
  cmd_args <- System.getArgs
351 0427285d Iustin Pop
  (opts, args) <- parseOpts cmd_args "hspace" options
352 e10be8f2 Iustin Pop
353 e10be8f2 Iustin Pop
  unless (null args) $ do
354 e10be8f2 Iustin Pop
         hPutStrLn stderr "Error: this program doesn't take any arguments."
355 e10be8f2 Iustin Pop
         exitWith $ ExitFailure 1
356 e10be8f2 Iustin Pop
357 2795466b Iustin Pop
  let verbose = optVerbose opts
358 1f9066c0 Iustin Pop
      ispec = optISpec opts
359 e98fb766 Iustin Pop
      shownodes = optShowNodes opts
360 9ef605a6 Iustin Pop
      disk_template = optDiskTemplate opts
361 9ef605a6 Iustin Pop
      req_nodes = Instance.requiredNodes disk_template
362 375969eb Iustin Pop
      machine_r = optMachineReadable opts
363 2795466b Iustin Pop
364 017a0c3d Iustin Pop
  (ClusterData gl fixed_nl il ctags) <- loadExternalData opts
365 2795466b Iustin Pop
366 9dcec001 Iustin Pop
  let num_instances = length $ Container.elems il
367 e10be8f2 Iustin Pop
368 4938fa30 Guido Trotter
  let offline_passed = optOffline opts
369 e10be8f2 Iustin Pop
      all_nodes = Container.elems fixed_nl
370 4938fa30 Guido Trotter
      offline_lkp = map (lookupName (map Node.name all_nodes)) offline_passed
371 4938fa30 Guido Trotter
      offline_wrong = filter (not . goodLookupResult) offline_lkp
372 4938fa30 Guido Trotter
      offline_names = map lrContent offline_lkp
373 e10be8f2 Iustin Pop
      offline_indices = map Node.idx $
374 4938fa30 Guido Trotter
                        filter (\n -> Node.name n `elem` offline_names)
375 e10be8f2 Iustin Pop
                               all_nodes
376 83a91400 Iustin Pop
      m_cpu = optMcpu opts
377 83a91400 Iustin Pop
      m_dsk = optMdsk opts
378 e10be8f2 Iustin Pop
379 4938fa30 Guido Trotter
  when (not (null offline_wrong)) $ do
380 2795466b Iustin Pop
         hPrintf stderr "Error: Wrong node name(s) set as offline: %s\n"
381 4938fa30 Guido Trotter
                     (commaJoin (map lrContent offline_wrong)) :: IO ()
382 e10be8f2 Iustin Pop
         exitWith $ ExitFailure 1
383 e10be8f2 Iustin Pop
384 9abe9caf Iustin Pop
  when (req_nodes /= 1 && req_nodes /= 2) $ do
385 c939b58e Iustin Pop
         hPrintf stderr "Error: Invalid required nodes (%d)\n"
386 c939b58e Iustin Pop
                                            req_nodes :: IO ()
387 9abe9caf Iustin Pop
         exitWith $ ExitFailure 1
388 9abe9caf Iustin Pop
389 5182e970 Iustin Pop
  let nm = Container.map (\n -> if Node.idx n `elem` offline_indices
390 e10be8f2 Iustin Pop
                                then Node.setOffline n True
391 e10be8f2 Iustin Pop
                                else n) fixed_nl
392 83a91400 Iustin Pop
      nl = Container.map (flip Node.setMdsk m_dsk . flip Node.setMcpu m_cpu)
393 83a91400 Iustin Pop
           nm
394 3e4480e0 Iustin Pop
      csf = commonSuffix fixed_nl il
395 e10be8f2 Iustin Pop
396 9f6dcdea Iustin Pop
  when (length csf > 0 && verbose > 1) $
397 2bbf77cc Iustin Pop
       hPrintf stderr "Note: Stripping common suffix of '%s' from names\n" csf
398 e10be8f2 Iustin Pop
399 e98fb766 Iustin Pop
  when (isJust shownodes) $
400 e10be8f2 Iustin Pop
       do
401 2bbf77cc Iustin Pop
         hPutStrLn stderr "Initial cluster status:"
402 e98fb766 Iustin Pop
         hPutStrLn stderr $ Cluster.printNodes nl (fromJust shownodes)
403 e10be8f2 Iustin Pop
404 e10be8f2 Iustin Pop
  let ini_cv = Cluster.compCV nl
405 621de5b7 Iustin Pop
      ini_stats = Cluster.totalResources nl
406 e10be8f2 Iustin Pop
407 2485487d Iustin Pop
  when (verbose > 2) $
408 2bbf77cc Iustin Pop
         hPrintf stderr "Initial coefficients: overall %.8f, %s\n"
409 2bbf77cc Iustin Pop
                 ini_cv (Cluster.printStats nl)
410 de4ac2c2 Iustin Pop
411 375969eb Iustin Pop
  printCluster machine_r ini_stats (length all_nodes)
412 375969eb Iustin Pop
413 375969eb Iustin Pop
  printISpec machine_r ispec SpecNormal disk_template
414 e10be8f2 Iustin Pop
415 dca7f396 Iustin Pop
  let bad_nodes = fst $ Cluster.computeBadItems nl il
416 317b1040 Iustin Pop
      stop_allocation = length bad_nodes > 0
417 d5ccec02 Iustin Pop
      result_noalloc = ([(FailN1, 1)]::FailStats, nl, il, [], [])
418 dca7f396 Iustin Pop
419 fcebc9db Iustin Pop
  -- utility functions
420 fcebc9db Iustin Pop
  let iofspec spx = Instance.create "new" (rspecMem spx) (rspecDsk spx)
421 9ef605a6 Iustin Pop
                    (rspecCpu spx) "running" [] True (-1) (-1) disk_template
422 fcebc9db Iustin Pop
      exitifbad val = (case val of
423 fcebc9db Iustin Pop
                         Bad s -> do
424 c939b58e Iustin Pop
                           hPrintf stderr "Failure: %s\n" s :: IO ()
425 fcebc9db Iustin Pop
                           exitWith $ ExitFailure 1
426 fcebc9db Iustin Pop
                         Ok x -> return x)
427 fcebc9db Iustin Pop
428 fcebc9db Iustin Pop
429 fcebc9db Iustin Pop
  let reqinst = iofspec ispec
430 fcebc9db Iustin Pop
431 6d0bc5ca Iustin Pop
  allocnodes <- exitifbad $ Cluster.genAllocNodes gl nl req_nodes True
432 41b5c85a Iustin Pop
433 fcebc9db Iustin Pop
  -- Run the tiered allocation, if enabled
434 fcebc9db Iustin Pop
435 fcebc9db Iustin Pop
  (case optTieredSpec opts of
436 fcebc9db Iustin Pop
     Nothing -> return ()
437 fcebc9db Iustin Pop
     Just tspec -> do
438 375969eb Iustin Pop
       (treason, trl_nl, trl_il, trl_ixes, _) <-
439 317b1040 Iustin Pop
           if stop_allocation
440 317b1040 Iustin Pop
           then return result_noalloc
441 8f48f67d Iustin Pop
           else exitifbad (Cluster.tieredAlloc nl il Nothing (iofspec tspec)
442 41b5c85a Iustin Pop
                                  allocnodes [] [])
443 756df409 Iustin Pop
       let spec_map' = tieredSpecMap trl_ixes
444 375969eb Iustin Pop
           treason' = sortReasons treason
445 fcebc9db Iustin Pop
446 6eaa7bb8 Iustin Pop
       printAllocationMap verbose "Tiered allocation map" trl_nl trl_ixes
447 83ad1f3c Iustin Pop
448 417f6b50 Iustin Pop
       maybePrintNodes shownodes "Tiered allocation"
449 417f6b50 Iustin Pop
                           (Cluster.printNodes trl_nl)
450 fcebc9db Iustin Pop
451 4188449c Iustin Pop
       maybeSaveData (optSaveCluster opts) "tiered" "after tiered allocation"
452 4188449c Iustin Pop
                     (ClusterData gl trl_nl trl_il ctags)
453 4188449c Iustin Pop
454 375969eb Iustin Pop
       printISpec machine_r tspec SpecTiered disk_template
455 375969eb Iustin Pop
456 375969eb Iustin Pop
       printTiered machine_r spec_map' m_cpu nl trl_nl treason'
457 375969eb Iustin Pop
       )
458 fcebc9db Iustin Pop
459 fcebc9db Iustin Pop
  -- Run the standard (avg-mode) allocation
460 e10be8f2 Iustin Pop
461 d5ccec02 Iustin Pop
  (ereason, fin_nl, fin_il, ixes, _) <-
462 317b1040 Iustin Pop
      if stop_allocation
463 317b1040 Iustin Pop
      then return result_noalloc
464 8f48f67d Iustin Pop
      else exitifbad (Cluster.iterateAlloc nl il Nothing
465 8f48f67d Iustin Pop
                      reqinst allocnodes [] [])
466 fcebc9db Iustin Pop
467 31e7ac17 Iustin Pop
  let allocs = length ixes
468 375969eb Iustin Pop
      sreason = sortReasons ereason
469 9dcec001 Iustin Pop
470 6eaa7bb8 Iustin Pop
  printAllocationMap verbose "Standard allocation map" fin_nl ixes
471 6eaa7bb8 Iustin Pop
472 417f6b50 Iustin Pop
  maybePrintNodes shownodes "Standard allocation" (Cluster.printNodes fin_nl)
473 2bbf77cc Iustin Pop
474 4188449c Iustin Pop
  maybeSaveData (optSaveCluster opts) "alloc" "after standard allocation"
475 4188449c Iustin Pop
       (ClusterData gl fin_nl fin_il ctags)
476 3e9501d0 Iustin Pop
477 375969eb Iustin Pop
  printResults machine_r nl fin_nl num_instances allocs sreason
478 375969eb Iustin Pop
479 375969eb Iustin Pop
  printFinal machine_r