Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Cluster.hs @ 23fe06c2

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