Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ 0ca66853

History | View | Annotate | Download (33.5 kB)

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