Statistics
| Branch: | Tag: | Revision:

root / htools / hspace.hs @ 2e5eb96a

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