Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (61.9 kB)

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