Statistics
| Branch: | Tag: | Revision:

root / hbal.hs @ 9b1e1cc9

History | View | Annotate | Download (11.8 kB)

1 e4f08c46 Iustin Pop
{-| Solver for N+1 cluster errors
2 e4f08c46 Iustin Pop
3 e4f08c46 Iustin Pop
-}
4 e4f08c46 Iustin Pop
5 e2fa2baf Iustin Pop
{-
6 e2fa2baf Iustin Pop
7 e2fa2baf Iustin Pop
Copyright (C) 2009 Google Inc.
8 e2fa2baf Iustin Pop
9 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
10 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
11 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 e2fa2baf Iustin Pop
(at your option) any later version.
13 e2fa2baf Iustin Pop
14 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
15 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 e2fa2baf Iustin Pop
General Public License for more details.
18 e2fa2baf Iustin Pop
19 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
20 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
21 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 e2fa2baf Iustin Pop
02110-1301, USA.
23 e2fa2baf Iustin Pop
24 e2fa2baf Iustin Pop
-}
25 e2fa2baf Iustin Pop
26 e4f08c46 Iustin Pop
module Main (main) where
27 e4f08c46 Iustin Pop
28 e4f08c46 Iustin Pop
import Data.List
29 e4f08c46 Iustin Pop
import Data.Function
30 e0eb63f0 Iustin Pop
import Data.Maybe (isJust, fromJust, fromMaybe)
31 e4f08c46 Iustin Pop
import Monad
32 e4f08c46 Iustin Pop
import System
33 e4f08c46 Iustin Pop
import System.IO
34 e4f08c46 Iustin Pop
import System.Console.GetOpt
35 e4f08c46 Iustin Pop
import qualified System
36 e4f08c46 Iustin Pop
37 e4f08c46 Iustin Pop
import Text.Printf (printf)
38 e4f08c46 Iustin Pop
39 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Container as Container
40 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
41 ec18dca9 Iustin Pop
import qualified Ganeti.HTools.Node as Node
42 209b3711 Iustin Pop
import qualified Ganeti.HTools.CLI as CLI
43 040afc35 Iustin Pop
44 669d7e3d Iustin Pop
import Ganeti.HTools.Utils
45 e4f08c46 Iustin Pop
46 e4f08c46 Iustin Pop
-- | Command line options structure.
47 e4f08c46 Iustin Pop
data Options = Options
48 e0eb63f0 Iustin Pop
    { optShowNodes :: Bool           -- ^ Whether to show node status
49 e0eb63f0 Iustin Pop
    , optShowCmds  :: Maybe FilePath -- ^ Whether to show the command list
50 e0eb63f0 Iustin Pop
    , optOneline   :: Bool           -- ^ Switch output to a single line
51 e0eb63f0 Iustin Pop
    , optNodef     :: FilePath       -- ^ Path to the nodes file
52 8032b3b5 Iustin Pop
    , optNodeSet   :: Bool           -- ^ The nodes have been set by options
53 e0eb63f0 Iustin Pop
    , optInstf     :: FilePath       -- ^ Path to the instances file
54 8032b3b5 Iustin Pop
    , optInstSet   :: Bool           -- ^ The insts have been set by options
55 e0eb63f0 Iustin Pop
    , optMaxLength :: Int            -- ^ Stop after this many steps
56 e0eb63f0 Iustin Pop
    , optMaster    :: String         -- ^ Collect data from RAPI
57 e0eb63f0 Iustin Pop
    , optVerbose   :: Int            -- ^ Verbosity level
58 e0eb63f0 Iustin Pop
    , optOffline   :: [String]       -- ^ Names of offline nodes
59 b0517d61 Iustin Pop
    , optMinScore  :: Cluster.Score  -- ^ The minimum score we aim for
60 e0eb63f0 Iustin Pop
    , optShowVer   :: Bool           -- ^ Just show the program version
61 e0eb63f0 Iustin Pop
    , optShowHelp  :: Bool           -- ^ Just show the help
62 e4f08c46 Iustin Pop
    } deriving Show
63 e4f08c46 Iustin Pop
64 75d1edf8 Iustin Pop
instance CLI.CLIOptions Options where
65 75d1edf8 Iustin Pop
    showVersion = optShowVer
66 75d1edf8 Iustin Pop
    showHelp    = optShowHelp
67 75d1edf8 Iustin Pop
68 fae371cc Iustin Pop
instance CLI.EToolOptions Options where
69 fae371cc Iustin Pop
    nodeFile   = optNodef
70 fae371cc Iustin Pop
    nodeSet    = optNodeSet
71 fae371cc Iustin Pop
    instFile   = optInstf
72 fae371cc Iustin Pop
    instSet    = optInstSet
73 fae371cc Iustin Pop
    masterName = optMaster
74 fae371cc Iustin Pop
    silent a   = (optVerbose a) == 0
75 fae371cc Iustin Pop
76 e4f08c46 Iustin Pop
-- | Default values for the command line options.
77 e4f08c46 Iustin Pop
defaultOptions :: Options
78 e4f08c46 Iustin Pop
defaultOptions  = Options
79 e4f08c46 Iustin Pop
 { optShowNodes = False
80 e0eb63f0 Iustin Pop
 , optShowCmds  = Nothing
81 27f96567 Iustin Pop
 , optOneline   = False
82 e4f08c46 Iustin Pop
 , optNodef     = "nodes"
83 8032b3b5 Iustin Pop
 , optNodeSet   = False
84 e4f08c46 Iustin Pop
 , optInstf     = "instances"
85 8032b3b5 Iustin Pop
 , optInstSet   = False
86 7dfaafb1 Iustin Pop
 , optMaxLength = -1
87 a30b2f5b Iustin Pop
 , optMaster    = ""
88 d09b6ed3 Iustin Pop
 , optVerbose   = 1
89 ec18dca9 Iustin Pop
 , optOffline   = []
90 b0517d61 Iustin Pop
 , optMinScore  = 1e-9
91 209b3711 Iustin Pop
 , optShowVer   = False
92 209b3711 Iustin Pop
 , optShowHelp  = False
93 e4f08c46 Iustin Pop
 }
94 e4f08c46 Iustin Pop
95 e4f08c46 Iustin Pop
-- | Options list and functions
96 e4f08c46 Iustin Pop
options :: [OptDescr (Options -> Options)]
97 e4f08c46 Iustin Pop
options =
98 e4f08c46 Iustin Pop
    [ Option ['p']     ["print-nodes"]
99 e4f08c46 Iustin Pop
      (NoArg (\ opts -> opts { optShowNodes = True }))
100 e4f08c46 Iustin Pop
      "print the final node list"
101 e4f08c46 Iustin Pop
    , Option ['C']     ["print-commands"]
102 e0eb63f0 Iustin Pop
      (OptArg ((\ f opts -> opts { optShowCmds = Just f }) . fromMaybe "-")
103 e0eb63f0 Iustin Pop
                  "FILE")
104 e0eb63f0 Iustin Pop
      "print the ganeti command list for reaching the solution,\
105 e0eb63f0 Iustin Pop
      \if an argument is passed then write the commands to a file named\
106 e0eb63f0 Iustin Pop
      \ as such"
107 27f96567 Iustin Pop
    , Option ['o']     ["oneline"]
108 27f96567 Iustin Pop
      (NoArg (\ opts -> opts { optOneline = True }))
109 27f96567 Iustin Pop
      "print the ganeti command list for reaching the solution"
110 7eff5b09 Iustin Pop
    , Option ['n']     ["nodes"]
111 8032b3b5 Iustin Pop
      (ReqArg (\ f opts -> opts { optNodef = f, optNodeSet = True }) "FILE")
112 e4f08c46 Iustin Pop
      "the node list FILE"
113 7eff5b09 Iustin Pop
    , Option ['i']     ["instances"]
114 8032b3b5 Iustin Pop
      (ReqArg (\ f opts -> opts { optInstf =  f, optInstSet = True }) "FILE")
115 e4f08c46 Iustin Pop
      "the instance list FILE"
116 7eff5b09 Iustin Pop
    , Option ['m']     ["master"]
117 a30b2f5b Iustin Pop
      (ReqArg (\ m opts -> opts { optMaster = m }) "ADDRESS")
118 a30b2f5b Iustin Pop
      "collect data via RAPI at the given ADDRESS"
119 7eff5b09 Iustin Pop
    , Option ['l']     ["max-length"]
120 7dfaafb1 Iustin Pop
      (ReqArg (\ i opts -> opts { optMaxLength =  (read i)::Int }) "N")
121 7dfaafb1 Iustin Pop
      "cap the solution at this many moves (useful for very unbalanced \
122 7dfaafb1 Iustin Pop
      \clusters)"
123 7eff5b09 Iustin Pop
    , Option ['v']     ["verbose"]
124 209b3711 Iustin Pop
      (NoArg (\ opts -> opts { optVerbose = (optVerbose opts) + 1 }))
125 7eff5b09 Iustin Pop
      "increase the verbosity level"
126 d09b6ed3 Iustin Pop
    , Option ['q']     ["quiet"]
127 d09b6ed3 Iustin Pop
      (NoArg (\ opts -> opts { optVerbose = (optVerbose opts) - 1 }))
128 d09b6ed3 Iustin Pop
      "decrease the verbosity level"
129 ec18dca9 Iustin Pop
    , Option ['O']     ["offline"]
130 ec18dca9 Iustin Pop
      (ReqArg (\ n opts -> opts { optOffline = n:optOffline opts }) "NODE")
131 b0517d61 Iustin Pop
      " set node as offline"
132 b0517d61 Iustin Pop
    , Option ['e']     ["min-score"]
133 b0517d61 Iustin Pop
      (ReqArg (\ e opts -> opts { optMinScore = read e }) "EPSILON")
134 b0517d61 Iustin Pop
      " mininum score to aim for"
135 209b3711 Iustin Pop
    , Option ['V']     ["version"]
136 209b3711 Iustin Pop
      (NoArg (\ opts -> opts { optShowVer = True}))
137 209b3711 Iustin Pop
      "show the version of the program"
138 209b3711 Iustin Pop
    , Option ['h']     ["help"]
139 209b3711 Iustin Pop
      (NoArg (\ opts -> opts { optShowHelp = True}))
140 209b3711 Iustin Pop
      "show help"
141 7ef4d93e Iustin Pop
    ]
142 e4f08c46 Iustin Pop
143 6dc960bc Iustin Pop
{- | Start computing the solution at the given depth and recurse until
144 6dc960bc Iustin Pop
we find a valid solution or we exceed the maximum depth.
145 6dc960bc Iustin Pop
146 6dc960bc Iustin Pop
-}
147 6dc960bc Iustin Pop
iterateDepth :: Cluster.Table    -- ^ The starting table
148 6dc960bc Iustin Pop
             -> Int              -- ^ Remaining length
149 6dc960bc Iustin Pop
             -> Int              -- ^ Max node name len
150 6dc960bc Iustin Pop
             -> Int              -- ^ Max instance name len
151 6dc960bc Iustin Pop
             -> [[String]]       -- ^ Current command list
152 6dc960bc Iustin Pop
             -> Bool             -- ^ Wheter to be silent
153 b0517d61 Iustin Pop
             -> Cluster.Score    -- ^ Score at which to stop
154 6dc960bc Iustin Pop
             -> IO (Cluster.Table, [[String]]) -- ^ The resulting table and
155 6dc960bc Iustin Pop
                                               -- commands
156 db1bcfe8 Iustin Pop
iterateDepth ini_tbl max_rounds nmlen imlen
157 b0517d61 Iustin Pop
             cmd_strs oneline min_score =
158 6dc960bc Iustin Pop
    let Cluster.Table ini_nl ini_il ini_cv ini_plc = ini_tbl
159 6dc960bc Iustin Pop
        all_inst = Container.elems ini_il
160 ec18dca9 Iustin Pop
        node_idx = map Node.idx . filter (not . Node.offline) $
161 ec18dca9 Iustin Pop
                   Container.elems ini_nl
162 6dc960bc Iustin Pop
        fin_tbl = Cluster.checkMove node_idx ini_tbl all_inst
163 6dc960bc Iustin Pop
        (Cluster.Table _ _ fin_cv fin_plc) = fin_tbl
164 6dc960bc Iustin Pop
        ini_plc_len = length ini_plc
165 6dc960bc Iustin Pop
        fin_plc_len = length fin_plc
166 6dc960bc Iustin Pop
        allowed_next = (max_rounds < 0 || length fin_plc < max_rounds)
167 6dc960bc Iustin Pop
    in
168 6dc960bc Iustin Pop
      do
169 6dc960bc Iustin Pop
        let
170 db1bcfe8 Iustin Pop
            (sol_line, cmds) = Cluster.printSolutionLine ini_nl ini_il
171 6dc960bc Iustin Pop
                               nmlen imlen (head fin_plc) fin_plc_len
172 6dc960bc Iustin Pop
            upd_cmd_strs = cmds:cmd_strs
173 6dc960bc Iustin Pop
        unless (oneline || fin_plc_len == ini_plc_len) $ do
174 6dc960bc Iustin Pop
          putStrLn sol_line
175 6dc960bc Iustin Pop
          hFlush stdout
176 6dc960bc Iustin Pop
        (if fin_cv < ini_cv then -- this round made success, try deeper
177 b0517d61 Iustin Pop
             if allowed_next && fin_cv > min_score
178 db1bcfe8 Iustin Pop
             then iterateDepth fin_tbl max_rounds
179 b0517d61 Iustin Pop
                  nmlen imlen upd_cmd_strs oneline min_score
180 6dc960bc Iustin Pop
             -- don't go deeper, but return the better solution
181 6dc960bc Iustin Pop
             else return (fin_tbl, upd_cmd_strs)
182 6dc960bc Iustin Pop
         else
183 6dc960bc Iustin Pop
             return (ini_tbl, cmd_strs))
184 6dc960bc Iustin Pop
185 ba6c6006 Iustin Pop
-- | Formats the solution for the oneline display
186 ba6c6006 Iustin Pop
formatOneline :: Double -> Int -> Double -> String
187 ba6c6006 Iustin Pop
formatOneline ini_cv plc_len fin_cv =
188 ba6c6006 Iustin Pop
    printf "%.8f %d %.8f %8.3f" ini_cv plc_len fin_cv
189 ba6c6006 Iustin Pop
               (if fin_cv == 0 then 1 else (ini_cv / fin_cv))
190 ba6c6006 Iustin Pop
191 e4f08c46 Iustin Pop
-- | Main function.
192 e4f08c46 Iustin Pop
main :: IO ()
193 e4f08c46 Iustin Pop
main = do
194 e4f08c46 Iustin Pop
  cmd_args <- System.getArgs
195 75d1edf8 Iustin Pop
  (opts, args) <- CLI.parseOpts cmd_args "hbal" options defaultOptions
196 45f01962 Iustin Pop
197 45f01962 Iustin Pop
  unless (null args) $ do
198 45f01962 Iustin Pop
         hPutStrLn stderr "Error: this program doesn't take any arguments."
199 45f01962 Iustin Pop
         exitWith $ ExitFailure 1
200 a30b2f5b Iustin Pop
201 fae371cc Iustin Pop
  let oneline = optOneline opts
202 7eff5b09 Iustin Pop
      verbose = optVerbose opts
203 fae371cc Iustin Pop
204 8472a321 Iustin Pop
  (fixed_nl, il, csf) <- CLI.loadExternalData opts
205 ec18dca9 Iustin Pop
206 ec18dca9 Iustin Pop
  let offline_names = optOffline opts
207 db1bcfe8 Iustin Pop
      all_nodes = Container.elems fixed_nl
208 db1bcfe8 Iustin Pop
      all_names = map Node.name all_nodes
209 3d7cd10b Iustin Pop
      offline_wrong = filter (\n -> not $ elem n all_names) offline_names
210 db1bcfe8 Iustin Pop
      offline_indices = map Node.idx $
211 db1bcfe8 Iustin Pop
                        filter (\n -> elem (Node.name n) offline_names)
212 db1bcfe8 Iustin Pop
                               all_nodes
213 ec18dca9 Iustin Pop
214 3d7cd10b Iustin Pop
  when (length offline_wrong > 0) $ do
215 3d7cd10b Iustin Pop
         printf "Wrong node name(s) set as offline: %s\n"
216 3d7cd10b Iustin Pop
                (commaJoin offline_wrong)
217 3d7cd10b Iustin Pop
         exitWith $ ExitFailure 1
218 3d7cd10b Iustin Pop
219 ec18dca9 Iustin Pop
  let nl = Container.map (\n -> if elem (Node.idx n) offline_indices
220 ec18dca9 Iustin Pop
                                then Node.setOffline n True
221 a1c6212e Iustin Pop
                                else n) fixed_nl
222 a30b2f5b Iustin Pop
223 dcbcdb58 Iustin Pop
  when (Container.size il == 0) $ do
224 926c35b1 Iustin Pop
         (if oneline then putStrLn $ formatOneline 0 0 0
225 926c35b1 Iustin Pop
          else printf "Cluster is empty, exiting.\n")
226 dcbcdb58 Iustin Pop
         exitWith ExitSuccess
227 dcbcdb58 Iustin Pop
228 27f96567 Iustin Pop
  unless oneline $ printf "Loaded %d nodes, %d instances\n"
229 e4f08c46 Iustin Pop
             (Container.size nl)
230 e4f08c46 Iustin Pop
             (Container.size il)
231 a0529a64 Iustin Pop
232 d09b6ed3 Iustin Pop
  when (length csf > 0 && not oneline && verbose > 1) $ do
233 a0529a64 Iustin Pop
         printf "Note: Stripping common suffix of '%s' from names\n" csf
234 a0529a64 Iustin Pop
235 e4f08c46 Iustin Pop
  let (bad_nodes, bad_instances) = Cluster.computeBadItems nl il
236 7eff5b09 Iustin Pop
  unless (oneline || verbose == 0) $ printf
237 27f96567 Iustin Pop
             "Initial check done: %d bad nodes, %d bad instances.\n"
238 e4f08c46 Iustin Pop
             (length bad_nodes) (length bad_instances)
239 e4f08c46 Iustin Pop
240 e4f08c46 Iustin Pop
  when (length bad_nodes > 0) $ do
241 289c3835 Iustin Pop
         putStrLn "Cluster is not N+1 happy, continuing but no guarantee \
242 289c3835 Iustin Pop
                  \that the cluster will end N+1 happy."
243 e4f08c46 Iustin Pop
244 e4f08c46 Iustin Pop
  when (optShowNodes opts) $
245 e4f08c46 Iustin Pop
       do
246 e4f08c46 Iustin Pop
         putStrLn "Initial cluster status:"
247 dbd6700b Iustin Pop
         putStrLn $ Cluster.printNodes nl
248 e4f08c46 Iustin Pop
249 e4f08c46 Iustin Pop
  let ini_cv = Cluster.compCV nl
250 e4f08c46 Iustin Pop
      ini_tbl = Cluster.Table nl il ini_cv []
251 b0517d61 Iustin Pop
      min_cv = optMinScore opts
252 b0517d61 Iustin Pop
253 b0517d61 Iustin Pop
  when (ini_cv < min_cv) $ do
254 b0517d61 Iustin Pop
         (if oneline then
255 ba6c6006 Iustin Pop
              putStrLn $ formatOneline ini_cv 0 ini_cv
256 b0517d61 Iustin Pop
          else printf "Cluster is already well balanced (initial score %.6g,\n\
257 b0517d61 Iustin Pop
                      \minimum score %.6g).\nNothing to do, exiting\n"
258 b0517d61 Iustin Pop
                      ini_cv min_cv)
259 b0517d61 Iustin Pop
         exitWith ExitSuccess
260 b0517d61 Iustin Pop
261 d09b6ed3 Iustin Pop
  unless oneline (if verbose > 2 then
262 7eff5b09 Iustin Pop
                      printf "Initial coefficients: overall %.8f, %s\n"
263 7eff5b09 Iustin Pop
                      ini_cv (Cluster.printStats nl)
264 7eff5b09 Iustin Pop
                  else
265 7eff5b09 Iustin Pop
                      printf "Initial score: %.8f\n" ini_cv)
266 e4f08c46 Iustin Pop
267 27f96567 Iustin Pop
  unless oneline $ putStrLn "Trying to minimize the CV..."
268 262a08a2 Iustin Pop
  let imlen = Container.maxNameLen il
269 262a08a2 Iustin Pop
      nmlen = Container.maxNameLen nl
270 7dfaafb1 Iustin Pop
271 7dfaafb1 Iustin Pop
  (fin_tbl, cmd_strs) <- iterateDepth ini_tbl (optMaxLength opts)
272 db1bcfe8 Iustin Pop
                         nmlen imlen [] oneline min_cv
273 e4f08c46 Iustin Pop
  let (Cluster.Table fin_nl _ fin_cv fin_plc) = fin_tbl
274 e4f08c46 Iustin Pop
      ord_plc = reverse fin_plc
275 7eff5b09 Iustin Pop
      sol_msg = if null fin_plc
276 7eff5b09 Iustin Pop
                then printf "No solution found\n"
277 d09b6ed3 Iustin Pop
                else (if verbose > 2
278 7eff5b09 Iustin Pop
                      then printf "Final coefficients:   overall %.8f, %s\n"
279 7eff5b09 Iustin Pop
                           fin_cv (Cluster.printStats fin_nl)
280 7eff5b09 Iustin Pop
                      else printf "Cluster score improved from %.8f to %.8f\n"
281 7eff5b09 Iustin Pop
                           ini_cv fin_cv
282 7eff5b09 Iustin Pop
                     )
283 e4f08c46 Iustin Pop
284 7eff5b09 Iustin Pop
  unless oneline $ putStr sol_msg
285 7eff5b09 Iustin Pop
286 7eff5b09 Iustin Pop
  unless (oneline || verbose == 0) $
287 7eff5b09 Iustin Pop
         printf "Solution length=%d\n" (length ord_plc)
288 e4f08c46 Iustin Pop
289 e0eb63f0 Iustin Pop
  let cmd_data = Cluster.formatCmds . reverse $ cmd_strs
290 e0eb63f0 Iustin Pop
291 e0eb63f0 Iustin Pop
  when (isJust $ optShowCmds opts) $
292 e4f08c46 Iustin Pop
       do
293 e0eb63f0 Iustin Pop
         let out_path = fromJust $ optShowCmds opts
294 e4f08c46 Iustin Pop
         putStrLn ""
295 e0eb63f0 Iustin Pop
         (if out_path == "-" then
296 e0eb63f0 Iustin Pop
              printf "Commands to run to reach the above solution:\n%s"
297 e0eb63f0 Iustin Pop
                     (unlines . map ("  " ++) .
298 e0eb63f0 Iustin Pop
                      filter (/= "check") .
299 e0eb63f0 Iustin Pop
                      lines $ cmd_data)
300 e0eb63f0 Iustin Pop
          else do
301 e0eb63f0 Iustin Pop
            writeFile out_path (CLI.shTemplate ++ cmd_data)
302 e0eb63f0 Iustin Pop
            printf "The commands have been written to file '%s'\n" out_path)
303 e0eb63f0 Iustin Pop
304 e4f08c46 Iustin Pop
  when (optShowNodes opts) $
305 e4f08c46 Iustin Pop
       do
306 e4f08c46 Iustin Pop
         let (orig_mem, orig_disk) = Cluster.totalResources nl
307 e4f08c46 Iustin Pop
             (final_mem, final_disk) = Cluster.totalResources fin_nl
308 e4f08c46 Iustin Pop
         putStrLn ""
309 e4f08c46 Iustin Pop
         putStrLn "Final cluster status:"
310 dbd6700b Iustin Pop
         putStrLn $ Cluster.printNodes fin_nl
311 d09b6ed3 Iustin Pop
         when (verbose > 3) $
312 7eff5b09 Iustin Pop
              do
313 7eff5b09 Iustin Pop
                printf "Original: mem=%d disk=%d\n" orig_mem orig_disk
314 7eff5b09 Iustin Pop
                printf "Final:    mem=%d disk=%d\n" final_mem final_disk
315 ba6c6006 Iustin Pop
  when oneline $
316 ba6c6006 Iustin Pop
         putStrLn $ formatOneline ini_cv (length ord_plc) fin_cv