Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Cluster.hs @ 4fe04580

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