Statistics
| Branch: | Tag: | Revision:

root / hbal.hs @ 691dcd2a

History | View | Annotate | Download (11.7 kB)

1 66d67ad4 Iustin Pop
{-| Cluster rebalancer
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 b2245847 Iustin Pop
import Control.Concurrent (threadDelay)
29 b2245847 Iustin Pop
import Control.Exception (bracket)
30 e4f08c46 Iustin Pop
import Data.List
31 0427285d Iustin Pop
import Data.Maybe (isJust, fromJust)
32 e4f08c46 Iustin Pop
import Monad
33 0903280b Iustin Pop
import System (exitWith, ExitCode(..))
34 e4f08c46 Iustin Pop
import System.IO
35 e4f08c46 Iustin Pop
import qualified System
36 e4f08c46 Iustin Pop
37 2795466b Iustin Pop
import Text.Printf (printf, hPrintf)
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 b2245847 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
43 040afc35 Iustin Pop
44 0427285d Iustin Pop
import Ganeti.HTools.CLI
45 e8f89bb6 Iustin Pop
import Ganeti.HTools.ExtLoader
46 669d7e3d Iustin Pop
import Ganeti.HTools.Utils
47 0e8ae201 Iustin Pop
import Ganeti.HTools.Types
48 e4f08c46 Iustin Pop
49 b2245847 Iustin Pop
import qualified Ganeti.Luxi as L
50 b2245847 Iustin Pop
import Ganeti.Jobs
51 b2245847 Iustin Pop
52 e4f08c46 Iustin Pop
-- | Options list and functions
53 0427285d Iustin Pop
options :: [OptType]
54 e4f08c46 Iustin Pop
options =
55 0427285d Iustin Pop
    [ oPrintNodes
56 507fda3f Iustin Pop
    , oPrintInsts
57 0427285d Iustin Pop
    , oPrintCommands
58 0427285d Iustin Pop
    , oOneline
59 16c2369c Iustin Pop
    , oDataFile
60 2e28ac32 Iustin Pop
    , oEvacMode
61 0427285d Iustin Pop
    , oRapiMaster
62 0427285d Iustin Pop
    , oLuxiSocket
63 b2245847 Iustin Pop
    , oExecJobs
64 0427285d Iustin Pop
    , oMaxSolLength
65 0427285d Iustin Pop
    , oVerbose
66 0427285d Iustin Pop
    , oQuiet
67 0427285d Iustin Pop
    , oOfflineNode
68 0427285d Iustin Pop
    , oMinScore
69 0427285d Iustin Pop
    , oMaxCpu
70 0427285d Iustin Pop
    , oMinDisk
71 c0501c69 Iustin Pop
    , oDiskMoves
72 aa8d2e71 Iustin Pop
    , oDynuFile
73 0f15cc76 Iustin Pop
    , oExTags
74 fcbf0da4 Iustin Pop
    , oExInst
75 0427285d Iustin Pop
    , oShowVer
76 0427285d Iustin Pop
    , oShowHelp
77 7ef4d93e Iustin Pop
    ]
78 e4f08c46 Iustin Pop
79 6dc960bc Iustin Pop
{- | Start computing the solution at the given depth and recurse until
80 6dc960bc Iustin Pop
we find a valid solution or we exceed the maximum depth.
81 6dc960bc Iustin Pop
82 6dc960bc Iustin Pop
-}
83 6dc960bc Iustin Pop
iterateDepth :: Cluster.Table    -- ^ The starting table
84 6dc960bc Iustin Pop
             -> Int              -- ^ Remaining length
85 c0501c69 Iustin Pop
             -> Bool             -- ^ Allow disk moves
86 6dc960bc Iustin Pop
             -> Int              -- ^ Max node name len
87 6dc960bc Iustin Pop
             -> Int              -- ^ Max instance name len
88 0e8ae201 Iustin Pop
             -> [MoveJob]        -- ^ Current command list
89 24acc2c6 Guido Trotter
             -> Bool             -- ^ Whether to be silent
90 92e32d76 Iustin Pop
             -> Score            -- ^ Score at which to stop
91 2e28ac32 Iustin Pop
             -> Bool             -- ^ Enable evacuation mode
92 0e8ae201 Iustin Pop
             -> IO (Cluster.Table, [MoveJob]) -- ^ The resulting table
93 0e8ae201 Iustin Pop
                                              -- and commands
94 c0501c69 Iustin Pop
iterateDepth ini_tbl max_rounds disk_moves nmlen imlen
95 2e28ac32 Iustin Pop
             cmd_strs oneline min_score evac_mode =
96 f25e5aac Iustin Pop
    let Cluster.Table ini_nl ini_il _ _ = ini_tbl
97 5ad86777 Iustin Pop
        allowed_next = Cluster.doNextBalance ini_tbl max_rounds min_score
98 5ad86777 Iustin Pop
        m_fin_tbl = if allowed_next
99 2e28ac32 Iustin Pop
                    then Cluster.tryBalance ini_tbl disk_moves evac_mode
100 5ad86777 Iustin Pop
                    else Nothing
101 6dc960bc Iustin Pop
    in
102 f25e5aac Iustin Pop
      case m_fin_tbl of
103 f25e5aac Iustin Pop
        Just fin_tbl ->
104 f25e5aac Iustin Pop
            do
105 f25e5aac Iustin Pop
              let
106 f25e5aac Iustin Pop
                  (Cluster.Table _ _ _ fin_plc) = fin_tbl
107 f25e5aac Iustin Pop
                  fin_plc_len = length fin_plc
108 924f9c16 Iustin Pop
                  cur_plc@(idx, _, _, move, _) = head fin_plc
109 f25e5aac Iustin Pop
                  (sol_line, cmds) = Cluster.printSolutionLine ini_nl ini_il
110 0e8ae201 Iustin Pop
                                     nmlen imlen cur_plc fin_plc_len
111 0e8ae201 Iustin Pop
                  afn = Cluster.involvedNodes ini_il cur_plc
112 924f9c16 Iustin Pop
                  upd_cmd_strs = (afn, idx, move, cmds):cmd_strs
113 f25e5aac Iustin Pop
              unless oneline $ do
114 f25e5aac Iustin Pop
                       putStrLn sol_line
115 f25e5aac Iustin Pop
                       hFlush stdout
116 f25e5aac Iustin Pop
              iterateDepth fin_tbl max_rounds disk_moves
117 f25e5aac Iustin Pop
                           nmlen imlen upd_cmd_strs oneline min_score
118 2e28ac32 Iustin Pop
                           evac_mode
119 f25e5aac Iustin Pop
        Nothing -> return (ini_tbl, cmd_strs)
120 6dc960bc Iustin Pop
121 ba6c6006 Iustin Pop
-- | Formats the solution for the oneline display
122 ba6c6006 Iustin Pop
formatOneline :: Double -> Int -> Double -> String
123 ba6c6006 Iustin Pop
formatOneline ini_cv plc_len fin_cv =
124 ba6c6006 Iustin Pop
    printf "%.8f %d %.8f %8.3f" ini_cv plc_len fin_cv
125 9f6dcdea Iustin Pop
               (if fin_cv == 0 then 1 else ini_cv / fin_cv)
126 ba6c6006 Iustin Pop
127 b2245847 Iustin Pop
-- | Polls a set of jobs at a fixed interval until all are finished
128 b2245847 Iustin Pop
-- one way or another
129 b2245847 Iustin Pop
waitForJobs :: L.Client -> [String] -> IO (Result [JobStatus])
130 b2245847 Iustin Pop
waitForJobs client jids = do
131 b2245847 Iustin Pop
  sts <- L.queryJobsStatus client jids
132 b2245847 Iustin Pop
  case sts of
133 b2245847 Iustin Pop
    Bad x -> return $ Bad x
134 7e98f782 Iustin Pop
    Ok s -> if any (<= JOB_STATUS_RUNNING) s
135 b2245847 Iustin Pop
            then do
136 b2245847 Iustin Pop
              -- TODO: replace hardcoded value with a better thing
137 b2245847 Iustin Pop
              threadDelay (1000000 * 15)
138 b2245847 Iustin Pop
              waitForJobs client jids
139 b2245847 Iustin Pop
            else return $ Ok s
140 b2245847 Iustin Pop
141 b2245847 Iustin Pop
-- | Check that a set of job statuses is all success
142 b2245847 Iustin Pop
checkJobsStatus :: [JobStatus] -> Bool
143 7e98f782 Iustin Pop
checkJobsStatus = all (== JOB_STATUS_SUCCESS)
144 b2245847 Iustin Pop
145 b2245847 Iustin Pop
-- | Execute an entire jobset
146 3e4480e0 Iustin Pop
execJobSet :: String -> Node.List
147 b2245847 Iustin Pop
           -> Instance.List -> [JobSet] -> IO ()
148 3e4480e0 Iustin Pop
execJobSet _      _  _  [] = return ()
149 3e4480e0 Iustin Pop
execJobSet master nl il (js:jss) = do
150 b2245847 Iustin Pop
  -- map from jobset (htools list of positions) to [[opcodes]]
151 b2245847 Iustin Pop
  let jobs = map (\(_, idx, move, _) ->
152 3e4480e0 Iustin Pop
                      Cluster.iMoveToJob nl il idx move) js
153 b2245847 Iustin Pop
  let descr = map (\(_, idx, _, _) -> Container.nameOf il idx) js
154 b2245847 Iustin Pop
  putStrLn $ "Executing jobset for instances " ++ commaJoin descr
155 b2245847 Iustin Pop
  jrs <- bracket (L.getClient master) L.closeClient
156 b2245847 Iustin Pop
         (\client -> do
157 683b1ca7 Iustin Pop
            jids <- L.submitManyJobs client jobs
158 b2245847 Iustin Pop
            case jids of
159 b2245847 Iustin Pop
              Bad x -> return $ Bad x
160 b2245847 Iustin Pop
              Ok x -> do
161 b2245847 Iustin Pop
                putStrLn $ "Got job IDs " ++ commaJoin x
162 b2245847 Iustin Pop
                waitForJobs client x
163 b2245847 Iustin Pop
         )
164 b2245847 Iustin Pop
  (case jrs of
165 b2245847 Iustin Pop
     Bad x -> do
166 b2245847 Iustin Pop
       hPutStrLn stderr $ "Cannot compute job status, aborting: " ++ show x
167 b2245847 Iustin Pop
       return ()
168 b2245847 Iustin Pop
     Ok x -> if checkJobsStatus x
169 3e4480e0 Iustin Pop
             then execJobSet master nl il jss
170 b2245847 Iustin Pop
             else do
171 b2245847 Iustin Pop
               hPutStrLn stderr $ "Not all jobs completed successfully: " ++
172 b2245847 Iustin Pop
                         show x
173 b2245847 Iustin Pop
               hPutStrLn stderr "Aborting.")
174 b2245847 Iustin Pop
175 e4f08c46 Iustin Pop
-- | Main function.
176 e4f08c46 Iustin Pop
main :: IO ()
177 e4f08c46 Iustin Pop
main = do
178 e4f08c46 Iustin Pop
  cmd_args <- System.getArgs
179 0427285d Iustin Pop
  (opts, args) <- parseOpts cmd_args "hbal" options
180 45f01962 Iustin Pop
181 45f01962 Iustin Pop
  unless (null args) $ do
182 45f01962 Iustin Pop
         hPutStrLn stderr "Error: this program doesn't take any arguments."
183 45f01962 Iustin Pop
         exitWith $ ExitFailure 1
184 a30b2f5b Iustin Pop
185 fae371cc Iustin Pop
  let oneline = optOneline opts
186 7eff5b09 Iustin Pop
      verbose = optVerbose opts
187 e98fb766 Iustin Pop
      shownodes = optShowNodes opts
188 fae371cc Iustin Pop
189 3e4480e0 Iustin Pop
  (fixed_nl, il, ctags) <- loadExternalData opts
190 ec18dca9 Iustin Pop
191 ec18dca9 Iustin Pop
  let offline_names = optOffline opts
192 db1bcfe8 Iustin Pop
      all_nodes = Container.elems fixed_nl
193 c854092b Iustin Pop
      all_names = concatMap allNames all_nodes
194 5182e970 Iustin Pop
      offline_wrong = filter (`notElem` all_names) offline_names
195 db1bcfe8 Iustin Pop
      offline_indices = map Node.idx $
196 f9acea10 Iustin Pop
                        filter (\n ->
197 f9acea10 Iustin Pop
                                 Node.name n `elem` offline_names ||
198 f9acea10 Iustin Pop
                                 Node.alias n `elem` offline_names)
199 db1bcfe8 Iustin Pop
                               all_nodes
200 66d67ad4 Iustin Pop
      m_cpu = optMcpu opts
201 66d67ad4 Iustin Pop
      m_dsk = optMdsk opts
202 3e4480e0 Iustin Pop
      csf = commonSuffix fixed_nl il
203 ec18dca9 Iustin Pop
204 3d7cd10b Iustin Pop
  when (length offline_wrong > 0) $ do
205 2795466b Iustin Pop
         hPrintf stderr "Wrong node name(s) set as offline: %s\n"
206 c939b58e Iustin Pop
                     (commaJoin offline_wrong) :: IO ()
207 3d7cd10b Iustin Pop
         exitWith $ ExitFailure 1
208 3d7cd10b Iustin Pop
209 5182e970 Iustin Pop
  let nm = Container.map (\n -> if Node.idx n `elem` offline_indices
210 ec18dca9 Iustin Pop
                                then Node.setOffline n True
211 a1c6212e Iustin Pop
                                else n) fixed_nl
212 66d67ad4 Iustin Pop
      nl = Container.map (flip Node.setMdsk m_dsk . flip Node.setMcpu m_cpu)
213 66d67ad4 Iustin Pop
           nm
214 a30b2f5b Iustin Pop
215 ea017cbc Iustin Pop
  when (not oneline && verbose > 1) $
216 ea017cbc Iustin Pop
       putStrLn $ "Loaded cluster tags: " ++ intercalate "," ctags
217 ea017cbc Iustin Pop
218 dcbcdb58 Iustin Pop
  when (Container.size il == 0) $ do
219 926c35b1 Iustin Pop
         (if oneline then putStrLn $ formatOneline 0 0 0
220 926c35b1 Iustin Pop
          else printf "Cluster is empty, exiting.\n")
221 dcbcdb58 Iustin Pop
         exitWith ExitSuccess
222 dcbcdb58 Iustin Pop
223 27f96567 Iustin Pop
  unless oneline $ printf "Loaded %d nodes, %d instances\n"
224 e4f08c46 Iustin Pop
             (Container.size nl)
225 e4f08c46 Iustin Pop
             (Container.size il)
226 a0529a64 Iustin Pop
227 9f6dcdea Iustin Pop
  when (length csf > 0 && not oneline && verbose > 1) $
228 9f6dcdea Iustin Pop
       printf "Note: Stripping common suffix of '%s' from names\n" csf
229 a0529a64 Iustin Pop
230 e4f08c46 Iustin Pop
  let (bad_nodes, bad_instances) = Cluster.computeBadItems nl il
231 7eff5b09 Iustin Pop
  unless (oneline || verbose == 0) $ printf
232 27f96567 Iustin Pop
             "Initial check done: %d bad nodes, %d bad instances.\n"
233 e4f08c46 Iustin Pop
             (length bad_nodes) (length bad_instances)
234 e4f08c46 Iustin Pop
235 9f6dcdea Iustin Pop
  when (length bad_nodes > 0) $
236 289c3835 Iustin Pop
         putStrLn "Cluster is not N+1 happy, continuing but no guarantee \
237 289c3835 Iustin Pop
                  \that the cluster will end N+1 happy."
238 e4f08c46 Iustin Pop
239 507fda3f Iustin Pop
  when (optShowInsts opts) $ do
240 507fda3f Iustin Pop
         putStrLn ""
241 507fda3f Iustin Pop
         putStrLn "Initial instance map:"
242 507fda3f Iustin Pop
         putStrLn $ Cluster.printInsts nl il
243 507fda3f Iustin Pop
244 e98fb766 Iustin Pop
  when (isJust shownodes) $
245 e4f08c46 Iustin Pop
       do
246 e4f08c46 Iustin Pop
         putStrLn "Initial cluster status:"
247 e98fb766 Iustin Pop
         putStrLn $ Cluster.printNodes nl (fromJust shownodes)
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 14c972c7 Iustin Pop
  let imlen = maximum . map (length . Instance.alias) $ Container.elems il
269 14c972c7 Iustin Pop
      nmlen = maximum . map (length . Node.alias) $ Container.elems nl
270 7dfaafb1 Iustin Pop
271 7dfaafb1 Iustin Pop
  (fin_tbl, cmd_strs) <- iterateDepth ini_tbl (optMaxLength opts)
272 c0501c69 Iustin Pop
                         (optDiskMoves opts)
273 2e28ac32 Iustin Pop
                         nmlen imlen [] oneline min_cv (optEvacMode opts)
274 507fda3f Iustin Pop
  let (Cluster.Table fin_nl fin_il fin_cv fin_plc) = fin_tbl
275 e4f08c46 Iustin Pop
      ord_plc = reverse fin_plc
276 9f6dcdea Iustin Pop
      sol_msg = if null fin_plc
277 9f6dcdea Iustin Pop
                then printf "No solution found\n"
278 9f6dcdea Iustin Pop
                else if verbose > 2
279 9f6dcdea Iustin Pop
                     then printf "Final coefficients:   overall %.8f, %s\n"
280 9f6dcdea Iustin Pop
                          fin_cv (Cluster.printStats fin_nl)
281 9f6dcdea Iustin Pop
                     else printf "Cluster score improved from %.8f to %.8f\n"
282 9f6dcdea Iustin Pop
                          ini_cv fin_cv
283 9f6dcdea Iustin Pop
                              ::String
284 e4f08c46 Iustin Pop
285 7eff5b09 Iustin Pop
  unless oneline $ putStr sol_msg
286 7eff5b09 Iustin Pop
287 7eff5b09 Iustin Pop
  unless (oneline || verbose == 0) $
288 7eff5b09 Iustin Pop
         printf "Solution length=%d\n" (length ord_plc)
289 e4f08c46 Iustin Pop
290 b2245847 Iustin Pop
  let cmd_jobs = Cluster.splitJobs cmd_strs
291 b2245847 Iustin Pop
      cmd_data = Cluster.formatCmds cmd_jobs
292 e0eb63f0 Iustin Pop
293 e0eb63f0 Iustin Pop
  when (isJust $ optShowCmds opts) $
294 e4f08c46 Iustin Pop
       do
295 e0eb63f0 Iustin Pop
         let out_path = fromJust $ optShowCmds opts
296 e4f08c46 Iustin Pop
         putStrLn ""
297 e0eb63f0 Iustin Pop
         (if out_path == "-" then
298 e0eb63f0 Iustin Pop
              printf "Commands to run to reach the above solution:\n%s"
299 e0eb63f0 Iustin Pop
                     (unlines . map ("  " ++) .
300 0e8ae201 Iustin Pop
                      filter (/= "  check") .
301 e0eb63f0 Iustin Pop
                      lines $ cmd_data)
302 e0eb63f0 Iustin Pop
          else do
303 0427285d Iustin Pop
            writeFile out_path (shTemplate ++ cmd_data)
304 e0eb63f0 Iustin Pop
            printf "The commands have been written to file '%s'\n" out_path)
305 e0eb63f0 Iustin Pop
306 b2245847 Iustin Pop
  when (optExecJobs opts && not (null ord_plc))
307 b2245847 Iustin Pop
           (case optLuxi opts of
308 b2245847 Iustin Pop
              Nothing -> do
309 b2245847 Iustin Pop
                hPutStrLn stderr "Execution of commands possible only on LUXI"
310 b2245847 Iustin Pop
                exitWith $ ExitFailure 1
311 3e4480e0 Iustin Pop
              Just master -> execJobSet master fin_nl il cmd_jobs)
312 b2245847 Iustin Pop
313 507fda3f Iustin Pop
  when (optShowInsts opts) $ do
314 507fda3f Iustin Pop
         putStrLn ""
315 507fda3f Iustin Pop
         putStrLn "Final instance map:"
316 507fda3f Iustin Pop
         putStr $ Cluster.printInsts fin_nl fin_il
317 507fda3f Iustin Pop
318 e98fb766 Iustin Pop
  when (isJust shownodes) $
319 e4f08c46 Iustin Pop
       do
320 1a7eff0e Iustin Pop
         let ini_cs = Cluster.totalResources nl
321 1a7eff0e Iustin Pop
             fin_cs = Cluster.totalResources fin_nl
322 e4f08c46 Iustin Pop
         putStrLn ""
323 e4f08c46 Iustin Pop
         putStrLn "Final cluster status:"
324 e98fb766 Iustin Pop
         putStrLn $ Cluster.printNodes fin_nl (fromJust shownodes)
325 d09b6ed3 Iustin Pop
         when (verbose > 3) $
326 7eff5b09 Iustin Pop
              do
327 1a7eff0e Iustin Pop
                printf "Original: mem=%d disk=%d\n"
328 c939b58e Iustin Pop
                       (Cluster.csFmem ini_cs) (Cluster.csFdsk ini_cs) :: IO ()
329 1a7eff0e Iustin Pop
                printf "Final:    mem=%d disk=%d\n"
330 f5b553da Iustin Pop
                       (Cluster.csFmem fin_cs) (Cluster.csFdsk fin_cs)
331 ba6c6006 Iustin Pop
  when oneline $
332 ba6c6006 Iustin Pop
         putStrLn $ formatOneline ini_cv (length ord_plc) fin_cv