Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Cluster.hs @ a3d1dc0a

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