Statistics
| Branch: | Tag: | Revision:

root / src / Cluster.hs @ e5f02e15

History | View | Annotate | Download (22.4 kB)

1 e4f08c46 Iustin Pop
{-| Implementation of cluster-wide logic.
2 e4f08c46 Iustin Pop
3 e4f08c46 Iustin Pop
This module holds all pure cluster-logic; I\/O related functionality
4 e4f08c46 Iustin Pop
goes into the "Main" module.
5 e4f08c46 Iustin Pop
6 e4f08c46 Iustin Pop
-}
7 e4f08c46 Iustin Pop
8 e4f08c46 Iustin Pop
module Cluster
9 e4f08c46 Iustin Pop
    (
10 e4f08c46 Iustin Pop
     -- * Types
11 e4f08c46 Iustin Pop
     NodeList
12 e4f08c46 Iustin Pop
    , InstanceList
13 e4f08c46 Iustin Pop
    , Placement
14 e4f08c46 Iustin Pop
    , Solution(..)
15 e4f08c46 Iustin Pop
    , Table(..)
16 e4f08c46 Iustin Pop
    , Removal
17 e4f08c46 Iustin Pop
    -- * Generic functions
18 e4f08c46 Iustin Pop
    , totalResources
19 e4f08c46 Iustin Pop
    -- * First phase functions
20 e4f08c46 Iustin Pop
    , computeBadItems
21 e4f08c46 Iustin Pop
    -- * Second phase functions
22 e4f08c46 Iustin Pop
    , computeSolution
23 e4f08c46 Iustin Pop
    , applySolution
24 e4f08c46 Iustin Pop
    , printSolution
25 e4f08c46 Iustin Pop
    , printNodes
26 e4f08c46 Iustin Pop
    -- * Balacing functions
27 e4f08c46 Iustin Pop
    , checkMove
28 e4f08c46 Iustin Pop
    , compCV
29 e4f08c46 Iustin Pop
    , printStats
30 e4f08c46 Iustin Pop
    -- * Loading functions
31 e4f08c46 Iustin Pop
    , loadData
32 e4f08c46 Iustin Pop
    ) where
33 e4f08c46 Iustin Pop
34 e4f08c46 Iustin Pop
import Data.List
35 e4f08c46 Iustin Pop
import Data.Maybe (isNothing, fromJust)
36 e4f08c46 Iustin Pop
import Text.Printf (printf)
37 e4f08c46 Iustin Pop
import Data.Function
38 e4f08c46 Iustin Pop
39 e4f08c46 Iustin Pop
import qualified Container
40 e4f08c46 Iustin Pop
import qualified Instance
41 e4f08c46 Iustin Pop
import qualified Node
42 e4f08c46 Iustin Pop
import Utils
43 e4f08c46 Iustin Pop
44 e4f08c46 Iustin Pop
type NodeList = Container.Container Node.Node
45 e4f08c46 Iustin Pop
type InstanceList = Container.Container Instance.Instance
46 e4f08c46 Iustin Pop
type Score = Double
47 e4f08c46 Iustin Pop
48 e4f08c46 Iustin Pop
-- | The description of an instance placement.
49 e4f08c46 Iustin Pop
type Placement = (Int, Int, Int)
50 e4f08c46 Iustin Pop
51 e4f08c46 Iustin Pop
{- | A cluster solution described as the solution delta and the list
52 e4f08c46 Iustin Pop
of placements.
53 e4f08c46 Iustin Pop
54 e4f08c46 Iustin Pop
-}
55 e4f08c46 Iustin Pop
data Solution = Solution Int [Placement]
56 e4f08c46 Iustin Pop
                deriving (Eq, Ord, Show)
57 e4f08c46 Iustin Pop
58 e4f08c46 Iustin Pop
-- | Returns the delta of a solution or -1 for Nothing
59 e4f08c46 Iustin Pop
solutionDelta :: Maybe Solution -> Int
60 e4f08c46 Iustin Pop
solutionDelta sol = case sol of
61 e4f08c46 Iustin Pop
                      Just (Solution d _) -> d
62 e4f08c46 Iustin Pop
                      _ -> -1
63 e4f08c46 Iustin Pop
64 e4f08c46 Iustin Pop
-- | A removal set.
65 e4f08c46 Iustin Pop
data Removal = Removal NodeList [Instance.Instance]
66 e4f08c46 Iustin Pop
67 e4f08c46 Iustin Pop
-- | An instance move definition
68 e4f08c46 Iustin Pop
data IMove = Failover
69 e4f08c46 Iustin Pop
           | ReplacePrimary Int
70 e4f08c46 Iustin Pop
           | ReplaceSecondary Int
71 e4f08c46 Iustin Pop
             deriving (Show)
72 e4f08c46 Iustin Pop
73 e4f08c46 Iustin Pop
-- | The complete state for the balancing solution
74 e4f08c46 Iustin Pop
data Table = Table NodeList InstanceList Score [Placement]
75 e4f08c46 Iustin Pop
             deriving (Show)
76 e4f08c46 Iustin Pop
77 e4f08c46 Iustin Pop
-- General functions
78 e4f08c46 Iustin Pop
79 e4f08c46 Iustin Pop
-- | Cap the removal list if needed.
80 e4f08c46 Iustin Pop
capRemovals :: [a] -> Int -> [a]
81 e4f08c46 Iustin Pop
capRemovals removals max_removals =
82 e4f08c46 Iustin Pop
    if max_removals > 0 then
83 e4f08c46 Iustin Pop
        take max_removals removals
84 e4f08c46 Iustin Pop
    else
85 e4f08c46 Iustin Pop
        removals
86 e4f08c46 Iustin Pop
87 e4f08c46 Iustin Pop
-- | Check if the given node list fails the N+1 check.
88 e4f08c46 Iustin Pop
verifyN1Check :: [Node.Node] -> Bool
89 e4f08c46 Iustin Pop
verifyN1Check nl = any Node.failN1 nl
90 e4f08c46 Iustin Pop
91 e4f08c46 Iustin Pop
-- | Verifies the N+1 status and return the affected nodes.
92 e4f08c46 Iustin Pop
verifyN1 :: [Node.Node] -> [Node.Node]
93 e4f08c46 Iustin Pop
verifyN1 nl = filter Node.failN1 nl
94 e4f08c46 Iustin Pop
95 e4f08c46 Iustin Pop
{-| Add an instance and return the new node and instance maps. -}
96 e4f08c46 Iustin Pop
addInstance :: NodeList -> Instance.Instance ->
97 e4f08c46 Iustin Pop
               Node.Node -> Node.Node -> Maybe NodeList
98 e4f08c46 Iustin Pop
addInstance nl idata pri sec =
99 e4f08c46 Iustin Pop
  let pdx = Node.idx pri
100 e4f08c46 Iustin Pop
      sdx = Node.idx sec
101 e4f08c46 Iustin Pop
  in do
102 e4f08c46 Iustin Pop
      pnode <- Node.addPri pri idata
103 e4f08c46 Iustin Pop
      snode <- Node.addSec sec idata pdx
104 e4f08c46 Iustin Pop
      new_nl <- return $ Container.addTwo sdx snode
105 e4f08c46 Iustin Pop
                         pdx pnode nl
106 e4f08c46 Iustin Pop
      return new_nl
107 e4f08c46 Iustin Pop
108 e4f08c46 Iustin Pop
-- | Remove an instance and return the new node and instance maps.
109 e4f08c46 Iustin Pop
removeInstance :: NodeList -> Instance.Instance -> NodeList
110 e4f08c46 Iustin Pop
removeInstance nl idata =
111 e4f08c46 Iustin Pop
  let pnode = Instance.pnode idata
112 e4f08c46 Iustin Pop
      snode = Instance.snode idata
113 e4f08c46 Iustin Pop
      pn = Container.find pnode nl
114 e4f08c46 Iustin Pop
      sn = Container.find snode nl
115 e4f08c46 Iustin Pop
      new_nl = Container.addTwo
116 e4f08c46 Iustin Pop
               pnode (Node.removePri pn idata)
117 e4f08c46 Iustin Pop
               snode (Node.removeSec sn idata) nl in
118 e4f08c46 Iustin Pop
  new_nl
119 e4f08c46 Iustin Pop
120 e4f08c46 Iustin Pop
-- | Remove an instance and return the new node map.
121 e4f08c46 Iustin Pop
removeInstances :: NodeList -> [Instance.Instance] -> NodeList
122 e4f08c46 Iustin Pop
removeInstances = foldl' removeInstance
123 e4f08c46 Iustin Pop
124 e4f08c46 Iustin Pop
-- | Compute the total free disk and memory in the cluster.
125 e4f08c46 Iustin Pop
totalResources :: Container.Container Node.Node -> (Int, Int)
126 e4f08c46 Iustin Pop
totalResources nl =
127 e4f08c46 Iustin Pop
    foldl'
128 e4f08c46 Iustin Pop
    (\ (mem, disk) node -> (mem + (Node.f_mem node),
129 e4f08c46 Iustin Pop
                            disk + (Node.f_disk node)))
130 e4f08c46 Iustin Pop
    (0, 0) (Container.elems nl)
131 e4f08c46 Iustin Pop
132 e4f08c46 Iustin Pop
{- | Compute a new version of a cluster given a solution.
133 e4f08c46 Iustin Pop
134 e4f08c46 Iustin Pop
This is not used for computing the solutions, but for applying a
135 e4f08c46 Iustin Pop
(known-good) solution to the original cluster for final display.
136 e4f08c46 Iustin Pop
137 e4f08c46 Iustin Pop
It first removes the relocated instances after which it places them on
138 e4f08c46 Iustin Pop
their new nodes.
139 e4f08c46 Iustin Pop
140 e4f08c46 Iustin Pop
 -}
141 e4f08c46 Iustin Pop
applySolution :: NodeList -> InstanceList -> [Placement] -> NodeList
142 e4f08c46 Iustin Pop
applySolution nl il sol =
143 e4f08c46 Iustin Pop
    let odxes = map (\ (a, b, c) -> (Container.find a il,
144 e4f08c46 Iustin Pop
                                     Node.idx (Container.find b nl),
145 e4f08c46 Iustin Pop
                                     Node.idx (Container.find c nl))
146 e4f08c46 Iustin Pop
                    ) sol
147 e4f08c46 Iustin Pop
        idxes = (\ (x, _, _) -> x) (unzip3 odxes)
148 e4f08c46 Iustin Pop
        nc = removeInstances nl idxes
149 e4f08c46 Iustin Pop
    in
150 e4f08c46 Iustin Pop
      foldl' (\ nz (a, b, c) ->
151 e4f08c46 Iustin Pop
                 let new_p = Container.find b nz
152 e4f08c46 Iustin Pop
                     new_s = Container.find c nz in
153 e4f08c46 Iustin Pop
                 fromJust (addInstance nz a new_p new_s)
154 e4f08c46 Iustin Pop
           ) nc odxes
155 e4f08c46 Iustin Pop
156 e4f08c46 Iustin Pop
157 e4f08c46 Iustin Pop
-- First phase functions
158 e4f08c46 Iustin Pop
159 e4f08c46 Iustin Pop
{- | Given a list 1,2,3..n build a list of pairs [(1, [2..n]), (2,
160 e4f08c46 Iustin Pop
    [3..n]), ...]
161 e4f08c46 Iustin Pop
162 e4f08c46 Iustin Pop
-}
163 e4f08c46 Iustin Pop
genParts :: [a] -> Int -> [(a, [a])]
164 e4f08c46 Iustin Pop
genParts l count =
165 e4f08c46 Iustin Pop
    case l of
166 e4f08c46 Iustin Pop
      [] -> []
167 e4f08c46 Iustin Pop
      x:xs ->
168 e4f08c46 Iustin Pop
          if length l < count then
169 e4f08c46 Iustin Pop
              []
170 e4f08c46 Iustin Pop
          else
171 e4f08c46 Iustin Pop
              (x, xs) : (genParts xs count)
172 e4f08c46 Iustin Pop
173 e4f08c46 Iustin Pop
-- | Generates combinations of count items from the names list.
174 e4f08c46 Iustin Pop
genNames :: Int -> [b] -> [[b]]
175 e4f08c46 Iustin Pop
genNames count1 names1 =
176 e4f08c46 Iustin Pop
  let aux_fn count names current =
177 e4f08c46 Iustin Pop
          case count of
178 e4f08c46 Iustin Pop
            0 -> [current]
179 e4f08c46 Iustin Pop
            _ ->
180 e4f08c46 Iustin Pop
                concatMap
181 e4f08c46 Iustin Pop
                (\ (x, xs) -> aux_fn (count - 1) xs (x:current))
182 e4f08c46 Iustin Pop
                (genParts names count)
183 e4f08c46 Iustin Pop
  in
184 e4f08c46 Iustin Pop
    aux_fn count1 names1 []
185 e4f08c46 Iustin Pop
186 e4f08c46 Iustin Pop
{- | Computes the pair of bad nodes and instances.
187 e4f08c46 Iustin Pop
188 e4f08c46 Iustin Pop
The bad node list is computed via a simple 'verifyN1' check, and the
189 e4f08c46 Iustin Pop
bad instance list is the list of primary and secondary instances of
190 e4f08c46 Iustin Pop
those nodes.
191 e4f08c46 Iustin Pop
192 e4f08c46 Iustin Pop
-}
193 e4f08c46 Iustin Pop
computeBadItems :: NodeList -> InstanceList ->
194 e4f08c46 Iustin Pop
                   ([Node.Node], [Instance.Instance])
195 e4f08c46 Iustin Pop
computeBadItems nl il =
196 e4f08c46 Iustin Pop
  let bad_nodes = verifyN1 $ Container.elems nl
197 e4f08c46 Iustin Pop
      bad_instances = map (\idx -> Container.find idx il) $
198 e4f08c46 Iustin Pop
                      sort $ nub $ concat $
199 e4f08c46 Iustin Pop
                      map (\ n -> (Node.slist n) ++ (Node.plist n)) bad_nodes
200 e4f08c46 Iustin Pop
  in
201 e4f08c46 Iustin Pop
    (bad_nodes, bad_instances)
202 e4f08c46 Iustin Pop
203 e4f08c46 Iustin Pop
204 e4f08c46 Iustin Pop
{- | Checks if removal of instances results in N+1 pass.
205 e4f08c46 Iustin Pop
206 e4f08c46 Iustin Pop
Note: the check removal cannot optimize by scanning only the affected
207 e4f08c46 Iustin Pop
nodes, since the cluster is known to be not healthy; only the check
208 e4f08c46 Iustin Pop
placement can make this shortcut.
209 e4f08c46 Iustin Pop
210 e4f08c46 Iustin Pop
-}
211 e4f08c46 Iustin Pop
checkRemoval :: NodeList -> [Instance.Instance] -> Maybe Removal
212 e4f08c46 Iustin Pop
checkRemoval nl victims =
213 e4f08c46 Iustin Pop
  let nx = removeInstances nl victims
214 e4f08c46 Iustin Pop
      failN1 = verifyN1Check (Container.elems nx)
215 e4f08c46 Iustin Pop
  in
216 e4f08c46 Iustin Pop
    if failN1 then
217 e4f08c46 Iustin Pop
      Nothing
218 e4f08c46 Iustin Pop
    else
219 e4f08c46 Iustin Pop
      Just $ Removal nx victims
220 e4f08c46 Iustin Pop
221 e4f08c46 Iustin Pop
222 e4f08c46 Iustin Pop
-- | Computes the removals list for a given depth
223 e4f08c46 Iustin Pop
computeRemovals :: Cluster.NodeList
224 e4f08c46 Iustin Pop
                 -> [Instance.Instance]
225 e4f08c46 Iustin Pop
                 -> Int
226 e4f08c46 Iustin Pop
                 -> [Maybe Cluster.Removal]
227 e4f08c46 Iustin Pop
computeRemovals nl bad_instances depth =
228 e4f08c46 Iustin Pop
    map (checkRemoval nl) $ genNames depth bad_instances
229 e4f08c46 Iustin Pop
230 e4f08c46 Iustin Pop
-- Second phase functions
231 e4f08c46 Iustin Pop
232 e4f08c46 Iustin Pop
-- | Single-node relocation cost
233 e4f08c46 Iustin Pop
nodeDelta :: Int -> Int -> Int -> Int
234 e4f08c46 Iustin Pop
nodeDelta i p s =
235 e4f08c46 Iustin Pop
    if i == p || i == s then
236 e4f08c46 Iustin Pop
        0
237 e4f08c46 Iustin Pop
    else
238 e4f08c46 Iustin Pop
        1
239 e4f08c46 Iustin Pop
240 e4f08c46 Iustin Pop
{-| Compute best solution.
241 e4f08c46 Iustin Pop
242 e4f08c46 Iustin Pop
    This function compares two solutions, choosing the minimum valid
243 e4f08c46 Iustin Pop
    solution.
244 e4f08c46 Iustin Pop
-}
245 e4f08c46 Iustin Pop
compareSolutions :: Maybe Solution -> Maybe Solution -> Maybe Solution
246 e4f08c46 Iustin Pop
compareSolutions a b = case (a, b) of
247 e4f08c46 Iustin Pop
  (Nothing, x) -> x
248 e4f08c46 Iustin Pop
  (x, Nothing) -> x
249 e4f08c46 Iustin Pop
  (x, y) -> min x y
250 e4f08c46 Iustin Pop
251 e4f08c46 Iustin Pop
-- | Compute best table. Note that the ordering of the arguments is important.
252 e4f08c46 Iustin Pop
compareTables :: Table -> Table -> Table
253 e4f08c46 Iustin Pop
compareTables a@(Table _ _ a_cv _) b@(Table _ _ b_cv _ ) =
254 e4f08c46 Iustin Pop
    if a_cv > b_cv then b else a
255 e4f08c46 Iustin Pop
256 e4f08c46 Iustin Pop
-- | Check if a given delta is worse then an existing solution.
257 e4f08c46 Iustin Pop
tooHighDelta :: Maybe Solution -> Int -> Int -> Bool
258 e4f08c46 Iustin Pop
tooHighDelta sol new_delta max_delta =
259 e4f08c46 Iustin Pop
    if new_delta > max_delta && max_delta >=0 then
260 e4f08c46 Iustin Pop
        True
261 e4f08c46 Iustin Pop
    else
262 e4f08c46 Iustin Pop
        case sol of
263 e4f08c46 Iustin Pop
          Nothing -> False
264 e4f08c46 Iustin Pop
          Just (Solution old_delta _) -> old_delta <= new_delta
265 e4f08c46 Iustin Pop
266 e4f08c46 Iustin Pop
{-| Check if placement of instances still keeps the cluster N+1 compliant.
267 e4f08c46 Iustin Pop
268 e4f08c46 Iustin Pop
    This is the workhorse of the allocation algorithm: given the
269 e4f08c46 Iustin Pop
    current node and instance maps, the list of instances to be
270 e4f08c46 Iustin Pop
    placed, and the current solution, this will return all possible
271 e4f08c46 Iustin Pop
    solution by recursing until all target instances are placed.
272 e4f08c46 Iustin Pop
273 e4f08c46 Iustin Pop
-}
274 e4f08c46 Iustin Pop
checkPlacement :: NodeList            -- ^ The current node list
275 e4f08c46 Iustin Pop
               -> [Instance.Instance] -- ^ List of instances still to place
276 e4f08c46 Iustin Pop
               -> [Placement]         -- ^ Partial solution until now
277 e4f08c46 Iustin Pop
               -> Int                 -- ^ The delta of the partial solution
278 e4f08c46 Iustin Pop
               -> Maybe Solution      -- ^ The previous solution
279 e4f08c46 Iustin Pop
               -> Int                 -- ^ Abort if the we go above this delta
280 e4f08c46 Iustin Pop
               -> Maybe Solution      -- ^ The new solution
281 e4f08c46 Iustin Pop
checkPlacement nl victims current current_delta prev_sol max_delta =
282 e4f08c46 Iustin Pop
  let target = head victims
283 e4f08c46 Iustin Pop
      opdx = Instance.pnode target
284 e4f08c46 Iustin Pop
      osdx = Instance.snode target
285 e4f08c46 Iustin Pop
      vtail = tail victims
286 e4f08c46 Iustin Pop
      have_tail = (length vtail) > 0
287 e4f08c46 Iustin Pop
      nodes = Container.elems nl
288 e4f08c46 Iustin Pop
  in
289 e4f08c46 Iustin Pop
    foldl'
290 e4f08c46 Iustin Pop
    (\ accu_p pri ->
291 e4f08c46 Iustin Pop
         let
292 e4f08c46 Iustin Pop
             pri_idx = Node.idx pri
293 e4f08c46 Iustin Pop
             upri_delta = current_delta + nodeDelta pri_idx opdx osdx
294 e4f08c46 Iustin Pop
             new_pri = Node.addPri pri target
295 e4f08c46 Iustin Pop
             fail_delta1 = tooHighDelta accu_p upri_delta max_delta
296 e4f08c46 Iustin Pop
         in
297 e4f08c46 Iustin Pop
           if fail_delta1 || isNothing(new_pri) then accu_p
298 e4f08c46 Iustin Pop
           else let pri_nl = Container.add pri_idx (fromJust new_pri) nl in
299 e4f08c46 Iustin Pop
                foldl'
300 e4f08c46 Iustin Pop
                (\ accu sec ->
301 e4f08c46 Iustin Pop
                     let
302 e4f08c46 Iustin Pop
                         sec_idx = Node.idx sec
303 e4f08c46 Iustin Pop
                         upd_delta = upri_delta +
304 e4f08c46 Iustin Pop
                                     nodeDelta sec_idx opdx osdx
305 e4f08c46 Iustin Pop
                         fail_delta2 = tooHighDelta accu upd_delta max_delta
306 e4f08c46 Iustin Pop
                         new_sec = Node.addSec sec target pri_idx
307 e4f08c46 Iustin Pop
                     in
308 e4f08c46 Iustin Pop
                       if sec_idx == pri_idx || fail_delta2 ||
309 e4f08c46 Iustin Pop
                          isNothing new_sec then accu
310 e4f08c46 Iustin Pop
                       else let
311 e4f08c46 Iustin Pop
                           nx = Container.add sec_idx (fromJust new_sec) pri_nl
312 e4f08c46 Iustin Pop
                           plc = (Instance.idx target, pri_idx, sec_idx)
313 e4f08c46 Iustin Pop
                           c2 = plc:current
314 e4f08c46 Iustin Pop
                           result =
315 e4f08c46 Iustin Pop
                               if have_tail then
316 e4f08c46 Iustin Pop
                                   checkPlacement nx vtail c2 upd_delta
317 e4f08c46 Iustin Pop
                                                  accu max_delta
318 e4f08c46 Iustin Pop
                               else
319 e4f08c46 Iustin Pop
                                   Just (Solution upd_delta c2)
320 e4f08c46 Iustin Pop
                      in compareSolutions accu result
321 e4f08c46 Iustin Pop
                ) accu_p nodes
322 e4f08c46 Iustin Pop
    ) prev_sol nodes
323 e4f08c46 Iustin Pop
324 e4f08c46 Iustin Pop
-- | Apply a move
325 e4f08c46 Iustin Pop
applyMove :: NodeList -> Instance.Instance
326 e4f08c46 Iustin Pop
          -> IMove -> (Maybe NodeList, Instance.Instance, Int, Int)
327 e4f08c46 Iustin Pop
applyMove nl inst Failover =
328 e4f08c46 Iustin Pop
    let old_pdx = Instance.pnode inst
329 e4f08c46 Iustin Pop
        old_sdx = Instance.snode inst
330 e4f08c46 Iustin Pop
        old_p = Container.find old_pdx nl
331 e4f08c46 Iustin Pop
        old_s = Container.find old_sdx nl
332 e4f08c46 Iustin Pop
        int_p = Node.removePri old_p inst
333 e4f08c46 Iustin Pop
        int_s = Node.removeSec old_s inst
334 e4f08c46 Iustin Pop
        new_p = Node.addPri int_s inst
335 e4f08c46 Iustin Pop
        new_s = Node.addSec int_p inst old_sdx
336 e4f08c46 Iustin Pop
        new_nl = if isNothing(new_p) || isNothing(new_s) then Nothing
337 e4f08c46 Iustin Pop
                 else Just $ Container.addTwo old_pdx (fromJust new_s)
338 e4f08c46 Iustin Pop
                      old_sdx (fromJust new_p) nl
339 e4f08c46 Iustin Pop
    in (new_nl, Instance.setBoth inst old_sdx old_pdx, old_sdx, old_pdx)
340 e4f08c46 Iustin Pop
341 e4f08c46 Iustin Pop
applyMove nl inst (ReplacePrimary new_pdx) =
342 e4f08c46 Iustin Pop
    let old_pdx = Instance.pnode inst
343 e4f08c46 Iustin Pop
        old_sdx = Instance.snode inst
344 e4f08c46 Iustin Pop
        old_p = Container.find old_pdx nl
345 e4f08c46 Iustin Pop
        old_s = Container.find old_sdx nl
346 e4f08c46 Iustin Pop
        tgt_n = Container.find new_pdx nl
347 e4f08c46 Iustin Pop
        int_p = Node.removePri old_p inst
348 e4f08c46 Iustin Pop
        int_s = Node.removeSec old_s inst
349 e4f08c46 Iustin Pop
        new_p = Node.addPri tgt_n inst
350 e4f08c46 Iustin Pop
        new_s = Node.addSec int_s inst new_pdx
351 e4f08c46 Iustin Pop
        new_nl = if isNothing(new_p) || isNothing(new_s) then Nothing
352 e4f08c46 Iustin Pop
                 else Just $ Container.add new_pdx (fromJust new_p) $
353 e4f08c46 Iustin Pop
                      Container.addTwo old_pdx int_p
354 e4f08c46 Iustin Pop
                               old_sdx (fromJust new_s) nl
355 e4f08c46 Iustin Pop
    in (new_nl, Instance.setPri inst new_pdx, new_pdx, old_sdx)
356 e4f08c46 Iustin Pop
357 e4f08c46 Iustin Pop
applyMove nl inst (ReplaceSecondary new_sdx) =
358 e4f08c46 Iustin Pop
    let old_pdx = Instance.pnode inst
359 e4f08c46 Iustin Pop
        old_sdx = Instance.snode inst
360 e4f08c46 Iustin Pop
        old_s = Container.find old_sdx nl
361 e4f08c46 Iustin Pop
        tgt_n = Container.find new_sdx nl
362 e4f08c46 Iustin Pop
        int_s = Node.removeSec old_s inst
363 e4f08c46 Iustin Pop
        new_s = Node.addSec tgt_n inst old_pdx
364 e4f08c46 Iustin Pop
        new_nl = if isNothing(new_s) then Nothing
365 e4f08c46 Iustin Pop
                 else Just $ Container.addTwo new_sdx (fromJust new_s)
366 e4f08c46 Iustin Pop
                      old_sdx int_s nl
367 e4f08c46 Iustin Pop
    in (new_nl, Instance.setSec inst new_sdx, old_pdx, new_sdx)
368 e4f08c46 Iustin Pop
369 e4f08c46 Iustin Pop
checkSingleStep :: Table -- ^ The original table
370 e4f08c46 Iustin Pop
                -> Instance.Instance -- ^ The instance to move
371 e4f08c46 Iustin Pop
                -> Table -- ^ The current best table
372 e4f08c46 Iustin Pop
                -> IMove -- ^ The move to apply
373 e4f08c46 Iustin Pop
                -> Table -- ^ The final best table
374 e4f08c46 Iustin Pop
checkSingleStep ini_tbl target cur_tbl move =
375 e4f08c46 Iustin Pop
    let
376 e4f08c46 Iustin Pop
        Table ini_nl ini_il _ ini_plc = ini_tbl
377 e4f08c46 Iustin Pop
        (tmp_nl, new_inst, pri_idx, sec_idx) =
378 e4f08c46 Iustin Pop
            applyMove ini_nl target move
379 e4f08c46 Iustin Pop
    in
380 e4f08c46 Iustin Pop
      if isNothing tmp_nl then cur_tbl
381 e4f08c46 Iustin Pop
      else
382 e4f08c46 Iustin Pop
          let tgt_idx = Instance.idx target
383 e4f08c46 Iustin Pop
              upd_nl = fromJust tmp_nl
384 e4f08c46 Iustin Pop
              upd_cvar = compCV upd_nl
385 e4f08c46 Iustin Pop
              upd_il = Container.add tgt_idx new_inst ini_il
386 e4f08c46 Iustin Pop
              tmp_plc = filter (\ (t, _, _) -> t /= tgt_idx) ini_plc
387 e4f08c46 Iustin Pop
              upd_plc = (tgt_idx, pri_idx, sec_idx):tmp_plc
388 e4f08c46 Iustin Pop
              upd_tbl = Table upd_nl upd_il upd_cvar upd_plc
389 e4f08c46 Iustin Pop
          in
390 e4f08c46 Iustin Pop
            compareTables cur_tbl upd_tbl
391 e4f08c46 Iustin Pop
392 e4f08c46 Iustin Pop
-- | Compute the best next move.
393 e4f08c46 Iustin Pop
checkMove :: Table            -- ^ The current solution
394 e4f08c46 Iustin Pop
          -> [Instance.Instance] -- ^ List of instances still to move
395 e4f08c46 Iustin Pop
          -> Table            -- ^ The new solution
396 e4f08c46 Iustin Pop
checkMove ini_tbl victims =
397 e4f08c46 Iustin Pop
  let target = head victims
398 e4f08c46 Iustin Pop
      opdx = Instance.pnode target
399 e4f08c46 Iustin Pop
      osdx = Instance.snode target
400 e4f08c46 Iustin Pop
      vtail = tail victims
401 e4f08c46 Iustin Pop
      have_tail = (length vtail) > 0
402 e4f08c46 Iustin Pop
      Table ini_nl _ _ _ = ini_tbl
403 e4f08c46 Iustin Pop
      nodes = filter (\node -> let idx = Node.idx node
404 e4f08c46 Iustin Pop
                               in idx /= opdx && idx /= osdx)
405 e4f08c46 Iustin Pop
              $ Container.elems ini_nl
406 e4f08c46 Iustin Pop
      aft_failover = checkSingleStep ini_tbl target ini_tbl Failover
407 e4f08c46 Iustin Pop
      next_tbl =
408 e4f08c46 Iustin Pop
          foldl'
409 e4f08c46 Iustin Pop
          (\ accu_p new_node ->
410 e4f08c46 Iustin Pop
               let
411 e4f08c46 Iustin Pop
                   new_idx = Node.idx new_node
412 e4f08c46 Iustin Pop
                   pmoves = [ReplacePrimary new_idx,
413 e4f08c46 Iustin Pop
                             ReplaceSecondary new_idx]
414 e4f08c46 Iustin Pop
               in
415 e4f08c46 Iustin Pop
                 foldl' (checkSingleStep ini_tbl target) accu_p pmoves
416 e4f08c46 Iustin Pop
          ) aft_failover nodes
417 e4f08c46 Iustin Pop
  in if have_tail then checkMove next_tbl vtail
418 e4f08c46 Iustin Pop
     else next_tbl
419 e4f08c46 Iustin Pop
420 e4f08c46 Iustin Pop
421 e4f08c46 Iustin Pop
422 e4f08c46 Iustin Pop
{- | Auxiliary function for solution computation.
423 e4f08c46 Iustin Pop
424 e4f08c46 Iustin Pop
We write this in an explicit recursive fashion in order to control
425 e4f08c46 Iustin Pop
early-abort in case we have met the min delta. We can't use foldr
426 e4f08c46 Iustin Pop
instead of explicit recursion since we need the accumulator for the
427 e4f08c46 Iustin Pop
abort decision.
428 e4f08c46 Iustin Pop
429 e4f08c46 Iustin Pop
-}
430 e4f08c46 Iustin Pop
advanceSolution :: [Maybe Removal] -- ^ The removal to process
431 e4f08c46 Iustin Pop
                -> Int             -- ^ Minimum delta parameter
432 e4f08c46 Iustin Pop
                -> Int             -- ^ Maximum delta parameter
433 e4f08c46 Iustin Pop
                -> Maybe Solution  -- ^ Current best solution
434 e4f08c46 Iustin Pop
                -> Maybe Solution  -- ^ New best solution
435 e4f08c46 Iustin Pop
advanceSolution [] _ _ sol = sol
436 e4f08c46 Iustin Pop
advanceSolution (Nothing:xs) m n sol = advanceSolution xs m n sol
437 e4f08c46 Iustin Pop
advanceSolution ((Just (Removal nx removed)):xs) min_d max_d prev_sol =
438 e4f08c46 Iustin Pop
    let new_sol = checkPlacement nx removed [] 0 prev_sol max_d
439 e4f08c46 Iustin Pop
        new_delta = solutionDelta $! new_sol
440 e4f08c46 Iustin Pop
    in
441 e4f08c46 Iustin Pop
      if new_delta >= 0 && new_delta <= min_d then
442 e4f08c46 Iustin Pop
          new_sol
443 e4f08c46 Iustin Pop
      else
444 e4f08c46 Iustin Pop
          advanceSolution xs min_d max_d new_sol
445 e4f08c46 Iustin Pop
446 e4f08c46 Iustin Pop
-- | Computes the placement solution.
447 e4f08c46 Iustin Pop
solutionFromRemovals :: [Maybe Removal] -- ^ The list of (possible) removals
448 e4f08c46 Iustin Pop
                     -> Int             -- ^ Minimum delta parameter
449 e4f08c46 Iustin Pop
                     -> Int             -- ^ Maximum delta parameter
450 e4f08c46 Iustin Pop
                     -> Maybe Solution  -- ^ The best solution found
451 e4f08c46 Iustin Pop
solutionFromRemovals removals min_delta max_delta =
452 e4f08c46 Iustin Pop
    advanceSolution removals min_delta max_delta Nothing
453 e4f08c46 Iustin Pop
454 e4f08c46 Iustin Pop
{- | Computes the solution at the given depth.
455 e4f08c46 Iustin Pop
456 e4f08c46 Iustin Pop
This is a wrapper over both computeRemovals and
457 e4f08c46 Iustin Pop
solutionFromRemovals. In case we have no solution, we return Nothing.
458 e4f08c46 Iustin Pop
459 e4f08c46 Iustin Pop
-}
460 e4f08c46 Iustin Pop
computeSolution :: NodeList        -- ^ The original node data
461 e4f08c46 Iustin Pop
                -> [Instance.Instance] -- ^ The list of /bad/ instances
462 e4f08c46 Iustin Pop
                -> Int             -- ^ The /depth/ of removals
463 e4f08c46 Iustin Pop
                -> Int             -- ^ Maximum number of removals to process
464 e4f08c46 Iustin Pop
                -> Int             -- ^ Minimum delta parameter
465 e4f08c46 Iustin Pop
                -> Int             -- ^ Maximum delta parameter
466 e4f08c46 Iustin Pop
                -> Maybe Solution  -- ^ The best solution found (or Nothing)
467 e4f08c46 Iustin Pop
computeSolution nl bad_instances depth max_removals min_delta max_delta =
468 e4f08c46 Iustin Pop
  let
469 e4f08c46 Iustin Pop
      removals = computeRemovals nl bad_instances depth
470 e4f08c46 Iustin Pop
      removals' = capRemovals removals max_removals
471 e4f08c46 Iustin Pop
  in
472 e4f08c46 Iustin Pop
    solutionFromRemovals removals' min_delta max_delta
473 e4f08c46 Iustin Pop
474 e4f08c46 Iustin Pop
-- Solution display functions (pure)
475 e4f08c46 Iustin Pop
476 e4f08c46 Iustin Pop
-- | Given the original and final nodes, computes the relocation description.
477 e4f08c46 Iustin Pop
computeMoves :: String -- ^ The instance name
478 e4f08c46 Iustin Pop
             -> String -- ^ Original primary
479 e4f08c46 Iustin Pop
             -> String -- ^ Original secondary
480 e4f08c46 Iustin Pop
             -> String -- ^ New primary
481 e4f08c46 Iustin Pop
             -> String -- ^ New secondary
482 e4f08c46 Iustin Pop
             -> (String, [String])
483 e4f08c46 Iustin Pop
                -- ^ Tuple of moves and commands list; moves is containing
484 e4f08c46 Iustin Pop
                -- either @/f/@ for failover or @/r:name/@ for replace
485 e4f08c46 Iustin Pop
                -- secondary, while the command list holds gnt-instance
486 e4f08c46 Iustin Pop
                -- commands (without that prefix), e.g \"@failover instance1@\"
487 e4f08c46 Iustin Pop
computeMoves i a b c d =
488 e4f08c46 Iustin Pop
    if c == a then {- Same primary -}
489 e4f08c46 Iustin Pop
        if d == b then {- Same sec??! -}
490 e4f08c46 Iustin Pop
            ("-", [])
491 e4f08c46 Iustin Pop
        else {- Change of secondary -}
492 e4f08c46 Iustin Pop
            (printf "r:%s" d,
493 e4f08c46 Iustin Pop
             [printf "replace-disks -n %s %s" d i])
494 e4f08c46 Iustin Pop
    else
495 e4f08c46 Iustin Pop
        if c == b then {- Failover and ... -}
496 e4f08c46 Iustin Pop
            if d == a then {- that's all -}
497 e4f08c46 Iustin Pop
                ("f", [printf "failover %s" i])
498 e4f08c46 Iustin Pop
            else
499 e4f08c46 Iustin Pop
                (printf "f r:%s" d,
500 e4f08c46 Iustin Pop
                 [printf "failover %s" i,
501 e4f08c46 Iustin Pop
                  printf "replace-disks -n %s %s" d i])
502 e4f08c46 Iustin Pop
        else
503 e4f08c46 Iustin Pop
            if d == a then {- ... and keep primary as secondary -}
504 e4f08c46 Iustin Pop
                (printf "r:%s f" c,
505 e4f08c46 Iustin Pop
                 [printf "replace-disks -n %s %s" c i,
506 e4f08c46 Iustin Pop
                  printf "failover %s" i])
507 e4f08c46 Iustin Pop
            else
508 e4f08c46 Iustin Pop
                if d == b then {- ... keep same secondary -}
509 e4f08c46 Iustin Pop
                    (printf "f r:%s f" c,
510 e4f08c46 Iustin Pop
                     [printf "failover %s" i,
511 e4f08c46 Iustin Pop
                      printf "replace-disks -n %s %s" c i,
512 e4f08c46 Iustin Pop
                      printf "failover %s" i])
513 e4f08c46 Iustin Pop
514 e4f08c46 Iustin Pop
                else {- Nothing in common -}
515 e4f08c46 Iustin Pop
                    (printf "r:%s f r:%s" c d,
516 e4f08c46 Iustin Pop
                     [printf "replace-disks -n %s %s" c i,
517 e4f08c46 Iustin Pop
                      printf "failover %s" i,
518 e4f08c46 Iustin Pop
                      printf "replace-disks -n %s %s" d i])
519 e4f08c46 Iustin Pop
520 e4f08c46 Iustin Pop
{-| Converts a solution to string format -}
521 e4f08c46 Iustin Pop
printSolution :: InstanceList
522 e4f08c46 Iustin Pop
              -> [(Int, String)]
523 e4f08c46 Iustin Pop
              -> [(Int, String)]
524 e4f08c46 Iustin Pop
              -> [Placement]
525 e4f08c46 Iustin Pop
              -> ([String], [[String]])
526 e4f08c46 Iustin Pop
printSolution il ktn kti sol =
527 e4f08c46 Iustin Pop
  unzip $ map
528 e4f08c46 Iustin Pop
    (\ (i, p, s) ->
529 e4f08c46 Iustin Pop
       let inst = Container.find i il
530 e4f08c46 Iustin Pop
           inam = fromJust $ lookup (Instance.idx inst) kti
531 e4f08c46 Iustin Pop
           npri = fromJust $ lookup p ktn
532 e4f08c46 Iustin Pop
           nsec = fromJust $ lookup s ktn
533 e4f08c46 Iustin Pop
           opri = fromJust $ lookup (Instance.pnode inst) ktn
534 e4f08c46 Iustin Pop
           osec = fromJust $ lookup (Instance.snode inst) ktn
535 e4f08c46 Iustin Pop
           (moves, cmds) =  computeMoves inam opri osec npri nsec
536 e4f08c46 Iustin Pop
537 e4f08c46 Iustin Pop
       in
538 e4f08c46 Iustin Pop
         (printf "  I: %s\to: %s+>%s\tn: %s+>%s\ta: %s"
539 e4f08c46 Iustin Pop
                 inam opri osec npri nsec moves,
540 e4f08c46 Iustin Pop
          cmds)
541 e4f08c46 Iustin Pop
    ) sol
542 e4f08c46 Iustin Pop
543 e4f08c46 Iustin Pop
-- | Print the node list.
544 e4f08c46 Iustin Pop
printNodes :: [(Int, String)] -> NodeList -> String
545 e4f08c46 Iustin Pop
printNodes ktn nl =
546 e4f08c46 Iustin Pop
    let snl = sortBy (compare `on` Node.idx) (Container.elems nl)
547 e4f08c46 Iustin Pop
        snl' = map (\ n -> ((fromJust $ lookup (Node.idx n) ktn), n)) snl
548 e4f08c46 Iustin Pop
    in unlines $ map (uncurry Node.list) snl'
549 e4f08c46 Iustin Pop
550 e4f08c46 Iustin Pop
-- | Compute the mem and disk covariance.
551 e4f08c46 Iustin Pop
compDetailedCV :: NodeList -> (Double, Double)
552 e4f08c46 Iustin Pop
compDetailedCV nl =
553 e4f08c46 Iustin Pop
    let nstats = map Node.normUsed $ Container.elems nl
554 e4f08c46 Iustin Pop
        (mem_l, dsk_l) = unzip nstats
555 e4f08c46 Iustin Pop
        mem_cv = varianceCoeff mem_l
556 e4f08c46 Iustin Pop
        dsk_cv = varianceCoeff dsk_l
557 e4f08c46 Iustin Pop
    in (mem_cv, dsk_cv)
558 e4f08c46 Iustin Pop
559 e4f08c46 Iustin Pop
-- | Compute the 'total' variance.
560 e4f08c46 Iustin Pop
compCV :: NodeList -> Double
561 e4f08c46 Iustin Pop
compCV nl =
562 e4f08c46 Iustin Pop
    let (mem_cv, dsk_cv) = compDetailedCV nl
563 e4f08c46 Iustin Pop
    in mem_cv + dsk_cv
564 e4f08c46 Iustin Pop
565 e4f08c46 Iustin Pop
printStats :: NodeList -> String
566 e4f08c46 Iustin Pop
printStats nl =
567 e4f08c46 Iustin Pop
    let (mem_cv, dsk_cv) = compDetailedCV nl
568 e4f08c46 Iustin Pop
    in printf "mem=%.8f, dsk=%.8f" mem_cv dsk_cv
569 e4f08c46 Iustin Pop
570 e4f08c46 Iustin Pop
-- Balancing functions
571 e4f08c46 Iustin Pop
572 e4f08c46 Iustin Pop
-- Loading functions
573 e4f08c46 Iustin Pop
574 e4f08c46 Iustin Pop
{- | Convert newline and delimiter-separated text.
575 e4f08c46 Iustin Pop
576 e4f08c46 Iustin Pop
This function converts a text in tabular format as generated by
577 e4f08c46 Iustin Pop
@gnt-instance list@ and @gnt-node list@ to a list of objects using a
578 e4f08c46 Iustin Pop
supplied conversion function.
579 e4f08c46 Iustin Pop
580 e4f08c46 Iustin Pop
-}
581 e4f08c46 Iustin Pop
loadTabular :: String -> ([String] -> (String, a))
582 e4f08c46 Iustin Pop
            -> (a -> Int -> a) -> ([(String, Int)], [(Int, a)])
583 e4f08c46 Iustin Pop
loadTabular text_data convert_fn set_fn =
584 e4f08c46 Iustin Pop
    let lines_data = lines text_data
585 e4f08c46 Iustin Pop
        rows = map (sepSplit '|') lines_data
586 e4f08c46 Iustin Pop
        kerows = (map convert_fn rows)
587 e4f08c46 Iustin Pop
        idxrows = map (\ (idx, (k, v)) -> ((k, idx), (idx, set_fn v idx)))
588 e4f08c46 Iustin Pop
                  (zip [0..] kerows)
589 e4f08c46 Iustin Pop
    in unzip idxrows
590 e4f08c46 Iustin Pop
591 01f6a5d2 Iustin Pop
-- | For each instance, add its index to its primary and secondary nodes
592 01f6a5d2 Iustin Pop
fixNodes :: [(Int, Node.Node)]
593 01f6a5d2 Iustin Pop
         -> [(Int, Instance.Instance)]
594 01f6a5d2 Iustin Pop
         -> [(Int, Node.Node)]
595 01f6a5d2 Iustin Pop
fixNodes nl il =
596 01f6a5d2 Iustin Pop
    foldl (\accu (idx, inst) ->
597 01f6a5d2 Iustin Pop
               let
598 01f6a5d2 Iustin Pop
                   assocEqual = (\ (i, _) (j, _) -> i == j)
599 01f6a5d2 Iustin Pop
                   pdx = Instance.pnode inst
600 01f6a5d2 Iustin Pop
                   sdx = Instance.snode inst
601 e5f02e15 Iustin Pop
                   pold = fromJust $ lookup pdx accu
602 e5f02e15 Iustin Pop
                   sold = fromJust $ lookup sdx accu
603 01f6a5d2 Iustin Pop
                   pnew = Node.setPri pold idx
604 01f6a5d2 Iustin Pop
                   snew = Node.setSec sold idx
605 01f6a5d2 Iustin Pop
                   ac1 = deleteBy assocEqual (pdx, pold) accu
606 01f6a5d2 Iustin Pop
                   ac2 = deleteBy assocEqual (sdx, sold) ac1
607 01f6a5d2 Iustin Pop
                   ac3 = (pdx, pnew):(sdx, snew):ac2
608 01f6a5d2 Iustin Pop
               in ac3) nl il
609 01f6a5d2 Iustin Pop
610 e4f08c46 Iustin Pop
611 e4f08c46 Iustin Pop
{-| Initializer function that loads the data from a node and list file
612 e4f08c46 Iustin Pop
    and massages it into the correct format. -}
613 e4f08c46 Iustin Pop
loadData :: String -- ^ Node data in text format
614 e4f08c46 Iustin Pop
         -> String -- ^ Instance data in text format
615 e4f08c46 Iustin Pop
         -> (Container.Container Node.Node,
616 e4f08c46 Iustin Pop
             Container.Container Instance.Instance,
617 e4f08c46 Iustin Pop
             [(Int, String)], [(Int, String)])
618 e4f08c46 Iustin Pop
loadData ndata idata =
619 01f6a5d2 Iustin Pop
    let
620 01f6a5d2 Iustin Pop
    {- node file: name mem disk -}
621 e4f08c46 Iustin Pop
        (ktn, nl) = loadTabular ndata
622 01f6a5d2 Iustin Pop
                    (\ (i:jt:jf:kt:kf:[]) -> (i, Node.create jt jf kt kf))
623 e4f08c46 Iustin Pop
                    Node.setIdx
624 01f6a5d2 Iustin Pop
    {- instance file: name mem disk -}
625 01f6a5d2 Iustin Pop
        (kti, il) = loadTabular idata
626 01f6a5d2 Iustin Pop
                    (\ (i:j:k:l:m:[]) -> (i,
627 01f6a5d2 Iustin Pop
                                           Instance.create j k
628 01f6a5d2 Iustin Pop
                                               (fromJust $ lookup l ktn)
629 01f6a5d2 Iustin Pop
                                               (fromJust $ lookup m ktn)))
630 01f6a5d2 Iustin Pop
                    Instance.setIdx
631 01f6a5d2 Iustin Pop
        nl2 = fixNodes nl il
632 01f6a5d2 Iustin Pop
        il3 = Container.fromAssocList il
633 e4f08c46 Iustin Pop
        nl3 = Container.fromAssocList
634 01f6a5d2 Iustin Pop
             (map (\ (k, v) -> (k, Node.buildPeers v il3 (length nl2))) nl2)
635 e4f08c46 Iustin Pop
    in
636 e4f08c46 Iustin Pop
      (nl3, il3, swapPairs ktn, swapPairs kti)