Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Cluster.hs @ 30ce253e

History | View | Annotate | Download (68.9 kB)

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