Statistics
| Branch: | Tag: | Revision:

root / hspace.hs @ 9739b6b8

History | View | Annotate | Download (12.3 kB)

1 e10be8f2 Iustin Pop
{-| Cluster space sizing
2 e10be8f2 Iustin Pop
3 e10be8f2 Iustin Pop
-}
4 e10be8f2 Iustin Pop
5 e10be8f2 Iustin Pop
{-
6 e10be8f2 Iustin Pop
7 e10be8f2 Iustin Pop
Copyright (C) 2009 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 e10be8f2 Iustin Pop
import Data.Function
31 e98fb766 Iustin Pop
import Data.Maybe (isJust, fromJust)
32 e10be8f2 Iustin Pop
import Monad
33 e10be8f2 Iustin Pop
import System
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 e10be8f2 Iustin Pop
49 e10be8f2 Iustin Pop
-- | Options list and functions
50 0427285d Iustin Pop
options :: [OptType]
51 e10be8f2 Iustin Pop
options =
52 0427285d Iustin Pop
    [ oPrintNodes
53 0427285d Iustin Pop
    , oNodeFile
54 0427285d Iustin Pop
    , oInstFile
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 0427285d Iustin Pop
    , oShowVer
69 0427285d Iustin Pop
    , oShowHelp
70 e10be8f2 Iustin Pop
    ]
71 e10be8f2 Iustin Pop
72 fcebc9db Iustin Pop
-- | The allocation phase we're in (initial, after tiered allocs, or
73 fcebc9db Iustin Pop
-- after regular allocation).
74 fcebc9db Iustin Pop
data Phase = PInitial
75 fcebc9db Iustin Pop
           | PFinal
76 fcebc9db Iustin Pop
           | PTiered
77 2bbf77cc Iustin Pop
78 2bbf77cc Iustin Pop
statsData :: [(String, Cluster.CStats -> String)]
79 f5b553da Iustin Pop
statsData = [ ("SCORE", printf "%.8f" . Cluster.csScore)
80 f5b553da Iustin Pop
            , ("INST_CNT", printf "%d" . Cluster.csNinst)
81 f5b553da Iustin Pop
            , ("MEM_FREE", printf "%d" . Cluster.csFmem)
82 f5b553da Iustin Pop
            , ("MEM_AVAIL", printf "%d" . Cluster.csAmem)
83 2bbf77cc Iustin Pop
            , ("MEM_RESVD",
84 f5b553da Iustin Pop
               \cs -> printf "%d" (Cluster.csFmem cs - Cluster.csAmem cs))
85 f5b553da Iustin Pop
            , ("MEM_INST", printf "%d" . Cluster.csImem)
86 2bbf77cc Iustin Pop
            , ("MEM_OVERHEAD",
87 f5b553da Iustin Pop
               \cs -> printf "%d" (Cluster.csXmem cs + Cluster.csNmem cs))
88 2bbf77cc Iustin Pop
            , ("MEM_EFF",
89 f5b553da Iustin Pop
               \cs -> printf "%.8f" (fromIntegral (Cluster.csImem cs) /
90 f5b553da Iustin Pop
                                     Cluster.csTmem cs))
91 f5b553da Iustin Pop
            , ("DSK_FREE", printf "%d" . Cluster.csFdsk)
92 9739b6b8 Iustin Pop
            , ("DSK_AVAIL", printf "%d". Cluster.csAdsk)
93 2bbf77cc Iustin Pop
            , ("DSK_RESVD",
94 f5b553da Iustin Pop
               \cs -> printf "%d" (Cluster.csFdsk cs - Cluster.csAdsk cs))
95 f5b553da Iustin Pop
            , ("DSK_INST", printf "%d" . Cluster.csIdsk)
96 2bbf77cc Iustin Pop
            , ("DSK_EFF",
97 f5b553da Iustin Pop
               \cs -> printf "%.8f" (fromIntegral (Cluster.csIdsk cs) /
98 f5b553da Iustin Pop
                                    Cluster.csTdsk cs))
99 f5b553da Iustin Pop
            , ("CPU_INST", printf "%d" . Cluster.csIcpu)
100 2bbf77cc Iustin Pop
            , ("CPU_EFF",
101 f5b553da Iustin Pop
               \cs -> printf "%.8f" (fromIntegral (Cluster.csIcpu cs) /
102 f5b553da Iustin Pop
                                     Cluster.csTcpu cs))
103 f5b553da Iustin Pop
            , ("MNODE_MEM_AVAIL", printf "%d" . Cluster.csMmem)
104 f5b553da Iustin Pop
            , ("MNODE_DSK_AVAIL", printf "%d" . Cluster.csMdsk)
105 2bbf77cc Iustin Pop
            ]
106 2bbf77cc Iustin Pop
107 1f9066c0 Iustin Pop
specData :: [(String, RSpec -> String)]
108 1f9066c0 Iustin Pop
specData = [ ("MEM", printf "%d" . rspecMem)
109 1f9066c0 Iustin Pop
           , ("DSK", printf "%d" . rspecDsk)
110 1f9066c0 Iustin Pop
           , ("CPU", printf "%d" . rspecCpu)
111 2bbf77cc Iustin Pop
           ]
112 2bbf77cc Iustin Pop
113 2bbf77cc Iustin Pop
clusterData :: [(String, Cluster.CStats -> String)]
114 f5b553da Iustin Pop
clusterData = [ ("MEM", printf "%.0f" . Cluster.csTmem)
115 f5b553da Iustin Pop
              , ("DSK", printf "%.0f" . Cluster.csTdsk)
116 f5b553da Iustin Pop
              , ("CPU", printf "%.0f" . Cluster.csTcpu)
117 2bbf77cc Iustin Pop
              ]
118 2bbf77cc Iustin Pop
119 58631b72 Iustin Pop
-- | Recursively place instances on the cluster until we're out of space
120 e10be8f2 Iustin Pop
iterateDepth :: Node.List
121 e10be8f2 Iustin Pop
             -> Instance.List
122 e10be8f2 Iustin Pop
             -> Instance.Instance
123 e10be8f2 Iustin Pop
             -> Int
124 9dcec001 Iustin Pop
             -> [Instance.Instance]
125 31e7ac17 Iustin Pop
             -> Result (FailStats, Node.List, [Instance.Instance])
126 9dcec001 Iustin Pop
iterateDepth nl il newinst nreq ixes =
127 9dcec001 Iustin Pop
      let depth = length ixes
128 9f6dcdea Iustin Pop
          newname = printf "new-%d" depth::String
129 9f6dcdea Iustin Pop
          newidx = length (Container.elems il) + depth
130 e10be8f2 Iustin Pop
          newi2 = Instance.setIdx (Instance.setName newinst newname) newidx
131 31e7ac17 Iustin Pop
      in case Cluster.tryAlloc nl il newi2 nreq of
132 31e7ac17 Iustin Pop
           Bad s -> Bad s
133 31e7ac17 Iustin Pop
           Ok (errs, _, sols3) ->
134 478df686 Iustin Pop
               case sols3 of
135 31e7ac17 Iustin Pop
                 Nothing -> Ok (Cluster.collapseFailures errs, nl, ixes)
136 478df686 Iustin Pop
                 Just (_, (xnl, xi, _)) ->
137 478df686 Iustin Pop
                     iterateDepth xnl il newinst nreq $! (xi:ixes)
138 e10be8f2 Iustin Pop
139 fcebc9db Iustin Pop
tieredAlloc :: Node.List
140 fcebc9db Iustin Pop
            -> Instance.List
141 fcebc9db Iustin Pop
            -> Instance.Instance
142 fcebc9db Iustin Pop
            -> Int
143 fcebc9db Iustin Pop
            -> [Instance.Instance]
144 fcebc9db Iustin Pop
            -> Result (FailStats, Node.List, [Instance.Instance])
145 fcebc9db Iustin Pop
tieredAlloc nl il newinst nreq ixes =
146 fcebc9db Iustin Pop
    case iterateDepth nl il newinst nreq ixes of
147 fcebc9db Iustin Pop
      Bad s -> Bad s
148 fcebc9db Iustin Pop
      Ok (errs, nl', ixes') ->
149 fcebc9db Iustin Pop
          case Instance.shrinkByType newinst . fst . last $
150 fcebc9db Iustin Pop
               sortBy (compare `on` snd) errs of
151 fcebc9db Iustin Pop
            Bad _ -> Ok (errs, nl', ixes')
152 fcebc9db Iustin Pop
            Ok newinst' ->
153 fcebc9db Iustin Pop
                tieredAlloc nl' il newinst' nreq ixes'
154 fcebc9db Iustin Pop
155 fcebc9db Iustin Pop
156 58631b72 Iustin Pop
-- | Function to print stats for a given phase
157 2bbf77cc Iustin Pop
printStats :: Phase -> Cluster.CStats -> [(String, String)]
158 2bbf77cc Iustin Pop
printStats ph cs =
159 2bbf77cc Iustin Pop
  map (\(s, fn) -> (printf "%s_%s" kind s, fn cs)) statsData
160 2bbf77cc Iustin Pop
  where kind = case ph of
161 2bbf77cc Iustin Pop
                 PInitial -> "INI"
162 2bbf77cc Iustin Pop
                 PFinal -> "FIN"
163 fcebc9db Iustin Pop
                 PTiered -> "TRL"
164 e10be8f2 Iustin Pop
165 dca7f396 Iustin Pop
-- | Print final stats and related metrics
166 dca7f396 Iustin Pop
printResults :: Node.List -> Int -> Int -> [(FailMode, Int)] -> IO ()
167 dca7f396 Iustin Pop
printResults fin_nl num_instances allocs sreason = do
168 dca7f396 Iustin Pop
  let fin_stats = Cluster.totalResources fin_nl
169 dca7f396 Iustin Pop
      fin_instances = num_instances + allocs
170 dca7f396 Iustin Pop
171 f5b553da Iustin Pop
  when (num_instances + allocs /= Cluster.csNinst fin_stats) $
172 de4ac2c2 Iustin Pop
       do
173 de4ac2c2 Iustin Pop
         hPrintf stderr "ERROR: internal inconsistency, allocated (%d)\
174 de4ac2c2 Iustin Pop
                        \ != counted (%d)\n" (num_instances + allocs)
175 f5b553da Iustin Pop
                                 (Cluster.csNinst fin_stats)
176 de4ac2c2 Iustin Pop
         exitWith $ ExitFailure 1
177 de4ac2c2 Iustin Pop
178 2bbf77cc Iustin Pop
  printKeys $ printStats PFinal fin_stats
179 2bbf77cc Iustin Pop
  printKeys [ ("ALLOC_USAGE", printf "%.8f"
180 2bbf77cc Iustin Pop
                                ((fromIntegral num_instances::Double) /
181 2bbf77cc Iustin Pop
                                 fromIntegral fin_instances))
182 31e7ac17 Iustin Pop
            , ("ALLOC_INSTANCES", printf "%d" allocs)
183 2bbf77cc Iustin Pop
            , ("ALLOC_FAIL_REASON", map toUpper . show . fst $ head sreason)
184 2bbf77cc Iustin Pop
            ]
185 2bbf77cc Iustin Pop
  printKeys $ map (\(x, y) -> (printf "ALLOC_%s_CNT" (show x),
186 2bbf77cc Iustin Pop
                               printf "%d" y)) sreason
187 2bbf77cc Iustin Pop
  -- this should be the final entry
188 2bbf77cc Iustin Pop
  printKeys [("OK", "1")]
189 2bbf77cc Iustin Pop
190 9739b6b8 Iustin Pop
-- | Ensure a value is quoted if needed
191 9739b6b8 Iustin Pop
ensureQuoted :: String -> String
192 9739b6b8 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 2bbf77cc 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 366a7c89 Iustin Pop
                     , (Container.nameOf nl $ Instance.pNode i)
204 366a7c89 Iustin Pop
                     , (let sdx = Instance.sNode i
205 366a7c89 Iustin Pop
                        in if sdx == Node.noSecondary then ""
206 366a7c89 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 e10be8f2 Iustin Pop
-- | Main function.
213 e10be8f2 Iustin Pop
main :: IO ()
214 e10be8f2 Iustin Pop
main = do
215 e10be8f2 Iustin Pop
  cmd_args <- System.getArgs
216 0427285d Iustin Pop
  (opts, args) <- parseOpts cmd_args "hspace" options
217 e10be8f2 Iustin Pop
218 e10be8f2 Iustin Pop
  unless (null args) $ do
219 e10be8f2 Iustin Pop
         hPutStrLn stderr "Error: this program doesn't take any arguments."
220 e10be8f2 Iustin Pop
         exitWith $ ExitFailure 1
221 e10be8f2 Iustin Pop
222 2795466b Iustin Pop
  let verbose = optVerbose opts
223 1f9066c0 Iustin Pop
      ispec = optISpec opts
224 e98fb766 Iustin Pop
      shownodes = optShowNodes opts
225 2795466b Iustin Pop
226 0427285d Iustin Pop
  (fixed_nl, il, csf) <- loadExternalData opts
227 2795466b Iustin Pop
228 1f9066c0 Iustin Pop
  printKeys $ map (\(a, fn) -> ("SPEC_" ++ a, fn ispec)) specData
229 1f9066c0 Iustin Pop
  printKeys [ ("SPEC_RQN", printf "%d" (optINodes opts)) ]
230 7e74e7db Iustin Pop
231 9dcec001 Iustin Pop
  let num_instances = length $ Container.elems il
232 e10be8f2 Iustin Pop
233 e10be8f2 Iustin Pop
  let offline_names = optOffline opts
234 e10be8f2 Iustin Pop
      all_nodes = Container.elems fixed_nl
235 e10be8f2 Iustin Pop
      all_names = map Node.name all_nodes
236 9f6dcdea Iustin Pop
      offline_wrong = filter (flip notElem all_names) offline_names
237 e10be8f2 Iustin Pop
      offline_indices = map Node.idx $
238 e10be8f2 Iustin Pop
                        filter (\n -> elem (Node.name n) offline_names)
239 e10be8f2 Iustin Pop
                               all_nodes
240 9abe9caf Iustin Pop
      req_nodes = optINodes opts
241 83a91400 Iustin Pop
      m_cpu = optMcpu opts
242 83a91400 Iustin Pop
      m_dsk = optMdsk opts
243 e10be8f2 Iustin Pop
244 e10be8f2 Iustin Pop
  when (length offline_wrong > 0) $ do
245 2795466b Iustin Pop
         hPrintf stderr "Error: Wrong node name(s) set as offline: %s\n"
246 2795466b Iustin Pop
                     (commaJoin offline_wrong)
247 e10be8f2 Iustin Pop
         exitWith $ ExitFailure 1
248 e10be8f2 Iustin Pop
249 9abe9caf Iustin Pop
  when (req_nodes /= 1 && req_nodes /= 2) $ do
250 2795466b Iustin Pop
         hPrintf stderr "Error: Invalid required nodes (%d)\n" req_nodes
251 9abe9caf Iustin Pop
         exitWith $ ExitFailure 1
252 9abe9caf Iustin Pop
253 83a91400 Iustin Pop
  let nm = Container.map (\n -> if elem (Node.idx n) offline_indices
254 e10be8f2 Iustin Pop
                                then Node.setOffline n True
255 e10be8f2 Iustin Pop
                                else n) fixed_nl
256 83a91400 Iustin Pop
      nl = Container.map (flip Node.setMdsk m_dsk . flip Node.setMcpu m_cpu)
257 83a91400 Iustin Pop
           nm
258 e10be8f2 Iustin Pop
259 9f6dcdea Iustin Pop
  when (length csf > 0 && verbose > 1) $
260 2bbf77cc Iustin Pop
       hPrintf stderr "Note: Stripping common suffix of '%s' from names\n" csf
261 e10be8f2 Iustin Pop
262 e98fb766 Iustin Pop
  when (isJust shownodes) $
263 e10be8f2 Iustin Pop
       do
264 2bbf77cc Iustin Pop
         hPutStrLn stderr "Initial cluster status:"
265 e98fb766 Iustin Pop
         hPutStrLn stderr $ Cluster.printNodes nl (fromJust shownodes)
266 e10be8f2 Iustin Pop
267 e10be8f2 Iustin Pop
  let ini_cv = Cluster.compCV nl
268 621de5b7 Iustin Pop
      ini_stats = Cluster.totalResources nl
269 e10be8f2 Iustin Pop
270 2485487d Iustin Pop
  when (verbose > 2) $
271 2bbf77cc Iustin Pop
         hPrintf stderr "Initial coefficients: overall %.8f, %s\n"
272 2bbf77cc Iustin Pop
                 ini_cv (Cluster.printStats nl)
273 de4ac2c2 Iustin Pop
274 2bbf77cc Iustin Pop
  printKeys $ map (\(a, fn) -> ("CLUSTER_" ++ a, fn ini_stats)) clusterData
275 2bbf77cc Iustin Pop
  printKeys [("CLUSTER_NODES", printf "%d" (length all_nodes))]
276 2bbf77cc Iustin Pop
  printKeys $ printStats PInitial ini_stats
277 e10be8f2 Iustin Pop
278 dca7f396 Iustin Pop
  let bad_nodes = fst $ Cluster.computeBadItems nl il
279 dca7f396 Iustin Pop
  when (length bad_nodes > 0) $ do
280 dca7f396 Iustin Pop
         -- This is failn1 case, so we print the same final stats and
281 dca7f396 Iustin Pop
         -- exit early
282 dca7f396 Iustin Pop
         printResults nl num_instances 0 [(FailN1, 1)]
283 dca7f396 Iustin Pop
         exitWith ExitSuccess
284 dca7f396 Iustin Pop
285 fcebc9db Iustin Pop
  -- utility functions
286 fcebc9db Iustin Pop
  let iofspec spx = Instance.create "new" (rspecMem spx) (rspecDsk spx)
287 fcebc9db Iustin Pop
                    (rspecCpu spx) "ADMIN_down" (-1) (-1)
288 fcebc9db Iustin Pop
      exitifbad val = (case val of
289 fcebc9db Iustin Pop
                         Bad s -> do
290 fcebc9db Iustin Pop
                           hPrintf stderr "Failure: %s\n" s
291 fcebc9db Iustin Pop
                           exitWith $ ExitFailure 1
292 fcebc9db Iustin Pop
                         Ok x -> return x)
293 fcebc9db Iustin Pop
294 fcebc9db Iustin Pop
295 fcebc9db Iustin Pop
  let reqinst = iofspec ispec
296 fcebc9db Iustin Pop
297 fcebc9db Iustin Pop
  -- Run the tiered allocation, if enabled
298 fcebc9db Iustin Pop
299 fcebc9db Iustin Pop
  (case optTieredSpec opts of
300 fcebc9db Iustin Pop
     Nothing -> return ()
301 fcebc9db Iustin Pop
     Just tspec -> do
302 fcebc9db Iustin Pop
       let tresu = tieredAlloc nl il (iofspec tspec) req_nodes []
303 fcebc9db Iustin Pop
       (_, trl_nl, trl_ixes) <- exitifbad tresu
304 fcebc9db Iustin Pop
       let fin_trl_ixes = reverse trl_ixes
305 83ad1f3c Iustin Pop
           ix_byspec = groupBy ((==) `on` Instance.specOf) fin_trl_ixes
306 83ad1f3c Iustin Pop
           spec_map = map (\ixs -> (Instance.specOf $ head ixs, length ixs))
307 83ad1f3c Iustin Pop
                      ix_byspec::[(RSpec, Int)]
308 a160c28e Iustin Pop
           spec_map' = map (\(spec, cnt) ->
309 a160c28e Iustin Pop
                                printf "%d,%d,%d=%d" (rspecMem spec)
310 a160c28e Iustin Pop
                                       (rspecDsk spec) (rspecCpu spec) cnt)
311 a160c28e Iustin Pop
                       spec_map::[String]
312 fcebc9db Iustin Pop
313 fcebc9db Iustin Pop
       when (verbose > 1) $ do
314 fcebc9db Iustin Pop
         hPutStrLn stderr "Tiered allocation map"
315 fcebc9db Iustin Pop
         hPutStr stderr . unlines . map ((:) ' ' .  intercalate " ") $
316 fcebc9db Iustin Pop
                 formatTable (map (printInstance trl_nl) fin_trl_ixes)
317 fcebc9db Iustin Pop
                                 [False, False, False, True, True, True]
318 83ad1f3c Iustin Pop
319 e98fb766 Iustin Pop
       when (isJust shownodes) $ do
320 fcebc9db Iustin Pop
         hPutStrLn stderr ""
321 fcebc9db Iustin Pop
         hPutStrLn stderr "Tiered allocation status:"
322 e98fb766 Iustin Pop
         hPutStrLn stderr $ Cluster.printNodes trl_nl (fromJust shownodes)
323 fcebc9db Iustin Pop
324 83ad1f3c Iustin Pop
       printKeys $ printStats PTiered (Cluster.totalResources trl_nl)
325 83ad1f3c Iustin Pop
       printKeys [("TSPEC", intercalate " " spec_map')])
326 fcebc9db Iustin Pop
327 fcebc9db Iustin Pop
  -- Run the standard (avg-mode) allocation
328 e10be8f2 Iustin Pop
329 1f9066c0 Iustin Pop
  let result = iterateDepth nl il reqinst req_nodes []
330 fcebc9db Iustin Pop
  (ereason, fin_nl, ixes) <- exitifbad result
331 fcebc9db Iustin Pop
332 31e7ac17 Iustin Pop
  let allocs = length ixes
333 9dcec001 Iustin Pop
      fin_ixes = reverse ixes
334 44763b51 Iustin Pop
      sreason = reverse $ sortBy (compare `on` snd) ereason
335 9dcec001 Iustin Pop
336 366a7c89 Iustin Pop
  when (verbose > 1) $ do
337 366a7c89 Iustin Pop
         hPutStrLn stderr "Instance map"
338 366a7c89 Iustin Pop
         hPutStr stderr . unlines . map ((:) ' ' .  intercalate " ") $
339 366a7c89 Iustin Pop
                 formatTable (map (printInstance fin_nl) fin_ixes)
340 366a7c89 Iustin Pop
                                 [False, False, False, True, True, True]
341 e98fb766 Iustin Pop
  when (isJust shownodes) $
342 e10be8f2 Iustin Pop
       do
343 2bbf77cc Iustin Pop
         hPutStrLn stderr ""
344 2bbf77cc Iustin Pop
         hPutStrLn stderr "Final cluster status:"
345 e98fb766 Iustin Pop
         hPutStrLn stderr $ Cluster.printNodes fin_nl (fromJust shownodes)
346 2bbf77cc Iustin Pop
347 2bbf77cc Iustin Pop
  printResults fin_nl num_instances allocs sreason