Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Cluster.hs @ 90c2f1e8

History | View | Annotate | Download (60.7 kB)

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