Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Program / Hspace.hs @ 81879d92

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