Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Cluster.hs @ 06c2fb4a

History | View | Annotate | Download (69.2 kB)

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