Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ 3a3c1eb4

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