Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ f25e5aac

History | View | Annotate | Download (25.9 kB)

1 e4f08c46 Iustin Pop
{-| Implementation of cluster-wide logic.
2 e4f08c46 Iustin Pop
3 e4f08c46 Iustin Pop
This module holds all pure cluster-logic; I\/O related functionality
4 7ae514ba Iustin Pop
goes into the "Main" module for the individual binaries.
5 e4f08c46 Iustin Pop
6 e4f08c46 Iustin Pop
-}
7 e4f08c46 Iustin Pop
8 e2fa2baf Iustin Pop
{-
9 e2fa2baf Iustin Pop
10 e2fa2baf Iustin Pop
Copyright (C) 2009 Google Inc.
11 e2fa2baf Iustin Pop
12 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
13 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
14 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 e2fa2baf Iustin Pop
(at your option) any later version.
16 e2fa2baf Iustin Pop
17 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
18 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 e2fa2baf Iustin Pop
General Public License for more details.
21 e2fa2baf Iustin Pop
22 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
23 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
24 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 e2fa2baf Iustin Pop
02110-1301, USA.
26 e2fa2baf Iustin Pop
27 e2fa2baf Iustin Pop
-}
28 e2fa2baf Iustin Pop
29 669d7e3d Iustin Pop
module Ganeti.HTools.Cluster
30 e4f08c46 Iustin Pop
    (
31 e4f08c46 Iustin Pop
     -- * Types
32 f9fc7a63 Iustin Pop
      Placement
33 78694255 Iustin Pop
    , AllocSolution
34 e4f08c46 Iustin Pop
    , Table(..)
35 b0517d61 Iustin Pop
    , Score
36 58709f92 Iustin Pop
    , IMove(..)
37 1a7eff0e Iustin Pop
    , CStats(..)
38 e4f08c46 Iustin Pop
    -- * Generic functions
39 e4f08c46 Iustin Pop
    , totalResources
40 e4f08c46 Iustin Pop
    -- * First phase functions
41 e4f08c46 Iustin Pop
    , computeBadItems
42 e4f08c46 Iustin Pop
    -- * Second phase functions
43 e4f08c46 Iustin Pop
    , printSolution
44 7dfaafb1 Iustin Pop
    , printSolutionLine
45 142538ff Iustin Pop
    , formatCmds
46 e4f08c46 Iustin Pop
    , printNodes
47 e4f08c46 Iustin Pop
    -- * Balacing functions
48 e4f08c46 Iustin Pop
    , checkMove
49 f25e5aac Iustin Pop
    , tryBalance
50 e4f08c46 Iustin Pop
    , compCV
51 e4f08c46 Iustin Pop
    , printStats
52 4a340313 Iustin Pop
    -- * IAllocator functions
53 dbba5246 Iustin Pop
    , tryAlloc
54 dbba5246 Iustin Pop
    , tryReloc
55 478df686 Iustin Pop
    , collapseFailures
56 e4f08c46 Iustin Pop
    ) where
57 e4f08c46 Iustin Pop
58 e4f08c46 Iustin Pop
import Data.List
59 e4f08c46 Iustin Pop
import Text.Printf (printf)
60 e4f08c46 Iustin Pop
import Data.Function
61 9d3fada5 Iustin Pop
import Control.Monad
62 e4f08c46 Iustin Pop
63 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Container as Container
64 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
65 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Node as Node
66 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
67 669d7e3d Iustin Pop
import Ganeti.HTools.Utils
68 e4f08c46 Iustin Pop
69 9188aeef Iustin Pop
-- * Types
70 9188aeef Iustin Pop
71 9188aeef Iustin Pop
-- | A separate name for the cluster score type.
72 e4f08c46 Iustin Pop
type Score = Double
73 e4f08c46 Iustin Pop
74 e4f08c46 Iustin Pop
-- | The description of an instance placement.
75 608efcce Iustin Pop
type Placement = (Idx, Ndx, Ndx, Score)
76 e4f08c46 Iustin Pop
77 0c936d24 Iustin Pop
-- | Allocation\/relocation solution.
78 478df686 Iustin Pop
type AllocSolution = ([FailMode], Int, Maybe (Score, AllocElement))
79 478df686 Iustin Pop
80 478df686 Iustin Pop
-- | Allocation\/relocation element.
81 478df686 Iustin Pop
type AllocElement = (Node.List, Instance.Instance, [Node.Node])
82 78694255 Iustin Pop
83 e4f08c46 Iustin Pop
-- | An instance move definition
84 00b51a14 Iustin Pop
data IMove = Failover                -- ^ Failover the instance (f)
85 608efcce Iustin Pop
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
86 608efcce Iustin Pop
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
87 608efcce Iustin Pop
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
88 608efcce Iustin Pop
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
89 e4f08c46 Iustin Pop
             deriving (Show)
90 e4f08c46 Iustin Pop
91 e4f08c46 Iustin Pop
-- | The complete state for the balancing solution
92 262a08a2 Iustin Pop
data Table = Table Node.List Instance.List Score [Placement]
93 e4f08c46 Iustin Pop
             deriving (Show)
94 e4f08c46 Iustin Pop
95 8c4c6a8a Iustin Pop
data CStats = CStats { cs_fmem :: Int    -- ^ Cluster free mem
96 8c4c6a8a Iustin Pop
                     , cs_fdsk :: Int    -- ^ Cluster free disk
97 8c4c6a8a Iustin Pop
                     , cs_amem :: Int    -- ^ Cluster allocatable mem
98 8c4c6a8a Iustin Pop
                     , cs_adsk :: Int    -- ^ Cluster allocatable disk
99 8c4c6a8a Iustin Pop
                     , cs_acpu :: Int    -- ^ Cluster allocatable cpus
100 8c4c6a8a Iustin Pop
                     , cs_mmem :: Int    -- ^ Max node allocatable mem
101 8c4c6a8a Iustin Pop
                     , cs_mdsk :: Int    -- ^ Max node allocatable disk
102 8c4c6a8a Iustin Pop
                     , cs_mcpu :: Int    -- ^ Max node allocatable cpu
103 8c4c6a8a Iustin Pop
                     , cs_imem :: Int    -- ^ Instance used mem
104 8c4c6a8a Iustin Pop
                     , cs_idsk :: Int    -- ^ Instance used disk
105 8c4c6a8a Iustin Pop
                     , cs_icpu :: Int    -- ^ Instance used cpu
106 8c4c6a8a Iustin Pop
                     , cs_tmem :: Double -- ^ Cluster total mem
107 8c4c6a8a Iustin Pop
                     , cs_tdsk :: Double -- ^ Cluster total disk
108 8c4c6a8a Iustin Pop
                     , cs_tcpu :: Double -- ^ Cluster total cpus
109 8c4c6a8a Iustin Pop
                     , cs_xmem :: Int    -- ^ Unnacounted for mem
110 8c4c6a8a Iustin Pop
                     , cs_nmem :: Int    -- ^ Node own memory
111 de4ac2c2 Iustin Pop
                     , cs_score :: Score -- ^ The cluster score
112 de4ac2c2 Iustin Pop
                     , cs_ninst :: Int   -- ^ The total number of instances
113 1a7eff0e Iustin Pop
                     }
114 1a7eff0e Iustin Pop
115 9188aeef Iustin Pop
-- * Utility functions
116 9188aeef Iustin Pop
117 e4f08c46 Iustin Pop
-- | Verifies the N+1 status and return the affected nodes.
118 e4f08c46 Iustin Pop
verifyN1 :: [Node.Node] -> [Node.Node]
119 9f6dcdea Iustin Pop
verifyN1 = filter Node.failN1
120 e4f08c46 Iustin Pop
121 9188aeef Iustin Pop
{-| Computes the pair of bad nodes and instances.
122 9188aeef Iustin Pop
123 9188aeef Iustin Pop
The bad node list is computed via a simple 'verifyN1' check, and the
124 9188aeef Iustin Pop
bad instance list is the list of primary and secondary instances of
125 9188aeef Iustin Pop
those nodes.
126 9188aeef Iustin Pop
127 9188aeef Iustin Pop
-}
128 9188aeef Iustin Pop
computeBadItems :: Node.List -> Instance.List ->
129 9188aeef Iustin Pop
                   ([Node.Node], [Instance.Instance])
130 9188aeef Iustin Pop
computeBadItems nl il =
131 dbba5246 Iustin Pop
  let bad_nodes = verifyN1 $ getOnline nl
132 9f6dcdea Iustin Pop
      bad_instances = map (\idx -> Container.find idx il) .
133 9f6dcdea Iustin Pop
                      sort . nub $
134 9f6dcdea Iustin Pop
                      concatMap (\ n -> Node.slist n ++ Node.plist n) bad_nodes
135 9188aeef Iustin Pop
  in
136 9188aeef Iustin Pop
    (bad_nodes, bad_instances)
137 9188aeef Iustin Pop
138 1a7eff0e Iustin Pop
emptyCStats :: CStats
139 1a7eff0e Iustin Pop
emptyCStats = CStats { cs_fmem = 0
140 1a7eff0e Iustin Pop
                     , cs_fdsk = 0
141 1a7eff0e Iustin Pop
                     , cs_amem = 0
142 1a7eff0e Iustin Pop
                     , cs_adsk = 0
143 1a7eff0e Iustin Pop
                     , cs_acpu = 0
144 1a7eff0e Iustin Pop
                     , cs_mmem = 0
145 1a7eff0e Iustin Pop
                     , cs_mdsk = 0
146 1a7eff0e Iustin Pop
                     , cs_mcpu = 0
147 8c4c6a8a Iustin Pop
                     , cs_imem = 0
148 8c4c6a8a Iustin Pop
                     , cs_idsk = 0
149 8c4c6a8a Iustin Pop
                     , cs_icpu = 0
150 8c4c6a8a Iustin Pop
                     , cs_tmem = 0
151 8c4c6a8a Iustin Pop
                     , cs_tdsk = 0
152 8c4c6a8a Iustin Pop
                     , cs_tcpu = 0
153 8c4c6a8a Iustin Pop
                     , cs_xmem = 0
154 8c4c6a8a Iustin Pop
                     , cs_nmem = 0
155 de4ac2c2 Iustin Pop
                     , cs_score = 0
156 de4ac2c2 Iustin Pop
                     , cs_ninst = 0
157 1a7eff0e Iustin Pop
                     }
158 1a7eff0e Iustin Pop
159 1a7eff0e Iustin Pop
updateCStats :: CStats -> Node.Node -> CStats
160 1a7eff0e Iustin Pop
updateCStats cs node =
161 1a7eff0e Iustin Pop
    let CStats { cs_fmem = x_fmem, cs_fdsk = x_fdsk,
162 1a7eff0e Iustin Pop
                 cs_amem = x_amem, cs_acpu = x_acpu, cs_adsk = x_adsk,
163 8c4c6a8a Iustin Pop
                 cs_mmem = x_mmem, cs_mdsk = x_mdsk, cs_mcpu = x_mcpu,
164 8c4c6a8a Iustin Pop
                 cs_imem = x_imem, cs_idsk = x_idsk, cs_icpu = x_icpu,
165 8c4c6a8a Iustin Pop
                 cs_tmem = x_tmem, cs_tdsk = x_tdsk, cs_tcpu = x_tcpu,
166 de4ac2c2 Iustin Pop
                 cs_xmem = x_xmem, cs_nmem = x_nmem, cs_ninst = x_ninst
167 8c4c6a8a Iustin Pop
               }
168 1a7eff0e Iustin Pop
            = cs
169 9f6dcdea Iustin Pop
        inc_amem = Node.f_mem node - Node.r_mem node
170 1a7eff0e Iustin Pop
        inc_amem' = if inc_amem > 0 then inc_amem else 0
171 301789f4 Iustin Pop
        inc_adsk = Node.availDisk node
172 8c4c6a8a Iustin Pop
        inc_imem = truncate (Node.t_mem node) - Node.n_mem node
173 8c4c6a8a Iustin Pop
                   - Node.x_mem node - Node.f_mem node
174 8c4c6a8a Iustin Pop
        inc_icpu = Node.u_cpu node
175 8c4c6a8a Iustin Pop
        inc_idsk = truncate (Node.t_dsk node) - Node.f_dsk node
176 8c4c6a8a Iustin Pop
177 de4ac2c2 Iustin Pop
    in cs { cs_fmem = x_fmem + Node.f_mem node
178 de4ac2c2 Iustin Pop
          , cs_fdsk = x_fdsk + Node.f_dsk node
179 de4ac2c2 Iustin Pop
          , cs_amem = x_amem + inc_amem'
180 de4ac2c2 Iustin Pop
          , cs_adsk = x_adsk + inc_adsk
181 de4ac2c2 Iustin Pop
          , cs_acpu = x_acpu
182 de4ac2c2 Iustin Pop
          , cs_mmem = max x_mmem inc_amem'
183 de4ac2c2 Iustin Pop
          , cs_mdsk = max x_mdsk inc_adsk
184 de4ac2c2 Iustin Pop
          , cs_mcpu = x_mcpu
185 de4ac2c2 Iustin Pop
          , cs_imem = x_imem + inc_imem
186 de4ac2c2 Iustin Pop
          , cs_idsk = x_idsk + inc_idsk
187 de4ac2c2 Iustin Pop
          , cs_icpu = x_icpu + inc_icpu
188 de4ac2c2 Iustin Pop
          , cs_tmem = x_tmem + Node.t_mem node
189 de4ac2c2 Iustin Pop
          , cs_tdsk = x_tdsk + Node.t_dsk node
190 de4ac2c2 Iustin Pop
          , cs_tcpu = x_tcpu + Node.t_cpu node
191 de4ac2c2 Iustin Pop
          , cs_xmem = x_xmem + Node.x_mem node
192 de4ac2c2 Iustin Pop
          , cs_nmem = x_nmem + Node.n_mem node
193 de4ac2c2 Iustin Pop
          , cs_ninst = x_ninst + length (Node.plist node)
194 de4ac2c2 Iustin Pop
          }
195 1a7eff0e Iustin Pop
196 9188aeef Iustin Pop
-- | Compute the total free disk and memory in the cluster.
197 1a7eff0e Iustin Pop
totalResources :: Node.List -> CStats
198 de4ac2c2 Iustin Pop
totalResources nl =
199 de4ac2c2 Iustin Pop
    let cs = foldl' updateCStats emptyCStats . Container.elems $ nl
200 de4ac2c2 Iustin Pop
    in cs { cs_score = compCV nl }
201 9188aeef Iustin Pop
202 9188aeef Iustin Pop
-- | Compute the mem and disk covariance.
203 0a8dd21d Iustin Pop
compDetailedCV :: Node.List -> (Double, Double, Double, Double, Double, Double)
204 9188aeef Iustin Pop
compDetailedCV nl =
205 9188aeef Iustin Pop
    let
206 9188aeef Iustin Pop
        all_nodes = Container.elems nl
207 9188aeef Iustin Pop
        (offline, nodes) = partition Node.offline all_nodes
208 9188aeef Iustin Pop
        mem_l = map Node.p_mem nodes
209 9188aeef Iustin Pop
        dsk_l = map Node.p_dsk nodes
210 9188aeef Iustin Pop
        mem_cv = varianceCoeff mem_l
211 9188aeef Iustin Pop
        dsk_cv = varianceCoeff dsk_l
212 9188aeef Iustin Pop
        n1_l = length $ filter Node.failN1 nodes
213 9f6dcdea Iustin Pop
        n1_score = fromIntegral n1_l /
214 9f6dcdea Iustin Pop
                   fromIntegral (length nodes)::Double
215 9188aeef Iustin Pop
        res_l = map Node.p_rem nodes
216 9188aeef Iustin Pop
        res_cv = varianceCoeff res_l
217 9188aeef Iustin Pop
        offline_inst = sum . map (\n -> (length . Node.plist $ n) +
218 9188aeef Iustin Pop
                                        (length . Node.slist $ n)) $ offline
219 9188aeef Iustin Pop
        online_inst = sum . map (\n -> (length . Node.plist $ n) +
220 9188aeef Iustin Pop
                                       (length . Node.slist $ n)) $ nodes
221 16103319 Iustin Pop
        off_score = if offline_inst == 0
222 16103319 Iustin Pop
                    then 0::Double
223 16103319 Iustin Pop
                    else fromIntegral offline_inst /
224 16103319 Iustin Pop
                         fromIntegral (offline_inst + online_inst)::Double
225 0a8dd21d Iustin Pop
        cpu_l = map Node.p_cpu nodes
226 0a8dd21d Iustin Pop
        cpu_cv = varianceCoeff cpu_l
227 0a8dd21d Iustin Pop
    in (mem_cv, dsk_cv, n1_score, res_cv, off_score, cpu_cv)
228 9188aeef Iustin Pop
229 9188aeef Iustin Pop
-- | Compute the /total/ variance.
230 9188aeef Iustin Pop
compCV :: Node.List -> Double
231 9188aeef Iustin Pop
compCV nl =
232 0a8dd21d Iustin Pop
    let (mem_cv, dsk_cv, n1_score, res_cv, off_score, cpu_cv) =
233 0a8dd21d Iustin Pop
            compDetailedCV nl
234 0a8dd21d Iustin Pop
    in mem_cv + dsk_cv + n1_score + res_cv + off_score + cpu_cv
235 9188aeef Iustin Pop
236 dbba5246 Iustin Pop
-- | Compute online nodes from a Node.List
237 dbba5246 Iustin Pop
getOnline :: Node.List -> [Node.Node]
238 dbba5246 Iustin Pop
getOnline = filter (not . Node.offline) . Container.elems
239 dbba5246 Iustin Pop
240 9188aeef Iustin Pop
-- * hbal functions
241 9188aeef Iustin Pop
242 9188aeef Iustin Pop
-- | Compute best table. Note that the ordering of the arguments is important.
243 9188aeef Iustin Pop
compareTables :: Table -> Table -> Table
244 9188aeef Iustin Pop
compareTables a@(Table _ _ a_cv _) b@(Table _ _ b_cv _ ) =
245 9188aeef Iustin Pop
    if a_cv > b_cv then b else a
246 9188aeef Iustin Pop
247 9188aeef Iustin Pop
-- | Applies an instance move to a given node list and instance.
248 262a08a2 Iustin Pop
applyMove :: Node.List -> Instance.Instance
249 8880d889 Iustin Pop
          -> IMove -> OpResult (Node.List, Instance.Instance, Ndx, Ndx)
250 00b51a14 Iustin Pop
-- Failover (f)
251 e4f08c46 Iustin Pop
applyMove nl inst Failover =
252 e4f08c46 Iustin Pop
    let old_pdx = Instance.pnode inst
253 e4f08c46 Iustin Pop
        old_sdx = Instance.snode inst
254 e4f08c46 Iustin Pop
        old_p = Container.find old_pdx nl
255 e4f08c46 Iustin Pop
        old_s = Container.find old_sdx nl
256 e4f08c46 Iustin Pop
        int_p = Node.removePri old_p inst
257 e4f08c46 Iustin Pop
        int_s = Node.removeSec old_s inst
258 b161386d Iustin Pop
        new_nl = do -- Maybe monad
259 b161386d Iustin Pop
          new_p <- Node.addPri int_s inst
260 b161386d Iustin Pop
          new_s <- Node.addSec int_p inst old_sdx
261 8880d889 Iustin Pop
          let new_inst = Instance.setBoth inst old_sdx old_pdx
262 8880d889 Iustin Pop
          return (Container.addTwo old_pdx new_s old_sdx new_p nl,
263 8880d889 Iustin Pop
                  new_inst, old_sdx, old_pdx)
264 8880d889 Iustin Pop
    in new_nl
265 e4f08c46 Iustin Pop
266 00b51a14 Iustin Pop
-- Replace the primary (f:, r:np, f)
267 e4f08c46 Iustin Pop
applyMove nl inst (ReplacePrimary new_pdx) =
268 e4f08c46 Iustin Pop
    let old_pdx = Instance.pnode inst
269 e4f08c46 Iustin Pop
        old_sdx = Instance.snode inst
270 e4f08c46 Iustin Pop
        old_p = Container.find old_pdx nl
271 e4f08c46 Iustin Pop
        old_s = Container.find old_sdx nl
272 e4f08c46 Iustin Pop
        tgt_n = Container.find new_pdx nl
273 e4f08c46 Iustin Pop
        int_p = Node.removePri old_p inst
274 e4f08c46 Iustin Pop
        int_s = Node.removeSec old_s inst
275 b161386d Iustin Pop
        new_nl = do -- Maybe monad
276 70db354e Iustin Pop
          -- check that the current secondary can host the instance
277 70db354e Iustin Pop
          -- during the migration
278 70db354e Iustin Pop
          tmp_s <- Node.addPri int_s inst
279 70db354e Iustin Pop
          let tmp_s' = Node.removePri tmp_s inst
280 b161386d Iustin Pop
          new_p <- Node.addPri tgt_n inst
281 70db354e Iustin Pop
          new_s <- Node.addSec tmp_s' inst new_pdx
282 8880d889 Iustin Pop
          let new_inst = Instance.setPri inst new_pdx
283 8880d889 Iustin Pop
          return (Container.add new_pdx new_p $
284 8880d889 Iustin Pop
                  Container.addTwo old_pdx int_p old_sdx new_s nl,
285 8880d889 Iustin Pop
                  new_inst, new_pdx, old_sdx)
286 8880d889 Iustin Pop
    in new_nl
287 e4f08c46 Iustin Pop
288 00b51a14 Iustin Pop
-- Replace the secondary (r:ns)
289 e4f08c46 Iustin Pop
applyMove nl inst (ReplaceSecondary new_sdx) =
290 e4f08c46 Iustin Pop
    let old_pdx = Instance.pnode inst
291 e4f08c46 Iustin Pop
        old_sdx = Instance.snode inst
292 e4f08c46 Iustin Pop
        old_s = Container.find old_sdx nl
293 e4f08c46 Iustin Pop
        tgt_n = Container.find new_sdx nl
294 e4f08c46 Iustin Pop
        int_s = Node.removeSec old_s inst
295 8880d889 Iustin Pop
        new_inst = Instance.setSec inst new_sdx
296 b161386d Iustin Pop
        new_nl = Node.addSec tgt_n inst old_pdx >>=
297 8880d889 Iustin Pop
                 \new_s -> return (Container.addTwo new_sdx
298 8880d889 Iustin Pop
                                   new_s old_sdx int_s nl,
299 8880d889 Iustin Pop
                                   new_inst, old_pdx, new_sdx)
300 8880d889 Iustin Pop
    in new_nl
301 e4f08c46 Iustin Pop
302 00b51a14 Iustin Pop
-- Replace the secondary and failover (r:np, f)
303 79ac6b6f Iustin Pop
applyMove nl inst (ReplaceAndFailover new_pdx) =
304 79ac6b6f Iustin Pop
    let old_pdx = Instance.pnode inst
305 79ac6b6f Iustin Pop
        old_sdx = Instance.snode inst
306 79ac6b6f Iustin Pop
        old_p = Container.find old_pdx nl
307 79ac6b6f Iustin Pop
        old_s = Container.find old_sdx nl
308 79ac6b6f Iustin Pop
        tgt_n = Container.find new_pdx nl
309 79ac6b6f Iustin Pop
        int_p = Node.removePri old_p inst
310 79ac6b6f Iustin Pop
        int_s = Node.removeSec old_s inst
311 b161386d Iustin Pop
        new_nl = do -- Maybe monad
312 b161386d Iustin Pop
          new_p <- Node.addPri tgt_n inst
313 b161386d Iustin Pop
          new_s <- Node.addSec int_p inst new_pdx
314 8880d889 Iustin Pop
          let new_inst = Instance.setBoth inst new_pdx old_pdx
315 8880d889 Iustin Pop
          return (Container.add new_pdx new_p $
316 8880d889 Iustin Pop
                  Container.addTwo old_pdx new_s old_sdx int_s nl,
317 8880d889 Iustin Pop
                  new_inst, new_pdx, old_pdx)
318 8880d889 Iustin Pop
    in new_nl
319 79ac6b6f Iustin Pop
320 19493d33 Iustin Pop
-- Failver and replace the secondary (f, r:ns)
321 19493d33 Iustin Pop
applyMove nl inst (FailoverAndReplace new_sdx) =
322 19493d33 Iustin Pop
    let old_pdx = Instance.pnode inst
323 19493d33 Iustin Pop
        old_sdx = Instance.snode inst
324 19493d33 Iustin Pop
        old_p = Container.find old_pdx nl
325 19493d33 Iustin Pop
        old_s = Container.find old_sdx nl
326 19493d33 Iustin Pop
        tgt_n = Container.find new_sdx nl
327 19493d33 Iustin Pop
        int_p = Node.removePri old_p inst
328 19493d33 Iustin Pop
        int_s = Node.removeSec old_s inst
329 b161386d Iustin Pop
        new_nl = do -- Maybe monad
330 b161386d Iustin Pop
          new_p <- Node.addPri int_s inst
331 b161386d Iustin Pop
          new_s <- Node.addSec tgt_n inst old_sdx
332 8880d889 Iustin Pop
          let new_inst = Instance.setBoth inst old_sdx new_sdx
333 8880d889 Iustin Pop
          return (Container.add new_sdx new_s $
334 8880d889 Iustin Pop
                  Container.addTwo old_sdx new_p old_pdx int_p nl,
335 8880d889 Iustin Pop
                  new_inst, old_sdx, new_sdx)
336 8880d889 Iustin Pop
    in new_nl
337 19493d33 Iustin Pop
338 9188aeef Iustin Pop
-- | Tries to allocate an instance on one given node.
339 262a08a2 Iustin Pop
allocateOnSingle :: Node.List -> Instance.Instance -> Node.Node
340 478df686 Iustin Pop
                 -> OpResult AllocElement
341 5e15f460 Iustin Pop
allocateOnSingle nl inst p =
342 5e15f460 Iustin Pop
    let new_pdx = Node.idx p
343 8880d889 Iustin Pop
        new_inst = Instance.setBoth inst new_pdx Node.noSecondary
344 5e15f460 Iustin Pop
        new_nl = Node.addPri p inst >>= \new_p ->
345 685935f7 Iustin Pop
                 return (Container.add new_pdx new_p nl, new_inst, [new_p])
346 8880d889 Iustin Pop
    in new_nl
347 5e15f460 Iustin Pop
348 9188aeef Iustin Pop
-- | Tries to allocate an instance on a given pair of nodes.
349 262a08a2 Iustin Pop
allocateOnPair :: Node.List -> Instance.Instance -> Node.Node -> Node.Node
350 478df686 Iustin Pop
               -> OpResult AllocElement
351 5e15f460 Iustin Pop
allocateOnPair nl inst tgt_p tgt_s =
352 5e15f460 Iustin Pop
    let new_pdx = Node.idx tgt_p
353 5e15f460 Iustin Pop
        new_sdx = Node.idx tgt_s
354 4a340313 Iustin Pop
        new_nl = do -- Maybe monad
355 4a340313 Iustin Pop
          new_p <- Node.addPri tgt_p inst
356 4a340313 Iustin Pop
          new_s <- Node.addSec tgt_s inst new_pdx
357 8880d889 Iustin Pop
          let new_inst = Instance.setBoth inst new_pdx new_sdx
358 685935f7 Iustin Pop
          return (Container.addTwo new_pdx new_p new_sdx new_s nl, new_inst,
359 685935f7 Iustin Pop
                 [new_p, new_s])
360 8880d889 Iustin Pop
    in new_nl
361 4a340313 Iustin Pop
362 9188aeef Iustin Pop
-- | Tries to perform an instance move and returns the best table
363 9188aeef Iustin Pop
-- between the original one and the new one.
364 e4f08c46 Iustin Pop
checkSingleStep :: Table -- ^ The original table
365 e4f08c46 Iustin Pop
                -> Instance.Instance -- ^ The instance to move
366 e4f08c46 Iustin Pop
                -> Table -- ^ The current best table
367 e4f08c46 Iustin Pop
                -> IMove -- ^ The move to apply
368 e4f08c46 Iustin Pop
                -> Table -- ^ The final best table
369 e4f08c46 Iustin Pop
checkSingleStep ini_tbl target cur_tbl move =
370 e4f08c46 Iustin Pop
    let
371 e4f08c46 Iustin Pop
        Table ini_nl ini_il _ ini_plc = ini_tbl
372 8880d889 Iustin Pop
        tmp_resu = applyMove ini_nl target move
373 e4f08c46 Iustin Pop
    in
374 8880d889 Iustin Pop
      case tmp_resu of
375 f2280553 Iustin Pop
        OpFail _ -> cur_tbl
376 8880d889 Iustin Pop
        OpGood (upd_nl, new_inst, pri_idx, sec_idx)  ->
377 f2280553 Iustin Pop
            let tgt_idx = Instance.idx target
378 f2280553 Iustin Pop
                upd_cvar = compCV upd_nl
379 f2280553 Iustin Pop
                upd_il = Container.add tgt_idx new_inst ini_il
380 f2280553 Iustin Pop
                upd_plc = (tgt_idx, pri_idx, sec_idx, upd_cvar):ini_plc
381 f2280553 Iustin Pop
                upd_tbl = Table upd_nl upd_il upd_cvar upd_plc
382 f2280553 Iustin Pop
            in
383 f2280553 Iustin Pop
              compareTables cur_tbl upd_tbl
384 e4f08c46 Iustin Pop
385 c0501c69 Iustin Pop
-- | Given the status of the current secondary as a valid new node and
386 c0501c69 Iustin Pop
-- the current candidate target node, generate the possible moves for
387 c0501c69 Iustin Pop
-- a instance.
388 c0501c69 Iustin Pop
possibleMoves :: Bool      -- ^ Whether the secondary node is a valid new node
389 c0501c69 Iustin Pop
              -> Ndx       -- ^ Target node candidate
390 c0501c69 Iustin Pop
              -> [IMove]   -- ^ List of valid result moves
391 40d4eba0 Iustin Pop
possibleMoves True tdx =
392 40d4eba0 Iustin Pop
    [ReplaceSecondary tdx,
393 40d4eba0 Iustin Pop
     ReplaceAndFailover tdx,
394 40d4eba0 Iustin Pop
     ReplacePrimary tdx,
395 40d4eba0 Iustin Pop
     FailoverAndReplace tdx]
396 40d4eba0 Iustin Pop
397 40d4eba0 Iustin Pop
possibleMoves False tdx =
398 40d4eba0 Iustin Pop
    [ReplaceSecondary tdx,
399 40d4eba0 Iustin Pop
     ReplaceAndFailover tdx]
400 40d4eba0 Iustin Pop
401 40d4eba0 Iustin Pop
-- | Compute the best move for a given instance.
402 c0501c69 Iustin Pop
checkInstanceMove :: [Ndx]             -- ^ Allowed target node indices
403 c0501c69 Iustin Pop
                  -> Bool              -- ^ Whether disk moves are allowed
404 c0501c69 Iustin Pop
                  -> Table             -- ^ Original table
405 c0501c69 Iustin Pop
                  -> Instance.Instance -- ^ Instance to move
406 c0501c69 Iustin Pop
                  -> Table             -- ^ Best new table for this instance
407 c0501c69 Iustin Pop
checkInstanceMove nodes_idx disk_moves ini_tbl target =
408 4e25d1c2 Iustin Pop
    let
409 4e25d1c2 Iustin Pop
        opdx = Instance.pnode target
410 4e25d1c2 Iustin Pop
        osdx = Instance.snode target
411 9dc6023f Iustin Pop
        nodes = filter (\idx -> idx /= opdx && idx /= osdx) nodes_idx
412 40d4eba0 Iustin Pop
        use_secondary = elem osdx nodes_idx
413 40d4eba0 Iustin Pop
        aft_failover = if use_secondary -- if allowed to failover
414 40d4eba0 Iustin Pop
                       then checkSingleStep ini_tbl target ini_tbl Failover
415 40d4eba0 Iustin Pop
                       else ini_tbl
416 c0501c69 Iustin Pop
        all_moves = if disk_moves
417 c0501c69 Iustin Pop
                    then concatMap (possibleMoves use_secondary) nodes
418 c0501c69 Iustin Pop
                    else []
419 4e25d1c2 Iustin Pop
    in
420 4e25d1c2 Iustin Pop
      -- iterate over the possible nodes for this instance
421 9dc6023f Iustin Pop
      foldl' (checkSingleStep ini_tbl target) aft_failover all_moves
422 4e25d1c2 Iustin Pop
423 e4f08c46 Iustin Pop
-- | Compute the best next move.
424 608efcce Iustin Pop
checkMove :: [Ndx]               -- ^ Allowed target node indices
425 c0501c69 Iustin Pop
          -> Bool                -- ^ Whether disk moves are allowed
426 256810de Iustin Pop
          -> Table               -- ^ The current solution
427 e4f08c46 Iustin Pop
          -> [Instance.Instance] -- ^ List of instances still to move
428 256810de Iustin Pop
          -> Table               -- ^ The new solution
429 c0501c69 Iustin Pop
checkMove nodes_idx disk_moves ini_tbl victims =
430 4e25d1c2 Iustin Pop
    let Table _ _ _ ini_plc = ini_tbl
431 4e25d1c2 Iustin Pop
        -- iterate over all instances, computing the best move
432 256810de Iustin Pop
        best_tbl =
433 256810de Iustin Pop
            foldl'
434 7e7f6ca2 Iustin Pop
            (\ step_tbl elem ->
435 040afc35 Iustin Pop
                 if Instance.snode elem == Node.noSecondary then step_tbl
436 7e7f6ca2 Iustin Pop
                    else compareTables step_tbl $
437 c0501c69 Iustin Pop
                         checkInstanceMove nodes_idx disk_moves ini_tbl elem)
438 256810de Iustin Pop
            ini_tbl victims
439 aaaa0e43 Iustin Pop
        Table _ _ _ best_plc = best_tbl
440 0a0f2533 Iustin Pop
    in
441 0a0f2533 Iustin Pop
      if length best_plc == length ini_plc then -- no advancement
442 0a0f2533 Iustin Pop
          ini_tbl
443 0a0f2533 Iustin Pop
      else
444 7dfaafb1 Iustin Pop
          best_tbl
445 e4f08c46 Iustin Pop
446 f25e5aac Iustin Pop
-- | Run a balance move
447 f25e5aac Iustin Pop
448 f25e5aac Iustin Pop
tryBalance :: Table       -- ^ The starting table
449 f25e5aac Iustin Pop
           -> Int         -- ^ Remaining length
450 f25e5aac Iustin Pop
           -> Bool        -- ^ Allow disk moves
451 f25e5aac Iustin Pop
           -> Score       -- ^ Score at which to stop
452 f25e5aac Iustin Pop
           -> Maybe Table -- ^ The resulting table and commands
453 f25e5aac Iustin Pop
tryBalance ini_tbl max_rounds disk_moves min_score =
454 f25e5aac Iustin Pop
    let Table ini_nl ini_il ini_cv ini_plc = ini_tbl
455 f25e5aac Iustin Pop
        ini_plc_len = length ini_plc
456 f25e5aac Iustin Pop
        allowed_next = (max_rounds < 0 || ini_plc_len < max_rounds) &&
457 f25e5aac Iustin Pop
                       ini_cv > min_score
458 f25e5aac Iustin Pop
    in
459 f25e5aac Iustin Pop
      if allowed_next
460 f25e5aac Iustin Pop
      then let all_inst = Container.elems ini_il
461 f25e5aac Iustin Pop
               node_idx = map Node.idx . filter (not . Node.offline) $
462 f25e5aac Iustin Pop
                          Container.elems ini_nl
463 f25e5aac Iustin Pop
               fin_tbl = checkMove node_idx disk_moves ini_tbl all_inst
464 f25e5aac Iustin Pop
               (Table _ _ fin_cv _) = fin_tbl
465 f25e5aac Iustin Pop
           in
466 f25e5aac Iustin Pop
             if fin_cv < ini_cv
467 f25e5aac Iustin Pop
             then Just fin_tbl -- this round made success, try deeper
468 f25e5aac Iustin Pop
             else Nothing
469 f25e5aac Iustin Pop
      else Nothing
470 f25e5aac Iustin Pop
471 478df686 Iustin Pop
-- * Allocation functions
472 478df686 Iustin Pop
473 478df686 Iustin Pop
-- | Build failure stats out of a list of failures
474 478df686 Iustin Pop
collapseFailures :: [FailMode] -> FailStats
475 478df686 Iustin Pop
collapseFailures flst =
476 478df686 Iustin Pop
    map (\k -> (k, length $ filter ((==) k) flst)) [minBound..maxBound]
477 478df686 Iustin Pop
478 478df686 Iustin Pop
-- | Update current Allocation solution and failure stats with new
479 478df686 Iustin Pop
-- elements
480 478df686 Iustin Pop
concatAllocs :: AllocSolution -> OpResult AllocElement -> AllocSolution
481 478df686 Iustin Pop
concatAllocs (flst, succ, sols) (OpFail reason) = (reason:flst, succ, sols)
482 478df686 Iustin Pop
483 478df686 Iustin Pop
concatAllocs (flst, succ, osols) (OpGood ns@(nl, _, _)) =
484 478df686 Iustin Pop
    let nscore = compCV nl
485 478df686 Iustin Pop
        -- Choose the old or new solution, based on the cluster score
486 478df686 Iustin Pop
        nsols = case osols of
487 478df686 Iustin Pop
                  Nothing -> Just (nscore, ns)
488 478df686 Iustin Pop
                  Just (oscore, _) ->
489 478df686 Iustin Pop
                      if oscore < nscore
490 478df686 Iustin Pop
                      then osols
491 478df686 Iustin Pop
                      else Just (nscore, ns)
492 478df686 Iustin Pop
        nsuc = succ + 1
493 478df686 Iustin Pop
    -- Note: we force evaluation of nsols here in order to keep the
494 478df686 Iustin Pop
    -- memory profile low - we know that we will need nsols for sure
495 478df686 Iustin Pop
    -- in the next cycle, so we force evaluation of nsols, since the
496 478df686 Iustin Pop
    -- foldl' in the caller will only evaluate the tuple, but not the
497 7d11799b Iustin Pop
    -- elements of the tuple
498 478df686 Iustin Pop
    in nsols `seq` nsuc `seq` (flst, nsuc, nsols)
499 dbba5246 Iustin Pop
500 dbba5246 Iustin Pop
-- | Try to allocate an instance on the cluster.
501 dbba5246 Iustin Pop
tryAlloc :: (Monad m) =>
502 dbba5246 Iustin Pop
            Node.List         -- ^ The node list
503 dbba5246 Iustin Pop
         -> Instance.List     -- ^ The instance list
504 dbba5246 Iustin Pop
         -> Instance.Instance -- ^ The instance to allocate
505 dbba5246 Iustin Pop
         -> Int               -- ^ Required number of nodes
506 78694255 Iustin Pop
         -> m AllocSolution   -- ^ Possible solution list
507 dbba5246 Iustin Pop
tryAlloc nl _ inst 2 =
508 dbba5246 Iustin Pop
    let all_nodes = getOnline nl
509 dbba5246 Iustin Pop
        all_pairs = liftM2 (,) all_nodes all_nodes
510 dbba5246 Iustin Pop
        ok_pairs = filter (\(x, y) -> Node.idx x /= Node.idx y) all_pairs
511 478df686 Iustin Pop
        sols = foldl' (\cstate (p, s) ->
512 478df686 Iustin Pop
                           concatAllocs cstate $ allocateOnPair nl inst p s
513 478df686 Iustin Pop
                      ) ([], 0, Nothing) ok_pairs
514 dbba5246 Iustin Pop
    in return sols
515 dbba5246 Iustin Pop
516 dbba5246 Iustin Pop
tryAlloc nl _ inst 1 =
517 dbba5246 Iustin Pop
    let all_nodes = getOnline nl
518 2485487d Iustin Pop
        sols = foldl' (\cstate ->
519 2485487d Iustin Pop
                           concatAllocs cstate . allocateOnSingle nl inst
520 478df686 Iustin Pop
                      ) ([], 0, Nothing) all_nodes
521 dbba5246 Iustin Pop
    in return sols
522 dbba5246 Iustin Pop
523 31e7ac17 Iustin Pop
tryAlloc _ _ _ reqn = fail $ "Unsupported number of allocation \
524 9f6dcdea Iustin Pop
                             \destinations required (" ++ show reqn ++
525 dbba5246 Iustin Pop
                                               "), only two supported"
526 dbba5246 Iustin Pop
527 dbba5246 Iustin Pop
-- | Try to allocate an instance on the cluster.
528 dbba5246 Iustin Pop
tryReloc :: (Monad m) =>
529 78694255 Iustin Pop
            Node.List       -- ^ The node list
530 78694255 Iustin Pop
         -> Instance.List   -- ^ The instance list
531 78694255 Iustin Pop
         -> Idx             -- ^ The index of the instance to move
532 478df686 Iustin Pop
         -> Int             -- ^ The number of nodes required
533 78694255 Iustin Pop
         -> [Ndx]           -- ^ Nodes which should not be used
534 78694255 Iustin Pop
         -> m AllocSolution -- ^ Solution list
535 dbba5246 Iustin Pop
tryReloc nl il xid 1 ex_idx =
536 dbba5246 Iustin Pop
    let all_nodes = getOnline nl
537 dbba5246 Iustin Pop
        inst = Container.find xid il
538 9f6dcdea Iustin Pop
        ex_idx' = Instance.pnode inst:ex_idx
539 dbba5246 Iustin Pop
        valid_nodes = filter (not . flip elem ex_idx' . Node.idx) all_nodes
540 dbba5246 Iustin Pop
        valid_idxes = map Node.idx valid_nodes
541 478df686 Iustin Pop
        sols1 = foldl' (\cstate x ->
542 478df686 Iustin Pop
                            let elem = do
543 478df686 Iustin Pop
                                  (mnl, i, _, _) <-
544 478df686 Iustin Pop
                                      applyMove nl inst (ReplaceSecondary x)
545 478df686 Iustin Pop
                                  return (mnl, i, [Container.find x mnl])
546 478df686 Iustin Pop
                            in concatAllocs cstate elem
547 478df686 Iustin Pop
                       ) ([], 0, Nothing) valid_idxes
548 dbba5246 Iustin Pop
    in return sols1
549 dbba5246 Iustin Pop
550 dbba5246 Iustin Pop
tryReloc _ _ _ reqn _  = fail $ "Unsupported number of relocation \
551 9f6dcdea Iustin Pop
                                \destinations required (" ++ show reqn ++
552 dbba5246 Iustin Pop
                                                  "), only one supported"
553 e4f08c46 Iustin Pop
554 9188aeef Iustin Pop
-- * Formatting functions
555 e4f08c46 Iustin Pop
556 e4f08c46 Iustin Pop
-- | Given the original and final nodes, computes the relocation description.
557 c9926b22 Iustin Pop
computeMoves :: Instance.Instance -- ^ The instance to be moved
558 c9926b22 Iustin Pop
             -> String -- ^ The instance name
559 e4f08c46 Iustin Pop
             -> String -- ^ Original primary
560 e4f08c46 Iustin Pop
             -> String -- ^ Original secondary
561 e4f08c46 Iustin Pop
             -> String -- ^ New primary
562 e4f08c46 Iustin Pop
             -> String -- ^ New secondary
563 e4f08c46 Iustin Pop
             -> (String, [String])
564 e4f08c46 Iustin Pop
                -- ^ Tuple of moves and commands list; moves is containing
565 e4f08c46 Iustin Pop
                -- either @/f/@ for failover or @/r:name/@ for replace
566 e4f08c46 Iustin Pop
                -- secondary, while the command list holds gnt-instance
567 e4f08c46 Iustin Pop
                -- commands (without that prefix), e.g \"@failover instance1@\"
568 c9926b22 Iustin Pop
computeMoves i inam a b c d
569 41c3b292 Iustin Pop
    -- same primary
570 41c3b292 Iustin Pop
    | c == a =
571 41c3b292 Iustin Pop
        if d == b
572 41c3b292 Iustin Pop
        then {- Same sec??! -} ("-", [])
573 e4f08c46 Iustin Pop
        else {- Change of secondary -}
574 41c3b292 Iustin Pop
            (printf "r:%s" d, [rep d])
575 41c3b292 Iustin Pop
    -- failover and ...
576 41c3b292 Iustin Pop
    | c == b =
577 41c3b292 Iustin Pop
        if d == a
578 41c3b292 Iustin Pop
        then {- that's all -} ("f", [mig])
579 41c3b292 Iustin Pop
        else (printf "f r:%s" d, [mig, rep d])
580 41c3b292 Iustin Pop
    -- ... and keep primary as secondary
581 41c3b292 Iustin Pop
    | d == a =
582 41c3b292 Iustin Pop
        (printf "r:%s f" c, [rep c, mig])
583 41c3b292 Iustin Pop
    -- ... keep same secondary
584 41c3b292 Iustin Pop
    | d == b =
585 41c3b292 Iustin Pop
        (printf "f r:%s f" c, [mig, rep c, mig])
586 41c3b292 Iustin Pop
    -- nothing in common -
587 41c3b292 Iustin Pop
    | otherwise =
588 41c3b292 Iustin Pop
        (printf "r:%s f r:%s" c d, [rep c, mig, rep d])
589 c9926b22 Iustin Pop
    where morf = if Instance.running i then "migrate" else "failover"
590 c9926b22 Iustin Pop
          mig = printf "%s -f %s" morf inam::String
591 c9926b22 Iustin Pop
          rep n = printf "replace-disks -n %s %s" n inam
592 e4f08c46 Iustin Pop
593 9188aeef Iustin Pop
-- | Converts a placement to string format.
594 9188aeef Iustin Pop
printSolutionLine :: Node.List     -- ^ The node list
595 9188aeef Iustin Pop
                  -> Instance.List -- ^ The instance list
596 9188aeef Iustin Pop
                  -> Int           -- ^ Maximum node name length
597 9188aeef Iustin Pop
                  -> Int           -- ^ Maximum instance name length
598 9188aeef Iustin Pop
                  -> Placement     -- ^ The current placement
599 9188aeef Iustin Pop
                  -> Int           -- ^ The index of the placement in
600 9188aeef Iustin Pop
                                   -- the solution
601 db1bcfe8 Iustin Pop
                  -> (String, [String])
602 db1bcfe8 Iustin Pop
printSolutionLine nl il nmlen imlen plc pos =
603 ca8258d9 Iustin Pop
    let
604 ca8258d9 Iustin Pop
        pmlen = (2*nmlen + 1)
605 ca8258d9 Iustin Pop
        (i, p, s, c) = plc
606 ca8258d9 Iustin Pop
        inst = Container.find i il
607 dbd6700b Iustin Pop
        inam = Instance.name inst
608 262a08a2 Iustin Pop
        npri = Container.nameOf nl p
609 262a08a2 Iustin Pop
        nsec = Container.nameOf nl s
610 262a08a2 Iustin Pop
        opri = Container.nameOf nl $ Instance.pnode inst
611 262a08a2 Iustin Pop
        osec = Container.nameOf nl $ Instance.snode inst
612 c9926b22 Iustin Pop
        (moves, cmds) =  computeMoves inst inam opri osec npri nsec
613 9f6dcdea Iustin Pop
        ostr = printf "%s:%s" opri osec::String
614 9f6dcdea Iustin Pop
        nstr = printf "%s:%s" npri nsec::String
615 ca8258d9 Iustin Pop
    in
616 ab271fc1 Iustin Pop
      (printf "  %3d. %-*s %-*s => %-*s %.8f a=%s"
617 ab271fc1 Iustin Pop
       pos imlen inam pmlen ostr
618 ca8258d9 Iustin Pop
       pmlen nstr c moves,
619 ca8258d9 Iustin Pop
       cmds)
620 ca8258d9 Iustin Pop
621 9188aeef Iustin Pop
-- | Given a list of commands, prefix them with @gnt-instance@ and
622 9188aeef Iustin Pop
-- also beautify the display a little.
623 142538ff Iustin Pop
formatCmds :: [[String]] -> String
624 9f6dcdea Iustin Pop
formatCmds =
625 9f6dcdea Iustin Pop
    unlines .
626 9f6dcdea Iustin Pop
    concatMap (\(a, b) ->
627 9f6dcdea Iustin Pop
               printf "echo step %d" (a::Int):
628 9f6dcdea Iustin Pop
               printf "check":
629 9f6dcdea Iustin Pop
               map ("gnt-instance " ++) b
630 9f6dcdea Iustin Pop
              ) .
631 9f6dcdea Iustin Pop
    zip [1..]
632 142538ff Iustin Pop
633 9188aeef Iustin Pop
-- | Converts a solution to string format.
634 262a08a2 Iustin Pop
printSolution :: Node.List
635 262a08a2 Iustin Pop
              -> Instance.List
636 e4f08c46 Iustin Pop
              -> [Placement]
637 e4f08c46 Iustin Pop
              -> ([String], [[String]])
638 db1bcfe8 Iustin Pop
printSolution nl il sol =
639 671b85b9 Iustin Pop
    let
640 262a08a2 Iustin Pop
        nmlen = Container.maxNameLen nl
641 262a08a2 Iustin Pop
        imlen = Container.maxNameLen il
642 671b85b9 Iustin Pop
    in
643 9f6dcdea Iustin Pop
      unzip $ zipWith (printSolutionLine nl il nmlen imlen) sol [1..]
644 e4f08c46 Iustin Pop
645 e4f08c46 Iustin Pop
-- | Print the node list.
646 262a08a2 Iustin Pop
printNodes :: Node.List -> String
647 dbd6700b Iustin Pop
printNodes nl =
648 e4f08c46 Iustin Pop
    let snl = sortBy (compare `on` Node.idx) (Container.elems nl)
649 dbd6700b Iustin Pop
        m_name = maximum . map (length . Node.name) $ snl
650 af53a5c4 Iustin Pop
        helper = Node.list m_name
651 9f6dcdea Iustin Pop
        header = printf
652 9f6dcdea Iustin Pop
                 "%2s %-*s %5s %5s %5s %5s %5s %5s %5s %5s %4s %4s \
653 9f6dcdea Iustin Pop
                 \%3s %3s %6s %6s %5s"
654 9f6dcdea Iustin Pop
                 " F" m_name "Name"
655 9f6dcdea Iustin Pop
                 "t_mem" "n_mem" "i_mem" "x_mem" "f_mem" "r_mem"
656 9f6dcdea Iustin Pop
                 "t_dsk" "f_dsk" "pcpu" "vcpu"
657 9f6dcdea Iustin Pop
                 "pri" "sec" "p_fmem" "p_fdsk" "r_cpu"::String
658 9f6dcdea Iustin Pop
    in unlines (header:map helper snl)
659 e4f08c46 Iustin Pop
660 9188aeef Iustin Pop
-- | Shows statistics for a given node list.
661 262a08a2 Iustin Pop
printStats :: Node.List -> String
662 e4f08c46 Iustin Pop
printStats nl =
663 0a8dd21d Iustin Pop
    let (mem_cv, dsk_cv, n1_score, res_cv, off_score, cpu_cv) =
664 0a8dd21d Iustin Pop
            compDetailedCV nl
665 0a8dd21d Iustin Pop
    in printf "f_mem=%.8f, r_mem=%.8f, f_dsk=%.8f, n1=%.3f, \
666 0a8dd21d Iustin Pop
              \uf=%.3f, r_cpu=%.3f"
667 0a8dd21d Iustin Pop
       mem_cv res_cv dsk_cv n1_score off_score cpu_cv