module Ganeti.HTools.Cluster.Evacuate
( EvacSolution(..)
, nodeEvacInstance
, tryNodeEvac
, emptyEvacSolution
, updateEvacSolution
, reverseEvacSolution
) where
import qualified Data.IntSet as IntSet
import Data.List (foldl')
import Data.Maybe (fromJust)
import Ganeti.BasicTypes
import Ganeti.HTools.AlgorithmParams (AlgorithmOptions(..))
import Ganeti.HTools.Cluster.Metrics (compCVNodes)
import Ganeti.HTools.Cluster.Moves (applyMoveEx)
import Ganeti.HTools.Cluster.Utils ( splitCluster, iMoveToJob
, instancePriGroup, availableGroupNodes)
import qualified Ganeti.HTools.Container as Container
import qualified Ganeti.HTools.Group as Group
import qualified Ganeti.HTools.Instance as Instance
import qualified Ganeti.HTools.Node as Node
import Ganeti.HTools.Types
import qualified Ganeti.OpCodes as OpCodes
import Ganeti.Types
data EvacSolution = EvacSolution
{ esMoved :: [(Idx, Gdx, [Ndx])]
, esFailed :: [(Idx, String)]
, esOpCodes :: [[OpCodes.OpCode]]
} deriving (Show)
emptyEvacSolution :: EvacSolution
emptyEvacSolution = EvacSolution { esMoved = []
, esFailed = []
, esOpCodes = []
}
reverseEvacSolution :: EvacSolution -> EvacSolution
reverseEvacSolution (EvacSolution f m o) =
EvacSolution (reverse f) (reverse m) (reverse o)
type EvacInnerState =
Either String (Node.List, Instance.Instance, Score, Ndx)
failOnSecondaryChange :: (Monad m) => EvacMode -> DiskTemplate -> m ()
failOnSecondaryChange ChangeSecondary dt =
fail $ "Instances with disk template '" ++ diskTemplateToRaw dt ++
"' can't execute change secondary"
failOnSecondaryChange _ _ = return ()
evacOneNodeInner :: AlgorithmOptions
-> Node.List
-> Instance.Instance
-> Gdx
-> (Ndx -> IMove)
-> EvacInnerState
-> Ndx
-> EvacInnerState
evacOneNodeInner opts nl inst gdx op_fn accu ndx =
case applyMoveEx (algIgnoreSoftErrors opts) nl inst (op_fn ndx) of
Bad fm -> let fail_msg = " Node " ++ Container.nameOf nl ndx ++
" failed: " ++ show fm ++ ";"
in either (Left . (++ fail_msg)) Right accu
Ok (nl', inst', _, _) ->
let nodes = Container.elems nl'
grpnodes = fromJust (gdx `lookup` Node.computeGroups nodes)
new_cv = compCVNodes grpnodes
new_accu = Right (nl', inst', new_cv, ndx)
in case accu of
Left _ -> new_accu
Right (_, _, old_cv, _) ->
if old_cv < new_cv
then accu
else new_accu
evacOneNodeOnly :: AlgorithmOptions
-> Node.List
-> Instance.List
-> Instance.Instance
-> Gdx
-> [Ndx]
-> Result (Node.List, Instance.List, [OpCodes.OpCode])
evacOneNodeOnly opts nl il inst gdx avail_nodes = do
op_fn <- case Instance.mirrorType inst of
MirrorNone -> Bad "Can't relocate/evacuate non-mirrored instances"
MirrorInternal -> Ok ReplaceSecondary
MirrorExternal -> Ok FailoverToAny
(nl', inst', _, ndx) <- annotateResult "Can't find any good node" .
eitherToResult $
foldl' (evacOneNodeInner opts nl inst gdx op_fn)
(Left "") avail_nodes
let idx = Instance.idx inst
il' = Container.add idx inst' il
ops = iMoveToJob nl' il' idx (op_fn ndx)
return (nl', il', ops)
evacDrbdAllInner :: AlgorithmOptions
-> Node.List
-> Instance.List
-> Instance.Instance
-> Gdx
-> (Ndx, Ndx)
-> Result (Node.List, Instance.List, [OpCodes.OpCode], Score)
evacDrbdAllInner opts nl il inst gdx (t_pdx, t_sdx) = do
let primary = Container.find (Instance.pNode inst) nl
idx = Instance.idx inst
apMove = applyMoveEx $ algIgnoreSoftErrors opts
(nl1, inst1, ops1) <-
if Node.offline primary
then do
(nl', inst', _, _) <-
annotateResult "Failing over to the secondary" .
opToResult $ apMove nl inst Failover
return (nl', inst', [Failover])
else return (nl, inst, [])
let (o1, o2, o3) = (ReplaceSecondary t_pdx,
Failover,
ReplaceSecondary t_sdx)
(nl2, inst2, _, _) <-
annotateResult "Changing secondary to new primary" .
opToResult $
apMove nl1 inst1 o1
let ops2 = o1:ops1
(nl3, inst3, _, _) <- annotateResult "Failing over to new primary" .
opToResult $ apMove nl2 inst2 o2
let ops3 = o2:ops2
(nl4, inst4, _, _) <-
annotateResult "Changing secondary to final secondary" .
opToResult $
apMove nl3 inst3 o3
let ops4 = o3:ops3
il' = Container.add idx inst4 il
ops = concatMap (iMoveToJob nl4 il' idx) $ reverse ops4
let nodes = Container.elems nl4
grpnodes = fromJust (gdx `lookup` Node.computeGroups nodes)
new_cv = compCVNodes grpnodes
return (nl4, il', ops, new_cv)
nodeEvacInstance :: AlgorithmOptions
-> Node.List
-> Instance.List
-> EvacMode
-> Instance.Instance
-> Gdx
-> [Ndx]
-> Result (Node.List, Instance.List, [OpCodes.OpCode])
nodeEvacInstance opts nl il mode inst@(Instance.Instance
{Instance.diskTemplate = dt@DTDiskless})
gdx avail_nodes =
failOnSecondaryChange mode dt >>
evacOneNodeOnly opts nl il inst gdx avail_nodes
nodeEvacInstance _ _ _ _ (Instance.Instance
{Instance.diskTemplate = DTPlain}) _ _ =
fail "Instances of type plain cannot be relocated"
nodeEvacInstance _ _ _ _ (Instance.Instance
{Instance.diskTemplate = DTFile}) _ _ =
fail "Instances of type file cannot be relocated"
nodeEvacInstance opts nl il mode inst@(Instance.Instance
{Instance.diskTemplate = dt@DTSharedFile})
gdx avail_nodes =
failOnSecondaryChange mode dt >>
evacOneNodeOnly opts nl il inst gdx avail_nodes
nodeEvacInstance opts nl il mode inst@(Instance.Instance
{Instance.diskTemplate = dt@DTBlock})
gdx avail_nodes =
failOnSecondaryChange mode dt >>
evacOneNodeOnly opts nl il inst gdx avail_nodes
nodeEvacInstance opts nl il mode inst@(Instance.Instance
{Instance.diskTemplate = dt@DTRbd})
gdx avail_nodes =
failOnSecondaryChange mode dt >>
evacOneNodeOnly opts nl il inst gdx avail_nodes
nodeEvacInstance opts nl il mode inst@(Instance.Instance
{Instance.diskTemplate = dt@DTExt})
gdx avail_nodes =
failOnSecondaryChange mode dt >>
evacOneNodeOnly opts nl il inst gdx avail_nodes
nodeEvacInstance opts nl il mode inst@(Instance.Instance
{Instance.diskTemplate = dt@DTGluster})
gdx avail_nodes =
failOnSecondaryChange mode dt >>
evacOneNodeOnly opts nl il inst gdx avail_nodes
nodeEvacInstance opts nl il ChangePrimary
inst@(Instance.Instance {Instance.diskTemplate = DTDrbd8})
_ _ =
do
(nl', inst', _, _) <- opToResult
$ applyMoveEx (algIgnoreSoftErrors opts) nl inst
Failover
let idx = Instance.idx inst
il' = Container.add idx inst' il
ops = iMoveToJob nl' il' idx Failover
return (nl', il', ops)
nodeEvacInstance opts nl il ChangeSecondary
inst@(Instance.Instance {Instance.diskTemplate = DTDrbd8})
gdx avail_nodes =
evacOneNodeOnly opts nl il inst gdx avail_nodes
nodeEvacInstance opts nl il ChangeAll
inst@(Instance.Instance {Instance.diskTemplate = DTDrbd8})
gdx avail_nodes =
do
let no_nodes = Left "no nodes available"
node_pairs = [(p,s) | p <- avail_nodes, s <- avail_nodes, p /= s]
(nl', il', ops, _) <-
annotateResult "Can't find any good nodes for relocation" .
eitherToResult $
foldl'
(\accu nodes -> case evacDrbdAllInner opts nl il inst gdx nodes of
Bad msg ->
case accu of
Right _ -> accu
Left _ -> Left $ "Allocation failed: " ++ msg
Ok result@(_, _, _, new_cv) ->
let new_accu = Right result in
case accu of
Left _ -> new_accu
Right (_, _, _, old_cv) ->
if old_cv < new_cv
then accu
else new_accu
) no_nodes node_pairs
return (nl', il', ops)
updateEvacSolution :: (Node.List, Instance.List, EvacSolution)
-> Idx
-> Result (Node.List, Instance.List, [OpCodes.OpCode])
-> (Node.List, Instance.List, EvacSolution)
updateEvacSolution (nl, il, es) idx (Bad msg) =
(nl, il, es { esFailed = (idx, msg):esFailed es})
updateEvacSolution (_, _, es) idx (Ok (nl, il, opcodes)) =
(nl, il, es { esMoved = new_elem:esMoved es
, esOpCodes = opcodes:esOpCodes es })
where inst = Container.find idx il
new_elem = (idx,
instancePriGroup nl inst,
Instance.allNodes inst)
nodesToEvacuate :: Instance.List
-> EvacMode
-> [Idx]
-> IntSet.IntSet
nodesToEvacuate il mode =
IntSet.delete Node.noSecondary .
foldl' (\ns idx ->
let i = Container.find idx il
pdx = Instance.pNode i
sdx = Instance.sNode i
dt = Instance.diskTemplate i
withSecondary = case dt of
DTDrbd8 -> IntSet.insert sdx ns
_ -> ns
in case mode of
ChangePrimary -> IntSet.insert pdx ns
ChangeSecondary -> withSecondary
ChangeAll -> IntSet.insert pdx withSecondary
) IntSet.empty
tryNodeEvac :: AlgorithmOptions
-> Group.List
-> Node.List
-> Instance.List
-> EvacMode
-> [Idx]
-> Result (Node.List, Instance.List, EvacSolution)
tryNodeEvac opts _ ini_nl ini_il mode idxs =
let evac_ndx = nodesToEvacuate ini_il mode idxs
offline = map Node.idx . filter Node.offline $ Container.elems ini_nl
excl_ndx = foldl' (flip IntSet.insert) evac_ndx offline
group_ndx = map (\(gdx, (nl, _)) -> (gdx, map Node.idx
(Container.elems nl))) $
splitCluster ini_nl ini_il
(fin_nl, fin_il, esol) =
foldl' (\state@(nl, il, _) inst ->
let gdx = instancePriGroup nl inst
pdx = Instance.pNode inst in
updateEvacSolution state (Instance.idx inst) $
availableGroupNodes group_ndx
(IntSet.insert pdx excl_ndx) gdx >>=
nodeEvacInstance opts nl il mode inst gdx
)
(ini_nl, ini_il, emptyEvacSolution)
(map (`Container.find` ini_il) idxs)
in return (fin_nl, fin_il, reverseEvacSolution esol)