Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ 54365762

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