Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ d6c76bd5

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