Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Cluster.hs @ 084565ac

History | View | Annotate | Download (61.7 kB)

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