Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Cluster.hs @ 756df409

History | View | Annotate | Download (60.1 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 525bfb36 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 4bc33d60 Iustin Pop
Copyright (C) 2009, 2010, 2011 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 47eed3f4 Iustin Pop
    , EvacSolution(..)
34 e4f08c46 Iustin Pop
    , Table(..)
35 1a7eff0e Iustin Pop
    , CStats(..)
36 9b8fac3d Iustin Pop
    , AllocStats
37 e4f08c46 Iustin Pop
    -- * Generic functions
38 e4f08c46 Iustin Pop
    , totalResources
39 9b8fac3d Iustin Pop
    , computeAllocationDelta
40 e4f08c46 Iustin Pop
    -- * First phase functions
41 e4f08c46 Iustin Pop
    , computeBadItems
42 e4f08c46 Iustin Pop
    -- * Second phase functions
43 7dfaafb1 Iustin Pop
    , printSolutionLine
44 142538ff Iustin Pop
    , formatCmds
45 0e8ae201 Iustin Pop
    , involvedNodes
46 0e8ae201 Iustin Pop
    , splitJobs
47 507fda3f Iustin Pop
    -- * Display functions
48 507fda3f Iustin Pop
    , printNodes
49 507fda3f Iustin Pop
    , printInsts
50 e4f08c46 Iustin Pop
    -- * Balacing functions
51 e4f08c46 Iustin Pop
    , checkMove
52 5ad86777 Iustin Pop
    , doNextBalance
53 f25e5aac Iustin Pop
    , tryBalance
54 e4f08c46 Iustin Pop
    , compCV
55 9bb5721c Iustin Pop
    , compCVNodes
56 6bc39970 Iustin Pop
    , compDetailedCV
57 e4f08c46 Iustin Pop
    , printStats
58 6b20875c Iustin Pop
    , iMoveToJob
59 4a340313 Iustin Pop
    -- * IAllocator functions
60 6cb1649f Iustin Pop
    , genAllocNodes
61 dbba5246 Iustin Pop
    , tryAlloc
62 9b1584fc Iustin Pop
    , tryMGAlloc
63 dbba5246 Iustin Pop
    , tryReloc
64 12b0511d Iustin Pop
    , tryEvac
65 47eed3f4 Iustin Pop
    , tryNodeEvac
66 20b376ff Iustin Pop
    , tryChangeGroup
67 478df686 Iustin Pop
    , collapseFailures
68 3ce8009a Iustin Pop
    -- * Allocation functions
69 3ce8009a Iustin Pop
    , iterateAlloc
70 3ce8009a Iustin Pop
    , tieredAlloc
71 949397c8 Iustin Pop
     -- * Node group functions
72 32b8d9c0 Iustin Pop
    , instanceGroup
73 32b8d9c0 Iustin Pop
    , findSplitInstances
74 f4161783 Iustin Pop
    , splitCluster
75 e4f08c46 Iustin Pop
    ) where
76 e4f08c46 Iustin Pop
77 63a78055 Iustin Pop
import qualified Data.IntSet as IntSet
78 e4f08c46 Iustin Pop
import Data.List
79 db56cfc4 Iustin Pop
import Data.Maybe (fromJust)
80 5182e970 Iustin Pop
import Data.Ord (comparing)
81 e4f08c46 Iustin Pop
import Text.Printf (printf)
82 9d3fada5 Iustin Pop
import Control.Monad
83 e4f08c46 Iustin Pop
84 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Container as Container
85 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
86 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Node as Node
87 aec636b9 Iustin Pop
import qualified Ganeti.HTools.Group as Group
88 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
89 669d7e3d Iustin Pop
import Ganeti.HTools.Utils
90 1adec4be Iustin Pop
import Ganeti.HTools.Compat
91 6b20875c Iustin Pop
import qualified Ganeti.OpCodes as OpCodes
92 e4f08c46 Iustin Pop
93 9188aeef Iustin Pop
-- * Types
94 9188aeef Iustin Pop
95 0c936d24 Iustin Pop
-- | Allocation\/relocation solution.
96 85d0ddc3 Iustin Pop
data AllocSolution = AllocSolution
97 85d0ddc3 Iustin Pop
  { asFailures  :: [FailMode]          -- ^ Failure counts
98 85d0ddc3 Iustin Pop
  , asAllocs    :: Int                 -- ^ Good allocation count
99 85d0ddc3 Iustin Pop
  , asSolutions :: [Node.AllocElement] -- ^ The actual result, length
100 85d0ddc3 Iustin Pop
                                       -- of the list depends on the
101 85d0ddc3 Iustin Pop
                                       -- allocation/relocation mode
102 859fc11d Iustin Pop
  , asLog       :: [String]            -- ^ A list of informational messages
103 85d0ddc3 Iustin Pop
  }
104 85d0ddc3 Iustin Pop
105 47eed3f4 Iustin Pop
-- | Node evacuation/group change iallocator result type. This result
106 47eed3f4 Iustin Pop
-- type consists of actual opcodes (a restricted subset) that are
107 47eed3f4 Iustin Pop
-- transmitted back to Ganeti.
108 47eed3f4 Iustin Pop
data EvacSolution = EvacSolution
109 5440c877 Iustin Pop
    { esMoved   :: [(Idx, Gdx, [Ndx])]  -- ^ Instances moved successfully
110 5440c877 Iustin Pop
    , esFailed  :: [(Idx, String)]      -- ^ Instances which were not
111 47eed3f4 Iustin Pop
                                        -- relocated
112 47eed3f4 Iustin Pop
    , esOpCodes :: [[[OpCodes.OpCode]]] -- ^ List of lists of jobs
113 47eed3f4 Iustin Pop
    }
114 47eed3f4 Iustin Pop
115 40ee14bc Iustin Pop
-- | Allocation results, as used in 'iterateAlloc' and 'tieredAlloc'.
116 40ee14bc Iustin Pop
type AllocResult = (FailStats, Node.List, Instance.List,
117 40ee14bc Iustin Pop
                    [Instance.Instance], [CStats])
118 40ee14bc Iustin Pop
119 6cb1649f Iustin Pop
-- | A type denoting the valid allocation mode/pairs.
120 525bfb36 Iustin Pop
--
121 6cb1649f Iustin Pop
-- For a one-node allocation, this will be a @Left ['Node.Node']@,
122 6cb1649f Iustin Pop
-- whereas for a two-node allocation, this will be a @Right
123 6cb1649f Iustin Pop
-- [('Node.Node', 'Node.Node')]@.
124 0d66ea67 Iustin Pop
type AllocNodes = Either [Ndx] [(Ndx, Ndx)]
125 6cb1649f Iustin Pop
126 525bfb36 Iustin Pop
-- | The empty solution we start with when computing allocations.
127 97936d51 Iustin Pop
emptyAllocSolution :: AllocSolution
128 97936d51 Iustin Pop
emptyAllocSolution = AllocSolution { asFailures = [], asAllocs = 0
129 97936d51 Iustin Pop
                                   , asSolutions = [], asLog = [] }
130 78694255 Iustin Pop
131 47eed3f4 Iustin Pop
-- | The empty evac solution.
132 47eed3f4 Iustin Pop
emptyEvacSolution :: EvacSolution
133 47eed3f4 Iustin Pop
emptyEvacSolution = EvacSolution { esMoved = []
134 47eed3f4 Iustin Pop
                                 , esFailed = []
135 47eed3f4 Iustin Pop
                                 , esOpCodes = []
136 47eed3f4 Iustin Pop
                                 }
137 47eed3f4 Iustin Pop
138 525bfb36 Iustin Pop
-- | The complete state for the balancing solution.
139 262a08a2 Iustin Pop
data Table = Table Node.List Instance.List Score [Placement]
140 6bc39970 Iustin Pop
             deriving (Show, Read)
141 e4f08c46 Iustin Pop
142 7034694d Iustin Pop
data CStats = CStats { csFmem :: Integer -- ^ Cluster free mem
143 7034694d Iustin Pop
                     , csFdsk :: Integer -- ^ Cluster free disk
144 7034694d Iustin Pop
                     , csAmem :: Integer -- ^ Cluster allocatable mem
145 7034694d Iustin Pop
                     , csAdsk :: Integer -- ^ Cluster allocatable disk
146 7034694d Iustin Pop
                     , csAcpu :: Integer -- ^ Cluster allocatable cpus
147 7034694d Iustin Pop
                     , csMmem :: Integer -- ^ Max node allocatable mem
148 7034694d Iustin Pop
                     , csMdsk :: Integer -- ^ Max node allocatable disk
149 7034694d Iustin Pop
                     , csMcpu :: Integer -- ^ Max node allocatable cpu
150 7034694d Iustin Pop
                     , csImem :: Integer -- ^ Instance used mem
151 7034694d Iustin Pop
                     , csIdsk :: Integer -- ^ Instance used disk
152 7034694d Iustin Pop
                     , csIcpu :: Integer -- ^ Instance used cpu
153 7034694d Iustin Pop
                     , csTmem :: Double  -- ^ Cluster total mem
154 7034694d Iustin Pop
                     , csTdsk :: Double  -- ^ Cluster total disk
155 7034694d Iustin Pop
                     , csTcpu :: Double  -- ^ Cluster total cpus
156 7034694d Iustin Pop
                     , csVcpu :: Integer -- ^ Cluster virtual cpus (if
157 7034694d Iustin Pop
                                         -- node pCpu has been set,
158 7034694d Iustin Pop
                                         -- otherwise -1)
159 7034694d Iustin Pop
                     , csXmem :: Integer -- ^ Unnacounted for mem
160 7034694d Iustin Pop
                     , csNmem :: Integer -- ^ Node own memory
161 7034694d Iustin Pop
                     , csScore :: Score  -- ^ The cluster score
162 7034694d Iustin Pop
                     , csNinst :: Int    -- ^ The total number of instances
163 1a7eff0e Iustin Pop
                     }
164 6bc39970 Iustin Pop
            deriving (Show, Read)
165 1a7eff0e Iustin Pop
166 525bfb36 Iustin Pop
-- | Currently used, possibly to allocate, unallocable.
167 9b8fac3d Iustin Pop
type AllocStats = (RSpec, RSpec, RSpec)
168 9b8fac3d Iustin Pop
169 9188aeef Iustin Pop
-- * Utility functions
170 9188aeef Iustin Pop
171 e4f08c46 Iustin Pop
-- | Verifies the N+1 status and return the affected nodes.
172 e4f08c46 Iustin Pop
verifyN1 :: [Node.Node] -> [Node.Node]
173 9f6dcdea Iustin Pop
verifyN1 = filter Node.failN1
174 e4f08c46 Iustin Pop
175 9188aeef Iustin Pop
{-| Computes the pair of bad nodes and instances.
176 9188aeef Iustin Pop
177 9188aeef Iustin Pop
The bad node list is computed via a simple 'verifyN1' check, and the
178 9188aeef Iustin Pop
bad instance list is the list of primary and secondary instances of
179 9188aeef Iustin Pop
those nodes.
180 9188aeef Iustin Pop
181 9188aeef Iustin Pop
-}
182 9188aeef Iustin Pop
computeBadItems :: Node.List -> Instance.List ->
183 9188aeef Iustin Pop
                   ([Node.Node], [Instance.Instance])
184 9188aeef Iustin Pop
computeBadItems nl il =
185 dbba5246 Iustin Pop
  let bad_nodes = verifyN1 $ getOnline nl
186 5182e970 Iustin Pop
      bad_instances = map (`Container.find` il) .
187 9f6dcdea Iustin Pop
                      sort . nub $
188 2060348b Iustin Pop
                      concatMap (\ n -> Node.sList n ++ Node.pList n) bad_nodes
189 9188aeef Iustin Pop
  in
190 9188aeef Iustin Pop
    (bad_nodes, bad_instances)
191 9188aeef Iustin Pop
192 525bfb36 Iustin Pop
-- | Zero-initializer for the CStats type.
193 1a7eff0e Iustin Pop
emptyCStats :: CStats
194 86ecce4a Iustin Pop
emptyCStats = CStats 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0
195 1a7eff0e Iustin Pop
196 525bfb36 Iustin Pop
-- | Update stats with data from a new node.
197 1a7eff0e Iustin Pop
updateCStats :: CStats -> Node.Node -> CStats
198 1a7eff0e Iustin Pop
updateCStats cs node =
199 f5b553da Iustin Pop
    let CStats { csFmem = x_fmem, csFdsk = x_fdsk,
200 f5b553da Iustin Pop
                 csAmem = x_amem, csAcpu = x_acpu, csAdsk = x_adsk,
201 f5b553da Iustin Pop
                 csMmem = x_mmem, csMdsk = x_mdsk, csMcpu = x_mcpu,
202 f5b553da Iustin Pop
                 csImem = x_imem, csIdsk = x_idsk, csIcpu = x_icpu,
203 f5b553da Iustin Pop
                 csTmem = x_tmem, csTdsk = x_tdsk, csTcpu = x_tcpu,
204 86ecce4a Iustin Pop
                 csVcpu = x_vcpu,
205 f5b553da Iustin Pop
                 csXmem = x_xmem, csNmem = x_nmem, csNinst = x_ninst
206 8c4c6a8a Iustin Pop
               }
207 1a7eff0e Iustin Pop
            = cs
208 2060348b Iustin Pop
        inc_amem = Node.fMem node - Node.rMem node
209 1a7eff0e Iustin Pop
        inc_amem' = if inc_amem > 0 then inc_amem else 0
210 301789f4 Iustin Pop
        inc_adsk = Node.availDisk node
211 2060348b Iustin Pop
        inc_imem = truncate (Node.tMem node) - Node.nMem node
212 2060348b Iustin Pop
                   - Node.xMem node - Node.fMem node
213 2060348b Iustin Pop
        inc_icpu = Node.uCpu node
214 2060348b Iustin Pop
        inc_idsk = truncate (Node.tDsk node) - Node.fDsk node
215 86ecce4a Iustin Pop
        inc_vcpu = Node.hiCpu node
216 f52dadb2 Iustin Pop
        inc_acpu = Node.availCpu node
217 8c4c6a8a Iustin Pop
218 7034694d Iustin Pop
    in cs { csFmem = x_fmem + fromIntegral (Node.fMem node)
219 7034694d Iustin Pop
          , csFdsk = x_fdsk + fromIntegral (Node.fDsk node)
220 7034694d Iustin Pop
          , csAmem = x_amem + fromIntegral inc_amem'
221 7034694d Iustin Pop
          , csAdsk = x_adsk + fromIntegral inc_adsk
222 7034694d Iustin Pop
          , csAcpu = x_acpu + fromIntegral inc_acpu
223 7034694d Iustin Pop
          , csMmem = max x_mmem (fromIntegral inc_amem')
224 7034694d Iustin Pop
          , csMdsk = max x_mdsk (fromIntegral inc_adsk)
225 7034694d Iustin Pop
          , csMcpu = max x_mcpu (fromIntegral inc_acpu)
226 7034694d Iustin Pop
          , csImem = x_imem + fromIntegral inc_imem
227 7034694d Iustin Pop
          , csIdsk = x_idsk + fromIntegral inc_idsk
228 7034694d Iustin Pop
          , csIcpu = x_icpu + fromIntegral inc_icpu
229 f5b553da Iustin Pop
          , csTmem = x_tmem + Node.tMem node
230 f5b553da Iustin Pop
          , csTdsk = x_tdsk + Node.tDsk node
231 f5b553da Iustin Pop
          , csTcpu = x_tcpu + Node.tCpu node
232 7034694d Iustin Pop
          , csVcpu = x_vcpu + fromIntegral inc_vcpu
233 7034694d Iustin Pop
          , csXmem = x_xmem + fromIntegral (Node.xMem node)
234 7034694d Iustin Pop
          , csNmem = x_nmem + fromIntegral (Node.nMem node)
235 f5b553da Iustin Pop
          , csNinst = x_ninst + length (Node.pList node)
236 de4ac2c2 Iustin Pop
          }
237 1a7eff0e Iustin Pop
238 9188aeef Iustin Pop
-- | Compute the total free disk and memory in the cluster.
239 1a7eff0e Iustin Pop
totalResources :: Node.List -> CStats
240 de4ac2c2 Iustin Pop
totalResources nl =
241 de4ac2c2 Iustin Pop
    let cs = foldl' updateCStats emptyCStats . Container.elems $ nl
242 f5b553da Iustin Pop
    in cs { csScore = compCV nl }
243 9188aeef Iustin Pop
244 9b8fac3d Iustin Pop
-- | Compute the delta between two cluster state.
245 9b8fac3d Iustin Pop
--
246 9b8fac3d Iustin Pop
-- This is used when doing allocations, to understand better the
247 e2436511 Iustin Pop
-- available cluster resources. The return value is a triple of the
248 e2436511 Iustin Pop
-- current used values, the delta that was still allocated, and what
249 e2436511 Iustin Pop
-- was left unallocated.
250 9b8fac3d Iustin Pop
computeAllocationDelta :: CStats -> CStats -> AllocStats
251 9b8fac3d Iustin Pop
computeAllocationDelta cini cfin =
252 9b8fac3d Iustin Pop
    let CStats {csImem = i_imem, csIdsk = i_idsk, csIcpu = i_icpu} = cini
253 9b8fac3d Iustin Pop
        CStats {csImem = f_imem, csIdsk = f_idsk, csIcpu = f_icpu,
254 9b8fac3d Iustin Pop
                csTmem = t_mem, csTdsk = t_dsk, csVcpu = v_cpu } = cfin
255 7034694d Iustin Pop
        rini = RSpec (fromIntegral i_icpu) (fromIntegral i_imem)
256 7034694d Iustin Pop
               (fromIntegral i_idsk)
257 7034694d Iustin Pop
        rfin = RSpec (fromIntegral (f_icpu - i_icpu))
258 7034694d Iustin Pop
               (fromIntegral (f_imem - i_imem))
259 7034694d Iustin Pop
               (fromIntegral (f_idsk - i_idsk))
260 7034694d Iustin Pop
        un_cpu = fromIntegral (v_cpu - f_icpu)::Int
261 7034694d Iustin Pop
        runa = RSpec un_cpu (truncate t_mem - fromIntegral f_imem)
262 7034694d Iustin Pop
               (truncate t_dsk - fromIntegral f_idsk)
263 9b8fac3d Iustin Pop
    in (rini, rfin, runa)
264 9b8fac3d Iustin Pop
265 525bfb36 Iustin Pop
-- | The names and weights of the individual elements in the CV list.
266 8a3b30ca Iustin Pop
detailedCVInfo :: [(Double, String)]
267 8a3b30ca Iustin Pop
detailedCVInfo = [ (1,  "free_mem_cv")
268 8a3b30ca Iustin Pop
                 , (1,  "free_disk_cv")
269 8a3b30ca Iustin Pop
                 , (1,  "n1_cnt")
270 8a3b30ca Iustin Pop
                 , (1,  "reserved_mem_cv")
271 8a3b30ca Iustin Pop
                 , (4,  "offline_all_cnt")
272 8a3b30ca Iustin Pop
                 , (16, "offline_pri_cnt")
273 8a3b30ca Iustin Pop
                 , (1,  "vcpu_ratio_cv")
274 8a3b30ca Iustin Pop
                 , (1,  "cpu_load_cv")
275 8a3b30ca Iustin Pop
                 , (1,  "mem_load_cv")
276 8a3b30ca Iustin Pop
                 , (1,  "disk_load_cv")
277 8a3b30ca Iustin Pop
                 , (1,  "net_load_cv")
278 306cccd5 Iustin Pop
                 , (2,  "pri_tags_score")
279 8a3b30ca Iustin Pop
                 ]
280 8a3b30ca Iustin Pop
281 8a3b30ca Iustin Pop
detailedCVWeights :: [Double]
282 8a3b30ca Iustin Pop
detailedCVWeights = map fst detailedCVInfo
283 fca250e9 Iustin Pop
284 9188aeef Iustin Pop
-- | Compute the mem and disk covariance.
285 9bb5721c Iustin Pop
compDetailedCV :: [Node.Node] -> [Double]
286 9bb5721c Iustin Pop
compDetailedCV all_nodes =
287 9188aeef Iustin Pop
    let
288 9188aeef Iustin Pop
        (offline, nodes) = partition Node.offline all_nodes
289 2060348b Iustin Pop
        mem_l = map Node.pMem nodes
290 2060348b Iustin Pop
        dsk_l = map Node.pDsk nodes
291 daee4bed Iustin Pop
        -- metric: memory covariance
292 4715711d Iustin Pop
        mem_cv = stdDev mem_l
293 daee4bed Iustin Pop
        -- metric: disk covariance
294 4715711d Iustin Pop
        dsk_cv = stdDev dsk_l
295 c3c7a0c1 Iustin Pop
        -- metric: count of instances living on N1 failing nodes
296 c3c7a0c1 Iustin Pop
        n1_score = fromIntegral . sum . map (\n -> length (Node.sList n) +
297 c3c7a0c1 Iustin Pop
                                                   length (Node.pList n)) .
298 c3c7a0c1 Iustin Pop
                   filter Node.failN1 $ nodes :: Double
299 2060348b Iustin Pop
        res_l = map Node.pRem nodes
300 daee4bed Iustin Pop
        -- metric: reserved memory covariance
301 4715711d Iustin Pop
        res_cv = stdDev res_l
302 e4d31268 Iustin Pop
        -- offline instances metrics
303 e4d31268 Iustin Pop
        offline_ipri = sum . map (length . Node.pList) $ offline
304 e4d31268 Iustin Pop
        offline_isec = sum . map (length . Node.sList) $ offline
305 e4d31268 Iustin Pop
        -- metric: count of instances on offline nodes
306 e4d31268 Iustin Pop
        off_score = fromIntegral (offline_ipri + offline_isec)::Double
307 673f0f00 Iustin Pop
        -- metric: count of primary instances on offline nodes (this
308 673f0f00 Iustin Pop
        -- helps with evacuation/failover of primary instances on
309 673f0f00 Iustin Pop
        -- 2-node clusters with one node offline)
310 673f0f00 Iustin Pop
        off_pri_score = fromIntegral offline_ipri::Double
311 2060348b Iustin Pop
        cpu_l = map Node.pCpu nodes
312 daee4bed Iustin Pop
        -- metric: covariance of vcpu/pcpu ratio
313 4715711d Iustin Pop
        cpu_cv = stdDev cpu_l
314 daee4bed Iustin Pop
        -- metrics: covariance of cpu, memory, disk and network load
315 ee9724b9 Iustin Pop
        (c_load, m_load, d_load, n_load) = unzip4 $
316 ee9724b9 Iustin Pop
            map (\n ->
317 ee9724b9 Iustin Pop
                     let DynUtil c1 m1 d1 n1 = Node.utilLoad n
318 ee9724b9 Iustin Pop
                         DynUtil c2 m2 d2 n2 = Node.utilPool n
319 ee9724b9 Iustin Pop
                     in (c1/c2, m1/m2, d1/d2, n1/n2)
320 ee9724b9 Iustin Pop
                ) nodes
321 d844fe88 Iustin Pop
        -- metric: conflicting instance count
322 d844fe88 Iustin Pop
        pri_tags_inst = sum $ map Node.conflictingPrimaries nodes
323 d844fe88 Iustin Pop
        pri_tags_score = fromIntegral pri_tags_inst::Double
324 673f0f00 Iustin Pop
    in [ mem_cv, dsk_cv, n1_score, res_cv, off_score, off_pri_score, cpu_cv
325 4715711d Iustin Pop
       , stdDev c_load, stdDev m_load , stdDev d_load, stdDev n_load
326 d844fe88 Iustin Pop
       , pri_tags_score ]
327 9188aeef Iustin Pop
328 9188aeef Iustin Pop
-- | Compute the /total/ variance.
329 9bb5721c Iustin Pop
compCVNodes :: [Node.Node] -> Double
330 9bb5721c Iustin Pop
compCVNodes = sum . zipWith (*) detailedCVWeights . compDetailedCV
331 9bb5721c Iustin Pop
332 9bb5721c Iustin Pop
-- | Wrapper over 'compCVNodes' for callers that have a 'Node.List'.
333 9188aeef Iustin Pop
compCV :: Node.List -> Double
334 9bb5721c Iustin Pop
compCV = compCVNodes . Container.elems
335 9bb5721c Iustin Pop
336 9188aeef Iustin Pop
337 525bfb36 Iustin Pop
-- | Compute online nodes from a 'Node.List'.
338 dbba5246 Iustin Pop
getOnline :: Node.List -> [Node.Node]
339 dbba5246 Iustin Pop
getOnline = filter (not . Node.offline) . Container.elems
340 dbba5246 Iustin Pop
341 525bfb36 Iustin Pop
-- * Balancing functions
342 9188aeef Iustin Pop
343 9188aeef Iustin Pop
-- | Compute best table. Note that the ordering of the arguments is important.
344 9188aeef Iustin Pop
compareTables :: Table -> Table -> Table
345 9188aeef Iustin Pop
compareTables a@(Table _ _ a_cv _) b@(Table _ _ b_cv _ ) =
346 9188aeef Iustin Pop
    if a_cv > b_cv then b else a
347 9188aeef Iustin Pop
348 9188aeef Iustin Pop
-- | Applies an instance move to a given node list and instance.
349 262a08a2 Iustin Pop
applyMove :: Node.List -> Instance.Instance
350 8880d889 Iustin Pop
          -> IMove -> OpResult (Node.List, Instance.Instance, Ndx, Ndx)
351 00b51a14 Iustin Pop
-- Failover (f)
352 e4f08c46 Iustin Pop
applyMove nl inst Failover =
353 2060348b Iustin Pop
    let old_pdx = Instance.pNode inst
354 2060348b Iustin Pop
        old_sdx = Instance.sNode inst
355 e4f08c46 Iustin Pop
        old_p = Container.find old_pdx nl
356 e4f08c46 Iustin Pop
        old_s = Container.find old_sdx nl
357 e4f08c46 Iustin Pop
        int_p = Node.removePri old_p inst
358 e4f08c46 Iustin Pop
        int_s = Node.removeSec old_s inst
359 2cae47e9 Iustin Pop
        force_p = Node.offline old_p
360 b161386d Iustin Pop
        new_nl = do -- Maybe monad
361 2cae47e9 Iustin Pop
          new_p <- Node.addPriEx force_p int_s inst
362 b161386d Iustin Pop
          new_s <- Node.addSec int_p inst old_sdx
363 8880d889 Iustin Pop
          let new_inst = Instance.setBoth inst old_sdx old_pdx
364 8880d889 Iustin Pop
          return (Container.addTwo old_pdx new_s old_sdx new_p nl,
365 8880d889 Iustin Pop
                  new_inst, old_sdx, old_pdx)
366 8880d889 Iustin Pop
    in new_nl
367 e4f08c46 Iustin Pop
368 00b51a14 Iustin Pop
-- Replace the primary (f:, r:np, f)
369 e4f08c46 Iustin Pop
applyMove nl inst (ReplacePrimary new_pdx) =
370 2060348b Iustin Pop
    let old_pdx = Instance.pNode inst
371 2060348b Iustin Pop
        old_sdx = Instance.sNode inst
372 e4f08c46 Iustin Pop
        old_p = Container.find old_pdx nl
373 e4f08c46 Iustin Pop
        old_s = Container.find old_sdx nl
374 e4f08c46 Iustin Pop
        tgt_n = Container.find new_pdx nl
375 e4f08c46 Iustin Pop
        int_p = Node.removePri old_p inst
376 e4f08c46 Iustin Pop
        int_s = Node.removeSec old_s inst
377 2cae47e9 Iustin Pop
        force_p = Node.offline old_p
378 b161386d Iustin Pop
        new_nl = do -- Maybe monad
379 70db354e Iustin Pop
          -- check that the current secondary can host the instance
380 70db354e Iustin Pop
          -- during the migration
381 2cae47e9 Iustin Pop
          tmp_s <- Node.addPriEx force_p int_s inst
382 70db354e Iustin Pop
          let tmp_s' = Node.removePri tmp_s inst
383 2cae47e9 Iustin Pop
          new_p <- Node.addPriEx force_p tgt_n inst
384 2cae47e9 Iustin Pop
          new_s <- Node.addSecEx force_p tmp_s' inst new_pdx
385 8880d889 Iustin Pop
          let new_inst = Instance.setPri inst new_pdx
386 8880d889 Iustin Pop
          return (Container.add new_pdx new_p $
387 8880d889 Iustin Pop
                  Container.addTwo old_pdx int_p old_sdx new_s nl,
388 8880d889 Iustin Pop
                  new_inst, new_pdx, old_sdx)
389 8880d889 Iustin Pop
    in new_nl
390 e4f08c46 Iustin Pop
391 00b51a14 Iustin Pop
-- Replace the secondary (r:ns)
392 e4f08c46 Iustin Pop
applyMove nl inst (ReplaceSecondary new_sdx) =
393 2060348b Iustin Pop
    let old_pdx = Instance.pNode inst
394 2060348b Iustin Pop
        old_sdx = Instance.sNode inst
395 e4f08c46 Iustin Pop
        old_s = Container.find old_sdx nl
396 e4f08c46 Iustin Pop
        tgt_n = Container.find new_sdx nl
397 e4f08c46 Iustin Pop
        int_s = Node.removeSec old_s inst
398 2cae47e9 Iustin Pop
        force_s = Node.offline old_s
399 8880d889 Iustin Pop
        new_inst = Instance.setSec inst new_sdx
400 2cae47e9 Iustin Pop
        new_nl = Node.addSecEx force_s tgt_n inst old_pdx >>=
401 8880d889 Iustin Pop
                 \new_s -> return (Container.addTwo new_sdx
402 8880d889 Iustin Pop
                                   new_s old_sdx int_s nl,
403 8880d889 Iustin Pop
                                   new_inst, old_pdx, new_sdx)
404 8880d889 Iustin Pop
    in new_nl
405 e4f08c46 Iustin Pop
406 00b51a14 Iustin Pop
-- Replace the secondary and failover (r:np, f)
407 79ac6b6f Iustin Pop
applyMove nl inst (ReplaceAndFailover new_pdx) =
408 2060348b Iustin Pop
    let old_pdx = Instance.pNode inst
409 2060348b Iustin Pop
        old_sdx = Instance.sNode inst
410 79ac6b6f Iustin Pop
        old_p = Container.find old_pdx nl
411 79ac6b6f Iustin Pop
        old_s = Container.find old_sdx nl
412 79ac6b6f Iustin Pop
        tgt_n = Container.find new_pdx nl
413 79ac6b6f Iustin Pop
        int_p = Node.removePri old_p inst
414 79ac6b6f Iustin Pop
        int_s = Node.removeSec old_s inst
415 2cae47e9 Iustin Pop
        force_s = Node.offline old_s
416 b161386d Iustin Pop
        new_nl = do -- Maybe monad
417 b161386d Iustin Pop
          new_p <- Node.addPri tgt_n inst
418 2cae47e9 Iustin Pop
          new_s <- Node.addSecEx force_s int_p inst new_pdx
419 8880d889 Iustin Pop
          let new_inst = Instance.setBoth inst new_pdx old_pdx
420 8880d889 Iustin Pop
          return (Container.add new_pdx new_p $
421 8880d889 Iustin Pop
                  Container.addTwo old_pdx new_s old_sdx int_s nl,
422 8880d889 Iustin Pop
                  new_inst, new_pdx, old_pdx)
423 8880d889 Iustin Pop
    in new_nl
424 79ac6b6f Iustin Pop
425 19493d33 Iustin Pop
-- Failver and replace the secondary (f, r:ns)
426 19493d33 Iustin Pop
applyMove nl inst (FailoverAndReplace new_sdx) =
427 2060348b Iustin Pop
    let old_pdx = Instance.pNode inst
428 2060348b Iustin Pop
        old_sdx = Instance.sNode inst
429 19493d33 Iustin Pop
        old_p = Container.find old_pdx nl
430 19493d33 Iustin Pop
        old_s = Container.find old_sdx nl
431 19493d33 Iustin Pop
        tgt_n = Container.find new_sdx nl
432 19493d33 Iustin Pop
        int_p = Node.removePri old_p inst
433 19493d33 Iustin Pop
        int_s = Node.removeSec old_s inst
434 2cae47e9 Iustin Pop
        force_p = Node.offline old_p
435 b161386d Iustin Pop
        new_nl = do -- Maybe monad
436 2cae47e9 Iustin Pop
          new_p <- Node.addPriEx force_p int_s inst
437 2cae47e9 Iustin Pop
          new_s <- Node.addSecEx force_p tgt_n inst old_sdx
438 8880d889 Iustin Pop
          let new_inst = Instance.setBoth inst old_sdx new_sdx
439 8880d889 Iustin Pop
          return (Container.add new_sdx new_s $
440 8880d889 Iustin Pop
                  Container.addTwo old_sdx new_p old_pdx int_p nl,
441 8880d889 Iustin Pop
                  new_inst, old_sdx, new_sdx)
442 8880d889 Iustin Pop
    in new_nl
443 19493d33 Iustin Pop
444 9188aeef Iustin Pop
-- | Tries to allocate an instance on one given node.
445 0d66ea67 Iustin Pop
allocateOnSingle :: Node.List -> Instance.Instance -> Ndx
446 1fe81531 Iustin Pop
                 -> OpResult Node.AllocElement
447 0d66ea67 Iustin Pop
allocateOnSingle nl inst new_pdx =
448 0d66ea67 Iustin Pop
    let p = Container.find new_pdx nl
449 8880d889 Iustin Pop
        new_inst = Instance.setBoth inst new_pdx Node.noSecondary
450 7d3f4253 Iustin Pop
    in  Node.addPri p inst >>= \new_p -> do
451 7d3f4253 Iustin Pop
      let new_nl = Container.add new_pdx new_p nl
452 7d3f4253 Iustin Pop
          new_score = compCV nl
453 7d3f4253 Iustin Pop
      return (new_nl, new_inst, [new_p], new_score)
454 5e15f460 Iustin Pop
455 9188aeef Iustin Pop
-- | Tries to allocate an instance on a given pair of nodes.
456 0d66ea67 Iustin Pop
allocateOnPair :: Node.List -> Instance.Instance -> Ndx -> Ndx
457 1fe81531 Iustin Pop
               -> OpResult Node.AllocElement
458 0d66ea67 Iustin Pop
allocateOnPair nl inst new_pdx new_sdx =
459 0d66ea67 Iustin Pop
    let tgt_p = Container.find new_pdx nl
460 0d66ea67 Iustin Pop
        tgt_s = Container.find new_sdx nl
461 7d3f4253 Iustin Pop
    in do
462 7d3f4253 Iustin Pop
      new_p <- Node.addPri tgt_p inst
463 7d3f4253 Iustin Pop
      new_s <- Node.addSec tgt_s inst new_pdx
464 7d3f4253 Iustin Pop
      let new_inst = Instance.setBoth inst new_pdx new_sdx
465 7d3f4253 Iustin Pop
          new_nl = Container.addTwo new_pdx new_p new_sdx new_s nl
466 7d3f4253 Iustin Pop
      return (new_nl, new_inst, [new_p, new_s], compCV new_nl)
467 4a340313 Iustin Pop
468 9188aeef Iustin Pop
-- | Tries to perform an instance move and returns the best table
469 9188aeef Iustin Pop
-- between the original one and the new one.
470 e4f08c46 Iustin Pop
checkSingleStep :: Table -- ^ The original table
471 e4f08c46 Iustin Pop
                -> Instance.Instance -- ^ The instance to move
472 e4f08c46 Iustin Pop
                -> Table -- ^ The current best table
473 e4f08c46 Iustin Pop
                -> IMove -- ^ The move to apply
474 e4f08c46 Iustin Pop
                -> Table -- ^ The final best table
475 e4f08c46 Iustin Pop
checkSingleStep ini_tbl target cur_tbl move =
476 e4f08c46 Iustin Pop
    let
477 e4f08c46 Iustin Pop
        Table ini_nl ini_il _ ini_plc = ini_tbl
478 8880d889 Iustin Pop
        tmp_resu = applyMove ini_nl target move
479 e4f08c46 Iustin Pop
    in
480 8880d889 Iustin Pop
      case tmp_resu of
481 f2280553 Iustin Pop
        OpFail _ -> cur_tbl
482 3173c987 Iustin Pop
        OpGood (upd_nl, new_inst, pri_idx, sec_idx) ->
483 f2280553 Iustin Pop
            let tgt_idx = Instance.idx target
484 f2280553 Iustin Pop
                upd_cvar = compCV upd_nl
485 f2280553 Iustin Pop
                upd_il = Container.add tgt_idx new_inst ini_il
486 3173c987 Iustin Pop
                upd_plc = (tgt_idx, pri_idx, sec_idx, move, upd_cvar):ini_plc
487 f2280553 Iustin Pop
                upd_tbl = Table upd_nl upd_il upd_cvar upd_plc
488 f2280553 Iustin Pop
            in
489 f2280553 Iustin Pop
              compareTables cur_tbl upd_tbl
490 e4f08c46 Iustin Pop
491 c0501c69 Iustin Pop
-- | Given the status of the current secondary as a valid new node and
492 c0501c69 Iustin Pop
-- the current candidate target node, generate the possible moves for
493 c0501c69 Iustin Pop
-- a instance.
494 c0501c69 Iustin Pop
possibleMoves :: Bool      -- ^ Whether the secondary node is a valid new node
495 e08424a8 Guido Trotter
              -> Bool      -- ^ Whether we can change the primary node
496 c0501c69 Iustin Pop
              -> Ndx       -- ^ Target node candidate
497 c0501c69 Iustin Pop
              -> [IMove]   -- ^ List of valid result moves
498 e08424a8 Guido Trotter
499 e08424a8 Guido Trotter
possibleMoves _ False tdx =
500 e08424a8 Guido Trotter
    [ReplaceSecondary tdx]
501 e08424a8 Guido Trotter
502 e08424a8 Guido Trotter
possibleMoves True True tdx =
503 40d4eba0 Iustin Pop
    [ReplaceSecondary tdx,
504 40d4eba0 Iustin Pop
     ReplaceAndFailover tdx,
505 40d4eba0 Iustin Pop
     ReplacePrimary tdx,
506 40d4eba0 Iustin Pop
     FailoverAndReplace tdx]
507 40d4eba0 Iustin Pop
508 e08424a8 Guido Trotter
possibleMoves False True tdx =
509 40d4eba0 Iustin Pop
    [ReplaceSecondary tdx,
510 40d4eba0 Iustin Pop
     ReplaceAndFailover tdx]
511 40d4eba0 Iustin Pop
512 40d4eba0 Iustin Pop
-- | Compute the best move for a given instance.
513 c0501c69 Iustin Pop
checkInstanceMove :: [Ndx]             -- ^ Allowed target node indices
514 c0501c69 Iustin Pop
                  -> Bool              -- ^ Whether disk moves are allowed
515 e08424a8 Guido Trotter
                  -> Bool              -- ^ Whether instance moves are allowed
516 c0501c69 Iustin Pop
                  -> Table             -- ^ Original table
517 c0501c69 Iustin Pop
                  -> Instance.Instance -- ^ Instance to move
518 c0501c69 Iustin Pop
                  -> Table             -- ^ Best new table for this instance
519 e08424a8 Guido Trotter
checkInstanceMove nodes_idx disk_moves inst_moves ini_tbl target =
520 4e25d1c2 Iustin Pop
    let
521 2060348b Iustin Pop
        opdx = Instance.pNode target
522 2060348b Iustin Pop
        osdx = Instance.sNode target
523 9dc6023f Iustin Pop
        nodes = filter (\idx -> idx /= opdx && idx /= osdx) nodes_idx
524 e08424a8 Guido Trotter
        use_secondary = elem osdx nodes_idx && inst_moves
525 40d4eba0 Iustin Pop
        aft_failover = if use_secondary -- if allowed to failover
526 40d4eba0 Iustin Pop
                       then checkSingleStep ini_tbl target ini_tbl Failover
527 40d4eba0 Iustin Pop
                       else ini_tbl
528 c0501c69 Iustin Pop
        all_moves = if disk_moves
529 e08424a8 Guido Trotter
                    then concatMap
530 e08424a8 Guido Trotter
                         (possibleMoves use_secondary inst_moves) nodes
531 c0501c69 Iustin Pop
                    else []
532 4e25d1c2 Iustin Pop
    in
533 4e25d1c2 Iustin Pop
      -- iterate over the possible nodes for this instance
534 9dc6023f Iustin Pop
      foldl' (checkSingleStep ini_tbl target) aft_failover all_moves
535 4e25d1c2 Iustin Pop
536 e4f08c46 Iustin Pop
-- | Compute the best next move.
537 608efcce Iustin Pop
checkMove :: [Ndx]               -- ^ Allowed target node indices
538 c0501c69 Iustin Pop
          -> Bool                -- ^ Whether disk moves are allowed
539 e08424a8 Guido Trotter
          -> Bool                -- ^ Whether instance moves are allowed
540 256810de Iustin Pop
          -> Table               -- ^ The current solution
541 e4f08c46 Iustin Pop
          -> [Instance.Instance] -- ^ List of instances still to move
542 256810de Iustin Pop
          -> Table               -- ^ The new solution
543 e08424a8 Guido Trotter
checkMove nodes_idx disk_moves inst_moves ini_tbl victims =
544 4e25d1c2 Iustin Pop
    let Table _ _ _ ini_plc = ini_tbl
545 a3eee4ad Iustin Pop
        -- we're using rwhnf from the Control.Parallel.Strategies
546 a3eee4ad Iustin Pop
        -- package; we don't need to use rnf as that would force too
547 a3eee4ad Iustin Pop
        -- much evaluation in single-threaded cases, and in
548 a3eee4ad Iustin Pop
        -- multi-threaded case the weak head normal form is enough to
549 a3eee4ad Iustin Pop
        -- spark the evaluation
550 e08424a8 Guido Trotter
        tables = parMap rwhnf (checkInstanceMove nodes_idx disk_moves
551 e08424a8 Guido Trotter
                               inst_moves ini_tbl)
552 a3eee4ad Iustin Pop
                 victims
553 4e25d1c2 Iustin Pop
        -- iterate over all instances, computing the best move
554 2a8e2dc9 Iustin Pop
        best_tbl = foldl' compareTables ini_tbl tables
555 aaaa0e43 Iustin Pop
        Table _ _ _ best_plc = best_tbl
556 a804261a Iustin Pop
    in if length best_plc == length ini_plc
557 a804261a Iustin Pop
       then ini_tbl -- no advancement
558 a804261a Iustin Pop
       else best_tbl
559 e4f08c46 Iustin Pop
560 525bfb36 Iustin Pop
-- | Check if we are allowed to go deeper in the balancing.
561 3fea6959 Iustin Pop
doNextBalance :: Table     -- ^ The starting table
562 3fea6959 Iustin Pop
              -> Int       -- ^ Remaining length
563 3fea6959 Iustin Pop
              -> Score     -- ^ Score at which to stop
564 3fea6959 Iustin Pop
              -> Bool      -- ^ The resulting table and commands
565 5ad86777 Iustin Pop
doNextBalance ini_tbl max_rounds min_score =
566 5ad86777 Iustin Pop
    let Table _ _ ini_cv ini_plc = ini_tbl
567 5ad86777 Iustin Pop
        ini_plc_len = length ini_plc
568 5ad86777 Iustin Pop
    in (max_rounds < 0 || ini_plc_len < max_rounds) && ini_cv > min_score
569 5ad86777 Iustin Pop
570 525bfb36 Iustin Pop
-- | Run a balance move.
571 f25e5aac Iustin Pop
tryBalance :: Table       -- ^ The starting table
572 f25e5aac Iustin Pop
           -> Bool        -- ^ Allow disk moves
573 e08424a8 Guido Trotter
           -> Bool        -- ^ Allow instance moves
574 2e28ac32 Iustin Pop
           -> Bool        -- ^ Only evacuate moves
575 848b65c9 Iustin Pop
           -> Score       -- ^ Min gain threshold
576 848b65c9 Iustin Pop
           -> Score       -- ^ Min gain
577 f25e5aac Iustin Pop
           -> Maybe Table -- ^ The resulting table and commands
578 e08424a8 Guido Trotter
tryBalance ini_tbl disk_moves inst_moves evac_mode mg_limit min_gain =
579 5ad86777 Iustin Pop
    let Table ini_nl ini_il ini_cv _ = ini_tbl
580 5ad86777 Iustin Pop
        all_inst = Container.elems ini_il
581 2e28ac32 Iustin Pop
        all_inst' = if evac_mode
582 2e28ac32 Iustin Pop
                    then let bad_nodes = map Node.idx . filter Node.offline $
583 2e28ac32 Iustin Pop
                                         Container.elems ini_nl
584 2e28ac32 Iustin Pop
                         in filter (\e -> Instance.sNode e `elem` bad_nodes ||
585 2e28ac32 Iustin Pop
                                          Instance.pNode e `elem` bad_nodes)
586 2e28ac32 Iustin Pop
                            all_inst
587 2e28ac32 Iustin Pop
                    else all_inst
588 c424cdc8 Iustin Pop
        reloc_inst = filter Instance.movable all_inst'
589 5ad86777 Iustin Pop
        node_idx = map Node.idx . filter (not . Node.offline) $
590 5ad86777 Iustin Pop
                   Container.elems ini_nl
591 e08424a8 Guido Trotter
        fin_tbl = checkMove node_idx disk_moves inst_moves ini_tbl reloc_inst
592 5ad86777 Iustin Pop
        (Table _ _ fin_cv _) = fin_tbl
593 f25e5aac Iustin Pop
    in
594 848b65c9 Iustin Pop
      if fin_cv < ini_cv && (ini_cv > mg_limit || ini_cv - fin_cv >= min_gain)
595 5ad86777 Iustin Pop
      then Just fin_tbl -- this round made success, return the new table
596 f25e5aac Iustin Pop
      else Nothing
597 f25e5aac Iustin Pop
598 478df686 Iustin Pop
-- * Allocation functions
599 478df686 Iustin Pop
600 525bfb36 Iustin Pop
-- | Build failure stats out of a list of failures.
601 478df686 Iustin Pop
collapseFailures :: [FailMode] -> FailStats
602 478df686 Iustin Pop
collapseFailures flst =
603 b4bae394 Iustin Pop
    map (\k -> (k, foldl' (\a e -> if e == k then a + 1 else a) 0 flst))
604 b4bae394 Iustin Pop
            [minBound..maxBound]
605 478df686 Iustin Pop
606 478df686 Iustin Pop
-- | Update current Allocation solution and failure stats with new
607 525bfb36 Iustin Pop
-- elements.
608 1fe81531 Iustin Pop
concatAllocs :: AllocSolution -> OpResult Node.AllocElement -> AllocSolution
609 85d0ddc3 Iustin Pop
concatAllocs as (OpFail reason) = as { asFailures = reason : asFailures as }
610 478df686 Iustin Pop
611 85d0ddc3 Iustin Pop
concatAllocs as (OpGood ns@(_, _, _, nscore)) =
612 7d3f4253 Iustin Pop
    let -- Choose the old or new solution, based on the cluster score
613 85d0ddc3 Iustin Pop
        cntok = asAllocs as
614 85d0ddc3 Iustin Pop
        osols = asSolutions as
615 478df686 Iustin Pop
        nsols = case osols of
616 a334d536 Iustin Pop
                  [] -> [ns]
617 a334d536 Iustin Pop
                  (_, _, _, oscore):[] ->
618 478df686 Iustin Pop
                      if oscore < nscore
619 478df686 Iustin Pop
                      then osols
620 a334d536 Iustin Pop
                      else [ns]
621 23f9ab76 Iustin Pop
                  -- FIXME: here we simply concat to lists with more
622 23f9ab76 Iustin Pop
                  -- than one element; we should instead abort, since
623 23f9ab76 Iustin Pop
                  -- this is not a valid usage of this function
624 a334d536 Iustin Pop
                  xs -> ns:xs
625 fbb95f28 Iustin Pop
        nsuc = cntok + 1
626 478df686 Iustin Pop
    -- Note: we force evaluation of nsols here in order to keep the
627 478df686 Iustin Pop
    -- memory profile low - we know that we will need nsols for sure
628 478df686 Iustin Pop
    -- in the next cycle, so we force evaluation of nsols, since the
629 478df686 Iustin Pop
    -- foldl' in the caller will only evaluate the tuple, but not the
630 7d11799b Iustin Pop
    -- elements of the tuple
631 85d0ddc3 Iustin Pop
    in nsols `seq` nsuc `seq` as { asAllocs = nsuc, asSolutions = nsols }
632 dbba5246 Iustin Pop
633 525bfb36 Iustin Pop
-- | Given a solution, generates a reasonable description for it.
634 859fc11d Iustin Pop
describeSolution :: AllocSolution -> String
635 859fc11d Iustin Pop
describeSolution as =
636 859fc11d Iustin Pop
  let fcnt = asFailures as
637 859fc11d Iustin Pop
      sols = asSolutions as
638 859fc11d Iustin Pop
      freasons =
639 859fc11d Iustin Pop
        intercalate ", " . map (\(a, b) -> printf "%s: %d" (show a) b) .
640 859fc11d Iustin Pop
        filter ((> 0) . snd) . collapseFailures $ fcnt
641 859fc11d Iustin Pop
  in if null sols
642 859fc11d Iustin Pop
     then "No valid allocation solutions, failure reasons: " ++
643 859fc11d Iustin Pop
          (if null fcnt
644 859fc11d Iustin Pop
           then "unknown reasons"
645 859fc11d Iustin Pop
           else freasons)
646 859fc11d Iustin Pop
     else let (_, _, nodes, cv) = head sols
647 859fc11d Iustin Pop
          in printf ("score: %.8f, successes %d, failures %d (%s)" ++
648 859fc11d Iustin Pop
                     " for node(s) %s") cv (asAllocs as) (length fcnt) freasons
649 859fc11d Iustin Pop
             (intercalate "/" . map Node.name $ nodes)
650 859fc11d Iustin Pop
651 525bfb36 Iustin Pop
-- | Annotates a solution with the appropriate string.
652 859fc11d Iustin Pop
annotateSolution :: AllocSolution -> AllocSolution
653 859fc11d Iustin Pop
annotateSolution as = as { asLog = describeSolution as : asLog as }
654 859fc11d Iustin Pop
655 47eed3f4 Iustin Pop
-- | Reverses an evacuation solution.
656 47eed3f4 Iustin Pop
--
657 47eed3f4 Iustin Pop
-- Rationale: we always concat the results to the top of the lists, so
658 47eed3f4 Iustin Pop
-- for proper jobset execution, we should reverse all lists.
659 47eed3f4 Iustin Pop
reverseEvacSolution :: EvacSolution -> EvacSolution
660 47eed3f4 Iustin Pop
reverseEvacSolution (EvacSolution f m o) =
661 47eed3f4 Iustin Pop
    EvacSolution (reverse f) (reverse m) (reverse o)
662 47eed3f4 Iustin Pop
663 6cb1649f Iustin Pop
-- | Generate the valid node allocation singles or pairs for a new instance.
664 6d0bc5ca Iustin Pop
genAllocNodes :: Group.List        -- ^ Group list
665 6d0bc5ca Iustin Pop
              -> Node.List         -- ^ The node map
666 6cb1649f Iustin Pop
              -> Int               -- ^ The number of nodes required
667 6d0bc5ca Iustin Pop
              -> Bool              -- ^ Whether to drop or not
668 6d0bc5ca Iustin Pop
                                   -- unallocable nodes
669 6cb1649f Iustin Pop
              -> Result AllocNodes -- ^ The (monadic) result
670 6d0bc5ca Iustin Pop
genAllocNodes gl nl count drop_unalloc =
671 6d0bc5ca Iustin Pop
    let filter_fn = if drop_unalloc
672 e4491427 Iustin Pop
                    then filter (Group.isAllocable .
673 e4491427 Iustin Pop
                                 flip Container.find gl . Node.group)
674 6d0bc5ca Iustin Pop
                    else id
675 6d0bc5ca Iustin Pop
        all_nodes = filter_fn $ getOnline nl
676 6cb1649f Iustin Pop
        all_pairs = liftM2 (,) all_nodes all_nodes
677 6cb1649f Iustin Pop
        ok_pairs = filter (\(x, y) -> Node.idx x /= Node.idx y &&
678 6cb1649f Iustin Pop
                                      Node.group x == Node.group y) all_pairs
679 6cb1649f Iustin Pop
    in case count of
680 0d66ea67 Iustin Pop
         1 -> Ok (Left (map Node.idx all_nodes))
681 0d66ea67 Iustin Pop
         2 -> Ok (Right (map (\(p, s) -> (Node.idx p, Node.idx s)) ok_pairs))
682 6cb1649f Iustin Pop
         _ -> Bad "Unsupported number of nodes, only one or two  supported"
683 6cb1649f Iustin Pop
684 dbba5246 Iustin Pop
-- | Try to allocate an instance on the cluster.
685 dbba5246 Iustin Pop
tryAlloc :: (Monad m) =>
686 dbba5246 Iustin Pop
            Node.List         -- ^ The node list
687 dbba5246 Iustin Pop
         -> Instance.List     -- ^ The instance list
688 dbba5246 Iustin Pop
         -> Instance.Instance -- ^ The instance to allocate
689 6cb1649f Iustin Pop
         -> AllocNodes        -- ^ The allocation targets
690 78694255 Iustin Pop
         -> m AllocSolution   -- ^ Possible solution list
691 6cb1649f Iustin Pop
tryAlloc nl _ inst (Right ok_pairs) =
692 6cb1649f Iustin Pop
    let sols = foldl' (\cstate (p, s) ->
693 478df686 Iustin Pop
                           concatAllocs cstate $ allocateOnPair nl inst p s
694 97936d51 Iustin Pop
                      ) emptyAllocSolution ok_pairs
695 859fc11d Iustin Pop
696 dec88196 Iustin Pop
    in if null ok_pairs -- means we have just one node
697 dec88196 Iustin Pop
       then fail "Not enough online nodes"
698 dec88196 Iustin Pop
       else return $ annotateSolution sols
699 dbba5246 Iustin Pop
700 6cb1649f Iustin Pop
tryAlloc nl _ inst (Left all_nodes) =
701 6cb1649f Iustin Pop
    let sols = foldl' (\cstate ->
702 2485487d Iustin Pop
                           concatAllocs cstate . allocateOnSingle nl inst
703 97936d51 Iustin Pop
                      ) emptyAllocSolution all_nodes
704 dec88196 Iustin Pop
    in if null all_nodes
705 dec88196 Iustin Pop
       then fail "No online nodes"
706 dec88196 Iustin Pop
       else return $ annotateSolution sols
707 dbba5246 Iustin Pop
708 525bfb36 Iustin Pop
-- | Given a group/result, describe it as a nice (list of) messages.
709 aec636b9 Iustin Pop
solutionDescription :: Group.List -> (Gdx, Result AllocSolution) -> [String]
710 aec636b9 Iustin Pop
solutionDescription gl (groupId, result) =
711 9b1584fc Iustin Pop
  case result of
712 73206d0a Iustin Pop
    Ok solution -> map (printf "Group %s (%s): %s" gname pol) (asLog solution)
713 aec636b9 Iustin Pop
    Bad message -> [printf "Group %s: error %s" gname message]
714 73206d0a Iustin Pop
  where grp = Container.find groupId gl
715 73206d0a Iustin Pop
        gname = Group.name grp
716 73206d0a Iustin Pop
        pol = apolToString (Group.allocPolicy grp)
717 9b1584fc Iustin Pop
718 9b1584fc Iustin Pop
-- | From a list of possibly bad and possibly empty solutions, filter
719 88253d03 Iustin Pop
-- only the groups with a valid result. Note that the result will be
720 525bfb36 Iustin Pop
-- reversed compared to the original list.
721 73206d0a Iustin Pop
filterMGResults :: Group.List
722 73206d0a Iustin Pop
                -> [(Gdx, Result AllocSolution)]
723 73206d0a Iustin Pop
                -> [(Gdx, AllocSolution)]
724 88253d03 Iustin Pop
filterMGResults gl = foldl' fn []
725 88253d03 Iustin Pop
    where unallocable = not . Group.isAllocable . flip Container.find gl
726 88253d03 Iustin Pop
          fn accu (gdx, rasol) =
727 88253d03 Iustin Pop
              case rasol of
728 88253d03 Iustin Pop
                Bad _ -> accu
729 88253d03 Iustin Pop
                Ok sol | null (asSolutions sol) -> accu
730 88253d03 Iustin Pop
                       | unallocable gdx -> accu
731 88253d03 Iustin Pop
                       | otherwise -> (gdx, sol):accu
732 9b1584fc Iustin Pop
733 525bfb36 Iustin Pop
-- | Sort multigroup results based on policy and score.
734 73206d0a Iustin Pop
sortMGResults :: Group.List
735 73206d0a Iustin Pop
             -> [(Gdx, AllocSolution)]
736 73206d0a Iustin Pop
             -> [(Gdx, AllocSolution)]
737 73206d0a Iustin Pop
sortMGResults gl sols =
738 2a8e2dc9 Iustin Pop
    let extractScore (_, _, _, x) = x
739 73206d0a Iustin Pop
        solScore (gdx, sol) = (Group.allocPolicy (Container.find gdx gl),
740 73206d0a Iustin Pop
                               (extractScore . head . asSolutions) sol)
741 73206d0a Iustin Pop
    in sortBy (comparing solScore) sols
742 73206d0a Iustin Pop
743 8fd09137 Iustin Pop
-- | Finds the best group for an instance on a multi-group cluster.
744 d72ff6c3 Iustin Pop
--
745 d72ff6c3 Iustin Pop
-- Only solutions in @preferred@ and @last_resort@ groups will be
746 d72ff6c3 Iustin Pop
-- accepted as valid, and additionally if the allowed groups parameter
747 d72ff6c3 Iustin Pop
-- is not null then allocation will only be run for those group
748 d72ff6c3 Iustin Pop
-- indices.
749 8fd09137 Iustin Pop
findBestAllocGroup :: Group.List           -- ^ The group list
750 8fd09137 Iustin Pop
                   -> Node.List            -- ^ The node list
751 8fd09137 Iustin Pop
                   -> Instance.List        -- ^ The instance list
752 d72ff6c3 Iustin Pop
                   -> Maybe [Gdx]          -- ^ The allowed groups
753 8fd09137 Iustin Pop
                   -> Instance.Instance    -- ^ The instance to allocate
754 8fd09137 Iustin Pop
                   -> Int                  -- ^ Required number of nodes
755 8fd09137 Iustin Pop
                   -> Result (Gdx, AllocSolution, [String])
756 d72ff6c3 Iustin Pop
findBestAllocGroup mggl mgnl mgil allowed_gdxs inst cnt =
757 9b1584fc Iustin Pop
  let groups = splitCluster mgnl mgil
758 d72ff6c3 Iustin Pop
      groups' = maybe groups (\gs -> filter ((`elem` gs) . fst) groups)
759 d72ff6c3 Iustin Pop
                allowed_gdxs
760 9b1584fc Iustin Pop
      sols = map (\(gid, (nl, il)) ->
761 6d0bc5ca Iustin Pop
                   (gid, genAllocNodes mggl nl cnt False >>=
762 6d0bc5ca Iustin Pop
                       tryAlloc nl il inst))
763 d72ff6c3 Iustin Pop
             groups'::[(Gdx, Result AllocSolution)]
764 aec636b9 Iustin Pop
      all_msgs = concatMap (solutionDescription mggl) sols
765 73206d0a Iustin Pop
      goodSols = filterMGResults mggl sols
766 73206d0a Iustin Pop
      sortedSols = sortMGResults mggl goodSols
767 9b1584fc Iustin Pop
  in if null sortedSols
768 9b1584fc Iustin Pop
     then Bad $ intercalate ", " all_msgs
769 9b1584fc Iustin Pop
     else let (final_group, final_sol) = head sortedSols
770 8fd09137 Iustin Pop
          in return (final_group, final_sol, all_msgs)
771 8fd09137 Iustin Pop
772 8fd09137 Iustin Pop
-- | Try to allocate an instance on a multi-group cluster.
773 8fd09137 Iustin Pop
tryMGAlloc :: Group.List           -- ^ The group list
774 8fd09137 Iustin Pop
           -> Node.List            -- ^ The node list
775 8fd09137 Iustin Pop
           -> Instance.List        -- ^ The instance list
776 8fd09137 Iustin Pop
           -> Instance.Instance    -- ^ The instance to allocate
777 8fd09137 Iustin Pop
           -> Int                  -- ^ Required number of nodes
778 8fd09137 Iustin Pop
           -> Result AllocSolution -- ^ Possible solution list
779 8fd09137 Iustin Pop
tryMGAlloc mggl mgnl mgil inst cnt = do
780 8fd09137 Iustin Pop
  (best_group, solution, all_msgs) <-
781 d72ff6c3 Iustin Pop
      findBestAllocGroup mggl mgnl mgil Nothing inst cnt
782 8fd09137 Iustin Pop
  let group_name = Group.name $ Container.find best_group mggl
783 8fd09137 Iustin Pop
      selmsg = "Selected group: " ++ group_name
784 8fd09137 Iustin Pop
  return $ solution { asLog = selmsg:all_msgs }
785 9b1584fc Iustin Pop
786 9b1584fc Iustin Pop
-- | Try to relocate an instance on the cluster.
787 dbba5246 Iustin Pop
tryReloc :: (Monad m) =>
788 78694255 Iustin Pop
            Node.List       -- ^ The node list
789 78694255 Iustin Pop
         -> Instance.List   -- ^ The instance list
790 78694255 Iustin Pop
         -> Idx             -- ^ The index of the instance to move
791 478df686 Iustin Pop
         -> Int             -- ^ The number of nodes required
792 78694255 Iustin Pop
         -> [Ndx]           -- ^ Nodes which should not be used
793 78694255 Iustin Pop
         -> m AllocSolution -- ^ Solution list
794 dbba5246 Iustin Pop
tryReloc nl il xid 1 ex_idx =
795 dbba5246 Iustin Pop
    let all_nodes = getOnline nl
796 dbba5246 Iustin Pop
        inst = Container.find xid il
797 2060348b Iustin Pop
        ex_idx' = Instance.pNode inst:ex_idx
798 dbba5246 Iustin Pop
        valid_nodes = filter (not . flip elem ex_idx' . Node.idx) all_nodes
799 dbba5246 Iustin Pop
        valid_idxes = map Node.idx valid_nodes
800 478df686 Iustin Pop
        sols1 = foldl' (\cstate x ->
801 fbb95f28 Iustin Pop
                            let em = do
802 478df686 Iustin Pop
                                  (mnl, i, _, _) <-
803 478df686 Iustin Pop
                                      applyMove nl inst (ReplaceSecondary x)
804 7d3f4253 Iustin Pop
                                  return (mnl, i, [Container.find x mnl],
805 7d3f4253 Iustin Pop
                                          compCV mnl)
806 fbb95f28 Iustin Pop
                            in concatAllocs cstate em
807 97936d51 Iustin Pop
                       ) emptyAllocSolution valid_idxes
808 dbba5246 Iustin Pop
    in return sols1
809 dbba5246 Iustin Pop
810 dbba5246 Iustin Pop
tryReloc _ _ _ reqn _  = fail $ "Unsupported number of relocation \
811 9f6dcdea Iustin Pop
                                \destinations required (" ++ show reqn ++
812 dbba5246 Iustin Pop
                                                  "), only one supported"
813 e4f08c46 Iustin Pop
814 525bfb36 Iustin Pop
-- | Change an instance's secondary node.
815 2ca68e2b Iustin Pop
evacInstance :: (Monad m) =>
816 2ca68e2b Iustin Pop
                [Ndx]                      -- ^ Excluded nodes
817 2ca68e2b Iustin Pop
             -> Instance.List              -- ^ The current instance list
818 2ca68e2b Iustin Pop
             -> (Node.List, AllocSolution) -- ^ The current state
819 2ca68e2b Iustin Pop
             -> Idx                        -- ^ The instance to evacuate
820 2ca68e2b Iustin Pop
             -> m (Node.List, AllocSolution)
821 2ca68e2b Iustin Pop
evacInstance ex_ndx il (nl, old_as) idx = do
822 2ca68e2b Iustin Pop
  -- FIXME: hardcoded one node here
823 2ca68e2b Iustin Pop
824 2ca68e2b Iustin Pop
  -- Longer explanation: evacuation is currently hardcoded to DRBD
825 2ca68e2b Iustin Pop
  -- instances (which have one secondary); hence, even if the
826 2ca68e2b Iustin Pop
  -- IAllocator protocol can request N nodes for an instance, and all
827 2ca68e2b Iustin Pop
  -- the message parsing/loading pass this, this implementation only
828 2ca68e2b Iustin Pop
  -- supports one; this situation needs to be revisited if we ever
829 2ca68e2b Iustin Pop
  -- support more than one secondary, or if we change the storage
830 2ca68e2b Iustin Pop
  -- model
831 2ca68e2b Iustin Pop
  new_as <- tryReloc nl il idx 1 ex_ndx
832 2ca68e2b Iustin Pop
  case asSolutions new_as of
833 2ca68e2b Iustin Pop
    -- an individual relocation succeeded, we kind of compose the data
834 2ca68e2b Iustin Pop
    -- from the two solutions
835 2ca68e2b Iustin Pop
    csol@(nl', _, _, _):_ ->
836 2ca68e2b Iustin Pop
        return (nl', new_as { asSolutions = csol:asSolutions old_as })
837 2ca68e2b Iustin Pop
    -- this relocation failed, so we fail the entire evac
838 2ca68e2b Iustin Pop
    _ -> fail $ "Can't evacuate instance " ++
839 2ca68e2b Iustin Pop
         Instance.name (Container.find idx il) ++
840 2ca68e2b Iustin Pop
             ": " ++ describeSolution new_as
841 2ca68e2b Iustin Pop
842 3fea6959 Iustin Pop
-- | Try to evacuate a list of nodes.
843 12b0511d Iustin Pop
tryEvac :: (Monad m) =>
844 12b0511d Iustin Pop
            Node.List       -- ^ The node list
845 12b0511d Iustin Pop
         -> Instance.List   -- ^ The instance list
846 1bc47d38 Iustin Pop
         -> [Idx]           -- ^ Instances to be evacuated
847 1bc47d38 Iustin Pop
         -> [Ndx]           -- ^ Restricted nodes (the ones being evacuated)
848 12b0511d Iustin Pop
         -> m AllocSolution -- ^ Solution list
849 1bc47d38 Iustin Pop
tryEvac nl il idxs ex_ndx = do
850 97936d51 Iustin Pop
  (_, sol) <- foldM (evacInstance ex_ndx il) (nl, emptyAllocSolution) idxs
851 1bc47d38 Iustin Pop
  return sol
852 1bc47d38 Iustin Pop
853 47eed3f4 Iustin Pop
-- | Function which fails if the requested mode is change secondary.
854 47eed3f4 Iustin Pop
--
855 47eed3f4 Iustin Pop
-- This is useful since except DRBD, no other disk template can
856 47eed3f4 Iustin Pop
-- execute change secondary; thus, we can just call this function
857 47eed3f4 Iustin Pop
-- instead of always checking for secondary mode. After the call to
858 47eed3f4 Iustin Pop
-- this function, whatever mode we have is just a primary change.
859 47eed3f4 Iustin Pop
failOnSecondaryChange :: (Monad m) => EvacMode -> DiskTemplate -> m ()
860 47eed3f4 Iustin Pop
failOnSecondaryChange ChangeSecondary dt =
861 47eed3f4 Iustin Pop
    fail $ "Instances with disk template '" ++ dtToString dt ++
862 47eed3f4 Iustin Pop
         "' can't execute change secondary"
863 47eed3f4 Iustin Pop
failOnSecondaryChange _ _ = return ()
864 47eed3f4 Iustin Pop
865 47eed3f4 Iustin Pop
-- | Run evacuation for a single instance.
866 20b376ff Iustin Pop
--
867 20b376ff Iustin Pop
-- /Note:/ this function should correctly execute both intra-group
868 20b376ff Iustin Pop
-- evacuations (in all modes) and inter-group evacuations (in the
869 20b376ff Iustin Pop
-- 'ChangeAll' mode). Of course, this requires that the correct list
870 20b376ff Iustin Pop
-- of target nodes is passed.
871 47eed3f4 Iustin Pop
nodeEvacInstance :: Node.List         -- ^ The node list (cluster-wide)
872 47eed3f4 Iustin Pop
                 -> Instance.List     -- ^ Instance list (cluster-wide)
873 47eed3f4 Iustin Pop
                 -> EvacMode          -- ^ The evacuation mode
874 47eed3f4 Iustin Pop
                 -> Instance.Instance -- ^ The instance to be evacuated
875 a86fbf36 Iustin Pop
                 -> Gdx               -- ^ The group we're targetting
876 47eed3f4 Iustin Pop
                 -> [Ndx]             -- ^ The list of available nodes
877 47eed3f4 Iustin Pop
                                      -- for allocation
878 47eed3f4 Iustin Pop
                 -> Result (Node.List, Instance.List, [OpCodes.OpCode])
879 47eed3f4 Iustin Pop
nodeEvacInstance _ _ mode (Instance.Instance
880 a86fbf36 Iustin Pop
                           {Instance.diskTemplate = dt@DTDiskless}) _ _ =
881 47eed3f4 Iustin Pop
                  failOnSecondaryChange mode dt >>
882 47eed3f4 Iustin Pop
                  fail "Diskless relocations not implemented yet"
883 47eed3f4 Iustin Pop
884 47eed3f4 Iustin Pop
nodeEvacInstance _ _ _ (Instance.Instance
885 a86fbf36 Iustin Pop
                        {Instance.diskTemplate = DTPlain}) _ _ =
886 47eed3f4 Iustin Pop
                  fail "Instances of type plain cannot be relocated"
887 47eed3f4 Iustin Pop
888 47eed3f4 Iustin Pop
nodeEvacInstance _ _ _ (Instance.Instance
889 a86fbf36 Iustin Pop
                        {Instance.diskTemplate = DTFile}) _ _ =
890 47eed3f4 Iustin Pop
                  fail "Instances of type file cannot be relocated"
891 47eed3f4 Iustin Pop
892 47eed3f4 Iustin Pop
nodeEvacInstance _ _ mode  (Instance.Instance
893 a86fbf36 Iustin Pop
                            {Instance.diskTemplate = dt@DTSharedFile}) _ _ =
894 47eed3f4 Iustin Pop
                  failOnSecondaryChange mode dt >>
895 47eed3f4 Iustin Pop
                  fail "Shared file relocations not implemented yet"
896 47eed3f4 Iustin Pop
897 47eed3f4 Iustin Pop
nodeEvacInstance _ _ mode (Instance.Instance
898 a86fbf36 Iustin Pop
                           {Instance.diskTemplate = dt@DTBlock}) _ _ =
899 47eed3f4 Iustin Pop
                  failOnSecondaryChange mode dt >>
900 47eed3f4 Iustin Pop
                  fail "Block device relocations not implemented yet"
901 47eed3f4 Iustin Pop
902 bef83fd1 Iustin Pop
nodeEvacInstance nl il ChangePrimary
903 a86fbf36 Iustin Pop
                 inst@(Instance.Instance {Instance.diskTemplate = DTDrbd8})
904 a86fbf36 Iustin Pop
                 _ _ =
905 bef83fd1 Iustin Pop
  do
906 bef83fd1 Iustin Pop
    (nl', inst', _, _) <- opToResult $ applyMove nl inst Failover
907 bef83fd1 Iustin Pop
    let idx = Instance.idx inst
908 bef83fd1 Iustin Pop
        il' = Container.add idx inst' il
909 bef83fd1 Iustin Pop
        ops = iMoveToJob nl' il' idx Failover
910 bef83fd1 Iustin Pop
    return (nl', il', ops)
911 bef83fd1 Iustin Pop
912 db56cfc4 Iustin Pop
nodeEvacInstance nl il ChangeSecondary
913 db56cfc4 Iustin Pop
                 inst@(Instance.Instance {Instance.diskTemplate = DTDrbd8})
914 a86fbf36 Iustin Pop
                 gdx avail_nodes =
915 db56cfc4 Iustin Pop
  do
916 db56cfc4 Iustin Pop
    (nl', inst', _, ndx) <- annotateResult "Can't find any good node" $
917 db56cfc4 Iustin Pop
                            eitherToResult $
918 db56cfc4 Iustin Pop
                            foldl' (evacDrbdSecondaryInner nl inst gdx)
919 db56cfc4 Iustin Pop
                            (Left "no nodes available") avail_nodes
920 db56cfc4 Iustin Pop
    let idx = Instance.idx inst
921 db56cfc4 Iustin Pop
        il' = Container.add idx inst' il
922 db56cfc4 Iustin Pop
        ops = iMoveToJob nl' il' idx (ReplaceSecondary ndx)
923 db56cfc4 Iustin Pop
    return (nl', il', ops)
924 db56cfc4 Iustin Pop
925 d52d41de Iustin Pop
nodeEvacInstance nl il ChangeAll
926 d52d41de Iustin Pop
                 inst@(Instance.Instance {Instance.diskTemplate = DTDrbd8})
927 a86fbf36 Iustin Pop
                 gdx avail_nodes =
928 d52d41de Iustin Pop
  do
929 d52d41de Iustin Pop
    let primary = Container.find (Instance.pNode inst) nl
930 d52d41de Iustin Pop
        idx = Instance.idx inst
931 d52d41de Iustin Pop
        no_nodes = Left "no nodes available"
932 d52d41de Iustin Pop
    -- if the primary is offline, then we first failover
933 d52d41de Iustin Pop
    (nl1, inst1, ops1) <-
934 d52d41de Iustin Pop
        if Node.offline primary
935 d52d41de Iustin Pop
        then do
936 d52d41de Iustin Pop
          (nl', inst', _, _) <-
937 d52d41de Iustin Pop
              annotateResult "Failing over to the secondary" $
938 d52d41de Iustin Pop
              opToResult $ applyMove nl inst Failover
939 d52d41de Iustin Pop
          return (nl', inst', [Failover])
940 d52d41de Iustin Pop
        else return (nl, inst, [])
941 d52d41de Iustin Pop
    -- we now need to execute a replace secondary to the future
942 d52d41de Iustin Pop
    -- primary node
943 d52d41de Iustin Pop
    (nl2, inst2, _, new_pdx) <- annotateResult "Searching for a new primary" $
944 d52d41de Iustin Pop
                                eitherToResult $
945 d52d41de Iustin Pop
                                foldl' (evacDrbdSecondaryInner nl1 inst1 gdx)
946 d52d41de Iustin Pop
                                no_nodes avail_nodes
947 d52d41de Iustin Pop
    let ops2 = ReplaceSecondary new_pdx:ops1
948 d52d41de Iustin Pop
    -- since we chose the new primary, we remove it from the list of
949 d52d41de Iustin Pop
    -- available nodes
950 d52d41de Iustin Pop
    let avail_nodes_sec = new_pdx `delete` avail_nodes
951 d52d41de Iustin Pop
    -- we now execute another failover, the primary stays fixed now
952 d52d41de Iustin Pop
    (nl3, inst3, _, _) <- annotateResult "Failing over to new primary" $
953 d52d41de Iustin Pop
                          opToResult $ applyMove nl2 inst2 Failover
954 d52d41de Iustin Pop
    let ops3 = Failover:ops2
955 d52d41de Iustin Pop
    -- and finally another replace secondary, to the final secondary
956 d52d41de Iustin Pop
    (nl4, inst4, _, new_sdx) <-
957 d52d41de Iustin Pop
        annotateResult "Searching for a new secondary" $
958 d52d41de Iustin Pop
        eitherToResult $
959 d52d41de Iustin Pop
        foldl' (evacDrbdSecondaryInner nl3 inst3 gdx) no_nodes avail_nodes_sec
960 d52d41de Iustin Pop
    let ops4 = ReplaceSecondary new_sdx:ops3
961 d52d41de Iustin Pop
        il' = Container.add idx inst4 il
962 d52d41de Iustin Pop
        ops = concatMap (iMoveToJob nl4 il' idx) $ reverse ops4
963 d52d41de Iustin Pop
    return (nl4, il', ops)
964 47eed3f4 Iustin Pop
965 db56cfc4 Iustin Pop
-- | Inner fold function for changing secondary of a DRBD instance.
966 db56cfc4 Iustin Pop
--
967 db56cfc4 Iustin Pop
-- The "running" solution is either a @Left String@, which means we
968 db56cfc4 Iustin Pop
-- don't have yet a working solution, or a @Right (...)@, which
969 db56cfc4 Iustin Pop
-- represents a valid solution; it holds the modified node list, the
970 db56cfc4 Iustin Pop
-- modified instance (after evacuation), the score of that solution,
971 db56cfc4 Iustin Pop
-- and the new secondary node index.
972 db56cfc4 Iustin Pop
evacDrbdSecondaryInner :: Node.List -- ^ Cluster node list
973 db56cfc4 Iustin Pop
                       -> Instance.Instance -- ^ Instance being evacuated
974 db56cfc4 Iustin Pop
                       -> Gdx -- ^ The group index of the instance
975 db56cfc4 Iustin Pop
                       -> Either String ( Node.List
976 db56cfc4 Iustin Pop
                                        , Instance.Instance
977 db56cfc4 Iustin Pop
                                        , Score
978 db56cfc4 Iustin Pop
                                        , Ndx)  -- ^ Current best solution
979 db56cfc4 Iustin Pop
                       -> Ndx  -- ^ Node we're evaluating as new secondary
980 db56cfc4 Iustin Pop
                       -> Either String ( Node.List
981 db56cfc4 Iustin Pop
                                        , Instance.Instance
982 db56cfc4 Iustin Pop
                                        , Score
983 db56cfc4 Iustin Pop
                                        , Ndx) -- ^ New best solution
984 db56cfc4 Iustin Pop
evacDrbdSecondaryInner nl inst gdx accu ndx =
985 db56cfc4 Iustin Pop
    case applyMove nl inst (ReplaceSecondary ndx) of
986 db56cfc4 Iustin Pop
      OpFail fm ->
987 db56cfc4 Iustin Pop
          case accu of
988 db56cfc4 Iustin Pop
            Right _ -> accu
989 db56cfc4 Iustin Pop
            Left _ -> Left $ "Node " ++ Container.nameOf nl ndx ++
990 db56cfc4 Iustin Pop
                      " failed: " ++ show fm
991 db56cfc4 Iustin Pop
      OpGood (nl', inst', _, _) ->
992 db56cfc4 Iustin Pop
          let nodes = Container.elems nl'
993 db56cfc4 Iustin Pop
              -- The fromJust below is ugly (it can fail nastily), but
994 db56cfc4 Iustin Pop
              -- at this point we should have any internal mismatches,
995 db56cfc4 Iustin Pop
              -- and adding a monad here would be quite involved
996 db56cfc4 Iustin Pop
              grpnodes = fromJust (gdx `lookup` (Node.computeGroups nodes))
997 db56cfc4 Iustin Pop
              new_cv = compCVNodes grpnodes
998 db56cfc4 Iustin Pop
              new_accu = Right (nl', inst', new_cv, ndx)
999 db56cfc4 Iustin Pop
          in case accu of
1000 db56cfc4 Iustin Pop
               Left _ -> new_accu
1001 db56cfc4 Iustin Pop
               Right (_, _, old_cv, _) ->
1002 db56cfc4 Iustin Pop
                   if old_cv < new_cv
1003 db56cfc4 Iustin Pop
                   then accu
1004 db56cfc4 Iustin Pop
                   else new_accu
1005 db56cfc4 Iustin Pop
1006 c9a9b853 Iustin Pop
-- | Computes the nodes in a given group which are available for
1007 c9a9b853 Iustin Pop
-- allocation.
1008 c9a9b853 Iustin Pop
availableGroupNodes :: [(Gdx, [Ndx])] -- ^ Group index/node index assoc list
1009 c9a9b853 Iustin Pop
                    -> IntSet.IntSet  -- ^ Nodes that are excluded
1010 c9a9b853 Iustin Pop
                    -> Gdx            -- ^ The group for which we
1011 c9a9b853 Iustin Pop
                                      -- query the nodes
1012 c9a9b853 Iustin Pop
                    -> Result [Ndx]   -- ^ List of available node indices
1013 c9a9b853 Iustin Pop
availableGroupNodes group_nodes excl_ndx gdx = do
1014 47eed3f4 Iustin Pop
  local_nodes <- maybe (Bad $ "Can't find group with index " ++ show gdx)
1015 47eed3f4 Iustin Pop
                 Ok (lookup gdx group_nodes)
1016 47eed3f4 Iustin Pop
  let avail_nodes = filter (not . flip IntSet.member excl_ndx) local_nodes
1017 47eed3f4 Iustin Pop
  return avail_nodes
1018 47eed3f4 Iustin Pop
1019 47eed3f4 Iustin Pop
-- | Updates the evac solution with the results of an instance
1020 47eed3f4 Iustin Pop
-- evacuation.
1021 47eed3f4 Iustin Pop
updateEvacSolution :: (Node.List, Instance.List, EvacSolution)
1022 5440c877 Iustin Pop
                   -> Idx
1023 47eed3f4 Iustin Pop
                   -> Result (Node.List, Instance.List, [OpCodes.OpCode])
1024 47eed3f4 Iustin Pop
                   -> (Node.List, Instance.List, EvacSolution)
1025 5440c877 Iustin Pop
updateEvacSolution (nl, il, es) idx (Bad msg) =
1026 5440c877 Iustin Pop
    (nl, il, es { esFailed = (idx, msg):esFailed es})
1027 5440c877 Iustin Pop
updateEvacSolution (_, _, es) idx (Ok (nl, il, opcodes)) =
1028 5440c877 Iustin Pop
    (nl, il, es { esMoved = new_elem:esMoved es
1029 47eed3f4 Iustin Pop
                , esOpCodes = [opcodes]:esOpCodes es })
1030 5440c877 Iustin Pop
     where inst = Container.find idx il
1031 5440c877 Iustin Pop
           new_elem = (idx,
1032 5440c877 Iustin Pop
                       instancePriGroup nl inst,
1033 5440c877 Iustin Pop
                       Instance.allNodes inst)
1034 47eed3f4 Iustin Pop
1035 47eed3f4 Iustin Pop
-- | Node-evacuation IAllocator mode main function.
1036 47eed3f4 Iustin Pop
tryNodeEvac :: Group.List    -- ^ The cluster groups
1037 47eed3f4 Iustin Pop
            -> Node.List     -- ^ The node list (cluster-wide, not per group)
1038 47eed3f4 Iustin Pop
            -> Instance.List -- ^ Instance list (cluster-wide)
1039 47eed3f4 Iustin Pop
            -> EvacMode      -- ^ The evacuation mode
1040 47eed3f4 Iustin Pop
            -> [Idx]         -- ^ List of instance (indices) to be evacuated
1041 4036f63a Iustin Pop
            -> Result (Node.List, Instance.List, EvacSolution)
1042 47eed3f4 Iustin Pop
tryNodeEvac _ ini_nl ini_il mode idxs =
1043 47eed3f4 Iustin Pop
    let evac_ndx = nodesToEvacuate ini_il mode idxs
1044 47eed3f4 Iustin Pop
        offline = map Node.idx . filter Node.offline $ Container.elems ini_nl
1045 47eed3f4 Iustin Pop
        excl_ndx = foldl' (flip IntSet.insert) evac_ndx offline
1046 47eed3f4 Iustin Pop
        group_ndx = map (\(gdx, (nl, _)) -> (gdx, map Node.idx
1047 47eed3f4 Iustin Pop
                                             (Container.elems nl))) $
1048 47eed3f4 Iustin Pop
                      splitCluster ini_nl ini_il
1049 4036f63a Iustin Pop
        (fin_nl, fin_il, esol) =
1050 47eed3f4 Iustin Pop
            foldl' (\state@(nl, il, _) inst ->
1051 a86fbf36 Iustin Pop
                        let gdx = instancePriGroup nl inst in
1052 5440c877 Iustin Pop
                        updateEvacSolution state (Instance.idx inst) $
1053 c9a9b853 Iustin Pop
                        availableGroupNodes group_ndx
1054 a86fbf36 Iustin Pop
                          excl_ndx gdx >>=
1055 a86fbf36 Iustin Pop
                        nodeEvacInstance nl il mode inst gdx
1056 47eed3f4 Iustin Pop
                   )
1057 47eed3f4 Iustin Pop
            (ini_nl, ini_il, emptyEvacSolution)
1058 47eed3f4 Iustin Pop
            (map (`Container.find` ini_il) idxs)
1059 4036f63a Iustin Pop
    in return (fin_nl, fin_il, reverseEvacSolution esol)
1060 47eed3f4 Iustin Pop
1061 20b376ff Iustin Pop
-- | Change-group IAllocator mode main function.
1062 20b376ff Iustin Pop
--
1063 20b376ff Iustin Pop
-- This is very similar to 'tryNodeEvac', the only difference is that
1064 20b376ff Iustin Pop
-- we don't choose as target group the current instance group, but
1065 20b376ff Iustin Pop
-- instead:
1066 20b376ff Iustin Pop
--
1067 20b376ff Iustin Pop
--   1. at the start of the function, we compute which are the target
1068 20b376ff Iustin Pop
--   groups; either no groups were passed in, in which case we choose
1069 20b376ff Iustin Pop
--   all groups out of which we don't evacuate instance, or there were
1070 20b376ff Iustin Pop
--   some groups passed, in which case we use those
1071 20b376ff Iustin Pop
--
1072 20b376ff Iustin Pop
--   2. for each instance, we use 'findBestAllocGroup' to choose the
1073 20b376ff Iustin Pop
--   best group to hold the instance, and then we do what
1074 20b376ff Iustin Pop
--   'tryNodeEvac' does, except for this group instead of the current
1075 20b376ff Iustin Pop
--   instance group.
1076 20b376ff Iustin Pop
--
1077 20b376ff Iustin Pop
-- Note that the correct behaviour of this function relies on the
1078 20b376ff Iustin Pop
-- function 'nodeEvacInstance' to be able to do correctly both
1079 20b376ff Iustin Pop
-- intra-group and inter-group moves when passed the 'ChangeAll' mode.
1080 20b376ff Iustin Pop
tryChangeGroup :: Group.List    -- ^ The cluster groups
1081 20b376ff Iustin Pop
               -> Node.List     -- ^ The node list (cluster-wide)
1082 20b376ff Iustin Pop
               -> Instance.List -- ^ Instance list (cluster-wide)
1083 20b376ff Iustin Pop
               -> [Gdx]         -- ^ Target groups; if empty, any
1084 20b376ff Iustin Pop
                                -- groups not being evacuated
1085 20b376ff Iustin Pop
               -> [Idx]         -- ^ List of instance (indices) to be evacuated
1086 4036f63a Iustin Pop
               -> Result (Node.List, Instance.List, EvacSolution)
1087 20b376ff Iustin Pop
tryChangeGroup gl ini_nl ini_il gdxs idxs =
1088 20b376ff Iustin Pop
    let evac_gdxs = nub $ map (instancePriGroup ini_nl .
1089 20b376ff Iustin Pop
                               flip Container.find ini_il) idxs
1090 20b376ff Iustin Pop
        target_gdxs = (if null gdxs
1091 20b376ff Iustin Pop
                       then Container.keys gl
1092 20b376ff Iustin Pop
                       else gdxs) \\ evac_gdxs
1093 20b376ff Iustin Pop
        offline = map Node.idx . filter Node.offline $ Container.elems ini_nl
1094 20b376ff Iustin Pop
        excl_ndx = foldl' (flip IntSet.insert) IntSet.empty offline
1095 20b376ff Iustin Pop
        group_ndx = map (\(gdx, (nl, _)) -> (gdx, map Node.idx
1096 20b376ff Iustin Pop
                                             (Container.elems nl))) $
1097 20b376ff Iustin Pop
                      splitCluster ini_nl ini_il
1098 4036f63a Iustin Pop
        (fin_nl, fin_il, esol) =
1099 20b376ff Iustin Pop
            foldl' (\state@(nl, il, _) inst ->
1100 20b376ff Iustin Pop
                        let solution = do
1101 20b376ff Iustin Pop
                              let ncnt = Instance.requiredNodes $
1102 20b376ff Iustin Pop
                                         Instance.diskTemplate inst
1103 20b376ff Iustin Pop
                              (gdx, _, _) <- findBestAllocGroup gl nl il
1104 20b376ff Iustin Pop
                                             (Just target_gdxs) inst ncnt
1105 20b376ff Iustin Pop
                              av_nodes <- availableGroupNodes group_ndx
1106 20b376ff Iustin Pop
                                          excl_ndx gdx
1107 a86fbf36 Iustin Pop
                              nodeEvacInstance nl il ChangeAll inst
1108 a86fbf36 Iustin Pop
                                       gdx av_nodes
1109 5440c877 Iustin Pop
                        in updateEvacSolution state
1110 5440c877 Iustin Pop
                               (Instance.idx inst) solution
1111 20b376ff Iustin Pop
                   )
1112 20b376ff Iustin Pop
            (ini_nl, ini_il, emptyEvacSolution)
1113 20b376ff Iustin Pop
            (map (`Container.find` ini_il) idxs)
1114 4036f63a Iustin Pop
    in return (fin_nl, fin_il, reverseEvacSolution esol)
1115 20b376ff Iustin Pop
1116 525bfb36 Iustin Pop
-- | Recursively place instances on the cluster until we're out of space.
1117 3ce8009a Iustin Pop
iterateAlloc :: Node.List
1118 3ce8009a Iustin Pop
             -> Instance.List
1119 8f48f67d Iustin Pop
             -> Maybe Int
1120 3ce8009a Iustin Pop
             -> Instance.Instance
1121 41b5c85a Iustin Pop
             -> AllocNodes
1122 3ce8009a Iustin Pop
             -> [Instance.Instance]
1123 d5ccec02 Iustin Pop
             -> [CStats]
1124 40ee14bc Iustin Pop
             -> Result AllocResult
1125 8f48f67d Iustin Pop
iterateAlloc nl il limit newinst allocnodes ixes cstats =
1126 3ce8009a Iustin Pop
      let depth = length ixes
1127 3ce8009a Iustin Pop
          newname = printf "new-%d" depth::String
1128 3ce8009a Iustin Pop
          newidx = length (Container.elems il) + depth
1129 3ce8009a Iustin Pop
          newi2 = Instance.setIdx (Instance.setName newinst newname) newidx
1130 8f48f67d Iustin Pop
          newlimit = fmap (flip (-) 1) limit
1131 41b5c85a Iustin Pop
      in case tryAlloc nl il newi2 allocnodes of
1132 3ce8009a Iustin Pop
           Bad s -> Bad s
1133 85d0ddc3 Iustin Pop
           Ok (AllocSolution { asFailures = errs, asSolutions = sols3 }) ->
1134 8f48f67d Iustin Pop
               let newsol = Ok (collapseFailures errs, nl, il, ixes, cstats) in
1135 3ce8009a Iustin Pop
               case sols3 of
1136 8f48f67d Iustin Pop
                 [] -> newsol
1137 a334d536 Iustin Pop
                 (xnl, xi, _, _):[] ->
1138 8f48f67d Iustin Pop
                     if limit == Just 0
1139 8f48f67d Iustin Pop
                     then newsol
1140 8f48f67d Iustin Pop
                     else iterateAlloc xnl (Container.add newidx xi il)
1141 8f48f67d Iustin Pop
                          newlimit newinst allocnodes (xi:ixes)
1142 8f48f67d Iustin Pop
                          (totalResources xnl:cstats)
1143 3ce8009a Iustin Pop
                 _ -> Bad "Internal error: multiple solutions for single\
1144 3ce8009a Iustin Pop
                          \ allocation"
1145 3ce8009a Iustin Pop
1146 525bfb36 Iustin Pop
-- | The core of the tiered allocation mode.
1147 3ce8009a Iustin Pop
tieredAlloc :: Node.List
1148 3ce8009a Iustin Pop
            -> Instance.List
1149 8f48f67d Iustin Pop
            -> Maybe Int
1150 3ce8009a Iustin Pop
            -> Instance.Instance
1151 41b5c85a Iustin Pop
            -> AllocNodes
1152 3ce8009a Iustin Pop
            -> [Instance.Instance]
1153 d5ccec02 Iustin Pop
            -> [CStats]
1154 40ee14bc Iustin Pop
            -> Result AllocResult
1155 8f48f67d Iustin Pop
tieredAlloc nl il limit newinst allocnodes ixes cstats =
1156 8f48f67d Iustin Pop
    case iterateAlloc nl il limit newinst allocnodes ixes cstats of
1157 3ce8009a Iustin Pop
      Bad s -> Bad s
1158 d5ccec02 Iustin Pop
      Ok (errs, nl', il', ixes', cstats') ->
1159 8f48f67d Iustin Pop
          let newsol = Ok (errs, nl', il', ixes', cstats')
1160 8f48f67d Iustin Pop
              ixes_cnt = length ixes'
1161 8f48f67d Iustin Pop
              (stop, newlimit) = case limit of
1162 8f48f67d Iustin Pop
                                   Nothing -> (False, Nothing)
1163 8f48f67d Iustin Pop
                                   Just n -> (n <= ixes_cnt,
1164 8f48f67d Iustin Pop
                                              Just (n - ixes_cnt)) in
1165 8f48f67d Iustin Pop
          if stop then newsol else
1166 3ce8009a Iustin Pop
          case Instance.shrinkByType newinst . fst . last $
1167 3ce8009a Iustin Pop
               sortBy (comparing snd) errs of
1168 8f48f67d Iustin Pop
            Bad _ -> newsol
1169 8f48f67d Iustin Pop
            Ok newinst' -> tieredAlloc nl' il' newlimit
1170 8f48f67d Iustin Pop
                           newinst' allocnodes ixes' cstats'
1171 3ce8009a Iustin Pop
1172 9188aeef Iustin Pop
-- * Formatting functions
1173 e4f08c46 Iustin Pop
1174 e4f08c46 Iustin Pop
-- | Given the original and final nodes, computes the relocation description.
1175 c9926b22 Iustin Pop
computeMoves :: Instance.Instance -- ^ The instance to be moved
1176 c9926b22 Iustin Pop
             -> String -- ^ The instance name
1177 668c03b3 Iustin Pop
             -> IMove  -- ^ The move being performed
1178 e4f08c46 Iustin Pop
             -> String -- ^ New primary
1179 e4f08c46 Iustin Pop
             -> String -- ^ New secondary
1180 e4f08c46 Iustin Pop
             -> (String, [String])
1181 e4f08c46 Iustin Pop
                -- ^ Tuple of moves and commands list; moves is containing
1182 e4f08c46 Iustin Pop
                -- either @/f/@ for failover or @/r:name/@ for replace
1183 e4f08c46 Iustin Pop
                -- secondary, while the command list holds gnt-instance
1184 e4f08c46 Iustin Pop
                -- commands (without that prefix), e.g \"@failover instance1@\"
1185 668c03b3 Iustin Pop
computeMoves i inam mv c d =
1186 668c03b3 Iustin Pop
    case mv of
1187 668c03b3 Iustin Pop
      Failover -> ("f", [mig])
1188 668c03b3 Iustin Pop
      FailoverAndReplace _ -> (printf "f r:%s" d, [mig, rep d])
1189 668c03b3 Iustin Pop
      ReplaceSecondary _ -> (printf "r:%s" d, [rep d])
1190 668c03b3 Iustin Pop
      ReplaceAndFailover _ -> (printf "r:%s f" c, [rep c, mig])
1191 668c03b3 Iustin Pop
      ReplacePrimary _ -> (printf "f r:%s f" c, [mig, rep c, mig])
1192 c9926b22 Iustin Pop
    where morf = if Instance.running i then "migrate" else "failover"
1193 c9926b22 Iustin Pop
          mig = printf "%s -f %s" morf inam::String
1194 c9926b22 Iustin Pop
          rep n = printf "replace-disks -n %s %s" n inam
1195 e4f08c46 Iustin Pop
1196 9188aeef Iustin Pop
-- | Converts a placement to string format.
1197 9188aeef Iustin Pop
printSolutionLine :: Node.List     -- ^ The node list
1198 9188aeef Iustin Pop
                  -> Instance.List -- ^ The instance list
1199 9188aeef Iustin Pop
                  -> Int           -- ^ Maximum node name length
1200 9188aeef Iustin Pop
                  -> Int           -- ^ Maximum instance name length
1201 9188aeef Iustin Pop
                  -> Placement     -- ^ The current placement
1202 9188aeef Iustin Pop
                  -> Int           -- ^ The index of the placement in
1203 9188aeef Iustin Pop
                                   -- the solution
1204 db1bcfe8 Iustin Pop
                  -> (String, [String])
1205 db1bcfe8 Iustin Pop
printSolutionLine nl il nmlen imlen plc pos =
1206 ca8258d9 Iustin Pop
    let
1207 ca8258d9 Iustin Pop
        pmlen = (2*nmlen + 1)
1208 668c03b3 Iustin Pop
        (i, p, s, mv, c) = plc
1209 ca8258d9 Iustin Pop
        inst = Container.find i il
1210 14c972c7 Iustin Pop
        inam = Instance.alias inst
1211 14c972c7 Iustin Pop
        npri = Node.alias $ Container.find p nl
1212 14c972c7 Iustin Pop
        nsec = Node.alias $ Container.find s nl
1213 14c972c7 Iustin Pop
        opri = Node.alias $ Container.find (Instance.pNode inst) nl
1214 14c972c7 Iustin Pop
        osec = Node.alias $ Container.find (Instance.sNode inst) nl
1215 668c03b3 Iustin Pop
        (moves, cmds) =  computeMoves inst inam mv npri nsec
1216 9f6dcdea Iustin Pop
        ostr = printf "%s:%s" opri osec::String
1217 9f6dcdea Iustin Pop
        nstr = printf "%s:%s" npri nsec::String
1218 ca8258d9 Iustin Pop
    in
1219 ab271fc1 Iustin Pop
      (printf "  %3d. %-*s %-*s => %-*s %.8f a=%s"
1220 ab271fc1 Iustin Pop
       pos imlen inam pmlen ostr
1221 ca8258d9 Iustin Pop
       pmlen nstr c moves,
1222 ca8258d9 Iustin Pop
       cmds)
1223 ca8258d9 Iustin Pop
1224 0e8ae201 Iustin Pop
-- | Return the instance and involved nodes in an instance move.
1225 0e8ae201 Iustin Pop
involvedNodes :: Instance.List -> Placement -> [Ndx]
1226 0e8ae201 Iustin Pop
involvedNodes il plc =
1227 3173c987 Iustin Pop
    let (i, np, ns, _, _) = plc
1228 0e8ae201 Iustin Pop
        inst = Container.find i il
1229 2060348b Iustin Pop
        op = Instance.pNode inst
1230 2060348b Iustin Pop
        os = Instance.sNode inst
1231 0e8ae201 Iustin Pop
    in nub [np, ns, op, os]
1232 0e8ae201 Iustin Pop
1233 0e8ae201 Iustin Pop
-- | Inner function for splitJobs, that either appends the next job to
1234 0e8ae201 Iustin Pop
-- the current jobset, or starts a new jobset.
1235 0e8ae201 Iustin Pop
mergeJobs :: ([JobSet], [Ndx]) -> MoveJob -> ([JobSet], [Ndx])
1236 924f9c16 Iustin Pop
mergeJobs ([], _) n@(ndx, _, _, _) = ([[n]], ndx)
1237 924f9c16 Iustin Pop
mergeJobs (cjs@(j:js), nbuf) n@(ndx, _, _, _)
1238 0e8ae201 Iustin Pop
    | null (ndx `intersect` nbuf) = ((n:j):js, ndx ++ nbuf)
1239 0e8ae201 Iustin Pop
    | otherwise = ([n]:cjs, ndx)
1240 0e8ae201 Iustin Pop
1241 0e8ae201 Iustin Pop
-- | Break a list of moves into independent groups. Note that this
1242 0e8ae201 Iustin Pop
-- will reverse the order of jobs.
1243 0e8ae201 Iustin Pop
splitJobs :: [MoveJob] -> [JobSet]
1244 0e8ae201 Iustin Pop
splitJobs = fst . foldl mergeJobs ([], [])
1245 0e8ae201 Iustin Pop
1246 0e8ae201 Iustin Pop
-- | Given a list of commands, prefix them with @gnt-instance@ and
1247 0e8ae201 Iustin Pop
-- also beautify the display a little.
1248 0e8ae201 Iustin Pop
formatJob :: Int -> Int -> (Int, MoveJob) -> [String]
1249 924f9c16 Iustin Pop
formatJob jsn jsl (sn, (_, _, _, cmds)) =
1250 0e8ae201 Iustin Pop
    let out =
1251 0e8ae201 Iustin Pop
            printf "  echo job %d/%d" jsn sn:
1252 0e8ae201 Iustin Pop
            printf "  check":
1253 0e8ae201 Iustin Pop
            map ("  gnt-instance " ++) cmds
1254 0e8ae201 Iustin Pop
    in if sn == 1
1255 0e8ae201 Iustin Pop
       then ["", printf "echo jobset %d, %d jobs" jsn jsl] ++ out
1256 0e8ae201 Iustin Pop
       else out
1257 0e8ae201 Iustin Pop
1258 9188aeef Iustin Pop
-- | Given a list of commands, prefix them with @gnt-instance@ and
1259 9188aeef Iustin Pop
-- also beautify the display a little.
1260 0e8ae201 Iustin Pop
formatCmds :: [JobSet] -> String
1261 9f6dcdea Iustin Pop
formatCmds =
1262 9f6dcdea Iustin Pop
    unlines .
1263 0e8ae201 Iustin Pop
    concatMap (\(jsn, js) -> concatMap (formatJob jsn (length js))
1264 0e8ae201 Iustin Pop
                             (zip [1..] js)) .
1265 9f6dcdea Iustin Pop
    zip [1..]
1266 142538ff Iustin Pop
1267 e4f08c46 Iustin Pop
-- | Print the node list.
1268 e98fb766 Iustin Pop
printNodes :: Node.List -> [String] -> String
1269 e98fb766 Iustin Pop
printNodes nl fs =
1270 6dfa04fd Iustin Pop
    let fields = case fs of
1271 6dfa04fd Iustin Pop
          [] -> Node.defaultFields
1272 6dfa04fd Iustin Pop
          "+":rest -> Node.defaultFields ++ rest
1273 6dfa04fd Iustin Pop
          _ -> fs
1274 5182e970 Iustin Pop
        snl = sortBy (comparing Node.idx) (Container.elems nl)
1275 e98fb766 Iustin Pop
        (header, isnum) = unzip $ map Node.showHeader fields
1276 c5f7412e Iustin Pop
    in unlines . map ((:) ' ' .  intercalate " ") $
1277 e98fb766 Iustin Pop
       formatTable (header:map (Node.list fields) snl) isnum
1278 e4f08c46 Iustin Pop
1279 507fda3f Iustin Pop
-- | Print the instance list.
1280 507fda3f Iustin Pop
printInsts :: Node.List -> Instance.List -> String
1281 507fda3f Iustin Pop
printInsts nl il =
1282 5182e970 Iustin Pop
    let sil = sortBy (comparing Instance.idx) (Container.elems il)
1283 30ff0c73 Iustin Pop
        helper inst = [ if Instance.running inst then "R" else " "
1284 30ff0c73 Iustin Pop
                      , Instance.name inst
1285 30ff0c73 Iustin Pop
                      , Container.nameOf nl (Instance.pNode inst)
1286 5182e970 Iustin Pop
                      , let sdx = Instance.sNode inst
1287 5182e970 Iustin Pop
                        in if sdx == Node.noSecondary
1288 5182e970 Iustin Pop
                           then  ""
1289 5182e970 Iustin Pop
                           else Container.nameOf nl sdx
1290 0e09422b Iustin Pop
                      , if Instance.autoBalance inst then "Y" else "N"
1291 30ff0c73 Iustin Pop
                      , printf "%3d" $ Instance.vcpus inst
1292 30ff0c73 Iustin Pop
                      , printf "%5d" $ Instance.mem inst
1293 30ff0c73 Iustin Pop
                      , printf "%5d" $ Instance.dsk inst `div` 1024
1294 30ff0c73 Iustin Pop
                      , printf "%5.3f" lC
1295 30ff0c73 Iustin Pop
                      , printf "%5.3f" lM
1296 30ff0c73 Iustin Pop
                      , printf "%5.3f" lD
1297 30ff0c73 Iustin Pop
                      , printf "%5.3f" lN
1298 30ff0c73 Iustin Pop
                      ]
1299 30ff0c73 Iustin Pop
            where DynUtil lC lM lD lN = Instance.util inst
1300 93439b1c Iustin Pop
        header = [ "F", "Name", "Pri_node", "Sec_node", "Auto_bal"
1301 93439b1c Iustin Pop
                 , "vcpu", "mem" , "dsk", "lCpu", "lMem", "lDsk", "lNet" ]
1302 93439b1c Iustin Pop
        isnum = False:False:False:False:False:repeat True
1303 c5f7412e Iustin Pop
    in unlines . map ((:) ' ' . intercalate " ") $
1304 c5f7412e Iustin Pop
       formatTable (header:map helper sil) isnum
1305 507fda3f Iustin Pop
1306 9188aeef Iustin Pop
-- | Shows statistics for a given node list.
1307 262a08a2 Iustin Pop
printStats :: Node.List -> String
1308 e4f08c46 Iustin Pop
printStats nl =
1309 9bb5721c Iustin Pop
    let dcvs = compDetailedCV $ Container.elems nl
1310 8a3b30ca Iustin Pop
        (weights, names) = unzip detailedCVInfo
1311 8a3b30ca Iustin Pop
        hd = zip3 (weights ++ repeat 1) (names ++ repeat "unknown") dcvs
1312 8a3b30ca Iustin Pop
        formatted = map (\(w, header, val) ->
1313 8a3b30ca Iustin Pop
                             printf "%s=%.8f(x%.2f)" header val w::String) hd
1314 fca250e9 Iustin Pop
    in intercalate ", " formatted
1315 6b20875c Iustin Pop
1316 6b20875c Iustin Pop
-- | Convert a placement into a list of OpCodes (basically a job).
1317 3e4480e0 Iustin Pop
iMoveToJob :: Node.List -> Instance.List
1318 6b20875c Iustin Pop
          -> Idx -> IMove -> [OpCodes.OpCode]
1319 3e4480e0 Iustin Pop
iMoveToJob nl il idx move =
1320 dfbbd43a Iustin Pop
    let inst = Container.find idx il
1321 3e4480e0 Iustin Pop
        iname = Instance.name inst
1322 3e4480e0 Iustin Pop
        lookNode  = Just . Container.nameOf nl
1323 10028866 René Nussbaumer
        opF = OpCodes.OpInstanceMigrate iname True False True
1324 10028866 René Nussbaumer
        opR n = OpCodes.OpInstanceReplaceDisks iname (lookNode n)
1325 6b20875c Iustin Pop
                OpCodes.ReplaceNewSecondary [] Nothing
1326 6b20875c Iustin Pop
    in case move of
1327 6b20875c Iustin Pop
         Failover -> [ opF ]
1328 6b20875c Iustin Pop
         ReplacePrimary np -> [ opF, opR np, opF ]
1329 6b20875c Iustin Pop
         ReplaceSecondary ns -> [ opR ns ]
1330 6b20875c Iustin Pop
         ReplaceAndFailover np -> [ opR np, opF ]
1331 6b20875c Iustin Pop
         FailoverAndReplace ns -> [ opF, opR ns ]
1332 32b8d9c0 Iustin Pop
1333 949397c8 Iustin Pop
-- * Node group functions
1334 949397c8 Iustin Pop
1335 525bfb36 Iustin Pop
-- | Computes the group of an instance.
1336 10ef6b4e Iustin Pop
instanceGroup :: Node.List -> Instance.Instance -> Result Gdx
1337 32b8d9c0 Iustin Pop
instanceGroup nl i =
1338 32b8d9c0 Iustin Pop
  let sidx = Instance.sNode i
1339 32b8d9c0 Iustin Pop
      pnode = Container.find (Instance.pNode i) nl
1340 32b8d9c0 Iustin Pop
      snode = if sidx == Node.noSecondary
1341 32b8d9c0 Iustin Pop
              then pnode
1342 32b8d9c0 Iustin Pop
              else Container.find sidx nl
1343 10ef6b4e Iustin Pop
      pgroup = Node.group pnode
1344 10ef6b4e Iustin Pop
      sgroup = Node.group snode
1345 10ef6b4e Iustin Pop
  in if pgroup /= sgroup
1346 10ef6b4e Iustin Pop
     then fail ("Instance placed accross two node groups, primary " ++
1347 10ef6b4e Iustin Pop
                show pgroup ++ ", secondary " ++ show sgroup)
1348 10ef6b4e Iustin Pop
     else return pgroup
1349 32b8d9c0 Iustin Pop
1350 525bfb36 Iustin Pop
-- | Computes the group of an instance per the primary node.
1351 4bc33d60 Iustin Pop
instancePriGroup :: Node.List -> Instance.Instance -> Gdx
1352 4bc33d60 Iustin Pop
instancePriGroup nl i =
1353 4bc33d60 Iustin Pop
  let pnode = Container.find (Instance.pNode i) nl
1354 4bc33d60 Iustin Pop
  in  Node.group pnode
1355 4bc33d60 Iustin Pop
1356 32b8d9c0 Iustin Pop
-- | Compute the list of badly allocated instances (split across node
1357 525bfb36 Iustin Pop
-- groups).
1358 32b8d9c0 Iustin Pop
findSplitInstances :: Node.List -> Instance.List -> [Instance.Instance]
1359 2a8e2dc9 Iustin Pop
findSplitInstances nl =
1360 2a8e2dc9 Iustin Pop
  filter (not . isOk . instanceGroup nl) . Container.elems
1361 f4161783 Iustin Pop
1362 525bfb36 Iustin Pop
-- | Splits a cluster into the component node groups.
1363 f4161783 Iustin Pop
splitCluster :: Node.List -> Instance.List ->
1364 10ef6b4e Iustin Pop
                [(Gdx, (Node.List, Instance.List))]
1365 f4161783 Iustin Pop
splitCluster nl il =
1366 f4161783 Iustin Pop
  let ngroups = Node.computeGroups (Container.elems nl)
1367 f4161783 Iustin Pop
  in map (\(guuid, nodes) ->
1368 f4161783 Iustin Pop
           let nidxs = map Node.idx nodes
1369 f4161783 Iustin Pop
               nodes' = zip nidxs nodes
1370 f4161783 Iustin Pop
               instances = Container.filter ((`elem` nidxs) . Instance.pNode) il
1371 cb0c77ff Iustin Pop
           in (guuid, (Container.fromList nodes', instances))) ngroups
1372 1f4ae205 Iustin Pop
1373 63a78055 Iustin Pop
-- | Compute the list of nodes that are to be evacuated, given a list
1374 63a78055 Iustin Pop
-- of instances and an evacuation mode.
1375 63a78055 Iustin Pop
nodesToEvacuate :: Instance.List -- ^ The cluster-wide instance list
1376 63a78055 Iustin Pop
                -> EvacMode      -- ^ The evacuation mode we're using
1377 63a78055 Iustin Pop
                -> [Idx]         -- ^ List of instance indices being evacuated
1378 63a78055 Iustin Pop
                -> IntSet.IntSet -- ^ Set of node indices
1379 63a78055 Iustin Pop
nodesToEvacuate il mode =
1380 63a78055 Iustin Pop
    IntSet.delete Node.noSecondary .
1381 63a78055 Iustin Pop
    foldl' (\ns idx ->
1382 63a78055 Iustin Pop
                let i = Container.find idx il
1383 63a78055 Iustin Pop
                    pdx = Instance.pNode i
1384 63a78055 Iustin Pop
                    sdx = Instance.sNode i
1385 63a78055 Iustin Pop
                    dt = Instance.diskTemplate i
1386 63a78055 Iustin Pop
                    withSecondary = case dt of
1387 63a78055 Iustin Pop
                                      DTDrbd8 -> IntSet.insert sdx ns
1388 63a78055 Iustin Pop
                                      _ -> ns
1389 63a78055 Iustin Pop
                in case mode of
1390 63a78055 Iustin Pop
                     ChangePrimary   -> IntSet.insert pdx ns
1391 63a78055 Iustin Pop
                     ChangeSecondary -> withSecondary
1392 63a78055 Iustin Pop
                     ChangeAll       -> IntSet.insert pdx withSecondary
1393 63a78055 Iustin Pop
           ) IntSet.empty