Statistics
| Branch: | Tag: | Revision:

root / hspace.hs @ 189bc08f

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