module Ganeti.HTools.GlobalN1
( canEvacuateNode
, redundant
, redundantGrp
, allocGlobalN1
) where
import Control.Monad (foldM, foldM_)
import qualified Data.Foldable as Foldable
import Data.Function (on)
import Data.List (partition, sortBy)
import Ganeti.BasicTypes (isOk, Result)
import Ganeti.HTools.AlgorithmParams (AlgorithmOptions(..), defaultOptions)
import Ganeti.HTools.Cluster.AllocatePrimitives (allocateOnSingle)
import qualified Ganeti.HTools.Cluster.AllocationSolution as AllocSol
import qualified Ganeti.HTools.Cluster.Evacuate as Evacuate
import Ganeti.HTools.Cluster.Moves (move)
import qualified Ganeti.HTools.Container as Container
import qualified Ganeti.HTools.Instance as Instance
import qualified Ganeti.HTools.Node as Node
import Ganeti.HTools.Types ( IMove(Failover), Ndx, Gdx, Idx, opToResult,
FailMode(FailN1) )
import Ganeti.Types ( DiskTemplate(DTDrbd8), diskTemplateMovable
, EvacMode(ChangePrimary))
evac :: Gdx -> [Ndx]
-> (Node.List, Instance.List) -> Idx -> Result (Node.List, Instance.List)
evac gdx ndxs (nl, il) idx = do
let opts = defaultOptions { algIgnoreSoftErrors = True, algEvacMode = True }
inst = Container.find idx il
(nl', il', _) <- Evacuate.nodeEvacInstance opts nl il ChangePrimary inst
gdx ndxs
return (nl', il')
recreate :: [Ndx]
-> (Node.List, Instance.List)
-> Instance.Instance
-> Result (Node.List, Instance.List)
recreate targetnodes (nl, il) inst = do
let opts = defaultOptions { algIgnoreSoftErrors = True, algEvacMode = True }
sols = foldl (\cstate ->
AllocSol.concatAllocCollections cstate
. allocateOnSingle opts nl inst
) AllocSol.emptyAllocCollection targetnodes
sol = AllocSol.collectionToSolution FailN1 (const True) sols
alloc <- maybe (fail "No solution found") return $ AllocSol.asSolution sol
let il' = AllocSol.updateIl il $ Just alloc
nl' = AllocSol.extractNl nl il $ Just alloc
return (nl', il')
canEvacuateNode :: (Node.List, Instance.List) -> Node.Node -> Bool
canEvacuateNode (nl, il) n = isOk $ do
let (drbdIdxs, otherIdxs) = partition ((==) DTDrbd8
. Instance.diskTemplate
. flip Container.find il)
$ Node.pList n
(sharedIdxs, nonMoveIdxs) = partition (diskTemplateMovable
. Instance.diskTemplate
. flip Container.find il) otherIdxs
(nl', il') <- opToResult
. foldM move (nl, il) $ map (flip (,) Failover) drbdIdxs
let grp = Node.group n
escapenodes = filter (/= Node.idx n)
. map Node.idx
. filter ((== grp) . Node.group)
$ Container.elems nl'
(nl'', il'') <- foldM (evac grp escapenodes) (nl',il') sharedIdxs
let recreateInstances = sortBy (flip compare `on` Instance.mem)
$ map (`Container.find` il'') nonMoveIdxs
foldM_ (recreate escapenodes) (nl'', il'') recreateInstances
redundant :: AlgorithmOptions -> Node.List -> Instance.List -> Bool
redundant opts nl il =
let filterFun = if algAcceptExisting opts
then Container.filter (not . Node.offline)
else id
in Foldable.all (canEvacuateNode (nl, il))
. Container.filter (not . (`elem` algCapacityIgnoreGroups opts)
. Node.group)
$ filterFun nl
redundantGrp :: AlgorithmOptions -> Node.List -> Instance.List -> Gdx -> Bool
redundantGrp opts nl il gdx =
redundant opts (Container.filter ((==) gdx . Node.group) nl) il
allocGlobalN1 :: AlgorithmOptions
-> Node.List
-> Instance.List
-> AllocSol.GenericAllocElement a -> Bool
allocGlobalN1 opts nl il alloc =
let il' = AllocSol.updateIl il $ Just alloc
nl' = AllocSol.extractNl nl il $ Just alloc
in redundant opts nl' il'