Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ 4bc33d60

History | View | Annotate | Download (42.3 kB)

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