Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Cluster.hs @ 94a420ed

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