Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Cluster.hs @ a30b473c

History | View | Annotate | Download (47.3 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 e4f08c46 Iustin Pop
    , Table(..)
34 1a7eff0e Iustin Pop
    , CStats(..)
35 9b8fac3d Iustin Pop
    , AllocStats
36 e4f08c46 Iustin Pop
    -- * Generic functions
37 e4f08c46 Iustin Pop
    , totalResources
38 9b8fac3d Iustin Pop
    , computeAllocationDelta
39 e4f08c46 Iustin Pop
    -- * First phase functions
40 e4f08c46 Iustin Pop
    , computeBadItems
41 e4f08c46 Iustin Pop
    -- * Second phase functions
42 7dfaafb1 Iustin Pop
    , printSolutionLine
43 142538ff Iustin Pop
    , formatCmds
44 0e8ae201 Iustin Pop
    , involvedNodes
45 0e8ae201 Iustin Pop
    , splitJobs
46 507fda3f Iustin Pop
    -- * Display functions
47 507fda3f Iustin Pop
    , printNodes
48 507fda3f Iustin Pop
    , printInsts
49 e4f08c46 Iustin Pop
    -- * Balacing functions
50 e4f08c46 Iustin Pop
    , checkMove
51 5ad86777 Iustin Pop
    , doNextBalance
52 f25e5aac Iustin Pop
    , tryBalance
53 e4f08c46 Iustin Pop
    , compCV
54 6bc39970 Iustin Pop
    , compDetailedCV
55 e4f08c46 Iustin Pop
    , printStats
56 6b20875c Iustin Pop
    , iMoveToJob
57 4a340313 Iustin Pop
    -- * IAllocator functions
58 6cb1649f Iustin Pop
    , genAllocNodes
59 dbba5246 Iustin Pop
    , tryAlloc
60 9b1584fc Iustin Pop
    , tryMGAlloc
61 dbba5246 Iustin Pop
    , tryReloc
62 4bc33d60 Iustin Pop
    , tryMGReloc
63 12b0511d Iustin Pop
    , tryEvac
64 1bc47d38 Iustin Pop
    , tryMGEvac
65 478df686 Iustin Pop
    , collapseFailures
66 3ce8009a Iustin Pop
    -- * Allocation functions
67 3ce8009a Iustin Pop
    , iterateAlloc
68 3ce8009a Iustin Pop
    , tieredAlloc
69 949397c8 Iustin Pop
    , tieredSpecMap
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 949397c8 Iustin Pop
import Data.Function (on)
77 63a78055 Iustin Pop
import qualified Data.IntSet as IntSet
78 e4f08c46 Iustin Pop
import Data.List
79 5182e970 Iustin Pop
import Data.Ord (comparing)
80 e4f08c46 Iustin Pop
import Text.Printf (printf)
81 9d3fada5 Iustin Pop
import Control.Monad
82 a3eee4ad Iustin Pop
import Control.Parallel.Strategies
83 e4f08c46 Iustin Pop
84 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Container as Container
85 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
86 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Node as Node
87 aec636b9 Iustin Pop
import qualified Ganeti.HTools.Group as Group
88 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
89 669d7e3d Iustin Pop
import Ganeti.HTools.Utils
90 6b20875c Iustin Pop
import qualified Ganeti.OpCodes as OpCodes
91 e4f08c46 Iustin Pop
92 9188aeef Iustin Pop
-- * Types
93 9188aeef Iustin Pop
94 0c936d24 Iustin Pop
-- | Allocation\/relocation solution.
95 85d0ddc3 Iustin Pop
data AllocSolution = AllocSolution
96 85d0ddc3 Iustin Pop
  { asFailures  :: [FailMode]          -- ^ Failure counts
97 85d0ddc3 Iustin Pop
  , asAllocs    :: Int                 -- ^ Good allocation count
98 85d0ddc3 Iustin Pop
  , asSolutions :: [Node.AllocElement] -- ^ The actual result, length
99 85d0ddc3 Iustin Pop
                                       -- of the list depends on the
100 85d0ddc3 Iustin Pop
                                       -- allocation/relocation mode
101 859fc11d Iustin Pop
  , asLog       :: [String]            -- ^ A list of informational messages
102 85d0ddc3 Iustin Pop
  }
103 85d0ddc3 Iustin Pop
104 40ee14bc Iustin Pop
-- | Allocation results, as used in 'iterateAlloc' and 'tieredAlloc'.
105 40ee14bc Iustin Pop
type AllocResult = (FailStats, Node.List, Instance.List,
106 40ee14bc Iustin Pop
                    [Instance.Instance], [CStats])
107 40ee14bc Iustin Pop
108 6cb1649f Iustin Pop
109 6cb1649f Iustin Pop
-- | A type denoting the valid allocation mode/pairs.
110 525bfb36 Iustin Pop
--
111 6cb1649f Iustin Pop
-- For a one-node allocation, this will be a @Left ['Node.Node']@,
112 6cb1649f Iustin Pop
-- whereas for a two-node allocation, this will be a @Right
113 6cb1649f Iustin Pop
-- [('Node.Node', 'Node.Node')]@.
114 0d66ea67 Iustin Pop
type AllocNodes = Either [Ndx] [(Ndx, Ndx)]
115 6cb1649f Iustin Pop
116 525bfb36 Iustin Pop
-- | The empty solution we start with when computing allocations.
117 97936d51 Iustin Pop
emptyAllocSolution :: AllocSolution
118 97936d51 Iustin Pop
emptyAllocSolution = AllocSolution { asFailures = [], asAllocs = 0
119 97936d51 Iustin Pop
                                   , asSolutions = [], asLog = [] }
120 78694255 Iustin Pop
121 525bfb36 Iustin Pop
-- | The complete state for the balancing solution.
122 262a08a2 Iustin Pop
data Table = Table Node.List Instance.List Score [Placement]
123 6bc39970 Iustin Pop
             deriving (Show, Read)
124 e4f08c46 Iustin Pop
125 7034694d Iustin Pop
data CStats = CStats { csFmem :: Integer -- ^ Cluster free mem
126 7034694d Iustin Pop
                     , csFdsk :: Integer -- ^ Cluster free disk
127 7034694d Iustin Pop
                     , csAmem :: Integer -- ^ Cluster allocatable mem
128 7034694d Iustin Pop
                     , csAdsk :: Integer -- ^ Cluster allocatable disk
129 7034694d Iustin Pop
                     , csAcpu :: Integer -- ^ Cluster allocatable cpus
130 7034694d Iustin Pop
                     , csMmem :: Integer -- ^ Max node allocatable mem
131 7034694d Iustin Pop
                     , csMdsk :: Integer -- ^ Max node allocatable disk
132 7034694d Iustin Pop
                     , csMcpu :: Integer -- ^ Max node allocatable cpu
133 7034694d Iustin Pop
                     , csImem :: Integer -- ^ Instance used mem
134 7034694d Iustin Pop
                     , csIdsk :: Integer -- ^ Instance used disk
135 7034694d Iustin Pop
                     , csIcpu :: Integer -- ^ Instance used cpu
136 7034694d Iustin Pop
                     , csTmem :: Double  -- ^ Cluster total mem
137 7034694d Iustin Pop
                     , csTdsk :: Double  -- ^ Cluster total disk
138 7034694d Iustin Pop
                     , csTcpu :: Double  -- ^ Cluster total cpus
139 7034694d Iustin Pop
                     , csVcpu :: Integer -- ^ Cluster virtual cpus (if
140 7034694d Iustin Pop
                                         -- node pCpu has been set,
141 7034694d Iustin Pop
                                         -- otherwise -1)
142 7034694d Iustin Pop
                     , csXmem :: Integer -- ^ Unnacounted for mem
143 7034694d Iustin Pop
                     , csNmem :: Integer -- ^ Node own memory
144 7034694d Iustin Pop
                     , csScore :: Score  -- ^ The cluster score
145 7034694d Iustin Pop
                     , csNinst :: Int    -- ^ The total number of instances
146 1a7eff0e Iustin Pop
                     }
147 6bc39970 Iustin Pop
            deriving (Show, Read)
148 1a7eff0e Iustin Pop
149 525bfb36 Iustin Pop
-- | Currently used, possibly to allocate, unallocable.
150 9b8fac3d Iustin Pop
type AllocStats = (RSpec, RSpec, RSpec)
151 9b8fac3d Iustin Pop
152 9188aeef Iustin Pop
-- * Utility functions
153 9188aeef Iustin Pop
154 e4f08c46 Iustin Pop
-- | Verifies the N+1 status and return the affected nodes.
155 e4f08c46 Iustin Pop
verifyN1 :: [Node.Node] -> [Node.Node]
156 9f6dcdea Iustin Pop
verifyN1 = filter Node.failN1
157 e4f08c46 Iustin Pop
158 9188aeef Iustin Pop
{-| Computes the pair of bad nodes and instances.
159 9188aeef Iustin Pop
160 9188aeef Iustin Pop
The bad node list is computed via a simple 'verifyN1' check, and the
161 9188aeef Iustin Pop
bad instance list is the list of primary and secondary instances of
162 9188aeef Iustin Pop
those nodes.
163 9188aeef Iustin Pop
164 9188aeef Iustin Pop
-}
165 9188aeef Iustin Pop
computeBadItems :: Node.List -> Instance.List ->
166 9188aeef Iustin Pop
                   ([Node.Node], [Instance.Instance])
167 9188aeef Iustin Pop
computeBadItems nl il =
168 dbba5246 Iustin Pop
  let bad_nodes = verifyN1 $ getOnline nl
169 5182e970 Iustin Pop
      bad_instances = map (`Container.find` il) .
170 9f6dcdea Iustin Pop
                      sort . nub $
171 2060348b Iustin Pop
                      concatMap (\ n -> Node.sList n ++ Node.pList n) bad_nodes
172 9188aeef Iustin Pop
  in
173 9188aeef Iustin Pop
    (bad_nodes, bad_instances)
174 9188aeef Iustin Pop
175 525bfb36 Iustin Pop
-- | Zero-initializer for the CStats type.
176 1a7eff0e Iustin Pop
emptyCStats :: CStats
177 86ecce4a Iustin Pop
emptyCStats = CStats 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0
178 1a7eff0e Iustin Pop
179 525bfb36 Iustin Pop
-- | Update stats with data from a new node.
180 1a7eff0e Iustin Pop
updateCStats :: CStats -> Node.Node -> CStats
181 1a7eff0e Iustin Pop
updateCStats cs node =
182 f5b553da Iustin Pop
    let CStats { csFmem = x_fmem, csFdsk = x_fdsk,
183 f5b553da Iustin Pop
                 csAmem = x_amem, csAcpu = x_acpu, csAdsk = x_adsk,
184 f5b553da Iustin Pop
                 csMmem = x_mmem, csMdsk = x_mdsk, csMcpu = x_mcpu,
185 f5b553da Iustin Pop
                 csImem = x_imem, csIdsk = x_idsk, csIcpu = x_icpu,
186 f5b553da Iustin Pop
                 csTmem = x_tmem, csTdsk = x_tdsk, csTcpu = x_tcpu,
187 86ecce4a Iustin Pop
                 csVcpu = x_vcpu,
188 f5b553da Iustin Pop
                 csXmem = x_xmem, csNmem = x_nmem, csNinst = x_ninst
189 8c4c6a8a Iustin Pop
               }
190 1a7eff0e Iustin Pop
            = cs
191 2060348b Iustin Pop
        inc_amem = Node.fMem node - Node.rMem node
192 1a7eff0e Iustin Pop
        inc_amem' = if inc_amem > 0 then inc_amem else 0
193 301789f4 Iustin Pop
        inc_adsk = Node.availDisk node
194 2060348b Iustin Pop
        inc_imem = truncate (Node.tMem node) - Node.nMem node
195 2060348b Iustin Pop
                   - Node.xMem node - Node.fMem node
196 2060348b Iustin Pop
        inc_icpu = Node.uCpu node
197 2060348b Iustin Pop
        inc_idsk = truncate (Node.tDsk node) - Node.fDsk node
198 86ecce4a Iustin Pop
        inc_vcpu = Node.hiCpu node
199 f52dadb2 Iustin Pop
        inc_acpu = Node.availCpu node
200 8c4c6a8a Iustin Pop
201 7034694d Iustin Pop
    in cs { csFmem = x_fmem + fromIntegral (Node.fMem node)
202 7034694d Iustin Pop
          , csFdsk = x_fdsk + fromIntegral (Node.fDsk node)
203 7034694d Iustin Pop
          , csAmem = x_amem + fromIntegral inc_amem'
204 7034694d Iustin Pop
          , csAdsk = x_adsk + fromIntegral inc_adsk
205 7034694d Iustin Pop
          , csAcpu = x_acpu + fromIntegral inc_acpu
206 7034694d Iustin Pop
          , csMmem = max x_mmem (fromIntegral inc_amem')
207 7034694d Iustin Pop
          , csMdsk = max x_mdsk (fromIntegral inc_adsk)
208 7034694d Iustin Pop
          , csMcpu = max x_mcpu (fromIntegral inc_acpu)
209 7034694d Iustin Pop
          , csImem = x_imem + fromIntegral inc_imem
210 7034694d Iustin Pop
          , csIdsk = x_idsk + fromIntegral inc_idsk
211 7034694d Iustin Pop
          , csIcpu = x_icpu + fromIntegral inc_icpu
212 f5b553da Iustin Pop
          , csTmem = x_tmem + Node.tMem node
213 f5b553da Iustin Pop
          , csTdsk = x_tdsk + Node.tDsk node
214 f5b553da Iustin Pop
          , csTcpu = x_tcpu + Node.tCpu node
215 7034694d Iustin Pop
          , csVcpu = x_vcpu + fromIntegral inc_vcpu
216 7034694d Iustin Pop
          , csXmem = x_xmem + fromIntegral (Node.xMem node)
217 7034694d Iustin Pop
          , csNmem = x_nmem + fromIntegral (Node.nMem node)
218 f5b553da Iustin Pop
          , csNinst = x_ninst + length (Node.pList node)
219 de4ac2c2 Iustin Pop
          }
220 1a7eff0e Iustin Pop
221 9188aeef Iustin Pop
-- | Compute the total free disk and memory in the cluster.
222 1a7eff0e Iustin Pop
totalResources :: Node.List -> CStats
223 de4ac2c2 Iustin Pop
totalResources nl =
224 de4ac2c2 Iustin Pop
    let cs = foldl' updateCStats emptyCStats . Container.elems $ nl
225 f5b553da Iustin Pop
    in cs { csScore = compCV nl }
226 9188aeef Iustin Pop
227 9b8fac3d Iustin Pop
-- | Compute the delta between two cluster state.
228 9b8fac3d Iustin Pop
--
229 9b8fac3d Iustin Pop
-- This is used when doing allocations, to understand better the
230 e2436511 Iustin Pop
-- available cluster resources. The return value is a triple of the
231 e2436511 Iustin Pop
-- current used values, the delta that was still allocated, and what
232 e2436511 Iustin Pop
-- was left unallocated.
233 9b8fac3d Iustin Pop
computeAllocationDelta :: CStats -> CStats -> AllocStats
234 9b8fac3d Iustin Pop
computeAllocationDelta cini cfin =
235 9b8fac3d Iustin Pop
    let CStats {csImem = i_imem, csIdsk = i_idsk, csIcpu = i_icpu} = cini
236 9b8fac3d Iustin Pop
        CStats {csImem = f_imem, csIdsk = f_idsk, csIcpu = f_icpu,
237 9b8fac3d Iustin Pop
                csTmem = t_mem, csTdsk = t_dsk, csVcpu = v_cpu } = cfin
238 7034694d Iustin Pop
        rini = RSpec (fromIntegral i_icpu) (fromIntegral i_imem)
239 7034694d Iustin Pop
               (fromIntegral i_idsk)
240 7034694d Iustin Pop
        rfin = RSpec (fromIntegral (f_icpu - i_icpu))
241 7034694d Iustin Pop
               (fromIntegral (f_imem - i_imem))
242 7034694d Iustin Pop
               (fromIntegral (f_idsk - i_idsk))
243 7034694d Iustin Pop
        un_cpu = fromIntegral (v_cpu - f_icpu)::Int
244 7034694d Iustin Pop
        runa = RSpec un_cpu (truncate t_mem - fromIntegral f_imem)
245 7034694d Iustin Pop
               (truncate t_dsk - fromIntegral f_idsk)
246 9b8fac3d Iustin Pop
    in (rini, rfin, runa)
247 9b8fac3d Iustin Pop
248 525bfb36 Iustin Pop
-- | The names and weights of the individual elements in the CV list.
249 8a3b30ca Iustin Pop
detailedCVInfo :: [(Double, String)]
250 8a3b30ca Iustin Pop
detailedCVInfo = [ (1,  "free_mem_cv")
251 8a3b30ca Iustin Pop
                 , (1,  "free_disk_cv")
252 8a3b30ca Iustin Pop
                 , (1,  "n1_cnt")
253 8a3b30ca Iustin Pop
                 , (1,  "reserved_mem_cv")
254 8a3b30ca Iustin Pop
                 , (4,  "offline_all_cnt")
255 8a3b30ca Iustin Pop
                 , (16, "offline_pri_cnt")
256 8a3b30ca Iustin Pop
                 , (1,  "vcpu_ratio_cv")
257 8a3b30ca Iustin Pop
                 , (1,  "cpu_load_cv")
258 8a3b30ca Iustin Pop
                 , (1,  "mem_load_cv")
259 8a3b30ca Iustin Pop
                 , (1,  "disk_load_cv")
260 8a3b30ca Iustin Pop
                 , (1,  "net_load_cv")
261 306cccd5 Iustin Pop
                 , (2,  "pri_tags_score")
262 8a3b30ca Iustin Pop
                 ]
263 8a3b30ca Iustin Pop
264 8a3b30ca Iustin Pop
detailedCVWeights :: [Double]
265 8a3b30ca Iustin Pop
detailedCVWeights = map fst detailedCVInfo
266 fca250e9 Iustin Pop
267 9188aeef Iustin Pop
-- | Compute the mem and disk covariance.
268 fca250e9 Iustin Pop
compDetailedCV :: Node.List -> [Double]
269 9188aeef Iustin Pop
compDetailedCV nl =
270 9188aeef Iustin Pop
    let
271 9188aeef Iustin Pop
        all_nodes = Container.elems nl
272 9188aeef Iustin Pop
        (offline, nodes) = partition Node.offline all_nodes
273 2060348b Iustin Pop
        mem_l = map Node.pMem nodes
274 2060348b Iustin Pop
        dsk_l = map Node.pDsk nodes
275 daee4bed Iustin Pop
        -- metric: memory covariance
276 4715711d Iustin Pop
        mem_cv = stdDev mem_l
277 daee4bed Iustin Pop
        -- metric: disk covariance
278 4715711d Iustin Pop
        dsk_cv = stdDev dsk_l
279 c3c7a0c1 Iustin Pop
        -- metric: count of instances living on N1 failing nodes
280 c3c7a0c1 Iustin Pop
        n1_score = fromIntegral . sum . map (\n -> length (Node.sList n) +
281 c3c7a0c1 Iustin Pop
                                                   length (Node.pList n)) .
282 c3c7a0c1 Iustin Pop
                   filter Node.failN1 $ nodes :: Double
283 2060348b Iustin Pop
        res_l = map Node.pRem nodes
284 daee4bed Iustin Pop
        -- metric: reserved memory covariance
285 4715711d Iustin Pop
        res_cv = stdDev res_l
286 e4d31268 Iustin Pop
        -- offline instances metrics
287 e4d31268 Iustin Pop
        offline_ipri = sum . map (length . Node.pList) $ offline
288 e4d31268 Iustin Pop
        offline_isec = sum . map (length . Node.sList) $ offline
289 e4d31268 Iustin Pop
        -- metric: count of instances on offline nodes
290 e4d31268 Iustin Pop
        off_score = fromIntegral (offline_ipri + offline_isec)::Double
291 673f0f00 Iustin Pop
        -- metric: count of primary instances on offline nodes (this
292 673f0f00 Iustin Pop
        -- helps with evacuation/failover of primary instances on
293 673f0f00 Iustin Pop
        -- 2-node clusters with one node offline)
294 673f0f00 Iustin Pop
        off_pri_score = fromIntegral offline_ipri::Double
295 2060348b Iustin Pop
        cpu_l = map Node.pCpu nodes
296 daee4bed Iustin Pop
        -- metric: covariance of vcpu/pcpu ratio
297 4715711d Iustin Pop
        cpu_cv = stdDev cpu_l
298 daee4bed Iustin Pop
        -- metrics: covariance of cpu, memory, disk and network load
299 ee9724b9 Iustin Pop
        (c_load, m_load, d_load, n_load) = unzip4 $
300 ee9724b9 Iustin Pop
            map (\n ->
301 ee9724b9 Iustin Pop
                     let DynUtil c1 m1 d1 n1 = Node.utilLoad n
302 ee9724b9 Iustin Pop
                         DynUtil c2 m2 d2 n2 = Node.utilPool n
303 ee9724b9 Iustin Pop
                     in (c1/c2, m1/m2, d1/d2, n1/n2)
304 ee9724b9 Iustin Pop
                ) nodes
305 d844fe88 Iustin Pop
        -- metric: conflicting instance count
306 d844fe88 Iustin Pop
        pri_tags_inst = sum $ map Node.conflictingPrimaries nodes
307 d844fe88 Iustin Pop
        pri_tags_score = fromIntegral pri_tags_inst::Double
308 673f0f00 Iustin Pop
    in [ mem_cv, dsk_cv, n1_score, res_cv, off_score, off_pri_score, cpu_cv
309 4715711d Iustin Pop
       , stdDev c_load, stdDev m_load , stdDev d_load, stdDev n_load
310 d844fe88 Iustin Pop
       , pri_tags_score ]
311 9188aeef Iustin Pop
312 9188aeef Iustin Pop
-- | Compute the /total/ variance.
313 9188aeef Iustin Pop
compCV :: Node.List -> Double
314 8a3b30ca Iustin Pop
compCV = sum . zipWith (*) detailedCVWeights . compDetailedCV
315 9188aeef Iustin Pop
316 525bfb36 Iustin Pop
-- | Compute online nodes from a 'Node.List'.
317 dbba5246 Iustin Pop
getOnline :: Node.List -> [Node.Node]
318 dbba5246 Iustin Pop
getOnline = filter (not . Node.offline) . Container.elems
319 dbba5246 Iustin Pop
320 525bfb36 Iustin Pop
-- * Balancing functions
321 9188aeef Iustin Pop
322 9188aeef Iustin Pop
-- | Compute best table. Note that the ordering of the arguments is important.
323 9188aeef Iustin Pop
compareTables :: Table -> Table -> Table
324 9188aeef Iustin Pop
compareTables a@(Table _ _ a_cv _) b@(Table _ _ b_cv _ ) =
325 9188aeef Iustin Pop
    if a_cv > b_cv then b else a
326 9188aeef Iustin Pop
327 9188aeef Iustin Pop
-- | Applies an instance move to a given node list and instance.
328 262a08a2 Iustin Pop
applyMove :: Node.List -> Instance.Instance
329 8880d889 Iustin Pop
          -> IMove -> OpResult (Node.List, Instance.Instance, Ndx, Ndx)
330 00b51a14 Iustin Pop
-- Failover (f)
331 e4f08c46 Iustin Pop
applyMove nl inst Failover =
332 2060348b Iustin Pop
    let old_pdx = Instance.pNode inst
333 2060348b Iustin Pop
        old_sdx = Instance.sNode inst
334 e4f08c46 Iustin Pop
        old_p = Container.find old_pdx nl
335 e4f08c46 Iustin Pop
        old_s = Container.find old_sdx nl
336 e4f08c46 Iustin Pop
        int_p = Node.removePri old_p inst
337 e4f08c46 Iustin Pop
        int_s = Node.removeSec old_s inst
338 2cae47e9 Iustin Pop
        force_p = Node.offline old_p
339 b161386d Iustin Pop
        new_nl = do -- Maybe monad
340 2cae47e9 Iustin Pop
          new_p <- Node.addPriEx force_p int_s inst
341 b161386d Iustin Pop
          new_s <- Node.addSec int_p inst old_sdx
342 8880d889 Iustin Pop
          let new_inst = Instance.setBoth inst old_sdx old_pdx
343 8880d889 Iustin Pop
          return (Container.addTwo old_pdx new_s old_sdx new_p nl,
344 8880d889 Iustin Pop
                  new_inst, old_sdx, old_pdx)
345 8880d889 Iustin Pop
    in new_nl
346 e4f08c46 Iustin Pop
347 00b51a14 Iustin Pop
-- Replace the primary (f:, r:np, f)
348 e4f08c46 Iustin Pop
applyMove nl inst (ReplacePrimary new_pdx) =
349 2060348b Iustin Pop
    let old_pdx = Instance.pNode inst
350 2060348b Iustin Pop
        old_sdx = Instance.sNode inst
351 e4f08c46 Iustin Pop
        old_p = Container.find old_pdx nl
352 e4f08c46 Iustin Pop
        old_s = Container.find old_sdx nl
353 e4f08c46 Iustin Pop
        tgt_n = Container.find new_pdx nl
354 e4f08c46 Iustin Pop
        int_p = Node.removePri old_p inst
355 e4f08c46 Iustin Pop
        int_s = Node.removeSec old_s inst
356 2cae47e9 Iustin Pop
        force_p = Node.offline old_p
357 b161386d Iustin Pop
        new_nl = do -- Maybe monad
358 70db354e Iustin Pop
          -- check that the current secondary can host the instance
359 70db354e Iustin Pop
          -- during the migration
360 2cae47e9 Iustin Pop
          tmp_s <- Node.addPriEx force_p int_s inst
361 70db354e Iustin Pop
          let tmp_s' = Node.removePri tmp_s inst
362 2cae47e9 Iustin Pop
          new_p <- Node.addPriEx force_p tgt_n inst
363 2cae47e9 Iustin Pop
          new_s <- Node.addSecEx force_p tmp_s' inst new_pdx
364 8880d889 Iustin Pop
          let new_inst = Instance.setPri inst new_pdx
365 8880d889 Iustin Pop
          return (Container.add new_pdx new_p $
366 8880d889 Iustin Pop
                  Container.addTwo old_pdx int_p old_sdx new_s nl,
367 8880d889 Iustin Pop
                  new_inst, new_pdx, old_sdx)
368 8880d889 Iustin Pop
    in new_nl
369 e4f08c46 Iustin Pop
370 00b51a14 Iustin Pop
-- Replace the secondary (r:ns)
371 e4f08c46 Iustin Pop
applyMove nl inst (ReplaceSecondary new_sdx) =
372 2060348b Iustin Pop
    let old_pdx = Instance.pNode inst
373 2060348b Iustin Pop
        old_sdx = Instance.sNode inst
374 e4f08c46 Iustin Pop
        old_s = Container.find old_sdx nl
375 e4f08c46 Iustin Pop
        tgt_n = Container.find new_sdx nl
376 e4f08c46 Iustin Pop
        int_s = Node.removeSec old_s inst
377 2cae47e9 Iustin Pop
        force_s = Node.offline old_s
378 8880d889 Iustin Pop
        new_inst = Instance.setSec inst new_sdx
379 2cae47e9 Iustin Pop
        new_nl = Node.addSecEx force_s tgt_n inst old_pdx >>=
380 8880d889 Iustin Pop
                 \new_s -> return (Container.addTwo new_sdx
381 8880d889 Iustin Pop
                                   new_s old_sdx int_s nl,
382 8880d889 Iustin Pop
                                   new_inst, old_pdx, new_sdx)
383 8880d889 Iustin Pop
    in new_nl
384 e4f08c46 Iustin Pop
385 00b51a14 Iustin Pop
-- Replace the secondary and failover (r:np, f)
386 79ac6b6f Iustin Pop
applyMove nl inst (ReplaceAndFailover new_pdx) =
387 2060348b Iustin Pop
    let old_pdx = Instance.pNode inst
388 2060348b Iustin Pop
        old_sdx = Instance.sNode inst
389 79ac6b6f Iustin Pop
        old_p = Container.find old_pdx nl
390 79ac6b6f Iustin Pop
        old_s = Container.find old_sdx nl
391 79ac6b6f Iustin Pop
        tgt_n = Container.find new_pdx nl
392 79ac6b6f Iustin Pop
        int_p = Node.removePri old_p inst
393 79ac6b6f Iustin Pop
        int_s = Node.removeSec old_s inst
394 2cae47e9 Iustin Pop
        force_s = Node.offline old_s
395 b161386d Iustin Pop
        new_nl = do -- Maybe monad
396 b161386d Iustin Pop
          new_p <- Node.addPri tgt_n inst
397 2cae47e9 Iustin Pop
          new_s <- Node.addSecEx force_s int_p inst new_pdx
398 8880d889 Iustin Pop
          let new_inst = Instance.setBoth inst new_pdx old_pdx
399 8880d889 Iustin Pop
          return (Container.add new_pdx new_p $
400 8880d889 Iustin Pop
                  Container.addTwo old_pdx new_s old_sdx int_s nl,
401 8880d889 Iustin Pop
                  new_inst, new_pdx, old_pdx)
402 8880d889 Iustin Pop
    in new_nl
403 79ac6b6f Iustin Pop
404 19493d33 Iustin Pop
-- Failver and replace the secondary (f, r:ns)
405 19493d33 Iustin Pop
applyMove nl inst (FailoverAndReplace new_sdx) =
406 2060348b Iustin Pop
    let old_pdx = Instance.pNode inst
407 2060348b Iustin Pop
        old_sdx = Instance.sNode inst
408 19493d33 Iustin Pop
        old_p = Container.find old_pdx nl
409 19493d33 Iustin Pop
        old_s = Container.find old_sdx nl
410 19493d33 Iustin Pop
        tgt_n = Container.find new_sdx nl
411 19493d33 Iustin Pop
        int_p = Node.removePri old_p inst
412 19493d33 Iustin Pop
        int_s = Node.removeSec old_s inst
413 2cae47e9 Iustin Pop
        force_p = Node.offline old_p
414 b161386d Iustin Pop
        new_nl = do -- Maybe monad
415 2cae47e9 Iustin Pop
          new_p <- Node.addPriEx force_p int_s inst
416 2cae47e9 Iustin Pop
          new_s <- Node.addSecEx force_p tgt_n inst old_sdx
417 8880d889 Iustin Pop
          let new_inst = Instance.setBoth inst old_sdx new_sdx
418 8880d889 Iustin Pop
          return (Container.add new_sdx new_s $
419 8880d889 Iustin Pop
                  Container.addTwo old_sdx new_p old_pdx int_p nl,
420 8880d889 Iustin Pop
                  new_inst, old_sdx, new_sdx)
421 8880d889 Iustin Pop
    in new_nl
422 19493d33 Iustin Pop
423 9188aeef Iustin Pop
-- | Tries to allocate an instance on one given node.
424 0d66ea67 Iustin Pop
allocateOnSingle :: Node.List -> Instance.Instance -> Ndx
425 1fe81531 Iustin Pop
                 -> OpResult Node.AllocElement
426 0d66ea67 Iustin Pop
allocateOnSingle nl inst new_pdx =
427 0d66ea67 Iustin Pop
    let p = Container.find new_pdx nl
428 8880d889 Iustin Pop
        new_inst = Instance.setBoth inst new_pdx Node.noSecondary
429 7d3f4253 Iustin Pop
    in  Node.addPri p inst >>= \new_p -> do
430 7d3f4253 Iustin Pop
      let new_nl = Container.add new_pdx new_p nl
431 7d3f4253 Iustin Pop
          new_score = compCV nl
432 7d3f4253 Iustin Pop
      return (new_nl, new_inst, [new_p], new_score)
433 5e15f460 Iustin Pop
434 9188aeef Iustin Pop
-- | Tries to allocate an instance on a given pair of nodes.
435 0d66ea67 Iustin Pop
allocateOnPair :: Node.List -> Instance.Instance -> Ndx -> Ndx
436 1fe81531 Iustin Pop
               -> OpResult Node.AllocElement
437 0d66ea67 Iustin Pop
allocateOnPair nl inst new_pdx new_sdx =
438 0d66ea67 Iustin Pop
    let tgt_p = Container.find new_pdx nl
439 0d66ea67 Iustin Pop
        tgt_s = Container.find new_sdx nl
440 7d3f4253 Iustin Pop
    in do
441 7d3f4253 Iustin Pop
      new_p <- Node.addPri tgt_p inst
442 7d3f4253 Iustin Pop
      new_s <- Node.addSec tgt_s inst new_pdx
443 7d3f4253 Iustin Pop
      let new_inst = Instance.setBoth inst new_pdx new_sdx
444 7d3f4253 Iustin Pop
          new_nl = Container.addTwo new_pdx new_p new_sdx new_s nl
445 7d3f4253 Iustin Pop
      return (new_nl, new_inst, [new_p, new_s], compCV new_nl)
446 4a340313 Iustin Pop
447 9188aeef Iustin Pop
-- | Tries to perform an instance move and returns the best table
448 9188aeef Iustin Pop
-- between the original one and the new one.
449 e4f08c46 Iustin Pop
checkSingleStep :: Table -- ^ The original table
450 e4f08c46 Iustin Pop
                -> Instance.Instance -- ^ The instance to move
451 e4f08c46 Iustin Pop
                -> Table -- ^ The current best table
452 e4f08c46 Iustin Pop
                -> IMove -- ^ The move to apply
453 e4f08c46 Iustin Pop
                -> Table -- ^ The final best table
454 e4f08c46 Iustin Pop
checkSingleStep ini_tbl target cur_tbl move =
455 e4f08c46 Iustin Pop
    let
456 e4f08c46 Iustin Pop
        Table ini_nl ini_il _ ini_plc = ini_tbl
457 8880d889 Iustin Pop
        tmp_resu = applyMove ini_nl target move
458 e4f08c46 Iustin Pop
    in
459 8880d889 Iustin Pop
      case tmp_resu of
460 f2280553 Iustin Pop
        OpFail _ -> cur_tbl
461 3173c987 Iustin Pop
        OpGood (upd_nl, new_inst, pri_idx, sec_idx) ->
462 f2280553 Iustin Pop
            let tgt_idx = Instance.idx target
463 f2280553 Iustin Pop
                upd_cvar = compCV upd_nl
464 f2280553 Iustin Pop
                upd_il = Container.add tgt_idx new_inst ini_il
465 3173c987 Iustin Pop
                upd_plc = (tgt_idx, pri_idx, sec_idx, move, upd_cvar):ini_plc
466 f2280553 Iustin Pop
                upd_tbl = Table upd_nl upd_il upd_cvar upd_plc
467 f2280553 Iustin Pop
            in
468 f2280553 Iustin Pop
              compareTables cur_tbl upd_tbl
469 e4f08c46 Iustin Pop
470 c0501c69 Iustin Pop
-- | Given the status of the current secondary as a valid new node and
471 c0501c69 Iustin Pop
-- the current candidate target node, generate the possible moves for
472 c0501c69 Iustin Pop
-- a instance.
473 c0501c69 Iustin Pop
possibleMoves :: Bool      -- ^ Whether the secondary node is a valid new node
474 e08424a8 Guido Trotter
              -> Bool      -- ^ Whether we can change the primary node
475 c0501c69 Iustin Pop
              -> Ndx       -- ^ Target node candidate
476 c0501c69 Iustin Pop
              -> [IMove]   -- ^ List of valid result moves
477 e08424a8 Guido Trotter
478 e08424a8 Guido Trotter
possibleMoves _ False tdx =
479 e08424a8 Guido Trotter
    [ReplaceSecondary tdx]
480 e08424a8 Guido Trotter
481 e08424a8 Guido Trotter
possibleMoves True True tdx =
482 40d4eba0 Iustin Pop
    [ReplaceSecondary tdx,
483 40d4eba0 Iustin Pop
     ReplaceAndFailover tdx,
484 40d4eba0 Iustin Pop
     ReplacePrimary tdx,
485 40d4eba0 Iustin Pop
     FailoverAndReplace tdx]
486 40d4eba0 Iustin Pop
487 e08424a8 Guido Trotter
possibleMoves False True tdx =
488 40d4eba0 Iustin Pop
    [ReplaceSecondary tdx,
489 40d4eba0 Iustin Pop
     ReplaceAndFailover tdx]
490 40d4eba0 Iustin Pop
491 40d4eba0 Iustin Pop
-- | Compute the best move for a given instance.
492 c0501c69 Iustin Pop
checkInstanceMove :: [Ndx]             -- ^ Allowed target node indices
493 c0501c69 Iustin Pop
                  -> Bool              -- ^ Whether disk moves are allowed
494 e08424a8 Guido Trotter
                  -> Bool              -- ^ Whether instance moves are allowed
495 c0501c69 Iustin Pop
                  -> Table             -- ^ Original table
496 c0501c69 Iustin Pop
                  -> Instance.Instance -- ^ Instance to move
497 c0501c69 Iustin Pop
                  -> Table             -- ^ Best new table for this instance
498 e08424a8 Guido Trotter
checkInstanceMove nodes_idx disk_moves inst_moves ini_tbl target =
499 4e25d1c2 Iustin Pop
    let
500 2060348b Iustin Pop
        opdx = Instance.pNode target
501 2060348b Iustin Pop
        osdx = Instance.sNode target
502 9dc6023f Iustin Pop
        nodes = filter (\idx -> idx /= opdx && idx /= osdx) nodes_idx
503 e08424a8 Guido Trotter
        use_secondary = elem osdx nodes_idx && inst_moves
504 40d4eba0 Iustin Pop
        aft_failover = if use_secondary -- if allowed to failover
505 40d4eba0 Iustin Pop
                       then checkSingleStep ini_tbl target ini_tbl Failover
506 40d4eba0 Iustin Pop
                       else ini_tbl
507 c0501c69 Iustin Pop
        all_moves = if disk_moves
508 e08424a8 Guido Trotter
                    then concatMap
509 e08424a8 Guido Trotter
                         (possibleMoves use_secondary inst_moves) nodes
510 c0501c69 Iustin Pop
                    else []
511 4e25d1c2 Iustin Pop
    in
512 4e25d1c2 Iustin Pop
      -- iterate over the possible nodes for this instance
513 9dc6023f Iustin Pop
      foldl' (checkSingleStep ini_tbl target) aft_failover all_moves
514 4e25d1c2 Iustin Pop
515 e4f08c46 Iustin Pop
-- | Compute the best next move.
516 608efcce Iustin Pop
checkMove :: [Ndx]               -- ^ Allowed target node indices
517 c0501c69 Iustin Pop
          -> Bool                -- ^ Whether disk moves are allowed
518 e08424a8 Guido Trotter
          -> Bool                -- ^ Whether instance moves are allowed
519 256810de Iustin Pop
          -> Table               -- ^ The current solution
520 e4f08c46 Iustin Pop
          -> [Instance.Instance] -- ^ List of instances still to move
521 256810de Iustin Pop
          -> Table               -- ^ The new solution
522 e08424a8 Guido Trotter
checkMove nodes_idx disk_moves inst_moves ini_tbl victims =
523 4e25d1c2 Iustin Pop
    let Table _ _ _ ini_plc = ini_tbl
524 a3eee4ad Iustin Pop
        -- we're using rwhnf from the Control.Parallel.Strategies
525 a3eee4ad Iustin Pop
        -- package; we don't need to use rnf as that would force too
526 a3eee4ad Iustin Pop
        -- much evaluation in single-threaded cases, and in
527 a3eee4ad Iustin Pop
        -- multi-threaded case the weak head normal form is enough to
528 a3eee4ad Iustin Pop
        -- spark the evaluation
529 e08424a8 Guido Trotter
        tables = parMap rwhnf (checkInstanceMove nodes_idx disk_moves
530 e08424a8 Guido Trotter
                               inst_moves ini_tbl)
531 a3eee4ad Iustin Pop
                 victims
532 4e25d1c2 Iustin Pop
        -- iterate over all instances, computing the best move
533 2a8e2dc9 Iustin Pop
        best_tbl = foldl' compareTables ini_tbl tables
534 aaaa0e43 Iustin Pop
        Table _ _ _ best_plc = best_tbl
535 a804261a Iustin Pop
    in if length best_plc == length ini_plc
536 a804261a Iustin Pop
       then ini_tbl -- no advancement
537 a804261a Iustin Pop
       else best_tbl
538 e4f08c46 Iustin Pop
539 525bfb36 Iustin Pop
-- | Check if we are allowed to go deeper in the balancing.
540 3fea6959 Iustin Pop
doNextBalance :: Table     -- ^ The starting table
541 3fea6959 Iustin Pop
              -> Int       -- ^ Remaining length
542 3fea6959 Iustin Pop
              -> Score     -- ^ Score at which to stop
543 3fea6959 Iustin Pop
              -> Bool      -- ^ The resulting table and commands
544 5ad86777 Iustin Pop
doNextBalance ini_tbl max_rounds min_score =
545 5ad86777 Iustin Pop
    let Table _ _ ini_cv ini_plc = ini_tbl
546 5ad86777 Iustin Pop
        ini_plc_len = length ini_plc
547 5ad86777 Iustin Pop
    in (max_rounds < 0 || ini_plc_len < max_rounds) && ini_cv > min_score
548 5ad86777 Iustin Pop
549 525bfb36 Iustin Pop
-- | Run a balance move.
550 f25e5aac Iustin Pop
tryBalance :: Table       -- ^ The starting table
551 f25e5aac Iustin Pop
           -> Bool        -- ^ Allow disk moves
552 e08424a8 Guido Trotter
           -> Bool        -- ^ Allow instance moves
553 2e28ac32 Iustin Pop
           -> Bool        -- ^ Only evacuate moves
554 848b65c9 Iustin Pop
           -> Score       -- ^ Min gain threshold
555 848b65c9 Iustin Pop
           -> Score       -- ^ Min gain
556 f25e5aac Iustin Pop
           -> Maybe Table -- ^ The resulting table and commands
557 e08424a8 Guido Trotter
tryBalance ini_tbl disk_moves inst_moves evac_mode mg_limit min_gain =
558 5ad86777 Iustin Pop
    let Table ini_nl ini_il ini_cv _ = ini_tbl
559 5ad86777 Iustin Pop
        all_inst = Container.elems ini_il
560 2e28ac32 Iustin Pop
        all_inst' = if evac_mode
561 2e28ac32 Iustin Pop
                    then let bad_nodes = map Node.idx . filter Node.offline $
562 2e28ac32 Iustin Pop
                                         Container.elems ini_nl
563 2e28ac32 Iustin Pop
                         in filter (\e -> Instance.sNode e `elem` bad_nodes ||
564 2e28ac32 Iustin Pop
                                          Instance.pNode e `elem` bad_nodes)
565 2e28ac32 Iustin Pop
                            all_inst
566 2e28ac32 Iustin Pop
                    else all_inst
567 c424cdc8 Iustin Pop
        reloc_inst = filter Instance.movable all_inst'
568 5ad86777 Iustin Pop
        node_idx = map Node.idx . filter (not . Node.offline) $
569 5ad86777 Iustin Pop
                   Container.elems ini_nl
570 e08424a8 Guido Trotter
        fin_tbl = checkMove node_idx disk_moves inst_moves ini_tbl reloc_inst
571 5ad86777 Iustin Pop
        (Table _ _ fin_cv _) = fin_tbl
572 f25e5aac Iustin Pop
    in
573 848b65c9 Iustin Pop
      if fin_cv < ini_cv && (ini_cv > mg_limit || ini_cv - fin_cv >= min_gain)
574 5ad86777 Iustin Pop
      then Just fin_tbl -- this round made success, return the new table
575 f25e5aac Iustin Pop
      else Nothing
576 f25e5aac Iustin Pop
577 478df686 Iustin Pop
-- * Allocation functions
578 478df686 Iustin Pop
579 525bfb36 Iustin Pop
-- | Build failure stats out of a list of failures.
580 478df686 Iustin Pop
collapseFailures :: [FailMode] -> FailStats
581 478df686 Iustin Pop
collapseFailures flst =
582 5182e970 Iustin Pop
    map (\k -> (k, length $ filter (k ==) flst)) [minBound..maxBound]
583 478df686 Iustin Pop
584 478df686 Iustin Pop
-- | Update current Allocation solution and failure stats with new
585 525bfb36 Iustin Pop
-- elements.
586 1fe81531 Iustin Pop
concatAllocs :: AllocSolution -> OpResult Node.AllocElement -> AllocSolution
587 85d0ddc3 Iustin Pop
concatAllocs as (OpFail reason) = as { asFailures = reason : asFailures as }
588 478df686 Iustin Pop
589 85d0ddc3 Iustin Pop
concatAllocs as (OpGood ns@(_, _, _, nscore)) =
590 7d3f4253 Iustin Pop
    let -- Choose the old or new solution, based on the cluster score
591 85d0ddc3 Iustin Pop
        cntok = asAllocs as
592 85d0ddc3 Iustin Pop
        osols = asSolutions as
593 478df686 Iustin Pop
        nsols = case osols of
594 a334d536 Iustin Pop
                  [] -> [ns]
595 a334d536 Iustin Pop
                  (_, _, _, oscore):[] ->
596 478df686 Iustin Pop
                      if oscore < nscore
597 478df686 Iustin Pop
                      then osols
598 a334d536 Iustin Pop
                      else [ns]
599 23f9ab76 Iustin Pop
                  -- FIXME: here we simply concat to lists with more
600 23f9ab76 Iustin Pop
                  -- than one element; we should instead abort, since
601 23f9ab76 Iustin Pop
                  -- this is not a valid usage of this function
602 a334d536 Iustin Pop
                  xs -> ns:xs
603 fbb95f28 Iustin Pop
        nsuc = cntok + 1
604 478df686 Iustin Pop
    -- Note: we force evaluation of nsols here in order to keep the
605 478df686 Iustin Pop
    -- memory profile low - we know that we will need nsols for sure
606 478df686 Iustin Pop
    -- in the next cycle, so we force evaluation of nsols, since the
607 478df686 Iustin Pop
    -- foldl' in the caller will only evaluate the tuple, but not the
608 7d11799b Iustin Pop
    -- elements of the tuple
609 85d0ddc3 Iustin Pop
    in nsols `seq` nsuc `seq` as { asAllocs = nsuc, asSolutions = nsols }
610 dbba5246 Iustin Pop
611 1bc47d38 Iustin Pop
-- | Sums two allocation solutions (e.g. for two separate node groups).
612 1bc47d38 Iustin Pop
sumAllocs :: AllocSolution -> AllocSolution -> AllocSolution
613 1bc47d38 Iustin Pop
sumAllocs (AllocSolution af aa as al) (AllocSolution bf ba bs bl) =
614 1bc47d38 Iustin Pop
    AllocSolution (af ++ bf) (aa + ba) (as ++ bs) (al ++ bl)
615 1bc47d38 Iustin Pop
616 525bfb36 Iustin Pop
-- | Given a solution, generates a reasonable description for it.
617 859fc11d Iustin Pop
describeSolution :: AllocSolution -> String
618 859fc11d Iustin Pop
describeSolution as =
619 859fc11d Iustin Pop
  let fcnt = asFailures as
620 859fc11d Iustin Pop
      sols = asSolutions as
621 859fc11d Iustin Pop
      freasons =
622 859fc11d Iustin Pop
        intercalate ", " . map (\(a, b) -> printf "%s: %d" (show a) b) .
623 859fc11d Iustin Pop
        filter ((> 0) . snd) . collapseFailures $ fcnt
624 859fc11d Iustin Pop
  in if null sols
625 859fc11d Iustin Pop
     then "No valid allocation solutions, failure reasons: " ++
626 859fc11d Iustin Pop
          (if null fcnt
627 859fc11d Iustin Pop
           then "unknown reasons"
628 859fc11d Iustin Pop
           else freasons)
629 859fc11d Iustin Pop
     else let (_, _, nodes, cv) = head sols
630 859fc11d Iustin Pop
          in printf ("score: %.8f, successes %d, failures %d (%s)" ++
631 859fc11d Iustin Pop
                     " for node(s) %s") cv (asAllocs as) (length fcnt) freasons
632 859fc11d Iustin Pop
             (intercalate "/" . map Node.name $ nodes)
633 859fc11d Iustin Pop
634 525bfb36 Iustin Pop
-- | Annotates a solution with the appropriate string.
635 859fc11d Iustin Pop
annotateSolution :: AllocSolution -> AllocSolution
636 859fc11d Iustin Pop
annotateSolution as = as { asLog = describeSolution as : asLog as }
637 859fc11d Iustin Pop
638 6cb1649f Iustin Pop
-- | Generate the valid node allocation singles or pairs for a new instance.
639 6d0bc5ca Iustin Pop
genAllocNodes :: Group.List        -- ^ Group list
640 6d0bc5ca Iustin Pop
              -> Node.List         -- ^ The node map
641 6cb1649f Iustin Pop
              -> Int               -- ^ The number of nodes required
642 6d0bc5ca Iustin Pop
              -> Bool              -- ^ Whether to drop or not
643 6d0bc5ca Iustin Pop
                                   -- unallocable nodes
644 6cb1649f Iustin Pop
              -> Result AllocNodes -- ^ The (monadic) result
645 6d0bc5ca Iustin Pop
genAllocNodes gl nl count drop_unalloc =
646 6d0bc5ca Iustin Pop
    let filter_fn = if drop_unalloc
647 e4491427 Iustin Pop
                    then filter (Group.isAllocable .
648 e4491427 Iustin Pop
                                 flip Container.find gl . Node.group)
649 6d0bc5ca Iustin Pop
                    else id
650 6d0bc5ca Iustin Pop
        all_nodes = filter_fn $ getOnline nl
651 6cb1649f Iustin Pop
        all_pairs = liftM2 (,) all_nodes all_nodes
652 6cb1649f Iustin Pop
        ok_pairs = filter (\(x, y) -> Node.idx x /= Node.idx y &&
653 6cb1649f Iustin Pop
                                      Node.group x == Node.group y) all_pairs
654 6cb1649f Iustin Pop
    in case count of
655 0d66ea67 Iustin Pop
         1 -> Ok (Left (map Node.idx all_nodes))
656 0d66ea67 Iustin Pop
         2 -> Ok (Right (map (\(p, s) -> (Node.idx p, Node.idx s)) ok_pairs))
657 6cb1649f Iustin Pop
         _ -> Bad "Unsupported number of nodes, only one or two  supported"
658 6cb1649f Iustin Pop
659 dbba5246 Iustin Pop
-- | Try to allocate an instance on the cluster.
660 dbba5246 Iustin Pop
tryAlloc :: (Monad m) =>
661 dbba5246 Iustin Pop
            Node.List         -- ^ The node list
662 dbba5246 Iustin Pop
         -> Instance.List     -- ^ The instance list
663 dbba5246 Iustin Pop
         -> Instance.Instance -- ^ The instance to allocate
664 6cb1649f Iustin Pop
         -> AllocNodes        -- ^ The allocation targets
665 78694255 Iustin Pop
         -> m AllocSolution   -- ^ Possible solution list
666 6cb1649f Iustin Pop
tryAlloc nl _ inst (Right ok_pairs) =
667 6cb1649f Iustin Pop
    let sols = foldl' (\cstate (p, s) ->
668 478df686 Iustin Pop
                           concatAllocs cstate $ allocateOnPair nl inst p s
669 97936d51 Iustin Pop
                      ) emptyAllocSolution ok_pairs
670 859fc11d Iustin Pop
671 dec88196 Iustin Pop
    in if null ok_pairs -- means we have just one node
672 dec88196 Iustin Pop
       then fail "Not enough online nodes"
673 dec88196 Iustin Pop
       else return $ annotateSolution sols
674 dbba5246 Iustin Pop
675 6cb1649f Iustin Pop
tryAlloc nl _ inst (Left all_nodes) =
676 6cb1649f Iustin Pop
    let sols = foldl' (\cstate ->
677 2485487d Iustin Pop
                           concatAllocs cstate . allocateOnSingle nl inst
678 97936d51 Iustin Pop
                      ) emptyAllocSolution all_nodes
679 dec88196 Iustin Pop
    in if null all_nodes
680 dec88196 Iustin Pop
       then fail "No online nodes"
681 dec88196 Iustin Pop
       else return $ annotateSolution sols
682 dbba5246 Iustin Pop
683 525bfb36 Iustin Pop
-- | Given a group/result, describe it as a nice (list of) messages.
684 aec636b9 Iustin Pop
solutionDescription :: Group.List -> (Gdx, Result AllocSolution) -> [String]
685 aec636b9 Iustin Pop
solutionDescription gl (groupId, result) =
686 9b1584fc Iustin Pop
  case result of
687 73206d0a Iustin Pop
    Ok solution -> map (printf "Group %s (%s): %s" gname pol) (asLog solution)
688 aec636b9 Iustin Pop
    Bad message -> [printf "Group %s: error %s" gname message]
689 73206d0a Iustin Pop
  where grp = Container.find groupId gl
690 73206d0a Iustin Pop
        gname = Group.name grp
691 73206d0a Iustin Pop
        pol = apolToString (Group.allocPolicy grp)
692 9b1584fc Iustin Pop
693 9b1584fc Iustin Pop
-- | From a list of possibly bad and possibly empty solutions, filter
694 88253d03 Iustin Pop
-- only the groups with a valid result. Note that the result will be
695 525bfb36 Iustin Pop
-- reversed compared to the original list.
696 73206d0a Iustin Pop
filterMGResults :: Group.List
697 73206d0a Iustin Pop
                -> [(Gdx, Result AllocSolution)]
698 73206d0a Iustin Pop
                -> [(Gdx, AllocSolution)]
699 88253d03 Iustin Pop
filterMGResults gl = foldl' fn []
700 88253d03 Iustin Pop
    where unallocable = not . Group.isAllocable . flip Container.find gl
701 88253d03 Iustin Pop
          fn accu (gdx, rasol) =
702 88253d03 Iustin Pop
              case rasol of
703 88253d03 Iustin Pop
                Bad _ -> accu
704 88253d03 Iustin Pop
                Ok sol | null (asSolutions sol) -> accu
705 88253d03 Iustin Pop
                       | unallocable gdx -> accu
706 88253d03 Iustin Pop
                       | otherwise -> (gdx, sol):accu
707 9b1584fc Iustin Pop
708 525bfb36 Iustin Pop
-- | Sort multigroup results based on policy and score.
709 73206d0a Iustin Pop
sortMGResults :: Group.List
710 73206d0a Iustin Pop
             -> [(Gdx, AllocSolution)]
711 73206d0a Iustin Pop
             -> [(Gdx, AllocSolution)]
712 73206d0a Iustin Pop
sortMGResults gl sols =
713 2a8e2dc9 Iustin Pop
    let extractScore (_, _, _, x) = x
714 73206d0a Iustin Pop
        solScore (gdx, sol) = (Group.allocPolicy (Container.find gdx gl),
715 73206d0a Iustin Pop
                               (extractScore . head . asSolutions) sol)
716 73206d0a Iustin Pop
    in sortBy (comparing solScore) sols
717 73206d0a Iustin Pop
718 9b1584fc Iustin Pop
-- | Try to allocate an instance on a multi-group cluster.
719 aec636b9 Iustin Pop
tryMGAlloc :: Group.List           -- ^ The group list
720 aec636b9 Iustin Pop
           -> Node.List            -- ^ The node list
721 aec636b9 Iustin Pop
           -> Instance.List        -- ^ The instance list
722 aec636b9 Iustin Pop
           -> Instance.Instance    -- ^ The instance to allocate
723 aec636b9 Iustin Pop
           -> Int                  -- ^ Required number of nodes
724 aec636b9 Iustin Pop
           -> Result AllocSolution -- ^ Possible solution list
725 aec636b9 Iustin Pop
tryMGAlloc mggl mgnl mgil inst cnt =
726 9b1584fc Iustin Pop
  let groups = splitCluster mgnl mgil
727 9b1584fc Iustin Pop
      sols = map (\(gid, (nl, il)) ->
728 6d0bc5ca Iustin Pop
                   (gid, genAllocNodes mggl nl cnt False >>=
729 6d0bc5ca Iustin Pop
                       tryAlloc nl il inst))
730 6cb1649f Iustin Pop
             groups::[(Gdx, Result AllocSolution)]
731 aec636b9 Iustin Pop
      all_msgs = concatMap (solutionDescription mggl) sols
732 73206d0a Iustin Pop
      goodSols = filterMGResults mggl sols
733 73206d0a Iustin Pop
      sortedSols = sortMGResults mggl goodSols
734 9b1584fc Iustin Pop
  in if null sortedSols
735 9b1584fc Iustin Pop
     then Bad $ intercalate ", " all_msgs
736 9b1584fc Iustin Pop
     else let (final_group, final_sol) = head sortedSols
737 aec636b9 Iustin Pop
              final_name = Group.name $ Container.find final_group mggl
738 aec636b9 Iustin Pop
              selmsg = "Selected group: " ++  final_name
739 9b1584fc Iustin Pop
          in Ok $ final_sol { asLog = selmsg:all_msgs }
740 9b1584fc Iustin Pop
741 9b1584fc Iustin Pop
-- | Try to relocate an instance on the cluster.
742 dbba5246 Iustin Pop
tryReloc :: (Monad m) =>
743 78694255 Iustin Pop
            Node.List       -- ^ The node list
744 78694255 Iustin Pop
         -> Instance.List   -- ^ The instance list
745 78694255 Iustin Pop
         -> Idx             -- ^ The index of the instance to move
746 478df686 Iustin Pop
         -> Int             -- ^ The number of nodes required
747 78694255 Iustin Pop
         -> [Ndx]           -- ^ Nodes which should not be used
748 78694255 Iustin Pop
         -> m AllocSolution -- ^ Solution list
749 dbba5246 Iustin Pop
tryReloc nl il xid 1 ex_idx =
750 dbba5246 Iustin Pop
    let all_nodes = getOnline nl
751 dbba5246 Iustin Pop
        inst = Container.find xid il
752 2060348b Iustin Pop
        ex_idx' = Instance.pNode inst:ex_idx
753 dbba5246 Iustin Pop
        valid_nodes = filter (not . flip elem ex_idx' . Node.idx) all_nodes
754 dbba5246 Iustin Pop
        valid_idxes = map Node.idx valid_nodes
755 478df686 Iustin Pop
        sols1 = foldl' (\cstate x ->
756 fbb95f28 Iustin Pop
                            let em = do
757 478df686 Iustin Pop
                                  (mnl, i, _, _) <-
758 478df686 Iustin Pop
                                      applyMove nl inst (ReplaceSecondary x)
759 7d3f4253 Iustin Pop
                                  return (mnl, i, [Container.find x mnl],
760 7d3f4253 Iustin Pop
                                          compCV mnl)
761 fbb95f28 Iustin Pop
                            in concatAllocs cstate em
762 97936d51 Iustin Pop
                       ) emptyAllocSolution valid_idxes
763 dbba5246 Iustin Pop
    in return sols1
764 dbba5246 Iustin Pop
765 dbba5246 Iustin Pop
tryReloc _ _ _ reqn _  = fail $ "Unsupported number of relocation \
766 9f6dcdea Iustin Pop
                                \destinations required (" ++ show reqn ++
767 dbba5246 Iustin Pop
                                                  "), only one supported"
768 e4f08c46 Iustin Pop
769 4bc33d60 Iustin Pop
tryMGReloc :: (Monad m) =>
770 4bc33d60 Iustin Pop
              Group.List      -- ^ The group list
771 4bc33d60 Iustin Pop
           -> Node.List       -- ^ The node list
772 4bc33d60 Iustin Pop
           -> Instance.List   -- ^ The instance list
773 4bc33d60 Iustin Pop
           -> Idx             -- ^ The index of the instance to move
774 4bc33d60 Iustin Pop
           -> Int             -- ^ The number of nodes required
775 4bc33d60 Iustin Pop
           -> [Ndx]           -- ^ Nodes which should not be used
776 4bc33d60 Iustin Pop
           -> m AllocSolution -- ^ Solution list
777 4bc33d60 Iustin Pop
tryMGReloc _ mgnl mgil xid ncount ex_ndx = do
778 4bc33d60 Iustin Pop
  let groups = splitCluster mgnl mgil
779 4bc33d60 Iustin Pop
      -- TODO: we only relocate inside the group for now
780 4bc33d60 Iustin Pop
      inst = Container.find xid mgil
781 4bc33d60 Iustin Pop
  (nl, il) <- case lookup (instancePriGroup mgnl inst) groups of
782 4bc33d60 Iustin Pop
                Nothing -> fail $ "Cannot find group for instance " ++
783 4bc33d60 Iustin Pop
                           Instance.name inst
784 4bc33d60 Iustin Pop
                Just v -> return v
785 4bc33d60 Iustin Pop
  tryReloc nl il xid ncount ex_ndx
786 4bc33d60 Iustin Pop
787 525bfb36 Iustin Pop
-- | Change an instance's secondary node.
788 2ca68e2b Iustin Pop
evacInstance :: (Monad m) =>
789 2ca68e2b Iustin Pop
                [Ndx]                      -- ^ Excluded nodes
790 2ca68e2b Iustin Pop
             -> Instance.List              -- ^ The current instance list
791 2ca68e2b Iustin Pop
             -> (Node.List, AllocSolution) -- ^ The current state
792 2ca68e2b Iustin Pop
             -> Idx                        -- ^ The instance to evacuate
793 2ca68e2b Iustin Pop
             -> m (Node.List, AllocSolution)
794 2ca68e2b Iustin Pop
evacInstance ex_ndx il (nl, old_as) idx = do
795 2ca68e2b Iustin Pop
  -- FIXME: hardcoded one node here
796 2ca68e2b Iustin Pop
797 2ca68e2b Iustin Pop
  -- Longer explanation: evacuation is currently hardcoded to DRBD
798 2ca68e2b Iustin Pop
  -- instances (which have one secondary); hence, even if the
799 2ca68e2b Iustin Pop
  -- IAllocator protocol can request N nodes for an instance, and all
800 2ca68e2b Iustin Pop
  -- the message parsing/loading pass this, this implementation only
801 2ca68e2b Iustin Pop
  -- supports one; this situation needs to be revisited if we ever
802 2ca68e2b Iustin Pop
  -- support more than one secondary, or if we change the storage
803 2ca68e2b Iustin Pop
  -- model
804 2ca68e2b Iustin Pop
  new_as <- tryReloc nl il idx 1 ex_ndx
805 2ca68e2b Iustin Pop
  case asSolutions new_as of
806 2ca68e2b Iustin Pop
    -- an individual relocation succeeded, we kind of compose the data
807 2ca68e2b Iustin Pop
    -- from the two solutions
808 2ca68e2b Iustin Pop
    csol@(nl', _, _, _):_ ->
809 2ca68e2b Iustin Pop
        return (nl', new_as { asSolutions = csol:asSolutions old_as })
810 2ca68e2b Iustin Pop
    -- this relocation failed, so we fail the entire evac
811 2ca68e2b Iustin Pop
    _ -> fail $ "Can't evacuate instance " ++
812 2ca68e2b Iustin Pop
         Instance.name (Container.find idx il) ++
813 2ca68e2b Iustin Pop
             ": " ++ describeSolution new_as
814 2ca68e2b Iustin Pop
815 3fea6959 Iustin Pop
-- | Try to evacuate a list of nodes.
816 12b0511d Iustin Pop
tryEvac :: (Monad m) =>
817 12b0511d Iustin Pop
            Node.List       -- ^ The node list
818 12b0511d Iustin Pop
         -> Instance.List   -- ^ The instance list
819 1bc47d38 Iustin Pop
         -> [Idx]           -- ^ Instances to be evacuated
820 1bc47d38 Iustin Pop
         -> [Ndx]           -- ^ Restricted nodes (the ones being evacuated)
821 12b0511d Iustin Pop
         -> m AllocSolution -- ^ Solution list
822 1bc47d38 Iustin Pop
tryEvac nl il idxs ex_ndx = do
823 97936d51 Iustin Pop
  (_, sol) <- foldM (evacInstance ex_ndx il) (nl, emptyAllocSolution) idxs
824 1bc47d38 Iustin Pop
  return sol
825 1bc47d38 Iustin Pop
826 1bc47d38 Iustin Pop
-- | Multi-group evacuation of a list of nodes.
827 1bc47d38 Iustin Pop
tryMGEvac :: (Monad m) =>
828 1bc47d38 Iustin Pop
             Group.List -- ^ The group list
829 1bc47d38 Iustin Pop
          -> Node.List       -- ^ The node list
830 1bc47d38 Iustin Pop
          -> Instance.List   -- ^ The instance list
831 1bc47d38 Iustin Pop
          -> [Ndx]           -- ^ Nodes to be evacuated
832 1bc47d38 Iustin Pop
          -> m AllocSolution -- ^ Solution list
833 1bc47d38 Iustin Pop
tryMGEvac _ nl il ex_ndx =
834 5182e970 Iustin Pop
    let ex_nodes = map (`Container.find` nl) ex_ndx
835 5182e970 Iustin Pop
        all_insts = nub . concatMap Node.sList $ ex_nodes
836 1f4ae205 Iustin Pop
        all_insts' = associateIdxs all_insts $ splitCluster nl il
837 12b0511d Iustin Pop
    in do
838 1f4ae205 Iustin Pop
      results <- mapM (\(_, (gnl, gil, idxs)) -> tryEvac gnl gil idxs ex_ndx)
839 1f4ae205 Iustin Pop
                 all_insts'
840 97936d51 Iustin Pop
      let sol = foldl' sumAllocs emptyAllocSolution results
841 859fc11d Iustin Pop
      return $ annotateSolution sol
842 12b0511d Iustin Pop
843 525bfb36 Iustin Pop
-- | Recursively place instances on the cluster until we're out of space.
844 3ce8009a Iustin Pop
iterateAlloc :: Node.List
845 3ce8009a Iustin Pop
             -> Instance.List
846 3ce8009a Iustin Pop
             -> Instance.Instance
847 41b5c85a Iustin Pop
             -> AllocNodes
848 3ce8009a Iustin Pop
             -> [Instance.Instance]
849 d5ccec02 Iustin Pop
             -> [CStats]
850 40ee14bc Iustin Pop
             -> Result AllocResult
851 41b5c85a Iustin Pop
iterateAlloc nl il newinst allocnodes ixes cstats =
852 3ce8009a Iustin Pop
      let depth = length ixes
853 3ce8009a Iustin Pop
          newname = printf "new-%d" depth::String
854 3ce8009a Iustin Pop
          newidx = length (Container.elems il) + depth
855 3ce8009a Iustin Pop
          newi2 = Instance.setIdx (Instance.setName newinst newname) newidx
856 41b5c85a Iustin Pop
      in case tryAlloc nl il newi2 allocnodes of
857 3ce8009a Iustin Pop
           Bad s -> Bad s
858 85d0ddc3 Iustin Pop
           Ok (AllocSolution { asFailures = errs, asSolutions = sols3 }) ->
859 3ce8009a Iustin Pop
               case sols3 of
860 d5ccec02 Iustin Pop
                 [] -> Ok (collapseFailures errs, nl, il, ixes, cstats)
861 a334d536 Iustin Pop
                 (xnl, xi, _, _):[] ->
862 94d08202 Iustin Pop
                     iterateAlloc xnl (Container.add newidx xi il)
863 41b5c85a Iustin Pop
                                  newinst allocnodes (xi:ixes)
864 d5ccec02 Iustin Pop
                                  (totalResources xnl:cstats)
865 3ce8009a Iustin Pop
                 _ -> Bad "Internal error: multiple solutions for single\
866 3ce8009a Iustin Pop
                          \ allocation"
867 3ce8009a Iustin Pop
868 525bfb36 Iustin Pop
-- | The core of the tiered allocation mode.
869 3ce8009a Iustin Pop
tieredAlloc :: Node.List
870 3ce8009a Iustin Pop
            -> Instance.List
871 3ce8009a Iustin Pop
            -> Instance.Instance
872 41b5c85a Iustin Pop
            -> AllocNodes
873 3ce8009a Iustin Pop
            -> [Instance.Instance]
874 d5ccec02 Iustin Pop
            -> [CStats]
875 40ee14bc Iustin Pop
            -> Result AllocResult
876 41b5c85a Iustin Pop
tieredAlloc nl il newinst allocnodes ixes cstats =
877 41b5c85a Iustin Pop
    case iterateAlloc nl il newinst allocnodes ixes cstats of
878 3ce8009a Iustin Pop
      Bad s -> Bad s
879 d5ccec02 Iustin Pop
      Ok (errs, nl', il', ixes', cstats') ->
880 3ce8009a Iustin Pop
          case Instance.shrinkByType newinst . fst . last $
881 3ce8009a Iustin Pop
               sortBy (comparing snd) errs of
882 d5ccec02 Iustin Pop
            Bad _ -> Ok (errs, nl', il', ixes', cstats')
883 3ce8009a Iustin Pop
            Ok newinst' ->
884 41b5c85a Iustin Pop
                tieredAlloc nl' il' newinst' allocnodes ixes' cstats'
885 3ce8009a Iustin Pop
886 949397c8 Iustin Pop
-- | Compute the tiered spec string description from a list of
887 949397c8 Iustin Pop
-- allocated instances.
888 949397c8 Iustin Pop
tieredSpecMap :: [Instance.Instance]
889 949397c8 Iustin Pop
              -> [String]
890 949397c8 Iustin Pop
tieredSpecMap trl_ixes =
891 949397c8 Iustin Pop
    let fin_trl_ixes = reverse trl_ixes
892 949397c8 Iustin Pop
        ix_byspec = groupBy ((==) `on` Instance.specOf) fin_trl_ixes
893 949397c8 Iustin Pop
        spec_map = map (\ixs -> (Instance.specOf $ head ixs, length ixs))
894 949397c8 Iustin Pop
                   ix_byspec
895 949397c8 Iustin Pop
    in  map (\(spec, cnt) -> printf "%d,%d,%d=%d" (rspecMem spec)
896 949397c8 Iustin Pop
                             (rspecDsk spec) (rspecCpu spec) cnt) spec_map
897 949397c8 Iustin Pop
898 9188aeef Iustin Pop
-- * Formatting functions
899 e4f08c46 Iustin Pop
900 e4f08c46 Iustin Pop
-- | Given the original and final nodes, computes the relocation description.
901 c9926b22 Iustin Pop
computeMoves :: Instance.Instance -- ^ The instance to be moved
902 c9926b22 Iustin Pop
             -> String -- ^ The instance name
903 668c03b3 Iustin Pop
             -> IMove  -- ^ The move being performed
904 e4f08c46 Iustin Pop
             -> String -- ^ New primary
905 e4f08c46 Iustin Pop
             -> String -- ^ New secondary
906 e4f08c46 Iustin Pop
             -> (String, [String])
907 e4f08c46 Iustin Pop
                -- ^ Tuple of moves and commands list; moves is containing
908 e4f08c46 Iustin Pop
                -- either @/f/@ for failover or @/r:name/@ for replace
909 e4f08c46 Iustin Pop
                -- secondary, while the command list holds gnt-instance
910 e4f08c46 Iustin Pop
                -- commands (without that prefix), e.g \"@failover instance1@\"
911 668c03b3 Iustin Pop
computeMoves i inam mv c d =
912 668c03b3 Iustin Pop
    case mv of
913 668c03b3 Iustin Pop
      Failover -> ("f", [mig])
914 668c03b3 Iustin Pop
      FailoverAndReplace _ -> (printf "f r:%s" d, [mig, rep d])
915 668c03b3 Iustin Pop
      ReplaceSecondary _ -> (printf "r:%s" d, [rep d])
916 668c03b3 Iustin Pop
      ReplaceAndFailover _ -> (printf "r:%s f" c, [rep c, mig])
917 668c03b3 Iustin Pop
      ReplacePrimary _ -> (printf "f r:%s f" c, [mig, rep c, mig])
918 c9926b22 Iustin Pop
    where morf = if Instance.running i then "migrate" else "failover"
919 c9926b22 Iustin Pop
          mig = printf "%s -f %s" morf inam::String
920 c9926b22 Iustin Pop
          rep n = printf "replace-disks -n %s %s" n inam
921 e4f08c46 Iustin Pop
922 9188aeef Iustin Pop
-- | Converts a placement to string format.
923 9188aeef Iustin Pop
printSolutionLine :: Node.List     -- ^ The node list
924 9188aeef Iustin Pop
                  -> Instance.List -- ^ The instance list
925 9188aeef Iustin Pop
                  -> Int           -- ^ Maximum node name length
926 9188aeef Iustin Pop
                  -> Int           -- ^ Maximum instance name length
927 9188aeef Iustin Pop
                  -> Placement     -- ^ The current placement
928 9188aeef Iustin Pop
                  -> Int           -- ^ The index of the placement in
929 9188aeef Iustin Pop
                                   -- the solution
930 db1bcfe8 Iustin Pop
                  -> (String, [String])
931 db1bcfe8 Iustin Pop
printSolutionLine nl il nmlen imlen plc pos =
932 ca8258d9 Iustin Pop
    let
933 ca8258d9 Iustin Pop
        pmlen = (2*nmlen + 1)
934 668c03b3 Iustin Pop
        (i, p, s, mv, c) = plc
935 ca8258d9 Iustin Pop
        inst = Container.find i il
936 14c972c7 Iustin Pop
        inam = Instance.alias inst
937 14c972c7 Iustin Pop
        npri = Node.alias $ Container.find p nl
938 14c972c7 Iustin Pop
        nsec = Node.alias $ Container.find s nl
939 14c972c7 Iustin Pop
        opri = Node.alias $ Container.find (Instance.pNode inst) nl
940 14c972c7 Iustin Pop
        osec = Node.alias $ Container.find (Instance.sNode inst) nl
941 668c03b3 Iustin Pop
        (moves, cmds) =  computeMoves inst inam mv npri nsec
942 9f6dcdea Iustin Pop
        ostr = printf "%s:%s" opri osec::String
943 9f6dcdea Iustin Pop
        nstr = printf "%s:%s" npri nsec::String
944 ca8258d9 Iustin Pop
    in
945 ab271fc1 Iustin Pop
      (printf "  %3d. %-*s %-*s => %-*s %.8f a=%s"
946 ab271fc1 Iustin Pop
       pos imlen inam pmlen ostr
947 ca8258d9 Iustin Pop
       pmlen nstr c moves,
948 ca8258d9 Iustin Pop
       cmds)
949 ca8258d9 Iustin Pop
950 0e8ae201 Iustin Pop
-- | Return the instance and involved nodes in an instance move.
951 0e8ae201 Iustin Pop
involvedNodes :: Instance.List -> Placement -> [Ndx]
952 0e8ae201 Iustin Pop
involvedNodes il plc =
953 3173c987 Iustin Pop
    let (i, np, ns, _, _) = plc
954 0e8ae201 Iustin Pop
        inst = Container.find i il
955 2060348b Iustin Pop
        op = Instance.pNode inst
956 2060348b Iustin Pop
        os = Instance.sNode inst
957 0e8ae201 Iustin Pop
    in nub [np, ns, op, os]
958 0e8ae201 Iustin Pop
959 0e8ae201 Iustin Pop
-- | Inner function for splitJobs, that either appends the next job to
960 0e8ae201 Iustin Pop
-- the current jobset, or starts a new jobset.
961 0e8ae201 Iustin Pop
mergeJobs :: ([JobSet], [Ndx]) -> MoveJob -> ([JobSet], [Ndx])
962 924f9c16 Iustin Pop
mergeJobs ([], _) n@(ndx, _, _, _) = ([[n]], ndx)
963 924f9c16 Iustin Pop
mergeJobs (cjs@(j:js), nbuf) n@(ndx, _, _, _)
964 0e8ae201 Iustin Pop
    | null (ndx `intersect` nbuf) = ((n:j):js, ndx ++ nbuf)
965 0e8ae201 Iustin Pop
    | otherwise = ([n]:cjs, ndx)
966 0e8ae201 Iustin Pop
967 0e8ae201 Iustin Pop
-- | Break a list of moves into independent groups. Note that this
968 0e8ae201 Iustin Pop
-- will reverse the order of jobs.
969 0e8ae201 Iustin Pop
splitJobs :: [MoveJob] -> [JobSet]
970 0e8ae201 Iustin Pop
splitJobs = fst . foldl mergeJobs ([], [])
971 0e8ae201 Iustin Pop
972 0e8ae201 Iustin Pop
-- | Given a list of commands, prefix them with @gnt-instance@ and
973 0e8ae201 Iustin Pop
-- also beautify the display a little.
974 0e8ae201 Iustin Pop
formatJob :: Int -> Int -> (Int, MoveJob) -> [String]
975 924f9c16 Iustin Pop
formatJob jsn jsl (sn, (_, _, _, cmds)) =
976 0e8ae201 Iustin Pop
    let out =
977 0e8ae201 Iustin Pop
            printf "  echo job %d/%d" jsn sn:
978 0e8ae201 Iustin Pop
            printf "  check":
979 0e8ae201 Iustin Pop
            map ("  gnt-instance " ++) cmds
980 0e8ae201 Iustin Pop
    in if sn == 1
981 0e8ae201 Iustin Pop
       then ["", printf "echo jobset %d, %d jobs" jsn jsl] ++ out
982 0e8ae201 Iustin Pop
       else out
983 0e8ae201 Iustin Pop
984 9188aeef Iustin Pop
-- | Given a list of commands, prefix them with @gnt-instance@ and
985 9188aeef Iustin Pop
-- also beautify the display a little.
986 0e8ae201 Iustin Pop
formatCmds :: [JobSet] -> String
987 9f6dcdea Iustin Pop
formatCmds =
988 9f6dcdea Iustin Pop
    unlines .
989 0e8ae201 Iustin Pop
    concatMap (\(jsn, js) -> concatMap (formatJob jsn (length js))
990 0e8ae201 Iustin Pop
                             (zip [1..] js)) .
991 9f6dcdea Iustin Pop
    zip [1..]
992 142538ff Iustin Pop
993 e4f08c46 Iustin Pop
-- | Print the node list.
994 e98fb766 Iustin Pop
printNodes :: Node.List -> [String] -> String
995 e98fb766 Iustin Pop
printNodes nl fs =
996 6dfa04fd Iustin Pop
    let fields = case fs of
997 6dfa04fd Iustin Pop
          [] -> Node.defaultFields
998 6dfa04fd Iustin Pop
          "+":rest -> Node.defaultFields ++ rest
999 6dfa04fd Iustin Pop
          _ -> fs
1000 5182e970 Iustin Pop
        snl = sortBy (comparing Node.idx) (Container.elems nl)
1001 e98fb766 Iustin Pop
        (header, isnum) = unzip $ map Node.showHeader fields
1002 c5f7412e Iustin Pop
    in unlines . map ((:) ' ' .  intercalate " ") $
1003 e98fb766 Iustin Pop
       formatTable (header:map (Node.list fields) snl) isnum
1004 e4f08c46 Iustin Pop
1005 507fda3f Iustin Pop
-- | Print the instance list.
1006 507fda3f Iustin Pop
printInsts :: Node.List -> Instance.List -> String
1007 507fda3f Iustin Pop
printInsts nl il =
1008 5182e970 Iustin Pop
    let sil = sortBy (comparing Instance.idx) (Container.elems il)
1009 30ff0c73 Iustin Pop
        helper inst = [ if Instance.running inst then "R" else " "
1010 30ff0c73 Iustin Pop
                      , Instance.name inst
1011 30ff0c73 Iustin Pop
                      , Container.nameOf nl (Instance.pNode inst)
1012 5182e970 Iustin Pop
                      , let sdx = Instance.sNode inst
1013 5182e970 Iustin Pop
                        in if sdx == Node.noSecondary
1014 5182e970 Iustin Pop
                           then  ""
1015 5182e970 Iustin Pop
                           else Container.nameOf nl sdx
1016 0e09422b Iustin Pop
                      , if Instance.autoBalance inst then "Y" else "N"
1017 30ff0c73 Iustin Pop
                      , printf "%3d" $ Instance.vcpus inst
1018 30ff0c73 Iustin Pop
                      , printf "%5d" $ Instance.mem inst
1019 30ff0c73 Iustin Pop
                      , printf "%5d" $ Instance.dsk inst `div` 1024
1020 30ff0c73 Iustin Pop
                      , printf "%5.3f" lC
1021 30ff0c73 Iustin Pop
                      , printf "%5.3f" lM
1022 30ff0c73 Iustin Pop
                      , printf "%5.3f" lD
1023 30ff0c73 Iustin Pop
                      , printf "%5.3f" lN
1024 30ff0c73 Iustin Pop
                      ]
1025 30ff0c73 Iustin Pop
            where DynUtil lC lM lD lN = Instance.util inst
1026 93439b1c Iustin Pop
        header = [ "F", "Name", "Pri_node", "Sec_node", "Auto_bal"
1027 93439b1c Iustin Pop
                 , "vcpu", "mem" , "dsk", "lCpu", "lMem", "lDsk", "lNet" ]
1028 93439b1c Iustin Pop
        isnum = False:False:False:False:False:repeat True
1029 c5f7412e Iustin Pop
    in unlines . map ((:) ' ' . intercalate " ") $
1030 c5f7412e Iustin Pop
       formatTable (header:map helper sil) isnum
1031 507fda3f Iustin Pop
1032 9188aeef Iustin Pop
-- | Shows statistics for a given node list.
1033 262a08a2 Iustin Pop
printStats :: Node.List -> String
1034 e4f08c46 Iustin Pop
printStats nl =
1035 fca250e9 Iustin Pop
    let dcvs = compDetailedCV nl
1036 8a3b30ca Iustin Pop
        (weights, names) = unzip detailedCVInfo
1037 8a3b30ca Iustin Pop
        hd = zip3 (weights ++ repeat 1) (names ++ repeat "unknown") dcvs
1038 8a3b30ca Iustin Pop
        formatted = map (\(w, header, val) ->
1039 8a3b30ca Iustin Pop
                             printf "%s=%.8f(x%.2f)" header val w::String) hd
1040 fca250e9 Iustin Pop
    in intercalate ", " formatted
1041 6b20875c Iustin Pop
1042 6b20875c Iustin Pop
-- | Convert a placement into a list of OpCodes (basically a job).
1043 3e4480e0 Iustin Pop
iMoveToJob :: Node.List -> Instance.List
1044 6b20875c Iustin Pop
          -> Idx -> IMove -> [OpCodes.OpCode]
1045 3e4480e0 Iustin Pop
iMoveToJob nl il idx move =
1046 dfbbd43a Iustin Pop
    let inst = Container.find idx il
1047 3e4480e0 Iustin Pop
        iname = Instance.name inst
1048 3e4480e0 Iustin Pop
        lookNode  = Just . Container.nameOf nl
1049 10028866 René Nussbaumer
        opF = OpCodes.OpInstanceMigrate iname True False True
1050 10028866 René Nussbaumer
        opR n = OpCodes.OpInstanceReplaceDisks iname (lookNode n)
1051 6b20875c Iustin Pop
                OpCodes.ReplaceNewSecondary [] Nothing
1052 6b20875c Iustin Pop
    in case move of
1053 6b20875c Iustin Pop
         Failover -> [ opF ]
1054 6b20875c Iustin Pop
         ReplacePrimary np -> [ opF, opR np, opF ]
1055 6b20875c Iustin Pop
         ReplaceSecondary ns -> [ opR ns ]
1056 6b20875c Iustin Pop
         ReplaceAndFailover np -> [ opR np, opF ]
1057 6b20875c Iustin Pop
         FailoverAndReplace ns -> [ opF, opR ns ]
1058 32b8d9c0 Iustin Pop
1059 949397c8 Iustin Pop
-- * Node group functions
1060 949397c8 Iustin Pop
1061 525bfb36 Iustin Pop
-- | Computes the group of an instance.
1062 10ef6b4e Iustin Pop
instanceGroup :: Node.List -> Instance.Instance -> Result Gdx
1063 32b8d9c0 Iustin Pop
instanceGroup nl i =
1064 32b8d9c0 Iustin Pop
  let sidx = Instance.sNode i
1065 32b8d9c0 Iustin Pop
      pnode = Container.find (Instance.pNode i) nl
1066 32b8d9c0 Iustin Pop
      snode = if sidx == Node.noSecondary
1067 32b8d9c0 Iustin Pop
              then pnode
1068 32b8d9c0 Iustin Pop
              else Container.find sidx nl
1069 10ef6b4e Iustin Pop
      pgroup = Node.group pnode
1070 10ef6b4e Iustin Pop
      sgroup = Node.group snode
1071 10ef6b4e Iustin Pop
  in if pgroup /= sgroup
1072 10ef6b4e Iustin Pop
     then fail ("Instance placed accross two node groups, primary " ++
1073 10ef6b4e Iustin Pop
                show pgroup ++ ", secondary " ++ show sgroup)
1074 10ef6b4e Iustin Pop
     else return pgroup
1075 32b8d9c0 Iustin Pop
1076 525bfb36 Iustin Pop
-- | Computes the group of an instance per the primary node.
1077 4bc33d60 Iustin Pop
instancePriGroup :: Node.List -> Instance.Instance -> Gdx
1078 4bc33d60 Iustin Pop
instancePriGroup nl i =
1079 4bc33d60 Iustin Pop
  let pnode = Container.find (Instance.pNode i) nl
1080 4bc33d60 Iustin Pop
  in  Node.group pnode
1081 4bc33d60 Iustin Pop
1082 32b8d9c0 Iustin Pop
-- | Compute the list of badly allocated instances (split across node
1083 525bfb36 Iustin Pop
-- groups).
1084 32b8d9c0 Iustin Pop
findSplitInstances :: Node.List -> Instance.List -> [Instance.Instance]
1085 2a8e2dc9 Iustin Pop
findSplitInstances nl =
1086 2a8e2dc9 Iustin Pop
  filter (not . isOk . instanceGroup nl) . Container.elems
1087 f4161783 Iustin Pop
1088 525bfb36 Iustin Pop
-- | Splits a cluster into the component node groups.
1089 f4161783 Iustin Pop
splitCluster :: Node.List -> Instance.List ->
1090 10ef6b4e Iustin Pop
                [(Gdx, (Node.List, Instance.List))]
1091 f4161783 Iustin Pop
splitCluster nl il =
1092 f4161783 Iustin Pop
  let ngroups = Node.computeGroups (Container.elems nl)
1093 f4161783 Iustin Pop
  in map (\(guuid, nodes) ->
1094 f4161783 Iustin Pop
           let nidxs = map Node.idx nodes
1095 f4161783 Iustin Pop
               nodes' = zip nidxs nodes
1096 f4161783 Iustin Pop
               instances = Container.filter ((`elem` nidxs) . Instance.pNode) il
1097 cb0c77ff Iustin Pop
           in (guuid, (Container.fromList nodes', instances))) ngroups
1098 1f4ae205 Iustin Pop
1099 1f4ae205 Iustin Pop
-- | Split a global instance index map into per-group, and associate
1100 1f4ae205 Iustin Pop
-- it with the group/node/instance lists.
1101 1f4ae205 Iustin Pop
associateIdxs :: [Idx] -- ^ Instance indices to be split/associated
1102 1f4ae205 Iustin Pop
              -> [(Gdx, (Node.List, Instance.List))]        -- ^ Input groups
1103 1f4ae205 Iustin Pop
              -> [(Gdx, (Node.List, Instance.List, [Idx]))] -- ^ Result
1104 1f4ae205 Iustin Pop
associateIdxs idxs =
1105 1f4ae205 Iustin Pop
    map (\(gdx, (nl, il)) ->
1106 1f4ae205 Iustin Pop
             (gdx, (nl, il, filter (`Container.member` il) idxs)))
1107 63a78055 Iustin Pop
1108 63a78055 Iustin Pop
-- | Compute the list of nodes that are to be evacuated, given a list
1109 63a78055 Iustin Pop
-- of instances and an evacuation mode.
1110 63a78055 Iustin Pop
nodesToEvacuate :: Instance.List -- ^ The cluster-wide instance list
1111 63a78055 Iustin Pop
                -> EvacMode      -- ^ The evacuation mode we're using
1112 63a78055 Iustin Pop
                -> [Idx]         -- ^ List of instance indices being evacuated
1113 63a78055 Iustin Pop
                -> IntSet.IntSet -- ^ Set of node indices
1114 63a78055 Iustin Pop
nodesToEvacuate il mode =
1115 63a78055 Iustin Pop
    IntSet.delete Node.noSecondary .
1116 63a78055 Iustin Pop
    foldl' (\ns idx ->
1117 63a78055 Iustin Pop
                let i = Container.find idx il
1118 63a78055 Iustin Pop
                    pdx = Instance.pNode i
1119 63a78055 Iustin Pop
                    sdx = Instance.sNode i
1120 63a78055 Iustin Pop
                    dt = Instance.diskTemplate i
1121 63a78055 Iustin Pop
                    withSecondary = case dt of
1122 63a78055 Iustin Pop
                                      DTDrbd8 -> IntSet.insert sdx ns
1123 63a78055 Iustin Pop
                                      _ -> ns
1124 63a78055 Iustin Pop
                in case mode of
1125 63a78055 Iustin Pop
                     ChangePrimary   -> IntSet.insert pdx ns
1126 63a78055 Iustin Pop
                     ChangeSecondary -> withSecondary
1127 63a78055 Iustin Pop
                     ChangeAll       -> IntSet.insert pdx withSecondary
1128 63a78055 Iustin Pop
           ) IntSet.empty