Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Cluster.hs @ 56c094b4

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