Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Cluster.hs @ 5f828ce4

History | View | Annotate | Download (63.2 kB)

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