Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ 673f0f00

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