Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ 859fc11d

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