Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Program / Hspace.hs @ 756df409

History | View | Annotate | Download (12.9 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 017a0c3d Iustin Pop
import Ganeti.HTools.Loader (ClusterData(..))
50 e10be8f2 Iustin Pop
51 e10be8f2 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 0427285d Iustin Pop
    , oMaxCpu
67 0427285d Iustin Pop
    , oMinDisk
68 1f9066c0 Iustin Pop
    , oTieredSpec
69 3e9501d0 Iustin Pop
    , oSaveCluster
70 0427285d Iustin Pop
    , oShowVer
71 0427285d Iustin Pop
    , oShowHelp
72 e10be8f2 Iustin Pop
    ]
73 e10be8f2 Iustin Pop
74 fcebc9db Iustin Pop
-- | The allocation phase we're in (initial, after tiered allocs, or
75 fcebc9db Iustin Pop
-- after regular allocation).
76 fcebc9db Iustin Pop
data Phase = PInitial
77 fcebc9db Iustin Pop
           | PFinal
78 fcebc9db Iustin Pop
           | PTiered
79 2bbf77cc Iustin Pop
80 2bbf77cc Iustin Pop
statsData :: [(String, Cluster.CStats -> String)]
81 f5b553da Iustin Pop
statsData = [ ("SCORE", printf "%.8f" . Cluster.csScore)
82 f5b553da Iustin Pop
            , ("INST_CNT", printf "%d" . Cluster.csNinst)
83 f5b553da Iustin Pop
            , ("MEM_FREE", printf "%d" . Cluster.csFmem)
84 f5b553da Iustin Pop
            , ("MEM_AVAIL", printf "%d" . Cluster.csAmem)
85 2bbf77cc Iustin Pop
            , ("MEM_RESVD",
86 f5b553da Iustin Pop
               \cs -> printf "%d" (Cluster.csFmem cs - Cluster.csAmem cs))
87 f5b553da Iustin Pop
            , ("MEM_INST", printf "%d" . Cluster.csImem)
88 2bbf77cc Iustin Pop
            , ("MEM_OVERHEAD",
89 f5b553da Iustin Pop
               \cs -> printf "%d" (Cluster.csXmem cs + Cluster.csNmem cs))
90 2bbf77cc Iustin Pop
            , ("MEM_EFF",
91 f5b553da Iustin Pop
               \cs -> printf "%.8f" (fromIntegral (Cluster.csImem cs) /
92 f5b553da Iustin Pop
                                     Cluster.csTmem cs))
93 f5b553da Iustin Pop
            , ("DSK_FREE", printf "%d" . Cluster.csFdsk)
94 9739b6b8 Iustin Pop
            , ("DSK_AVAIL", printf "%d". Cluster.csAdsk)
95 2bbf77cc Iustin Pop
            , ("DSK_RESVD",
96 f5b553da Iustin Pop
               \cs -> printf "%d" (Cluster.csFdsk cs - Cluster.csAdsk cs))
97 f5b553da Iustin Pop
            , ("DSK_INST", printf "%d" . Cluster.csIdsk)
98 2bbf77cc Iustin Pop
            , ("DSK_EFF",
99 f5b553da Iustin Pop
               \cs -> printf "%.8f" (fromIntegral (Cluster.csIdsk cs) /
100 f5b553da Iustin Pop
                                    Cluster.csTdsk cs))
101 f5b553da Iustin Pop
            , ("CPU_INST", printf "%d" . Cluster.csIcpu)
102 2bbf77cc Iustin Pop
            , ("CPU_EFF",
103 f5b553da Iustin Pop
               \cs -> printf "%.8f" (fromIntegral (Cluster.csIcpu cs) /
104 f5b553da Iustin Pop
                                     Cluster.csTcpu cs))
105 f5b553da Iustin Pop
            , ("MNODE_MEM_AVAIL", printf "%d" . Cluster.csMmem)
106 f5b553da Iustin Pop
            , ("MNODE_DSK_AVAIL", printf "%d" . Cluster.csMdsk)
107 2bbf77cc Iustin Pop
            ]
108 2bbf77cc Iustin Pop
109 1f9066c0 Iustin Pop
specData :: [(String, RSpec -> String)]
110 1f9066c0 Iustin Pop
specData = [ ("MEM", printf "%d" . rspecMem)
111 1f9066c0 Iustin Pop
           , ("DSK", printf "%d" . rspecDsk)
112 1f9066c0 Iustin Pop
           , ("CPU", printf "%d" . rspecCpu)
113 2bbf77cc Iustin Pop
           ]
114 2bbf77cc Iustin Pop
115 2bbf77cc Iustin Pop
clusterData :: [(String, Cluster.CStats -> String)]
116 f5b553da Iustin Pop
clusterData = [ ("MEM", printf "%.0f" . Cluster.csTmem)
117 f5b553da Iustin Pop
              , ("DSK", printf "%.0f" . Cluster.csTdsk)
118 f5b553da Iustin Pop
              , ("CPU", printf "%.0f" . Cluster.csTcpu)
119 bd3286e9 Iustin Pop
              , ("VCPU", printf "%d" . Cluster.csVcpu)
120 2bbf77cc Iustin Pop
              ]
121 2bbf77cc Iustin Pop
122 58631b72 Iustin Pop
-- | Function to print stats for a given phase
123 2bbf77cc Iustin Pop
printStats :: Phase -> Cluster.CStats -> [(String, String)]
124 2bbf77cc Iustin Pop
printStats ph cs =
125 2bbf77cc Iustin Pop
  map (\(s, fn) -> (printf "%s_%s" kind s, fn cs)) statsData
126 2bbf77cc Iustin Pop
  where kind = case ph of
127 2bbf77cc Iustin Pop
                 PInitial -> "INI"
128 2bbf77cc Iustin Pop
                 PFinal -> "FIN"
129 fcebc9db Iustin Pop
                 PTiered -> "TRL"
130 e10be8f2 Iustin Pop
131 dca7f396 Iustin Pop
-- | Print final stats and related metrics
132 dca7f396 Iustin Pop
printResults :: Node.List -> Int -> Int -> [(FailMode, Int)] -> IO ()
133 dca7f396 Iustin Pop
printResults fin_nl num_instances allocs sreason = do
134 dca7f396 Iustin Pop
  let fin_stats = Cluster.totalResources fin_nl
135 dca7f396 Iustin Pop
      fin_instances = num_instances + allocs
136 dca7f396 Iustin Pop
137 f5b553da Iustin Pop
  when (num_instances + allocs /= Cluster.csNinst fin_stats) $
138 de4ac2c2 Iustin Pop
       do
139 de4ac2c2 Iustin Pop
         hPrintf stderr "ERROR: internal inconsistency, allocated (%d)\
140 de4ac2c2 Iustin Pop
                        \ != counted (%d)\n" (num_instances + allocs)
141 c939b58e Iustin Pop
                                 (Cluster.csNinst fin_stats) :: IO ()
142 de4ac2c2 Iustin Pop
         exitWith $ ExitFailure 1
143 de4ac2c2 Iustin Pop
144 2bbf77cc Iustin Pop
  printKeys $ printStats PFinal fin_stats
145 2bbf77cc Iustin Pop
  printKeys [ ("ALLOC_USAGE", printf "%.8f"
146 2bbf77cc Iustin Pop
                                ((fromIntegral num_instances::Double) /
147 2bbf77cc Iustin Pop
                                 fromIntegral fin_instances))
148 31e7ac17 Iustin Pop
            , ("ALLOC_INSTANCES", printf "%d" allocs)
149 2bbf77cc Iustin Pop
            , ("ALLOC_FAIL_REASON", map toUpper . show . fst $ head sreason)
150 2bbf77cc Iustin Pop
            ]
151 2bbf77cc Iustin Pop
  printKeys $ map (\(x, y) -> (printf "ALLOC_%s_CNT" (show x),
152 2bbf77cc Iustin Pop
                               printf "%d" y)) sreason
153 2bbf77cc Iustin Pop
  -- this should be the final entry
154 2bbf77cc Iustin Pop
  printKeys [("OK", "1")]
155 2bbf77cc Iustin Pop
156 756df409 Iustin Pop
-- | Compute the tiered spec counts from a list of allocated
157 756df409 Iustin Pop
-- instances.
158 756df409 Iustin Pop
tieredSpecMap :: [Instance.Instance]
159 756df409 Iustin Pop
              -> [(RSpec, Int)]
160 756df409 Iustin Pop
tieredSpecMap trl_ixes =
161 756df409 Iustin Pop
    let fin_trl_ixes = reverse trl_ixes
162 756df409 Iustin Pop
        ix_byspec = groupBy ((==) `on` Instance.specOf) fin_trl_ixes
163 756df409 Iustin Pop
        spec_map = map (\ixs -> (Instance.specOf $ head ixs, length ixs))
164 756df409 Iustin Pop
                   ix_byspec
165 756df409 Iustin Pop
    in spec_map
166 756df409 Iustin Pop
167 756df409 Iustin Pop
-- | Formats a spec map to strings.
168 756df409 Iustin Pop
formatSpecMap :: [(RSpec, Int)] -> [String]
169 756df409 Iustin Pop
formatSpecMap =
170 756df409 Iustin Pop
    map (\(spec, cnt) -> printf "%d,%d,%d=%d" (rspecMem spec)
171 756df409 Iustin Pop
                         (rspecDsk spec) (rspecCpu spec) cnt)
172 756df409 Iustin Pop
173 4886952e Iustin Pop
formatRSpec :: Double -> String -> RSpec -> [(String, String)]
174 4886952e Iustin Pop
formatRSpec m_cpu s r =
175 bd3286e9 Iustin Pop
    [ ("KM_" ++ s ++ "_CPU", show $ rspecCpu r)
176 4886952e Iustin Pop
    , ("KM_" ++ s ++ "_NPU", show $ fromIntegral (rspecCpu r) / m_cpu)
177 bd3286e9 Iustin Pop
    , ("KM_" ++ s ++ "_MEM", show $ rspecMem r)
178 bd3286e9 Iustin Pop
    , ("KM_" ++ s ++ "_DSK", show $ rspecDsk r)
179 bd3286e9 Iustin Pop
    ]
180 bd3286e9 Iustin Pop
181 4886952e Iustin Pop
printAllocationStats :: Double -> Node.List -> Node.List -> IO ()
182 4886952e Iustin Pop
printAllocationStats m_cpu ini_nl fin_nl = do
183 bd3286e9 Iustin Pop
  let ini_stats = Cluster.totalResources ini_nl
184 bd3286e9 Iustin Pop
      fin_stats = Cluster.totalResources fin_nl
185 bd3286e9 Iustin Pop
      (rini, ralo, runa) = Cluster.computeAllocationDelta ini_stats fin_stats
186 4886952e Iustin Pop
  printKeys $ formatRSpec m_cpu  "USED" rini
187 4886952e Iustin Pop
  printKeys $ formatRSpec m_cpu "POOL"ralo
188 4886952e Iustin Pop
  printKeys $ formatRSpec m_cpu "UNAV" runa
189 bd3286e9 Iustin Pop
190 9739b6b8 Iustin Pop
-- | Ensure a value is quoted if needed
191 9739b6b8 Iustin Pop
ensureQuoted :: String -> String
192 cc532bdd Iustin Pop
ensureQuoted v = if not (all (\c -> isAlphaNum c || c == '.') v)
193 9739b6b8 Iustin Pop
                 then '\'':v ++ "'"
194 9739b6b8 Iustin Pop
                 else v
195 9739b6b8 Iustin Pop
196 3ed46bb7 Iustin Pop
-- | Format a list of key\/values as a shell fragment
197 2bbf77cc Iustin Pop
printKeys :: [(String, String)] -> IO ()
198 9739b6b8 Iustin Pop
printKeys = mapM_ (\(k, v) ->
199 9739b6b8 Iustin Pop
                   printf "HTS_%s=%s\n" (map toUpper k) (ensureQuoted v))
200 dca7f396 Iustin Pop
201 366a7c89 Iustin Pop
printInstance :: Node.List -> Instance.Instance -> [String]
202 366a7c89 Iustin Pop
printInstance nl i = [ Instance.name i
203 5182e970 Iustin Pop
                     , Container.nameOf nl $ Instance.pNode i
204 5182e970 Iustin Pop
                     , let sdx = Instance.sNode i
205 5182e970 Iustin Pop
                       in if sdx == Node.noSecondary then ""
206 5182e970 Iustin Pop
                          else Container.nameOf nl sdx
207 366a7c89 Iustin Pop
                     , show (Instance.mem i)
208 366a7c89 Iustin Pop
                     , show (Instance.dsk i)
209 366a7c89 Iustin Pop
                     , show (Instance.vcpus i)
210 366a7c89 Iustin Pop
                     ]
211 366a7c89 Iustin Pop
212 6eaa7bb8 Iustin Pop
-- | Optionally print the allocation map
213 6eaa7bb8 Iustin Pop
printAllocationMap :: Int -> String
214 6eaa7bb8 Iustin Pop
                   -> Node.List -> [Instance.Instance] -> IO ()
215 6eaa7bb8 Iustin Pop
printAllocationMap verbose msg nl ixes =
216 6eaa7bb8 Iustin Pop
  when (verbose > 1) $ do
217 6eaa7bb8 Iustin Pop
    hPutStrLn stderr msg
218 6eaa7bb8 Iustin Pop
    hPutStr stderr . unlines . map ((:) ' ' .  intercalate " ") $
219 6eaa7bb8 Iustin Pop
            formatTable (map (printInstance nl) (reverse ixes))
220 6eaa7bb8 Iustin Pop
                        -- This is the numberic-or-not field
221 6eaa7bb8 Iustin Pop
                        -- specification; the first three fields are
222 6eaa7bb8 Iustin Pop
                        -- strings, whereas the rest are numeric
223 6eaa7bb8 Iustin Pop
                       [False, False, False, True, True, True]
224 6eaa7bb8 Iustin Pop
225 e10be8f2 Iustin Pop
-- | Main function.
226 e10be8f2 Iustin Pop
main :: IO ()
227 e10be8f2 Iustin Pop
main = do
228 e10be8f2 Iustin Pop
  cmd_args <- System.getArgs
229 0427285d Iustin Pop
  (opts, args) <- parseOpts cmd_args "hspace" options
230 e10be8f2 Iustin Pop
231 e10be8f2 Iustin Pop
  unless (null args) $ do
232 e10be8f2 Iustin Pop
         hPutStrLn stderr "Error: this program doesn't take any arguments."
233 e10be8f2 Iustin Pop
         exitWith $ ExitFailure 1
234 e10be8f2 Iustin Pop
235 2795466b Iustin Pop
  let verbose = optVerbose opts
236 1f9066c0 Iustin Pop
      ispec = optISpec opts
237 e98fb766 Iustin Pop
      shownodes = optShowNodes opts
238 9ef605a6 Iustin Pop
      disk_template = optDiskTemplate opts
239 9ef605a6 Iustin Pop
      req_nodes = Instance.requiredNodes disk_template
240 2795466b Iustin Pop
241 017a0c3d Iustin Pop
  (ClusterData gl fixed_nl il ctags) <- loadExternalData opts
242 2795466b Iustin Pop
243 1f9066c0 Iustin Pop
  printKeys $ map (\(a, fn) -> ("SPEC_" ++ a, fn ispec)) specData
244 9ef605a6 Iustin Pop
  printKeys [ ("SPEC_RQN", printf "%d" req_nodes) ]
245 1cc97b7f Iustin Pop
  printKeys [ ("SPEC_DISK_TEMPLATE", dtToString disk_template) ]
246 7e74e7db Iustin Pop
247 9dcec001 Iustin Pop
  let num_instances = length $ Container.elems il
248 e10be8f2 Iustin Pop
249 e10be8f2 Iustin Pop
  let offline_names = optOffline opts
250 e10be8f2 Iustin Pop
      all_nodes = Container.elems fixed_nl
251 e10be8f2 Iustin Pop
      all_names = map Node.name all_nodes
252 5182e970 Iustin Pop
      offline_wrong = filter (`notElem` all_names) offline_names
253 e10be8f2 Iustin Pop
      offline_indices = map Node.idx $
254 f9acea10 Iustin Pop
                        filter (\n ->
255 f9acea10 Iustin Pop
                                 Node.name n `elem` offline_names ||
256 f9acea10 Iustin Pop
                                 Node.alias n `elem` offline_names)
257 e10be8f2 Iustin Pop
                               all_nodes
258 83a91400 Iustin Pop
      m_cpu = optMcpu opts
259 83a91400 Iustin Pop
      m_dsk = optMdsk opts
260 e10be8f2 Iustin Pop
261 e10be8f2 Iustin Pop
  when (length offline_wrong > 0) $ do
262 2795466b Iustin Pop
         hPrintf stderr "Error: Wrong node name(s) set as offline: %s\n"
263 c939b58e Iustin Pop
                     (commaJoin offline_wrong) :: IO ()
264 e10be8f2 Iustin Pop
         exitWith $ ExitFailure 1
265 e10be8f2 Iustin Pop
266 9abe9caf Iustin Pop
  when (req_nodes /= 1 && req_nodes /= 2) $ do
267 c939b58e Iustin Pop
         hPrintf stderr "Error: Invalid required nodes (%d)\n"
268 c939b58e Iustin Pop
                                            req_nodes :: IO ()
269 9abe9caf Iustin Pop
         exitWith $ ExitFailure 1
270 9abe9caf Iustin Pop
271 5182e970 Iustin Pop
  let nm = Container.map (\n -> if Node.idx n `elem` offline_indices
272 e10be8f2 Iustin Pop
                                then Node.setOffline n True
273 e10be8f2 Iustin Pop
                                else n) fixed_nl
274 83a91400 Iustin Pop
      nl = Container.map (flip Node.setMdsk m_dsk . flip Node.setMcpu m_cpu)
275 83a91400 Iustin Pop
           nm
276 3e4480e0 Iustin Pop
      csf = commonSuffix fixed_nl il
277 e10be8f2 Iustin Pop
278 9f6dcdea Iustin Pop
  when (length csf > 0 && verbose > 1) $
279 2bbf77cc Iustin Pop
       hPrintf stderr "Note: Stripping common suffix of '%s' from names\n" csf
280 e10be8f2 Iustin Pop
281 e98fb766 Iustin Pop
  when (isJust shownodes) $
282 e10be8f2 Iustin Pop
       do
283 2bbf77cc Iustin Pop
         hPutStrLn stderr "Initial cluster status:"
284 e98fb766 Iustin Pop
         hPutStrLn stderr $ Cluster.printNodes nl (fromJust shownodes)
285 e10be8f2 Iustin Pop
286 e10be8f2 Iustin Pop
  let ini_cv = Cluster.compCV nl
287 621de5b7 Iustin Pop
      ini_stats = Cluster.totalResources nl
288 e10be8f2 Iustin Pop
289 2485487d Iustin Pop
  when (verbose > 2) $
290 2bbf77cc Iustin Pop
         hPrintf stderr "Initial coefficients: overall %.8f, %s\n"
291 2bbf77cc Iustin Pop
                 ini_cv (Cluster.printStats nl)
292 de4ac2c2 Iustin Pop
293 2bbf77cc Iustin Pop
  printKeys $ map (\(a, fn) -> ("CLUSTER_" ++ a, fn ini_stats)) clusterData
294 2bbf77cc Iustin Pop
  printKeys [("CLUSTER_NODES", printf "%d" (length all_nodes))]
295 2bbf77cc Iustin Pop
  printKeys $ printStats PInitial ini_stats
296 e10be8f2 Iustin Pop
297 dca7f396 Iustin Pop
  let bad_nodes = fst $ Cluster.computeBadItems nl il
298 317b1040 Iustin Pop
      stop_allocation = length bad_nodes > 0
299 d5ccec02 Iustin Pop
      result_noalloc = ([(FailN1, 1)]::FailStats, nl, il, [], [])
300 dca7f396 Iustin Pop
301 fcebc9db Iustin Pop
  -- utility functions
302 fcebc9db Iustin Pop
  let iofspec spx = Instance.create "new" (rspecMem spx) (rspecDsk spx)
303 9ef605a6 Iustin Pop
                    (rspecCpu spx) "running" [] True (-1) (-1) disk_template
304 fcebc9db Iustin Pop
      exitifbad val = (case val of
305 fcebc9db Iustin Pop
                         Bad s -> do
306 c939b58e Iustin Pop
                           hPrintf stderr "Failure: %s\n" s :: IO ()
307 fcebc9db Iustin Pop
                           exitWith $ ExitFailure 1
308 fcebc9db Iustin Pop
                         Ok x -> return x)
309 fcebc9db Iustin Pop
310 fcebc9db Iustin Pop
311 fcebc9db Iustin Pop
  let reqinst = iofspec ispec
312 fcebc9db Iustin Pop
313 6d0bc5ca Iustin Pop
  allocnodes <- exitifbad $ Cluster.genAllocNodes gl nl req_nodes True
314 41b5c85a Iustin Pop
315 fcebc9db Iustin Pop
  -- Run the tiered allocation, if enabled
316 fcebc9db Iustin Pop
317 fcebc9db Iustin Pop
  (case optTieredSpec opts of
318 fcebc9db Iustin Pop
     Nothing -> return ()
319 fcebc9db Iustin Pop
     Just tspec -> do
320 d5ccec02 Iustin Pop
       (_, trl_nl, trl_il, trl_ixes, _) <-
321 317b1040 Iustin Pop
           if stop_allocation
322 317b1040 Iustin Pop
           then return result_noalloc
323 8f48f67d Iustin Pop
           else exitifbad (Cluster.tieredAlloc nl il Nothing (iofspec tspec)
324 41b5c85a Iustin Pop
                                  allocnodes [] [])
325 756df409 Iustin Pop
       let spec_map' = tieredSpecMap trl_ixes
326 fcebc9db Iustin Pop
327 6eaa7bb8 Iustin Pop
       printAllocationMap verbose "Tiered allocation map" trl_nl trl_ixes
328 83ad1f3c Iustin Pop
329 417f6b50 Iustin Pop
       maybePrintNodes shownodes "Tiered allocation"
330 417f6b50 Iustin Pop
                           (Cluster.printNodes trl_nl)
331 fcebc9db Iustin Pop
332 4188449c Iustin Pop
       maybeSaveData (optSaveCluster opts) "tiered" "after tiered allocation"
333 4188449c Iustin Pop
                     (ClusterData gl trl_nl trl_il ctags)
334 4188449c Iustin Pop
335 8dda364e Iustin Pop
       printKeys $ map (\(a, fn) -> ("TSPEC_INI_" ++ a, fn tspec)) specData
336 83ad1f3c Iustin Pop
       printKeys $ printStats PTiered (Cluster.totalResources trl_nl)
337 756df409 Iustin Pop
       printKeys [("TSPEC", intercalate " " (formatSpecMap spec_map'))]
338 4886952e Iustin Pop
       printAllocationStats m_cpu nl trl_nl)
339 fcebc9db Iustin Pop
340 fcebc9db Iustin Pop
  -- Run the standard (avg-mode) allocation
341 e10be8f2 Iustin Pop
342 d5ccec02 Iustin Pop
  (ereason, fin_nl, fin_il, ixes, _) <-
343 317b1040 Iustin Pop
      if stop_allocation
344 317b1040 Iustin Pop
      then return result_noalloc
345 8f48f67d Iustin Pop
      else exitifbad (Cluster.iterateAlloc nl il Nothing
346 8f48f67d Iustin Pop
                      reqinst allocnodes [] [])
347 fcebc9db Iustin Pop
348 31e7ac17 Iustin Pop
  let allocs = length ixes
349 5182e970 Iustin Pop
      sreason = reverse $ sortBy (comparing snd) ereason
350 9dcec001 Iustin Pop
351 6eaa7bb8 Iustin Pop
  printAllocationMap verbose "Standard allocation map" fin_nl ixes
352 6eaa7bb8 Iustin Pop
353 417f6b50 Iustin Pop
  maybePrintNodes shownodes "Standard allocation" (Cluster.printNodes fin_nl)
354 2bbf77cc Iustin Pop
355 4188449c Iustin Pop
  maybeSaveData (optSaveCluster opts) "alloc" "after standard allocation"
356 4188449c Iustin Pop
       (ClusterData gl fin_nl fin_il ctags)
357 3e9501d0 Iustin Pop
358 2bbf77cc Iustin Pop
  printResults fin_nl num_instances allocs sreason