Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ e0eb63f0

History | View | Annotate | Download (30.6 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 669d7e3d Iustin Pop
module Ganeti.HTools.Cluster
9 e4f08c46 Iustin Pop
    (
10 e4f08c46 Iustin Pop
     -- * Types
11 e4f08c46 Iustin Pop
     NodeList
12 e4f08c46 Iustin Pop
    , InstanceList
13 740ec004 Iustin Pop
    , NameList
14 e4f08c46 Iustin Pop
    , Placement
15 e4f08c46 Iustin Pop
    , Solution(..)
16 e4f08c46 Iustin Pop
    , Table(..)
17 e4f08c46 Iustin Pop
    , Removal
18 e4f08c46 Iustin Pop
    -- * Generic functions
19 e4f08c46 Iustin Pop
    , totalResources
20 e4f08c46 Iustin Pop
    -- * First phase functions
21 e4f08c46 Iustin Pop
    , computeBadItems
22 e4f08c46 Iustin Pop
    -- * Second phase functions
23 e4f08c46 Iustin Pop
    , computeSolution
24 e4f08c46 Iustin Pop
    , applySolution
25 e4f08c46 Iustin Pop
    , printSolution
26 7dfaafb1 Iustin Pop
    , printSolutionLine
27 142538ff Iustin Pop
    , formatCmds
28 e4f08c46 Iustin Pop
    , printNodes
29 e4f08c46 Iustin Pop
    -- * Balacing functions
30 e4f08c46 Iustin Pop
    , checkMove
31 e4f08c46 Iustin Pop
    , compCV
32 e4f08c46 Iustin Pop
    , printStats
33 e4f08c46 Iustin Pop
    -- * Loading functions
34 e4f08c46 Iustin Pop
    , loadData
35 5d1baf63 Iustin Pop
    , checkData
36 e4f08c46 Iustin Pop
    ) where
37 e4f08c46 Iustin Pop
38 e4f08c46 Iustin Pop
import Data.List
39 e4f08c46 Iustin Pop
import Data.Maybe (isNothing, fromJust)
40 e4f08c46 Iustin Pop
import Text.Printf (printf)
41 e4f08c46 Iustin Pop
import Data.Function
42 e4f08c46 Iustin Pop
43 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Container as Container
44 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
45 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Node as Node
46 669d7e3d Iustin Pop
import Ganeti.HTools.Utils
47 e4f08c46 Iustin Pop
48 e4f08c46 Iustin Pop
type NodeList = Container.Container Node.Node
49 e4f08c46 Iustin Pop
type InstanceList = Container.Container Instance.Instance
50 740ec004 Iustin Pop
-- | The type used to hold idx-to-name mappings
51 740ec004 Iustin Pop
type NameList = [(Int, String)]
52 7ae514ba Iustin Pop
-- | A separate name for the cluster score type
53 e4f08c46 Iustin Pop
type Score = Double
54 e4f08c46 Iustin Pop
55 e4f08c46 Iustin Pop
-- | The description of an instance placement.
56 c5c295bc Iustin Pop
type Placement = (Int, Int, Int, Score)
57 e4f08c46 Iustin Pop
58 e4f08c46 Iustin Pop
{- | A cluster solution described as the solution delta and the list
59 e4f08c46 Iustin Pop
of placements.
60 e4f08c46 Iustin Pop
61 e4f08c46 Iustin Pop
-}
62 e4f08c46 Iustin Pop
data Solution = Solution Int [Placement]
63 e4f08c46 Iustin Pop
                deriving (Eq, Ord, Show)
64 e4f08c46 Iustin Pop
65 e4f08c46 Iustin Pop
-- | Returns the delta of a solution or -1 for Nothing
66 e4f08c46 Iustin Pop
solutionDelta :: Maybe Solution -> Int
67 e4f08c46 Iustin Pop
solutionDelta sol = case sol of
68 e4f08c46 Iustin Pop
                      Just (Solution d _) -> d
69 e4f08c46 Iustin Pop
                      _ -> -1
70 e4f08c46 Iustin Pop
71 e4f08c46 Iustin Pop
-- | A removal set.
72 e4f08c46 Iustin Pop
data Removal = Removal NodeList [Instance.Instance]
73 e4f08c46 Iustin Pop
74 e4f08c46 Iustin Pop
-- | An instance move definition
75 00b51a14 Iustin Pop
data IMove = Failover                -- ^ Failover the instance (f)
76 19493d33 Iustin Pop
           | ReplacePrimary Int      -- ^ Replace primary (f, r:np, f)
77 19493d33 Iustin Pop
           | ReplaceSecondary Int    -- ^ Replace secondary (r:ns)
78 19493d33 Iustin Pop
           | ReplaceAndFailover Int  -- ^ Replace secondary, failover (r:np, f)
79 19493d33 Iustin Pop
           | FailoverAndReplace Int  -- ^ Failover, replace secondary (f, r:ns)
80 e4f08c46 Iustin Pop
             deriving (Show)
81 e4f08c46 Iustin Pop
82 e4f08c46 Iustin Pop
-- | The complete state for the balancing solution
83 e4f08c46 Iustin Pop
data Table = Table NodeList InstanceList Score [Placement]
84 e4f08c46 Iustin Pop
             deriving (Show)
85 e4f08c46 Iustin Pop
86 e4f08c46 Iustin Pop
-- General functions
87 e4f08c46 Iustin Pop
88 e4f08c46 Iustin Pop
-- | Cap the removal list if needed.
89 e4f08c46 Iustin Pop
capRemovals :: [a] -> Int -> [a]
90 e4f08c46 Iustin Pop
capRemovals removals max_removals =
91 e4f08c46 Iustin Pop
    if max_removals > 0 then
92 e4f08c46 Iustin Pop
        take max_removals removals
93 e4f08c46 Iustin Pop
    else
94 e4f08c46 Iustin Pop
        removals
95 e4f08c46 Iustin Pop
96 e4f08c46 Iustin Pop
-- | Check if the given node list fails the N+1 check.
97 e4f08c46 Iustin Pop
verifyN1Check :: [Node.Node] -> Bool
98 e4f08c46 Iustin Pop
verifyN1Check nl = any Node.failN1 nl
99 e4f08c46 Iustin Pop
100 e4f08c46 Iustin Pop
-- | Verifies the N+1 status and return the affected nodes.
101 e4f08c46 Iustin Pop
verifyN1 :: [Node.Node] -> [Node.Node]
102 e4f08c46 Iustin Pop
verifyN1 nl = filter Node.failN1 nl
103 e4f08c46 Iustin Pop
104 e4f08c46 Iustin Pop
{-| Add an instance and return the new node and instance maps. -}
105 e4f08c46 Iustin Pop
addInstance :: NodeList -> Instance.Instance ->
106 e4f08c46 Iustin Pop
               Node.Node -> Node.Node -> Maybe NodeList
107 e4f08c46 Iustin Pop
addInstance nl idata pri sec =
108 e4f08c46 Iustin Pop
  let pdx = Node.idx pri
109 e4f08c46 Iustin Pop
      sdx = Node.idx sec
110 e4f08c46 Iustin Pop
  in do
111 e4f08c46 Iustin Pop
      pnode <- Node.addPri pri idata
112 e4f08c46 Iustin Pop
      snode <- Node.addSec sec idata pdx
113 e4f08c46 Iustin Pop
      new_nl <- return $ Container.addTwo sdx snode
114 e4f08c46 Iustin Pop
                         pdx pnode nl
115 e4f08c46 Iustin Pop
      return new_nl
116 e4f08c46 Iustin Pop
117 e4f08c46 Iustin Pop
-- | Remove an instance and return the new node and instance maps.
118 e4f08c46 Iustin Pop
removeInstance :: NodeList -> Instance.Instance -> NodeList
119 e4f08c46 Iustin Pop
removeInstance nl idata =
120 e4f08c46 Iustin Pop
  let pnode = Instance.pnode idata
121 e4f08c46 Iustin Pop
      snode = Instance.snode idata
122 e4f08c46 Iustin Pop
      pn = Container.find pnode nl
123 e4f08c46 Iustin Pop
      sn = Container.find snode nl
124 e4f08c46 Iustin Pop
      new_nl = Container.addTwo
125 e4f08c46 Iustin Pop
               pnode (Node.removePri pn idata)
126 e4f08c46 Iustin Pop
               snode (Node.removeSec sn idata) nl in
127 e4f08c46 Iustin Pop
  new_nl
128 e4f08c46 Iustin Pop
129 e4f08c46 Iustin Pop
-- | Remove an instance and return the new node map.
130 e4f08c46 Iustin Pop
removeInstances :: NodeList -> [Instance.Instance] -> NodeList
131 e4f08c46 Iustin Pop
removeInstances = foldl' removeInstance
132 e4f08c46 Iustin Pop
133 e4f08c46 Iustin Pop
-- | Compute the total free disk and memory in the cluster.
134 e4f08c46 Iustin Pop
totalResources :: Container.Container Node.Node -> (Int, Int)
135 e4f08c46 Iustin Pop
totalResources nl =
136 e4f08c46 Iustin Pop
    foldl'
137 962367fe Iustin Pop
    (\ (mem, dsk) node -> (mem + (Node.f_mem node),
138 962367fe Iustin Pop
                           dsk + (Node.f_dsk node)))
139 e4f08c46 Iustin Pop
    (0, 0) (Container.elems nl)
140 e4f08c46 Iustin Pop
141 e4f08c46 Iustin Pop
{- | Compute a new version of a cluster given a solution.
142 e4f08c46 Iustin Pop
143 e4f08c46 Iustin Pop
This is not used for computing the solutions, but for applying a
144 e4f08c46 Iustin Pop
(known-good) solution to the original cluster for final display.
145 e4f08c46 Iustin Pop
146 e4f08c46 Iustin Pop
It first removes the relocated instances after which it places them on
147 e4f08c46 Iustin Pop
their new nodes.
148 e4f08c46 Iustin Pop
149 e4f08c46 Iustin Pop
 -}
150 e4f08c46 Iustin Pop
applySolution :: NodeList -> InstanceList -> [Placement] -> NodeList
151 e4f08c46 Iustin Pop
applySolution nl il sol =
152 c5c295bc Iustin Pop
    let odxes = map (\ (a, b, c, _) -> (Container.find a il,
153 c5c295bc Iustin Pop
                                        Node.idx (Container.find b nl),
154 c5c295bc Iustin Pop
                                        Node.idx (Container.find c nl))
155 e4f08c46 Iustin Pop
                    ) sol
156 e4f08c46 Iustin Pop
        idxes = (\ (x, _, _) -> x) (unzip3 odxes)
157 e4f08c46 Iustin Pop
        nc = removeInstances nl idxes
158 e4f08c46 Iustin Pop
    in
159 e4f08c46 Iustin Pop
      foldl' (\ nz (a, b, c) ->
160 e4f08c46 Iustin Pop
                 let new_p = Container.find b nz
161 e4f08c46 Iustin Pop
                     new_s = Container.find c nz in
162 e4f08c46 Iustin Pop
                 fromJust (addInstance nz a new_p new_s)
163 e4f08c46 Iustin Pop
           ) nc odxes
164 e4f08c46 Iustin Pop
165 e4f08c46 Iustin Pop
166 e4f08c46 Iustin Pop
-- First phase functions
167 e4f08c46 Iustin Pop
168 e4f08c46 Iustin Pop
{- | Given a list 1,2,3..n build a list of pairs [(1, [2..n]), (2,
169 e4f08c46 Iustin Pop
    [3..n]), ...]
170 e4f08c46 Iustin Pop
171 e4f08c46 Iustin Pop
-}
172 e4f08c46 Iustin Pop
genParts :: [a] -> Int -> [(a, [a])]
173 e4f08c46 Iustin Pop
genParts l count =
174 e4f08c46 Iustin Pop
    case l of
175 e4f08c46 Iustin Pop
      [] -> []
176 e4f08c46 Iustin Pop
      x:xs ->
177 e4f08c46 Iustin Pop
          if length l < count then
178 e4f08c46 Iustin Pop
              []
179 e4f08c46 Iustin Pop
          else
180 e4f08c46 Iustin Pop
              (x, xs) : (genParts xs count)
181 e4f08c46 Iustin Pop
182 e4f08c46 Iustin Pop
-- | Generates combinations of count items from the names list.
183 e4f08c46 Iustin Pop
genNames :: Int -> [b] -> [[b]]
184 e4f08c46 Iustin Pop
genNames count1 names1 =
185 e4f08c46 Iustin Pop
  let aux_fn count names current =
186 e4f08c46 Iustin Pop
          case count of
187 e4f08c46 Iustin Pop
            0 -> [current]
188 e4f08c46 Iustin Pop
            _ ->
189 e4f08c46 Iustin Pop
                concatMap
190 e4f08c46 Iustin Pop
                (\ (x, xs) -> aux_fn (count - 1) xs (x:current))
191 e4f08c46 Iustin Pop
                (genParts names count)
192 e4f08c46 Iustin Pop
  in
193 e4f08c46 Iustin Pop
    aux_fn count1 names1 []
194 e4f08c46 Iustin Pop
195 e4f08c46 Iustin Pop
{- | Computes the pair of bad nodes and instances.
196 e4f08c46 Iustin Pop
197 e4f08c46 Iustin Pop
The bad node list is computed via a simple 'verifyN1' check, and the
198 e4f08c46 Iustin Pop
bad instance list is the list of primary and secondary instances of
199 e4f08c46 Iustin Pop
those nodes.
200 e4f08c46 Iustin Pop
201 e4f08c46 Iustin Pop
-}
202 e4f08c46 Iustin Pop
computeBadItems :: NodeList -> InstanceList ->
203 e4f08c46 Iustin Pop
                   ([Node.Node], [Instance.Instance])
204 e4f08c46 Iustin Pop
computeBadItems nl il =
205 e4f08c46 Iustin Pop
  let bad_nodes = verifyN1 $ Container.elems nl
206 e4f08c46 Iustin Pop
      bad_instances = map (\idx -> Container.find idx il) $
207 e4f08c46 Iustin Pop
                      sort $ nub $ concat $
208 e4f08c46 Iustin Pop
                      map (\ n -> (Node.slist n) ++ (Node.plist n)) bad_nodes
209 e4f08c46 Iustin Pop
  in
210 e4f08c46 Iustin Pop
    (bad_nodes, bad_instances)
211 e4f08c46 Iustin Pop
212 e4f08c46 Iustin Pop
213 e4f08c46 Iustin Pop
{- | Checks if removal of instances results in N+1 pass.
214 e4f08c46 Iustin Pop
215 e4f08c46 Iustin Pop
Note: the check removal cannot optimize by scanning only the affected
216 e4f08c46 Iustin Pop
nodes, since the cluster is known to be not healthy; only the check
217 e4f08c46 Iustin Pop
placement can make this shortcut.
218 e4f08c46 Iustin Pop
219 e4f08c46 Iustin Pop
-}
220 e4f08c46 Iustin Pop
checkRemoval :: NodeList -> [Instance.Instance] -> Maybe Removal
221 e4f08c46 Iustin Pop
checkRemoval nl victims =
222 e4f08c46 Iustin Pop
  let nx = removeInstances nl victims
223 e4f08c46 Iustin Pop
      failN1 = verifyN1Check (Container.elems nx)
224 e4f08c46 Iustin Pop
  in
225 e4f08c46 Iustin Pop
    if failN1 then
226 e4f08c46 Iustin Pop
      Nothing
227 e4f08c46 Iustin Pop
    else
228 e4f08c46 Iustin Pop
      Just $ Removal nx victims
229 e4f08c46 Iustin Pop
230 e4f08c46 Iustin Pop
231 e4f08c46 Iustin Pop
-- | Computes the removals list for a given depth
232 669d7e3d Iustin Pop
computeRemovals :: NodeList
233 e4f08c46 Iustin Pop
                 -> [Instance.Instance]
234 e4f08c46 Iustin Pop
                 -> Int
235 669d7e3d Iustin Pop
                 -> [Maybe Removal]
236 e4f08c46 Iustin Pop
computeRemovals nl bad_instances depth =
237 e4f08c46 Iustin Pop
    map (checkRemoval nl) $ genNames depth bad_instances
238 e4f08c46 Iustin Pop
239 e4f08c46 Iustin Pop
-- Second phase functions
240 e4f08c46 Iustin Pop
241 e4f08c46 Iustin Pop
-- | Single-node relocation cost
242 e4f08c46 Iustin Pop
nodeDelta :: Int -> Int -> Int -> Int
243 e4f08c46 Iustin Pop
nodeDelta i p s =
244 e4f08c46 Iustin Pop
    if i == p || i == s then
245 e4f08c46 Iustin Pop
        0
246 e4f08c46 Iustin Pop
    else
247 e4f08c46 Iustin Pop
        1
248 e4f08c46 Iustin Pop
249 e4f08c46 Iustin Pop
{-| Compute best solution.
250 e4f08c46 Iustin Pop
251 e4f08c46 Iustin Pop
    This function compares two solutions, choosing the minimum valid
252 e4f08c46 Iustin Pop
    solution.
253 e4f08c46 Iustin Pop
-}
254 e4f08c46 Iustin Pop
compareSolutions :: Maybe Solution -> Maybe Solution -> Maybe Solution
255 e4f08c46 Iustin Pop
compareSolutions a b = case (a, b) of
256 e4f08c46 Iustin Pop
  (Nothing, x) -> x
257 e4f08c46 Iustin Pop
  (x, Nothing) -> x
258 e4f08c46 Iustin Pop
  (x, y) -> min x y
259 e4f08c46 Iustin Pop
260 e4f08c46 Iustin Pop
-- | Compute best table. Note that the ordering of the arguments is important.
261 e4f08c46 Iustin Pop
compareTables :: Table -> Table -> Table
262 e4f08c46 Iustin Pop
compareTables a@(Table _ _ a_cv _) b@(Table _ _ b_cv _ ) =
263 e4f08c46 Iustin Pop
    if a_cv > b_cv then b else a
264 e4f08c46 Iustin Pop
265 e4f08c46 Iustin Pop
-- | Check if a given delta is worse then an existing solution.
266 e4f08c46 Iustin Pop
tooHighDelta :: Maybe Solution -> Int -> Int -> Bool
267 e4f08c46 Iustin Pop
tooHighDelta sol new_delta max_delta =
268 e4f08c46 Iustin Pop
    if new_delta > max_delta && max_delta >=0 then
269 e4f08c46 Iustin Pop
        True
270 e4f08c46 Iustin Pop
    else
271 e4f08c46 Iustin Pop
        case sol of
272 e4f08c46 Iustin Pop
          Nothing -> False
273 e4f08c46 Iustin Pop
          Just (Solution old_delta _) -> old_delta <= new_delta
274 e4f08c46 Iustin Pop
275 e4f08c46 Iustin Pop
{-| Check if placement of instances still keeps the cluster N+1 compliant.
276 e4f08c46 Iustin Pop
277 e4f08c46 Iustin Pop
    This is the workhorse of the allocation algorithm: given the
278 e4f08c46 Iustin Pop
    current node and instance maps, the list of instances to be
279 e4f08c46 Iustin Pop
    placed, and the current solution, this will return all possible
280 e4f08c46 Iustin Pop
    solution by recursing until all target instances are placed.
281 e4f08c46 Iustin Pop
282 e4f08c46 Iustin Pop
-}
283 e4f08c46 Iustin Pop
checkPlacement :: NodeList            -- ^ The current node list
284 e4f08c46 Iustin Pop
               -> [Instance.Instance] -- ^ List of instances still to place
285 e4f08c46 Iustin Pop
               -> [Placement]         -- ^ Partial solution until now
286 e4f08c46 Iustin Pop
               -> Int                 -- ^ The delta of the partial solution
287 e4f08c46 Iustin Pop
               -> Maybe Solution      -- ^ The previous solution
288 e4f08c46 Iustin Pop
               -> Int                 -- ^ Abort if the we go above this delta
289 e4f08c46 Iustin Pop
               -> Maybe Solution      -- ^ The new solution
290 e4f08c46 Iustin Pop
checkPlacement nl victims current current_delta prev_sol max_delta =
291 e4f08c46 Iustin Pop
  let target = head victims
292 e4f08c46 Iustin Pop
      opdx = Instance.pnode target
293 e4f08c46 Iustin Pop
      osdx = Instance.snode target
294 e4f08c46 Iustin Pop
      vtail = tail victims
295 e4f08c46 Iustin Pop
      have_tail = (length vtail) > 0
296 e4f08c46 Iustin Pop
      nodes = Container.elems nl
297 c5c295bc Iustin Pop
      iidx = Instance.idx target
298 e4f08c46 Iustin Pop
  in
299 e4f08c46 Iustin Pop
    foldl'
300 e4f08c46 Iustin Pop
    (\ accu_p pri ->
301 e4f08c46 Iustin Pop
         let
302 e4f08c46 Iustin Pop
             pri_idx = Node.idx pri
303 e4f08c46 Iustin Pop
             upri_delta = current_delta + nodeDelta pri_idx opdx osdx
304 e4f08c46 Iustin Pop
             new_pri = Node.addPri pri target
305 e4f08c46 Iustin Pop
             fail_delta1 = tooHighDelta accu_p upri_delta max_delta
306 e4f08c46 Iustin Pop
         in
307 e4f08c46 Iustin Pop
           if fail_delta1 || isNothing(new_pri) then accu_p
308 e4f08c46 Iustin Pop
           else let pri_nl = Container.add pri_idx (fromJust new_pri) nl in
309 e4f08c46 Iustin Pop
                foldl'
310 e4f08c46 Iustin Pop
                (\ accu sec ->
311 e4f08c46 Iustin Pop
                     let
312 e4f08c46 Iustin Pop
                         sec_idx = Node.idx sec
313 e4f08c46 Iustin Pop
                         upd_delta = upri_delta +
314 e4f08c46 Iustin Pop
                                     nodeDelta sec_idx opdx osdx
315 e4f08c46 Iustin Pop
                         fail_delta2 = tooHighDelta accu upd_delta max_delta
316 e4f08c46 Iustin Pop
                         new_sec = Node.addSec sec target pri_idx
317 e4f08c46 Iustin Pop
                     in
318 e4f08c46 Iustin Pop
                       if sec_idx == pri_idx || fail_delta2 ||
319 e4f08c46 Iustin Pop
                          isNothing new_sec then accu
320 e4f08c46 Iustin Pop
                       else let
321 e4f08c46 Iustin Pop
                           nx = Container.add sec_idx (fromJust new_sec) pri_nl
322 c5c295bc Iustin Pop
                           upd_cv = compCV nx
323 c5c295bc Iustin Pop
                           plc = (iidx, pri_idx, sec_idx, upd_cv)
324 e4f08c46 Iustin Pop
                           c2 = plc:current
325 e4f08c46 Iustin Pop
                           result =
326 e4f08c46 Iustin Pop
                               if have_tail then
327 e4f08c46 Iustin Pop
                                   checkPlacement nx vtail c2 upd_delta
328 e4f08c46 Iustin Pop
                                                  accu max_delta
329 e4f08c46 Iustin Pop
                               else
330 e4f08c46 Iustin Pop
                                   Just (Solution upd_delta c2)
331 e4f08c46 Iustin Pop
                      in compareSolutions accu result
332 e4f08c46 Iustin Pop
                ) accu_p nodes
333 e4f08c46 Iustin Pop
    ) prev_sol nodes
334 e4f08c46 Iustin Pop
335 e4f08c46 Iustin Pop
-- | Apply a move
336 e4f08c46 Iustin Pop
applyMove :: NodeList -> Instance.Instance
337 e4f08c46 Iustin Pop
          -> IMove -> (Maybe NodeList, Instance.Instance, Int, Int)
338 00b51a14 Iustin Pop
-- Failover (f)
339 e4f08c46 Iustin Pop
applyMove nl inst Failover =
340 e4f08c46 Iustin Pop
    let old_pdx = Instance.pnode inst
341 e4f08c46 Iustin Pop
        old_sdx = Instance.snode inst
342 e4f08c46 Iustin Pop
        old_p = Container.find old_pdx nl
343 e4f08c46 Iustin Pop
        old_s = Container.find old_sdx nl
344 e4f08c46 Iustin Pop
        int_p = Node.removePri old_p inst
345 e4f08c46 Iustin Pop
        int_s = Node.removeSec old_s inst
346 e4f08c46 Iustin Pop
        new_p = Node.addPri int_s inst
347 e4f08c46 Iustin Pop
        new_s = Node.addSec int_p inst old_sdx
348 e4f08c46 Iustin Pop
        new_nl = if isNothing(new_p) || isNothing(new_s) then Nothing
349 e4f08c46 Iustin Pop
                 else Just $ Container.addTwo old_pdx (fromJust new_s)
350 e4f08c46 Iustin Pop
                      old_sdx (fromJust new_p) nl
351 e4f08c46 Iustin Pop
    in (new_nl, Instance.setBoth inst old_sdx old_pdx, old_sdx, old_pdx)
352 e4f08c46 Iustin Pop
353 00b51a14 Iustin Pop
-- Replace the primary (f:, r:np, f)
354 e4f08c46 Iustin Pop
applyMove nl inst (ReplacePrimary new_pdx) =
355 e4f08c46 Iustin Pop
    let old_pdx = Instance.pnode inst
356 e4f08c46 Iustin Pop
        old_sdx = Instance.snode inst
357 e4f08c46 Iustin Pop
        old_p = Container.find old_pdx nl
358 e4f08c46 Iustin Pop
        old_s = Container.find old_sdx nl
359 e4f08c46 Iustin Pop
        tgt_n = Container.find new_pdx nl
360 e4f08c46 Iustin Pop
        int_p = Node.removePri old_p inst
361 e4f08c46 Iustin Pop
        int_s = Node.removeSec old_s inst
362 e4f08c46 Iustin Pop
        new_p = Node.addPri tgt_n inst
363 e4f08c46 Iustin Pop
        new_s = Node.addSec int_s inst new_pdx
364 e4f08c46 Iustin Pop
        new_nl = if isNothing(new_p) || isNothing(new_s) then Nothing
365 e4f08c46 Iustin Pop
                 else Just $ Container.add new_pdx (fromJust new_p) $
366 e4f08c46 Iustin Pop
                      Container.addTwo old_pdx int_p
367 e4f08c46 Iustin Pop
                               old_sdx (fromJust new_s) nl
368 e4f08c46 Iustin Pop
    in (new_nl, Instance.setPri inst new_pdx, new_pdx, old_sdx)
369 e4f08c46 Iustin Pop
370 00b51a14 Iustin Pop
-- Replace the secondary (r:ns)
371 e4f08c46 Iustin Pop
applyMove nl inst (ReplaceSecondary new_sdx) =
372 e4f08c46 Iustin Pop
    let old_pdx = Instance.pnode inst
373 e4f08c46 Iustin Pop
        old_sdx = Instance.snode inst
374 e4f08c46 Iustin Pop
        old_s = Container.find old_sdx nl
375 e4f08c46 Iustin Pop
        tgt_n = Container.find new_sdx nl
376 e4f08c46 Iustin Pop
        int_s = Node.removeSec old_s inst
377 e4f08c46 Iustin Pop
        new_s = Node.addSec tgt_n inst old_pdx
378 e4f08c46 Iustin Pop
        new_nl = if isNothing(new_s) then Nothing
379 e4f08c46 Iustin Pop
                 else Just $ Container.addTwo new_sdx (fromJust new_s)
380 e4f08c46 Iustin Pop
                      old_sdx int_s nl
381 e4f08c46 Iustin Pop
    in (new_nl, Instance.setSec inst new_sdx, old_pdx, new_sdx)
382 e4f08c46 Iustin Pop
383 00b51a14 Iustin Pop
-- Replace the secondary and failover (r:np, f)
384 79ac6b6f Iustin Pop
applyMove nl inst (ReplaceAndFailover new_pdx) =
385 79ac6b6f Iustin Pop
    let old_pdx = Instance.pnode inst
386 79ac6b6f Iustin Pop
        old_sdx = Instance.snode inst
387 79ac6b6f Iustin Pop
        old_p = Container.find old_pdx nl
388 79ac6b6f Iustin Pop
        old_s = Container.find old_sdx nl
389 79ac6b6f Iustin Pop
        tgt_n = Container.find new_pdx nl
390 79ac6b6f Iustin Pop
        int_p = Node.removePri old_p inst
391 79ac6b6f Iustin Pop
        int_s = Node.removeSec old_s inst
392 79ac6b6f Iustin Pop
        new_p = Node.addPri tgt_n inst
393 79ac6b6f Iustin Pop
        new_s = Node.addSec int_p inst new_pdx
394 79ac6b6f Iustin Pop
        new_nl = if isNothing(new_p) || isNothing(new_s) then Nothing
395 79ac6b6f Iustin Pop
                 else Just $ Container.add new_pdx (fromJust new_p) $
396 79ac6b6f Iustin Pop
                      Container.addTwo old_pdx (fromJust new_s)
397 79ac6b6f Iustin Pop
                               old_sdx int_s nl
398 79ac6b6f Iustin Pop
    in (new_nl, Instance.setBoth inst new_pdx old_pdx, new_pdx, old_pdx)
399 79ac6b6f Iustin Pop
400 19493d33 Iustin Pop
-- Failver and replace the secondary (f, r:ns)
401 19493d33 Iustin Pop
applyMove nl inst (FailoverAndReplace new_sdx) =
402 19493d33 Iustin Pop
    let old_pdx = Instance.pnode inst
403 19493d33 Iustin Pop
        old_sdx = Instance.snode inst
404 19493d33 Iustin Pop
        old_p = Container.find old_pdx nl
405 19493d33 Iustin Pop
        old_s = Container.find old_sdx nl
406 19493d33 Iustin Pop
        tgt_n = Container.find new_sdx nl
407 19493d33 Iustin Pop
        int_p = Node.removePri old_p inst
408 19493d33 Iustin Pop
        int_s = Node.removeSec old_s inst
409 19493d33 Iustin Pop
        new_p = Node.addPri int_s inst
410 19493d33 Iustin Pop
        new_s = Node.addSec tgt_n inst old_sdx
411 19493d33 Iustin Pop
        new_nl = if isNothing(new_p) || isNothing(new_s) then Nothing
412 19493d33 Iustin Pop
                 else Just $ Container.add new_sdx (fromJust new_s) $
413 19493d33 Iustin Pop
                      Container.addTwo old_sdx (fromJust new_p)
414 19493d33 Iustin Pop
                               old_pdx int_p nl
415 19493d33 Iustin Pop
    in (new_nl, Instance.setBoth inst old_sdx new_sdx, old_sdx, new_sdx)
416 19493d33 Iustin Pop
417 e4f08c46 Iustin Pop
checkSingleStep :: Table -- ^ The original table
418 e4f08c46 Iustin Pop
                -> Instance.Instance -- ^ The instance to move
419 e4f08c46 Iustin Pop
                -> Table -- ^ The current best table
420 e4f08c46 Iustin Pop
                -> IMove -- ^ The move to apply
421 e4f08c46 Iustin Pop
                -> Table -- ^ The final best table
422 e4f08c46 Iustin Pop
checkSingleStep ini_tbl target cur_tbl move =
423 e4f08c46 Iustin Pop
    let
424 e4f08c46 Iustin Pop
        Table ini_nl ini_il _ ini_plc = ini_tbl
425 0a0f2533 Iustin Pop
        (tmp_nl, new_inst, pri_idx, sec_idx) = applyMove ini_nl target move
426 e4f08c46 Iustin Pop
    in
427 e4f08c46 Iustin Pop
      if isNothing tmp_nl then cur_tbl
428 e4f08c46 Iustin Pop
      else
429 e4f08c46 Iustin Pop
          let tgt_idx = Instance.idx target
430 e4f08c46 Iustin Pop
              upd_nl = fromJust tmp_nl
431 e4f08c46 Iustin Pop
              upd_cvar = compCV upd_nl
432 e4f08c46 Iustin Pop
              upd_il = Container.add tgt_idx new_inst ini_il
433 0a0f2533 Iustin Pop
              upd_plc = (tgt_idx, pri_idx, sec_idx, upd_cvar):ini_plc
434 e4f08c46 Iustin Pop
              upd_tbl = Table upd_nl upd_il upd_cvar upd_plc
435 e4f08c46 Iustin Pop
          in
436 e4f08c46 Iustin Pop
            compareTables cur_tbl upd_tbl
437 e4f08c46 Iustin Pop
438 40d4eba0 Iustin Pop
-- | Given the status of the current secondary as a valid new node
439 40d4eba0 Iustin Pop
-- and the current candidate target node,
440 40d4eba0 Iustin Pop
-- generate the possible moves for a instance.
441 40d4eba0 Iustin Pop
possibleMoves :: Bool -> Int -> [IMove]
442 40d4eba0 Iustin Pop
possibleMoves True tdx =
443 40d4eba0 Iustin Pop
    [ReplaceSecondary tdx,
444 40d4eba0 Iustin Pop
     ReplaceAndFailover tdx,
445 40d4eba0 Iustin Pop
     ReplacePrimary tdx,
446 40d4eba0 Iustin Pop
     FailoverAndReplace tdx]
447 40d4eba0 Iustin Pop
448 40d4eba0 Iustin Pop
possibleMoves False tdx =
449 40d4eba0 Iustin Pop
    [ReplaceSecondary tdx,
450 40d4eba0 Iustin Pop
     ReplaceAndFailover tdx]
451 40d4eba0 Iustin Pop
452 40d4eba0 Iustin Pop
-- | Compute the best move for a given instance.
453 256810de Iustin Pop
checkInstanceMove :: [Int]             -- Allowed target node indices
454 256810de Iustin Pop
                  -> Table             -- Original table
455 256810de Iustin Pop
                  -> Instance.Instance -- Instance to move
456 256810de Iustin Pop
                  -> Table             -- Best new table for this instance
457 256810de Iustin Pop
checkInstanceMove nodes_idx ini_tbl target =
458 4e25d1c2 Iustin Pop
    let
459 4e25d1c2 Iustin Pop
        opdx = Instance.pnode target
460 4e25d1c2 Iustin Pop
        osdx = Instance.snode target
461 9dc6023f Iustin Pop
        nodes = filter (\idx -> idx /= opdx && idx /= osdx) nodes_idx
462 40d4eba0 Iustin Pop
        use_secondary = elem osdx nodes_idx
463 40d4eba0 Iustin Pop
        aft_failover = if use_secondary -- if allowed to failover
464 40d4eba0 Iustin Pop
                       then checkSingleStep ini_tbl target ini_tbl Failover
465 40d4eba0 Iustin Pop
                       else ini_tbl
466 40d4eba0 Iustin Pop
        all_moves = concatMap (possibleMoves use_secondary) nodes
467 4e25d1c2 Iustin Pop
    in
468 4e25d1c2 Iustin Pop
      -- iterate over the possible nodes for this instance
469 9dc6023f Iustin Pop
      foldl' (checkSingleStep ini_tbl target) aft_failover all_moves
470 4e25d1c2 Iustin Pop
471 e4f08c46 Iustin Pop
-- | Compute the best next move.
472 256810de Iustin Pop
checkMove :: [Int]               -- ^ Allowed target node indices
473 256810de Iustin Pop
          -> Table               -- ^ The current solution
474 e4f08c46 Iustin Pop
          -> [Instance.Instance] -- ^ List of instances still to move
475 256810de Iustin Pop
          -> Table               -- ^ The new solution
476 256810de Iustin Pop
checkMove nodes_idx ini_tbl victims =
477 4e25d1c2 Iustin Pop
    let Table _ _ _ ini_plc = ini_tbl
478 4e25d1c2 Iustin Pop
        -- iterate over all instances, computing the best move
479 256810de Iustin Pop
        best_tbl =
480 256810de Iustin Pop
            foldl'
481 256810de Iustin Pop
            (\ step_tbl elem -> compareTables step_tbl $
482 256810de Iustin Pop
                                checkInstanceMove nodes_idx ini_tbl elem)
483 256810de Iustin Pop
            ini_tbl victims
484 aaaa0e43 Iustin Pop
        Table _ _ _ best_plc = best_tbl
485 0a0f2533 Iustin Pop
    in
486 0a0f2533 Iustin Pop
      if length best_plc == length ini_plc then -- no advancement
487 0a0f2533 Iustin Pop
          ini_tbl
488 0a0f2533 Iustin Pop
      else
489 7dfaafb1 Iustin Pop
          best_tbl
490 e4f08c46 Iustin Pop
491 e4f08c46 Iustin Pop
{- | Auxiliary function for solution computation.
492 e4f08c46 Iustin Pop
493 e4f08c46 Iustin Pop
We write this in an explicit recursive fashion in order to control
494 e4f08c46 Iustin Pop
early-abort in case we have met the min delta. We can't use foldr
495 e4f08c46 Iustin Pop
instead of explicit recursion since we need the accumulator for the
496 e4f08c46 Iustin Pop
abort decision.
497 e4f08c46 Iustin Pop
498 e4f08c46 Iustin Pop
-}
499 e4f08c46 Iustin Pop
advanceSolution :: [Maybe Removal] -- ^ The removal to process
500 e4f08c46 Iustin Pop
                -> Int             -- ^ Minimum delta parameter
501 e4f08c46 Iustin Pop
                -> Int             -- ^ Maximum delta parameter
502 e4f08c46 Iustin Pop
                -> Maybe Solution  -- ^ Current best solution
503 e4f08c46 Iustin Pop
                -> Maybe Solution  -- ^ New best solution
504 e4f08c46 Iustin Pop
advanceSolution [] _ _ sol = sol
505 e4f08c46 Iustin Pop
advanceSolution (Nothing:xs) m n sol = advanceSolution xs m n sol
506 e4f08c46 Iustin Pop
advanceSolution ((Just (Removal nx removed)):xs) min_d max_d prev_sol =
507 e4f08c46 Iustin Pop
    let new_sol = checkPlacement nx removed [] 0 prev_sol max_d
508 e4f08c46 Iustin Pop
        new_delta = solutionDelta $! new_sol
509 e4f08c46 Iustin Pop
    in
510 e4f08c46 Iustin Pop
      if new_delta >= 0 && new_delta <= min_d then
511 e4f08c46 Iustin Pop
          new_sol
512 e4f08c46 Iustin Pop
      else
513 e4f08c46 Iustin Pop
          advanceSolution xs min_d max_d new_sol
514 e4f08c46 Iustin Pop
515 e4f08c46 Iustin Pop
-- | Computes the placement solution.
516 e4f08c46 Iustin Pop
solutionFromRemovals :: [Maybe Removal] -- ^ The list of (possible) removals
517 e4f08c46 Iustin Pop
                     -> Int             -- ^ Minimum delta parameter
518 e4f08c46 Iustin Pop
                     -> Int             -- ^ Maximum delta parameter
519 e4f08c46 Iustin Pop
                     -> Maybe Solution  -- ^ The best solution found
520 e4f08c46 Iustin Pop
solutionFromRemovals removals min_delta max_delta =
521 e4f08c46 Iustin Pop
    advanceSolution removals min_delta max_delta Nothing
522 e4f08c46 Iustin Pop
523 e4f08c46 Iustin Pop
{- | Computes the solution at the given depth.
524 e4f08c46 Iustin Pop
525 e4f08c46 Iustin Pop
This is a wrapper over both computeRemovals and
526 e4f08c46 Iustin Pop
solutionFromRemovals. In case we have no solution, we return Nothing.
527 e4f08c46 Iustin Pop
528 e4f08c46 Iustin Pop
-}
529 e4f08c46 Iustin Pop
computeSolution :: NodeList        -- ^ The original node data
530 e4f08c46 Iustin Pop
                -> [Instance.Instance] -- ^ The list of /bad/ instances
531 e4f08c46 Iustin Pop
                -> Int             -- ^ The /depth/ of removals
532 e4f08c46 Iustin Pop
                -> Int             -- ^ Maximum number of removals to process
533 e4f08c46 Iustin Pop
                -> Int             -- ^ Minimum delta parameter
534 e4f08c46 Iustin Pop
                -> Int             -- ^ Maximum delta parameter
535 e4f08c46 Iustin Pop
                -> Maybe Solution  -- ^ The best solution found (or Nothing)
536 e4f08c46 Iustin Pop
computeSolution nl bad_instances depth max_removals min_delta max_delta =
537 e4f08c46 Iustin Pop
  let
538 e4f08c46 Iustin Pop
      removals = computeRemovals nl bad_instances depth
539 e4f08c46 Iustin Pop
      removals' = capRemovals removals max_removals
540 e4f08c46 Iustin Pop
  in
541 e4f08c46 Iustin Pop
    solutionFromRemovals removals' min_delta max_delta
542 e4f08c46 Iustin Pop
543 e4f08c46 Iustin Pop
-- Solution display functions (pure)
544 e4f08c46 Iustin Pop
545 e4f08c46 Iustin Pop
-- | Given the original and final nodes, computes the relocation description.
546 e4f08c46 Iustin Pop
computeMoves :: String -- ^ The instance name
547 e4f08c46 Iustin Pop
             -> String -- ^ Original primary
548 e4f08c46 Iustin Pop
             -> String -- ^ Original secondary
549 e4f08c46 Iustin Pop
             -> String -- ^ New primary
550 e4f08c46 Iustin Pop
             -> String -- ^ New secondary
551 e4f08c46 Iustin Pop
             -> (String, [String])
552 e4f08c46 Iustin Pop
                -- ^ Tuple of moves and commands list; moves is containing
553 e4f08c46 Iustin Pop
                -- either @/f/@ for failover or @/r:name/@ for replace
554 e4f08c46 Iustin Pop
                -- secondary, while the command list holds gnt-instance
555 e4f08c46 Iustin Pop
                -- commands (without that prefix), e.g \"@failover instance1@\"
556 e4f08c46 Iustin Pop
computeMoves i a b c d =
557 e4f08c46 Iustin Pop
    if c == a then {- Same primary -}
558 e4f08c46 Iustin Pop
        if d == b then {- Same sec??! -}
559 e4f08c46 Iustin Pop
            ("-", [])
560 e4f08c46 Iustin Pop
        else {- Change of secondary -}
561 e4f08c46 Iustin Pop
            (printf "r:%s" d,
562 e4f08c46 Iustin Pop
             [printf "replace-disks -n %s %s" d i])
563 e4f08c46 Iustin Pop
    else
564 e4f08c46 Iustin Pop
        if c == b then {- Failover and ... -}
565 e4f08c46 Iustin Pop
            if d == a then {- that's all -}
566 e0eb63f0 Iustin Pop
                ("f", [printf "migrate -f %s" i])
567 e4f08c46 Iustin Pop
            else
568 e4f08c46 Iustin Pop
                (printf "f r:%s" d,
569 e0eb63f0 Iustin Pop
                 [printf "migrate -f %s" i,
570 e4f08c46 Iustin Pop
                  printf "replace-disks -n %s %s" d i])
571 e4f08c46 Iustin Pop
        else
572 e4f08c46 Iustin Pop
            if d == a then {- ... and keep primary as secondary -}
573 e4f08c46 Iustin Pop
                (printf "r:%s f" c,
574 e4f08c46 Iustin Pop
                 [printf "replace-disks -n %s %s" c i,
575 e0eb63f0 Iustin Pop
                  printf "migrate -f %s" i])
576 e4f08c46 Iustin Pop
            else
577 e4f08c46 Iustin Pop
                if d == b then {- ... keep same secondary -}
578 e4f08c46 Iustin Pop
                    (printf "f r:%s f" c,
579 e0eb63f0 Iustin Pop
                     [printf "migrate -f %s" i,
580 e4f08c46 Iustin Pop
                      printf "replace-disks -n %s %s" c i,
581 e0eb63f0 Iustin Pop
                      printf "migrate -f %s" i])
582 e4f08c46 Iustin Pop
583 e4f08c46 Iustin Pop
                else {- Nothing in common -}
584 e4f08c46 Iustin Pop
                    (printf "r:%s f r:%s" c d,
585 e4f08c46 Iustin Pop
                     [printf "replace-disks -n %s %s" c i,
586 e0eb63f0 Iustin Pop
                      printf "migrate -f %s" i,
587 e4f08c46 Iustin Pop
                      printf "replace-disks -n %s %s" d i])
588 e4f08c46 Iustin Pop
589 ca8258d9 Iustin Pop
{-| Converts a placement to string format -}
590 ca8258d9 Iustin Pop
printSolutionLine :: InstanceList
591 740ec004 Iustin Pop
              -> NameList
592 740ec004 Iustin Pop
              -> NameList
593 ca8258d9 Iustin Pop
              -> Int
594 ca8258d9 Iustin Pop
              -> Int
595 ca8258d9 Iustin Pop
              -> Placement
596 ab271fc1 Iustin Pop
              -> Int
597 ca8258d9 Iustin Pop
              -> (String, [String])
598 ab271fc1 Iustin Pop
printSolutionLine il ktn kti nmlen imlen plc pos =
599 ca8258d9 Iustin Pop
    let
600 ca8258d9 Iustin Pop
        pmlen = (2*nmlen + 1)
601 ca8258d9 Iustin Pop
        (i, p, s, c) = plc
602 ca8258d9 Iustin Pop
        inst = Container.find i il
603 ca8258d9 Iustin Pop
        inam = fromJust $ lookup (Instance.idx inst) kti
604 ca8258d9 Iustin Pop
        npri = fromJust $ lookup p ktn
605 ca8258d9 Iustin Pop
        nsec = fromJust $ lookup s ktn
606 ca8258d9 Iustin Pop
        opri = fromJust $ lookup (Instance.pnode inst) ktn
607 ca8258d9 Iustin Pop
        osec = fromJust $ lookup (Instance.snode inst) ktn
608 ca8258d9 Iustin Pop
        (moves, cmds) =  computeMoves inam opri osec npri nsec
609 ca8258d9 Iustin Pop
        ostr = (printf "%s:%s" opri osec)::String
610 ca8258d9 Iustin Pop
        nstr = (printf "%s:%s" npri nsec)::String
611 ca8258d9 Iustin Pop
    in
612 ab271fc1 Iustin Pop
      (printf "  %3d. %-*s %-*s => %-*s %.8f a=%s"
613 ab271fc1 Iustin Pop
       pos imlen inam pmlen ostr
614 ca8258d9 Iustin Pop
       pmlen nstr c moves,
615 ca8258d9 Iustin Pop
       cmds)
616 ca8258d9 Iustin Pop
617 142538ff Iustin Pop
formatCmds :: [[String]] -> String
618 142538ff Iustin Pop
formatCmds cmd_strs =
619 e0eb63f0 Iustin Pop
    unlines $
620 142538ff Iustin Pop
    concat $ map (\(a, b) ->
621 e0eb63f0 Iustin Pop
        (printf "echo step %d" (a::Int)):
622 e0eb63f0 Iustin Pop
        (printf "check"):
623 e0eb63f0 Iustin Pop
        (map ("gnt-instance " ++) b)) $
624 142538ff Iustin Pop
        zip [1..] cmd_strs
625 142538ff Iustin Pop
626 e4f08c46 Iustin Pop
{-| Converts a solution to string format -}
627 e4f08c46 Iustin Pop
printSolution :: InstanceList
628 740ec004 Iustin Pop
              -> NameList
629 740ec004 Iustin Pop
              -> NameList
630 e4f08c46 Iustin Pop
              -> [Placement]
631 e4f08c46 Iustin Pop
              -> ([String], [[String]])
632 e4f08c46 Iustin Pop
printSolution il ktn kti sol =
633 671b85b9 Iustin Pop
    let
634 671b85b9 Iustin Pop
        mlen_fn = maximum . (map length) . snd . unzip
635 671b85b9 Iustin Pop
        imlen = mlen_fn kti
636 671b85b9 Iustin Pop
        nmlen = mlen_fn ktn
637 671b85b9 Iustin Pop
    in
638 ab271fc1 Iustin Pop
      unzip $ map (uncurry $ printSolutionLine il ktn kti nmlen imlen) $
639 ab271fc1 Iustin Pop
            zip sol [1..]
640 e4f08c46 Iustin Pop
641 e4f08c46 Iustin Pop
-- | Print the node list.
642 740ec004 Iustin Pop
printNodes :: NameList -> NodeList -> String
643 e4f08c46 Iustin Pop
printNodes ktn nl =
644 e4f08c46 Iustin Pop
    let snl = sortBy (compare `on` Node.idx) (Container.elems nl)
645 e4f08c46 Iustin Pop
        snl' = map (\ n -> ((fromJust $ lookup (Node.idx n) ktn), n)) snl
646 af53a5c4 Iustin Pop
        m_name = maximum . (map length) . fst . unzip $ snl'
647 af53a5c4 Iustin Pop
        helper = Node.list m_name
648 a1c6212e Iustin Pop
        header = printf
649 a1c6212e Iustin Pop
                 "%2s %-*s %5s %5s %5s %5s %5s %5s %5s %5s %3s %3s %7s %7s"
650 a1c6212e Iustin Pop
                 " F" m_name "Name"
651 a1c6212e Iustin Pop
                 "t_mem" "n_mem" "i_mem" "x_mem" "f_mem" "r_mem"
652 ced859f3 Iustin Pop
                 "t_dsk" "f_dsk"
653 ced859f3 Iustin Pop
                 "pri" "sec" "p_fmem" "p_fdsk"
654 ced859f3 Iustin Pop
    in unlines $ (header:map (uncurry helper) snl')
655 e4f08c46 Iustin Pop
656 e4f08c46 Iustin Pop
-- | Compute the mem and disk covariance.
657 19777638 Iustin Pop
compDetailedCV :: NodeList -> (Double, Double, Double, Double, Double)
658 e4f08c46 Iustin Pop
compDetailedCV nl =
659 0335fe4a Iustin Pop
    let
660 19777638 Iustin Pop
        all_nodes = Container.elems nl
661 19777638 Iustin Pop
        (offline, nodes) = partition Node.offline all_nodes
662 0335fe4a Iustin Pop
        mem_l = map Node.p_mem nodes
663 0335fe4a Iustin Pop
        dsk_l = map Node.p_dsk nodes
664 e4f08c46 Iustin Pop
        mem_cv = varianceCoeff mem_l
665 e4f08c46 Iustin Pop
        dsk_cv = varianceCoeff dsk_l
666 34a6e127 Iustin Pop
        n1_l = length $ filter Node.failN1 nodes
667 34a6e127 Iustin Pop
        n1_score = (fromIntegral n1_l) / (fromIntegral $ length nodes)
668 d6be0775 Iustin Pop
        res_l = map Node.p_rem nodes
669 d6be0775 Iustin Pop
        res_cv = varianceCoeff res_l
670 19777638 Iustin Pop
        offline_inst = sum . map (\n -> (length . Node.plist $ n) +
671 19777638 Iustin Pop
                                        (length . Node.slist $ n)) $ offline
672 19777638 Iustin Pop
        online_inst = sum . map (\n -> (length . Node.plist $ n) +
673 19777638 Iustin Pop
                                       (length . Node.slist $ n)) $ nodes
674 19777638 Iustin Pop
        off_score = (fromIntegral offline_inst) /
675 19777638 Iustin Pop
                    (fromIntegral $ online_inst + offline_inst)
676 19777638 Iustin Pop
    in (mem_cv, dsk_cv, n1_score, res_cv, off_score)
677 e4f08c46 Iustin Pop
678 e4f08c46 Iustin Pop
-- | Compute the 'total' variance.
679 e4f08c46 Iustin Pop
compCV :: NodeList -> Double
680 e4f08c46 Iustin Pop
compCV nl =
681 19777638 Iustin Pop
    let (mem_cv, dsk_cv, n1_score, res_cv, off_score) = compDetailedCV nl
682 19777638 Iustin Pop
    in mem_cv + dsk_cv + n1_score + res_cv + off_score
683 e4f08c46 Iustin Pop
684 e4f08c46 Iustin Pop
printStats :: NodeList -> String
685 e4f08c46 Iustin Pop
printStats nl =
686 19777638 Iustin Pop
    let (mem_cv, dsk_cv, n1_score, res_cv, off_score) = compDetailedCV nl
687 19777638 Iustin Pop
    in printf "f_mem=%.8f, r_mem=%.8f, f_dsk=%.8f, n1=%.3f, uf=%.3f"
688 19777638 Iustin Pop
       mem_cv res_cv dsk_cv n1_score off_score
689 e4f08c46 Iustin Pop
690 e4f08c46 Iustin Pop
-- Balancing functions
691 e4f08c46 Iustin Pop
692 e4f08c46 Iustin Pop
-- Loading functions
693 e4f08c46 Iustin Pop
694 e4f08c46 Iustin Pop
{- | Convert newline and delimiter-separated text.
695 e4f08c46 Iustin Pop
696 e4f08c46 Iustin Pop
This function converts a text in tabular format as generated by
697 e4f08c46 Iustin Pop
@gnt-instance list@ and @gnt-node list@ to a list of objects using a
698 e4f08c46 Iustin Pop
supplied conversion function.
699 e4f08c46 Iustin Pop
700 e4f08c46 Iustin Pop
-}
701 e4f08c46 Iustin Pop
loadTabular :: String -> ([String] -> (String, a))
702 e4f08c46 Iustin Pop
            -> (a -> Int -> a) -> ([(String, Int)], [(Int, a)])
703 e4f08c46 Iustin Pop
loadTabular text_data convert_fn set_fn =
704 e4f08c46 Iustin Pop
    let lines_data = lines text_data
705 e4f08c46 Iustin Pop
        rows = map (sepSplit '|') lines_data
706 e4f08c46 Iustin Pop
        kerows = (map convert_fn rows)
707 e4f08c46 Iustin Pop
        idxrows = map (\ (idx, (k, v)) -> ((k, idx), (idx, set_fn v idx)))
708 e4f08c46 Iustin Pop
                  (zip [0..] kerows)
709 e4f08c46 Iustin Pop
    in unzip idxrows
710 e4f08c46 Iustin Pop
711 01f6a5d2 Iustin Pop
-- | For each instance, add its index to its primary and secondary nodes
712 01f6a5d2 Iustin Pop
fixNodes :: [(Int, Node.Node)]
713 01f6a5d2 Iustin Pop
         -> [(Int, Instance.Instance)]
714 01f6a5d2 Iustin Pop
         -> [(Int, Node.Node)]
715 01f6a5d2 Iustin Pop
fixNodes nl il =
716 d4f62d4e Iustin Pop
    foldl' (\accu (idx, inst) ->
717 d4f62d4e Iustin Pop
                let
718 d4f62d4e Iustin Pop
                    assocEqual = (\ (i, _) (j, _) -> i == j)
719 d4f62d4e Iustin Pop
                    pdx = Instance.pnode inst
720 d4f62d4e Iustin Pop
                    sdx = Instance.snode inst
721 d4f62d4e Iustin Pop
                    pold = fromJust $ lookup pdx accu
722 d4f62d4e Iustin Pop
                    sold = fromJust $ lookup sdx accu
723 d4f62d4e Iustin Pop
                    pnew = Node.setPri pold idx
724 d4f62d4e Iustin Pop
                    snew = Node.setSec sold idx
725 d4f62d4e Iustin Pop
                    ac1 = deleteBy assocEqual (pdx, pold) accu
726 d4f62d4e Iustin Pop
                    ac2 = deleteBy assocEqual (sdx, sold) ac1
727 d4f62d4e Iustin Pop
                    ac3 = (pdx, pnew):(sdx, snew):ac2
728 d4f62d4e Iustin Pop
                in ac3) nl il
729 01f6a5d2 Iustin Pop
730 740ec004 Iustin Pop
-- | Compute the longest common suffix of a NameList list that
731 a0529a64 Iustin Pop
-- | starts with a dot
732 740ec004 Iustin Pop
longestDomain :: NameList -> String
733 a0529a64 Iustin Pop
longestDomain [] = ""
734 a0529a64 Iustin Pop
longestDomain ((_,x):xs) =
735 a0529a64 Iustin Pop
    let
736 a0529a64 Iustin Pop
        onlyStrings = snd $ unzip xs
737 a0529a64 Iustin Pop
    in
738 a0529a64 Iustin Pop
      foldr (\ suffix accu -> if all (isSuffixOf suffix) onlyStrings
739 a0529a64 Iustin Pop
                              then suffix
740 a0529a64 Iustin Pop
                              else accu)
741 a0529a64 Iustin Pop
      "" $ filter (isPrefixOf ".") (tails x)
742 a0529a64 Iustin Pop
743 a0529a64 Iustin Pop
-- | Remove tails from the (Int, String) lists
744 740ec004 Iustin Pop
stripSuffix :: String -> NameList -> NameList
745 a0529a64 Iustin Pop
stripSuffix suffix lst =
746 a0529a64 Iustin Pop
    let sflen = length suffix in
747 a0529a64 Iustin Pop
    map (\ (key, name) -> (key, take ((length name) - sflen) name)) lst
748 e4f08c46 Iustin Pop
749 e4f08c46 Iustin Pop
{-| Initializer function that loads the data from a node and list file
750 e4f08c46 Iustin Pop
    and massages it into the correct format. -}
751 e4f08c46 Iustin Pop
loadData :: String -- ^ Node data in text format
752 e4f08c46 Iustin Pop
         -> String -- ^ Instance data in text format
753 e4f08c46 Iustin Pop
         -> (Container.Container Node.Node,
754 e4f08c46 Iustin Pop
             Container.Container Instance.Instance,
755 740ec004 Iustin Pop
             String, NameList, NameList)
756 e4f08c46 Iustin Pop
loadData ndata idata =
757 01f6a5d2 Iustin Pop
    let
758 04be800a Iustin Pop
    {- node file: name t_mem n_mem f_mem t_disk f_disk -}
759 e4f08c46 Iustin Pop
        (ktn, nl) = loadTabular ndata
760 04be800a Iustin Pop
                    (\ (name:tm:nm:fm:td:fd:[]) ->
761 47a8bade Iustin Pop
                         (name,
762 04be800a Iustin Pop
                          Node.create (read tm) (read nm)
763 04be800a Iustin Pop
                                  (read fm) (read td) (read fd)))
764 e4f08c46 Iustin Pop
                    Node.setIdx
765 f82f1f39 Iustin Pop
    {- instance file: name mem disk status pnode snode -}
766 01f6a5d2 Iustin Pop
        (kti, il) = loadTabular idata
767 f82f1f39 Iustin Pop
                    (\ (name:mem:dsk:status:pnode:snode:[]) ->
768 47a8bade Iustin Pop
                         (name,
769 47a8bade Iustin Pop
                          Instance.create (read mem) (read dsk)
770 f82f1f39 Iustin Pop
                              status
771 47a8bade Iustin Pop
                              (fromJust $ lookup pnode ktn)
772 47a8bade Iustin Pop
                              (fromJust $ lookup snode ktn)))
773 01f6a5d2 Iustin Pop
                    Instance.setIdx
774 01f6a5d2 Iustin Pop
        nl2 = fixNodes nl il
775 01f6a5d2 Iustin Pop
        il3 = Container.fromAssocList il
776 e4f08c46 Iustin Pop
        nl3 = Container.fromAssocList
777 01f6a5d2 Iustin Pop
             (map (\ (k, v) -> (k, Node.buildPeers v il3 (length nl2))) nl2)
778 a0529a64 Iustin Pop
        xtn = swapPairs ktn
779 a0529a64 Iustin Pop
        xti = swapPairs kti
780 a0529a64 Iustin Pop
        common_suffix = longestDomain (xti ++ xtn)
781 a0529a64 Iustin Pop
        stn = stripSuffix common_suffix xtn
782 a0529a64 Iustin Pop
        sti = stripSuffix common_suffix xti
783 e4f08c46 Iustin Pop
    in
784 a0529a64 Iustin Pop
      (nl3, il3, common_suffix, stn, sti)
785 5d1baf63 Iustin Pop
786 5d1baf63 Iustin Pop
-- | Compute the amount of memory used by primary instances on a node.
787 5d1baf63 Iustin Pop
nodeImem :: Node.Node -> InstanceList -> Int
788 5d1baf63 Iustin Pop
nodeImem node il =
789 5d1baf63 Iustin Pop
    let rfind = flip Container.find $ il
790 5d1baf63 Iustin Pop
    in sum . map Instance.mem .
791 5d1baf63 Iustin Pop
       map rfind $ Node.plist node
792 5d1baf63 Iustin Pop
793 9cded5d3 Iustin Pop
-- | Compute the amount of disk used by instances on a node (either primary
794 9cded5d3 Iustin Pop
-- or secondary).
795 9cded5d3 Iustin Pop
nodeIdsk :: Node.Node -> InstanceList -> Int
796 9cded5d3 Iustin Pop
nodeIdsk node il =
797 9cded5d3 Iustin Pop
    let rfind = flip Container.find $ il
798 9cded5d3 Iustin Pop
    in sum . map Instance.dsk .
799 9cded5d3 Iustin Pop
       map rfind $ (Node.plist node) ++ (Node.slist node)
800 9cded5d3 Iustin Pop
801 5d1baf63 Iustin Pop
802 5d1baf63 Iustin Pop
-- | Check cluster data for consistency
803 5d1baf63 Iustin Pop
checkData :: NodeList -> InstanceList -> NameList -> NameList
804 5d1baf63 Iustin Pop
          -> ([String], NodeList)
805 53f00b20 Iustin Pop
checkData nl il ktn _ =
806 5d1baf63 Iustin Pop
    Container.mapAccum
807 5d1baf63 Iustin Pop
        (\ msgs node ->
808 5d1baf63 Iustin Pop
             let nname = fromJust $ lookup (Node.idx node) ktn
809 53f00b20 Iustin Pop
                 nilst = map (flip Container.find $ il) (Node.plist node)
810 53f00b20 Iustin Pop
                 dilst = filter (not . Instance.running) nilst
811 53f00b20 Iustin Pop
                 adj_mem = sum . map Instance.mem $ dilst
812 53f00b20 Iustin Pop
                 delta_mem = (truncate $ Node.t_mem node)
813 53f00b20 Iustin Pop
                             - (Node.n_mem node)
814 53f00b20 Iustin Pop
                             - (Node.f_mem node)
815 53f00b20 Iustin Pop
                             - (nodeImem node il)
816 53f00b20 Iustin Pop
                             + adj_mem
817 9cded5d3 Iustin Pop
                 delta_dsk = (truncate $ Node.t_dsk node)
818 9cded5d3 Iustin Pop
                             - (Node.f_dsk node)
819 9cded5d3 Iustin Pop
                             - (nodeIdsk node il)
820 53f00b20 Iustin Pop
                 newn = Node.setFmem (Node.setXmem node delta_mem)
821 53f00b20 Iustin Pop
                        (Node.f_mem node - adj_mem)
822 9cded5d3 Iustin Pop
                 umsg1 = if delta_mem > 16 || delta_dsk > 1024
823 9cded5d3 Iustin Pop
                         then [printf "node %s is missing %d MB ram \
824 9cded5d3 Iustin Pop
                                     \and %d GB disk"
825 9cded5d3 Iustin Pop
                                     nname delta_mem (delta_dsk `div` 1024)]
826 9cded5d3 Iustin Pop
                         else []
827 9cded5d3 Iustin Pop
             in (msgs ++ umsg1, newn)
828 5d1baf63 Iustin Pop
        ) [] nl