module Ganeti.HTools.Node
( Node(..)
, List
, pCpuEff
, pCpuEffForth
, create
, buildPeers
, setIdx
, setAlias
, setOffline
, setPri
, calcFmemOfflineOrForthcoming
, setSec
, setMaster
, setNodeTags
, setMdsk
, setMcpu
, setPolicy
, setCpuSpeed
, setMigrationTags
, setRecvMigrationTags
, setLocationTags
, setHypervisor
, addTags
, delTags
, rejectAddTags
, getPolicyHealth
, removePri
, removeSec
, addPri
, addPriEx
, addSec
, addSecEx
, addSecExEx
, checkMigration
, availDisk
, availMem
, missingMem
, unallocatedMem
, recordedFreeMem
, availCpu
, iDsk
, conflictingPrimaries
, genPowerOnOpCodes
, genPowerOffOpCodes
, genAddTagsOpCode
, defaultFields
, showHeader
, showField
, list
, AssocList
, noSecondary
, computeGroups
, mkNodeGraph
, mkRebootNodeGraph
, haveExclStorage
) where
import Control.Monad (liftM, liftM2)
import Control.Monad.Fail (MonadFail)
import qualified Data.Foldable as Foldable
import Data.Function (on)
import qualified Data.Graph as Graph
import qualified Data.IntMap as IntMap
import Data.List hiding (group)
import qualified Data.Map as Map
import Data.Ord (comparing)
import qualified Data.Set as Set
import Text.Printf (printf)
import qualified Ganeti.Constants as C
import qualified Ganeti.OpCodes as OpCodes
import Ganeti.Types (Hypervisor(..), OobCommand(..), TagKind(..), mkNonEmpty)
import Ganeti.HTools.Container (Container)
import qualified Ganeti.HTools.Container as Container
import Ganeti.HTools.Instance (Instance)
import qualified Ganeti.HTools.Instance as Instance
import qualified Ganeti.HTools.PeerMap as P
import Ganeti.BasicTypes
import qualified Ganeti.HTools.Types as T
type TagMap = Map.Map String Int
data Node = Node
{ name :: String
, alias :: String
, tMem :: Double
, nMem :: Int
, iMem :: Int
, fMem :: Int
, fMemForth :: Int
, xMem :: Int
, tDsk :: Double
, fDsk :: Int
, fDskForth :: Int
, tCpu :: Double
, tCpuSpeed :: Double
, nCpu :: Int
, uCpu :: Int
, uCpuForth :: Int
, tSpindles :: Int
, fSpindles :: Int
, fSpindlesForth :: Int
, pList :: [T.Idx]
, pListForth :: [T.Idx]
, sList :: [T.Idx]
, sListForth :: [T.Idx]
, idx :: T.Ndx
, peers :: P.PeerMap
, failN1 :: Bool
, failN1Forth :: Bool
, rMem :: Int
, rMemForth :: Int
, pMem :: Double
, pMemForth :: Double
, pDsk :: Double
, pDskForth :: Double
, pRem :: Double
, pRemForth :: Double
, pCpu :: Double
, pCpuForth :: Double
, mDsk :: Double
, loDsk :: Int
, hiCpu :: Int
, hiSpindles :: Double
, instSpindles :: Double
, instSpindlesForth :: Double
, offline :: Bool
, isMaster :: Bool
, nTags :: [String]
, utilPool :: T.DynUtil
, utilLoad :: T.DynUtil
, utilLoadForth :: T.DynUtil
, pTags :: TagMap
, group :: T.Gdx
, iPolicy :: T.IPolicy
, exclStorage :: Bool
, migTags :: Set.Set String
, rmigTags :: Set.Set String
, locationTags :: Set.Set String
, locationScore :: Int
, instanceMap :: Map.Map (String, String) Int
, hypervisor :: Maybe Hypervisor
} deriving (Show, Eq)
instance T.Element Node where
nameOf = name
idxOf = idx
setAlias = setAlias
setIdx = setIdx
allNames n = [name n, alias n]
pCpuEff :: Node -> Double
pCpuEff n = pCpu n / tCpuSpeed n
pCpuEffForth :: Node -> Double
pCpuEffForth n = pCpuForth n / tCpuSpeed n
type AssocList = [(T.Ndx, Node)]
type List = Container.Container Node
noSecondary :: T.Ndx
noSecondary = 1
addTag :: (Ord k) => Map.Map k Int -> k -> Map.Map k Int
addTag t s = Map.insertWith (+) s 1 t
addTags :: (Ord k) => Map.Map k Int -> [k] -> Map.Map k Int
addTags = foldl' addTag
delTag :: (Ord k) => Map.Map k Int -> k -> Map.Map k Int
delTag t s = Map.update (\v -> if v > 1
then Just (v1)
else Nothing)
s t
delTags :: (Ord k) => Map.Map k Int -> [k] -> Map.Map k Int
delTags = foldl' delTag
rejectAddTags :: TagMap -> [String] -> Bool
rejectAddTags t = any (`Map.member` t)
conflictingPrimaries :: Node -> Int
conflictingPrimaries (Node { pTags = t }) = Foldable.sum t Map.size t
incIf :: (Num a) => Bool -> a -> a -> a
incIf True base delta = base + delta
incIf False base _ = base
decIf :: (Num a) => Bool -> a -> a -> a
decIf True base delta = base delta
decIf False base _ = base
haveExclStorage :: List -> Bool
haveExclStorage nl =
any exclStorage $ Container.elems nl
create :: String -> Double -> Int -> Int
-> Double -> Int -> Double -> Int -> Bool
-> Int -> Int -> T.Gdx -> Bool
-> Node
create name_init mem_t_init mem_n_init mem_f_init
dsk_t_init dsk_f_init cpu_t_init cpu_n_init offline_init
spindles_t_init spindles_f_init group_init excl_stor =
Node { name = name_init
, alias = name_init
, tMem = mem_t_init
, nMem = mem_n_init
, iMem = 0
, xMem = 0
, pMem = 0
, fMem = mem_f_init
, fMemForth = mem_f_init
, tDsk = dsk_t_init
, fDsk = dsk_f_init
, fDskForth = dsk_f_init
, tCpu = cpu_t_init
, tCpuSpeed = 1
, nCpu = cpu_n_init
, uCpu = cpu_n_init
, uCpuForth = cpu_n_init
, tSpindles = spindles_t_init
, fSpindles = spindles_f_init
, fSpindlesForth = spindles_f_init
, pList = []
, pListForth = []
, sList = []
, sListForth = []
, failN1 = True
, failN1Forth = True
, idx = 1
, peers = P.empty
, rMem = 0
, rMemForth = 0
, pMemForth = fromIntegral mem_f_init / mem_t_init
, pDsk = if excl_stor
then computePDsk spindles_f_init $ fromIntegral spindles_t_init
else computePDsk dsk_f_init dsk_t_init
, pDskForth =
if excl_stor
then computePDsk spindles_f_init $ fromIntegral spindles_t_init
else computePDsk dsk_f_init dsk_t_init
, pRem = 0
, pRemForth = 0
, pCpu = fromIntegral cpu_n_init / cpu_t_init
, pCpuForth = fromIntegral cpu_n_init / cpu_t_init
, offline = offline_init
, isMaster = False
, nTags = []
, mDsk = T.defReservedDiskRatio
, loDsk = mDskToloDsk T.defReservedDiskRatio dsk_t_init
, hiCpu = mCpuTohiCpu (T.iPolicyVcpuRatio T.defIPolicy) cpu_t_init
, hiSpindles = computeHiSpindles (T.iPolicySpindleRatio T.defIPolicy)
spindles_t_init
, instSpindles = 0
, instSpindlesForth = 0
, utilPool = T.baseUtil
, utilLoad = T.zeroUtil
, utilLoadForth = T.zeroUtil
, pTags = Map.empty
, group = group_init
, iPolicy = T.defIPolicy
, exclStorage = excl_stor
, migTags = Set.empty
, rmigTags = Set.empty
, locationTags = Set.empty
, locationScore = 0
, instanceMap = Map.empty
, hypervisor = Nothing
}
mDskToloDsk :: Double -> Double -> Int
mDskToloDsk mval = floor . (mval *)
mCpuTohiCpu :: Double -> Double -> Int
mCpuTohiCpu mval = floor . (mval *)
computeHiSpindles :: Double -> Int -> Double
computeHiSpindles spindle_ratio = (spindle_ratio *) . fromIntegral
setIdx :: Node -> T.Ndx -> Node
setIdx t i = t {idx = i}
setAlias :: Node -> String -> Node
setAlias t s = t { alias = s }
setOffline :: Node -> Bool -> Node
setOffline t val = t { offline = val }
setMaster :: Node -> Bool -> Node
setMaster t val = t { isMaster = val }
setNodeTags :: Node -> [String] -> Node
setNodeTags t val = t { nTags = val }
setMigrationTags :: Node -> Set.Set String -> Node
setMigrationTags t val = t { migTags = val }
setRecvMigrationTags :: Node -> Set.Set String -> Node
setRecvMigrationTags t val = t { rmigTags = val }
setLocationTags :: Node -> Set.Set String -> Node
setLocationTags t val = t { locationTags = val }
setHypervisor :: Node -> Hypervisor -> Node
setHypervisor t val = t { hypervisor = Just val }
setMdsk :: Node -> Double -> Node
setMdsk t val = t { mDsk = val, loDsk = mDskToloDsk val (tDsk t) }
setMcpu :: Node -> Double -> Node
setMcpu t val =
let new_ipol = (iPolicy t) { T.iPolicyVcpuRatio = val }
in t { hiCpu = mCpuTohiCpu val (tCpu t), iPolicy = new_ipol }
setPolicy :: T.IPolicy -> Node -> Node
setPolicy pol node =
node { iPolicy = pol
, hiCpu = mCpuTohiCpu (T.iPolicyVcpuRatio pol) (tCpu node)
, hiSpindles = computeHiSpindles (T.iPolicySpindleRatio pol)
(tSpindles node)
}
computeMaxRes :: P.PeerMap -> P.Elem
computeMaxRes = P.maxElem
buildPeers :: Node -> Instance.List -> Node
buildPeers t il =
let mdata = map
(\i_idx -> let inst = Container.find i_idx il
mem = if Instance.usesSecMem inst
&& not (Instance.forthcoming inst)
then Instance.mem inst
else 0
in (Instance.pNode inst, mem))
(sList t)
pmap = P.accumArray (+) mdata
new_rmem = computeMaxRes pmap
new_failN1 = fMem t < new_rmem
new_prem = fromIntegral new_rmem / tMem t
in t { peers = pmap
, failN1 = new_failN1
, rMem = new_rmem
, pRem = new_prem
}
calcSpindleUse ::
Bool
-> Node -> Instance.Instance -> Double
calcSpindleUse _ (Node {exclStorage = True}) _ = 0.0
calcSpindleUse act n@(Node {exclStorage = False}) i =
f (Instance.usesLocalStorage i) (instSpindles n)
(fromIntegral $ Instance.spindleUse i)
where
f :: Bool -> Double -> Double -> Double
f = if act then incIf else decIf
calcSpindleUseForth :: Bool
-> Node -> Instance.Instance -> Double
calcSpindleUseForth _ (Node {exclStorage = True}) _ = 0.0
calcSpindleUseForth act n@(Node {exclStorage = False}) i =
f (Instance.usesLocalStorage i) (instSpindlesForth n)
(fromIntegral $ Instance.spindleUse i)
where
f :: Bool -> Double -> Double -> Double
f = if act then incIf else decIf
calcNewFreeSpindles ::
Bool
-> Node -> Instance.Instance -> Int
calcNewFreeSpindles _ (Node {exclStorage = False}) _ = 0
calcNewFreeSpindles act n@(Node {exclStorage = True}) i =
case Instance.getTotalSpindles i of
Nothing -> if act
then 1
else fSpindles n
Just s -> (if act then () else (+)) (fSpindles n) s
calcNewFreeSpindlesForth :: Bool
-> Node -> Instance.Instance -> Int
calcNewFreeSpindlesForth _ (Node {exclStorage = False}) _ = 0
calcNewFreeSpindlesForth act n@(Node {exclStorage = True}) i =
case Instance.getTotalSpindles i of
Nothing -> if act
then 1
else fSpindlesForth n
Just s -> (if act then () else (+)) (fSpindlesForth n) s
calcFmemOfflineOrForthcoming :: Node -> Container Instance -> Int
calcFmemOfflineOrForthcoming node allInstances =
let nodeInstances = map (`Container.find` allInstances) (pList node)
in sum . map Instance.mem
. filter (not . Instance.usesMemory)
$ nodeInstances
getInstanceDsrdLocScore :: Node
-> Instance.Instance
-> Int
getInstanceDsrdLocScore p t =
desiredLocationScore (Instance.dsrdLocTags t) (locationTags p)
where desiredLocationScore instTags nodeTags =
Set.size instTags Set.size ( instTags `Set.intersection` nodeTags )
getLocationExclusionPairs :: Node
-> Instance.Instance
-> [(String, String)]
getLocationExclusionPairs p inst =
[(loc, excl) | loc <- Set.toList (locationTags p)
, excl <- Instance.exclTags inst]
setPri :: Node -> Instance.Instance -> Node
setPri t inst
| not (Instance.forthcoming inst) =
updateForthcomingFields $
t { pList = Instance.idx inst:pList t
, uCpu = new_count
, pCpu = fromIntegral new_count / tCpu t
, utilLoad = utilLoad t `T.addUtil` Instance.util inst
, instSpindles = calcSpindleUse True t inst
, locationScore = locationScore t + Instance.locationScore inst
+ getInstanceDsrdLocScore t inst
, instanceMap = new_instance_map
}
| otherwise = updateForthcomingOnlyFields $ updateForthcomingFields t
where
new_count = Instance.applyIfOnline inst (+ Instance.vcpus inst) (uCpu t)
new_count_forth = Instance.applyIfOnline inst (+ Instance.vcpus inst)
(uCpuForth t)
new_instance_map = addTags (instanceMap t)
$ getLocationExclusionPairs t inst
uses_disk = Instance.usesLocalStorage inst
updateForthcomingFields node =
let new_fMemForth = decIf (not $ Instance.usesMemory inst)
(fMemForth node)
(Instance.mem inst)
new_pMemForth = fromIntegral new_fMemForth / tMem node
in node
{ pTags = addTags (pTags node) (Instance.exclTags inst)
, pListForth = Instance.idx inst:pListForth node
, uCpuForth = new_count_forth
, pCpuForth = fromIntegral new_count_forth / tCpu node
, utilLoadForth = utilLoadForth node `T.addUtil` Instance.util inst
, fMemForth = new_fMemForth
, pMemForth = new_pMemForth
, instSpindlesForth = calcSpindleUseForth True node inst
}
updateForthcomingOnlyFields node =
let new_fDskForth = decIf uses_disk
(fDskForth node)
(Instance.dsk inst)
new_free_sp_forth = calcNewFreeSpindlesForth True node inst
new_pDskForth = computeNewPDsk node new_free_sp_forth new_fDskForth
in node
{ fDskForth = new_fDskForth
, pDskForth = new_pDskForth
, fSpindlesForth = new_free_sp_forth
}
setSec :: Node -> Instance.Instance -> Node
setSec t inst
| not (Instance.forthcoming inst) =
updateForthcomingFields $
t { sList = Instance.idx inst:sList t
, utilLoad = old_load { T.dskWeight = T.dskWeight old_load +
T.dskWeight (Instance.util inst) }
, instSpindles = calcSpindleUse True t inst
}
| otherwise = updateForthcomingOnlyFields $ updateForthcomingFields t
where
old_load = utilLoad t
uses_disk = Instance.usesLocalStorage inst
updateForthcomingFields node =
let old_load_forth = utilLoadForth node
in node
{ sListForth = Instance.idx inst:sListForth node
, utilLoadForth = old_load_forth
{ T.dskWeight = T.dskWeight old_load_forth +
T.dskWeight (Instance.util inst)
}
, instSpindlesForth = calcSpindleUseForth True node inst
}
updateForthcomingOnlyFields node =
let new_fDskForth = decIf uses_disk
(fDskForth node)
(Instance.dsk inst)
new_free_sp_forth = calcNewFreeSpindlesForth True node inst
new_pDskForth = computeNewPDsk node new_free_sp_forth new_fDskForth
in node
{ fDskForth = new_fDskForth
, pDskForth = new_pDskForth
, fSpindlesForth = new_free_sp_forth
}
computePDsk :: Int -> Double -> Double
computePDsk _ 0 = 1
computePDsk free total = fromIntegral free / total
computeNewPDsk :: Node -> Int -> Int -> Double
computeNewPDsk node new_free_sp new_free_dsk =
if exclStorage node
then computePDsk new_free_sp . fromIntegral $ tSpindles node
else computePDsk new_free_dsk $ tDsk node
getPolicyHealth :: Node -> T.OpResult ()
getPolicyHealth n =
case () of
_ | instSpindles n > hiSpindles n -> Bad T.FailDisk
| pCpu n > T.iPolicyVcpuRatio (iPolicy n) -> Bad T.FailCPU
| otherwise -> Ok ()
setCpuSpeed :: Node -> Double -> Node
setCpuSpeed n f = n { tCpuSpeed = f }
removePri :: Node -> Instance.Instance -> Node
removePri t inst =
let iname = Instance.idx inst
forthcoming = Instance.forthcoming inst
i_online = Instance.notOffline inst
uses_disk = Instance.usesLocalStorage inst
updateForthcomingFields n =
let
new_plist_forth = delete iname (pListForth n)
new_mem_forth = fMemForth n + Instance.mem inst
new_dsk_forth = incIf uses_disk (fDskForth n) (Instance.dsk inst)
new_free_sp_forth = calcNewFreeSpindlesForth False n inst
new_inst_sp_forth = calcSpindleUseForth False n inst
new_mp_forth = fromIntegral new_mem_forth / tMem n
new_dp_forth = computeNewPDsk n new_free_sp_forth new_dsk_forth
new_ucpu_forth = decIf i_online (uCpuForth n) (Instance.vcpus inst)
new_rcpu_forth = fromIntegral new_ucpu_forth / tCpu n
new_load_forth = utilLoadForth n `T.subUtil` Instance.util inst
in n { pTags = delTags (pTags t) (Instance.exclTags inst)
, pListForth = new_plist_forth
, fMemForth = new_mem_forth
, fDskForth = new_dsk_forth
, pMemForth = new_mp_forth
, pDskForth = new_dp_forth
, uCpuForth = new_ucpu_forth
, pCpuForth = new_rcpu_forth
, utilLoadForth = new_load_forth
, instSpindlesForth = new_inst_sp_forth
, fSpindlesForth = new_free_sp_forth
}
in if forthcoming
then updateForthcomingFields t
else let
new_plist = delete iname (pList t)
(new_i_mem, new_free_mem) = prospectiveMem t inst False
new_p_mem = fromIntegral new_free_mem / tMem t
new_failn1 = new_free_mem <= rMem t
new_dsk = incIf uses_disk (fDsk t) (Instance.dsk inst)
new_free_sp = calcNewFreeSpindles False t inst
new_inst_sp = calcSpindleUse False t inst
new_dp = computeNewPDsk t new_free_sp new_dsk
new_ucpu = decIf i_online (uCpu t) (Instance.vcpus inst)
new_rcpu = fromIntegral new_ucpu / tCpu t
new_load = utilLoad t `T.subUtil` Instance.util inst
new_instance_map = delTags (instanceMap t)
$ getLocationExclusionPairs t inst
in updateForthcomingFields $
t { pList = new_plist, iMem = new_i_mem, fDsk = new_dsk
, failN1 = new_failn1, pMem = new_p_mem, pDsk = new_dp
, uCpu = new_ucpu, pCpu = new_rcpu, utilLoad = new_load
, instSpindles = new_inst_sp, fSpindles = new_free_sp
, locationScore = locationScore t
Instance.locationScore inst
getInstanceDsrdLocScore t inst
, instanceMap = new_instance_map
}
removeSec :: Node -> Instance.Instance -> Node
removeSec t inst =
let iname = Instance.idx inst
forthcoming = Instance.forthcoming inst
uses_disk = Instance.usesLocalStorage inst
cur_dsk = fDsk t
pnode = Instance.pNode inst
updateForthcomingFields n =
let
new_slist_forth = delete iname (sListForth n)
new_dsk_forth = incIf uses_disk (fDskForth n) (Instance.dsk inst)
new_free_sp_forth = calcNewFreeSpindlesForth False n inst
new_inst_sp_forth = calcSpindleUseForth False n inst
new_dp_forth = computeNewPDsk n new_free_sp_forth new_dsk_forth
old_load_forth = utilLoadForth n
new_load_forth = old_load_forth
{ T.dskWeight = T.dskWeight old_load_forth
T.dskWeight (Instance.util inst)
}
in n { sListForth = new_slist_forth
, fDskForth = new_dsk_forth
, pDskForth = new_dp_forth
, utilLoadForth = new_load_forth
, instSpindlesForth = new_inst_sp_forth
, fSpindlesForth = new_free_sp_forth
}
in if forthcoming
then updateForthcomingFields t
else let
new_slist = delete iname (sList t)
new_dsk = incIf uses_disk cur_dsk (Instance.dsk inst)
new_free_sp = calcNewFreeSpindles False t inst
new_inst_sp = calcSpindleUse False t inst
old_peers = peers t
old_peem = P.find pnode old_peers
new_peem = decIf (Instance.usesSecMem inst) old_peem
(Instance.mem inst)
new_peers = if new_peem > 0
then P.add pnode new_peem old_peers
else P.remove pnode old_peers
old_rmem = rMem t
new_rmem = if old_peem < old_rmem
then old_rmem
else computeMaxRes new_peers
new_prem = fromIntegral new_rmem / tMem t
new_failn1 = unallocatedMem t <= new_rmem
new_dp = computeNewPDsk t new_free_sp new_dsk
old_load = utilLoad t
new_load = old_load
{ T.dskWeight = T.dskWeight old_load
T.dskWeight (Instance.util inst)
}
in updateForthcomingFields $
t { sList = new_slist, fDsk = new_dsk, peers = new_peers
, failN1 = new_failn1, rMem = new_rmem, pDsk = new_dp
, pRem = new_prem, utilLoad = new_load
, instSpindles = new_inst_sp, fSpindles = new_free_sp
}
addPri :: Node -> Instance.Instance -> T.OpResult Node
addPri = addPriEx False
addPriEx :: Bool
-> Node
-> Instance.Instance
-> T.OpResult Node
addPriEx force t inst =
let iname = Instance.idx inst
forthcoming = Instance.forthcoming inst
i_online = Instance.notOffline inst
uses_disk = Instance.usesLocalStorage inst
l_cpu = T.iPolicyVcpuRatio $ iPolicy t
old_tags = pTags t
strict = not force
inst_tags = Instance.exclTags inst
new_mem_forth = fMemForth t Instance.mem inst
new_mp_forth = fromIntegral new_mem_forth / tMem t
new_dsk_forth = decIf uses_disk (fDskForth t) (Instance.dsk inst)
new_free_sp_forth = calcNewFreeSpindlesForth True t inst
new_inst_sp_forth = calcSpindleUseForth True t inst
new_ucpu_forth = incIf i_online (uCpuForth t) (Instance.vcpus inst)
new_pcpu_forth = fromIntegral new_ucpu_forth / tCpu t
new_dp_forth = computeNewPDsk t new_free_sp_forth new_dsk_forth
new_load_forth = utilLoadForth t `T.addUtil` Instance.util inst
new_plist_forth = iname:pListForth t
updateForthcomingFields n =
n { pTags = addTags old_tags inst_tags
, pListForth = new_plist_forth
, fMemForth = new_mem_forth
, fDskForth = new_dsk_forth
, pMemForth = new_mp_forth
, pDskForth = new_dp_forth
, uCpuForth = new_ucpu_forth
, pCpuForth = new_pcpu_forth
, utilLoadForth = new_load_forth
, instSpindlesForth = new_inst_sp_forth
, fSpindlesForth = new_free_sp_forth
}
checkForthcomingViolation
| new_mem_forth <= 0 = Bad T.FailMem
| uses_disk && new_dsk_forth <= 0 = Bad T.FailDisk
| uses_disk && new_dsk_forth < loDsk t = Bad T.FailDisk
| uses_disk && exclStorage t
&& new_free_sp_forth < 0 = Bad T.FailSpindles
| uses_disk && new_inst_sp_forth > hiSpindles t = Bad T.FailDisk
| l_cpu >= 0 && l_cpu < new_pcpu_forth = Bad T.FailCPU
| otherwise = Ok ()
in
if forthcoming
then case strict of
True | Bad err <- checkForthcomingViolation -> Bad err
_ -> Ok $ updateForthcomingFields t
else let
(new_i_mem, new_free_mem) = prospectiveMem t inst True
new_p_mem = fromIntegral new_free_mem / tMem t
new_failn1 = new_free_mem <= rMem t
new_dsk = decIf uses_disk (fDsk t) (Instance.dsk inst)
new_free_sp = calcNewFreeSpindles True t inst
new_inst_sp = calcSpindleUse True t inst
new_ucpu = incIf i_online (uCpu t) (Instance.vcpus inst)
new_pcpu = fromIntegral new_ucpu / tCpu t
new_dp = computeNewPDsk t new_free_sp new_dsk
new_load = utilLoad t `T.addUtil` Instance.util inst
new_plist = iname:pList t
new_instance_map = addTags (instanceMap t)
$ getLocationExclusionPairs t inst
in case () of
_ | new_free_mem <= 0 -> Bad T.FailMem
| uses_disk && new_dsk <= 0 -> Bad T.FailDisk
| strict && uses_disk && new_dsk < loDsk t -> Bad T.FailDisk
| uses_disk && exclStorage t && new_free_sp < 0 -> Bad T.FailSpindles
| strict && uses_disk && new_inst_sp > hiSpindles t -> Bad T.FailDisk
| strict && new_failn1 && not (failN1 t) -> Bad T.FailMem
| strict && l_cpu >= 0 && l_cpu < new_pcpu -> Bad T.FailCPU
| strict && rejectAddTags old_tags inst_tags -> Bad T.FailTags
| strict, Bad err <- checkForthcomingViolation -> Bad err
| otherwise ->
Ok . updateForthcomingFields $
t { pList = new_plist
, iMem = new_i_mem
, fDsk = new_dsk
, failN1 = new_failn1
, pMem = new_p_mem
, pDsk = new_dp
, uCpu = new_ucpu
, pCpu = new_pcpu
, utilLoad = new_load
, instSpindles = new_inst_sp
, fSpindles = new_free_sp
, locationScore = locationScore t
+ Instance.locationScore inst
+ getInstanceDsrdLocScore t inst
, instanceMap = new_instance_map
}
addSec :: Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
addSec = addSecEx False
addSecEx :: Bool -> Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
addSecEx = addSecExEx False
addSecExEx :: Bool
-> Bool -> Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
addSecExEx ignore_disks force t inst pdx =
let iname = Instance.idx inst
forthcoming = Instance.forthcoming inst
old_peers = peers t
strict = not force
secondary_needed_mem = if Instance.usesSecMem inst
then Instance.mem inst
else 0
new_peem = P.find pdx old_peers + secondary_needed_mem
new_peers = P.add pdx new_peem old_peers
old_mem_forth = fMemForth t
new_dsk_forth = fDskForth t Instance.dsk inst
new_free_sp_forth = calcNewFreeSpindlesForth True t inst
new_inst_sp_forth = calcSpindleUseForth True t inst
new_dp_forth = computeNewPDsk t new_free_sp_forth new_dsk_forth
old_load_forth = utilLoadForth t
new_load_forth = old_load_forth
{ T.dskWeight = T.dskWeight old_load_forth +
T.dskWeight (Instance.util inst)
}
new_slist_forth = iname:sListForth t
updateForthcomingFields n =
n { sListForth = new_slist_forth
, fDskForth = new_dsk_forth
, pDskForth = new_dp_forth
, utilLoadForth = new_load_forth
, instSpindlesForth = new_inst_sp_forth
, fSpindlesForth = new_free_sp_forth
}
checkForthcomingViolation
| not (Instance.hasSecondary inst) = Bad T.FailDisk
| new_dsk_forth <= 0 = Bad T.FailDisk
| new_dsk_forth < loDsk t = Bad T.FailDisk
| exclStorage t && new_free_sp_forth < 0 = Bad T.FailSpindles
| new_inst_sp_forth > hiSpindles t = Bad T.FailDisk
| secondary_needed_mem >= old_mem_forth = Bad T.FailMem
| otherwise = Ok ()
in if forthcoming
then case strict of
True | Bad err <- checkForthcomingViolation -> Bad err
_ -> Ok $ updateForthcomingFields t
else let
old_mem = unallocatedMem t
new_dsk = fDsk t Instance.dsk inst
new_free_sp = calcNewFreeSpindles True t inst
new_inst_sp = calcSpindleUse True t inst
new_rmem = max (rMem t) new_peem
new_prem = fromIntegral new_rmem / tMem t
new_failn1 = old_mem <= new_rmem
new_dp = computeNewPDsk t new_free_sp new_dsk
old_load = utilLoad t
new_load = old_load
{ T.dskWeight = T.dskWeight old_load +
T.dskWeight (Instance.util inst)
}
new_slist = iname:sList t
in case () of
_ | not (Instance.hasSecondary inst) -> Bad T.FailDisk
| not ignore_disks && new_dsk <= 0 -> Bad T.FailDisk
| strict && new_dsk < loDsk t -> Bad T.FailDisk
| exclStorage t && new_free_sp < 0 -> Bad T.FailSpindles
| strict && new_inst_sp > hiSpindles t -> Bad T.FailDisk
| strict && secondary_needed_mem >= old_mem -> Bad T.FailMem
| strict && new_failn1 && not (failN1 t) -> Bad T.FailMem
| strict, Bad err <- checkForthcomingViolation -> Bad err
| otherwise ->
Ok . updateForthcomingFields $
t { sList = new_slist, fDsk = new_dsk
, peers = new_peers, failN1 = new_failn1
, rMem = new_rmem, pDsk = new_dp
, pRem = new_prem, utilLoad = new_load
, instSpindles = new_inst_sp
, fSpindles = new_free_sp
}
checkMigration :: Node -> Node -> T.OpResult ()
checkMigration nsrc ntarget =
if migTags nsrc `Set.isSubsetOf` rmigTags ntarget
then Ok ()
else Bad T.FailMig
availDisk :: Node -> Int
availDisk t =
let _f = fDsk t
_l = loDsk t
in if _f < _l
then 0
else _f _l
iDsk :: Node -> Int
iDsk t = truncate (tDsk t) fDsk t
reportedFreeMem :: Node -> Int
reportedFreeMem = fMem
recordedFreeMem :: Node -> Int
recordedFreeMem t =
let total = tMem t
node = nMem t
inst = iMem t
in truncate total node inst
missingMem :: Node -> Int
missingMem t =
recordedFreeMem t reportedFreeMem t
unallocatedMem :: Node -> Int
unallocatedMem t =
let state_of_record = recordedFreeMem t
in state_of_record max 0 (xMem t)
availMem :: Node -> Int
availMem t =
let reserved = rMem t
unallocated = unallocatedMem t
in max 0 (unallocated reserved)
prospectiveMem :: Node -> Instance
-> Bool
-> (Int, Int)
prospectiveMem node inst add =
let uses_mem = (Instance.usesMemory inst)
condOp = if add then incIf else decIf
new_i_mem = condOp uses_mem (iMem node) (Instance.mem inst)
new_node = node { iMem = new_i_mem }
new_free_mem = unallocatedMem new_node
in (new_i_mem, new_free_mem)
availCpu :: Node -> Int
availCpu t =
let _u = uCpu t
_l = hiCpu t
in if _l >= _u
then _l _u
else 0
instanceToEdges :: Instance.Instance -> [Graph.Edge]
instanceToEdges i
| Instance.hasSecondary i = [(pnode,snode), (snode,pnode)]
| otherwise = []
where pnode = Instance.pNode i
snode = Instance.sNode i
instancesToEdges :: Instance.List -> [Graph.Edge]
instancesToEdges = concatMap instanceToEdges . Container.elems
nodesToBounds :: List -> Maybe Graph.Bounds
nodesToBounds nl = liftM2 (,) nmin nmax
where nmin = fmap (fst . fst) (IntMap.minViewWithKey nl)
nmax = fmap (fst . fst) (IntMap.maxViewWithKey nl)
nodeToSharedSecondaryEdge :: Instance.List -> Node -> [Graph.Edge]
nodeToSharedSecondaryEdge il n = (,) <$> primaries <*> primaries
where primaries = map (Instance.pNode . flip Container.find il) $ sList n
filterValid :: List -> [Graph.Edge] -> [Graph.Edge]
filterValid nl = filter $ \(x,y) -> IntMap.member x nl && IntMap.member y nl
mkNodeGraph :: List -> Instance.List -> Maybe Graph.Graph
mkNodeGraph nl il =
liftM (`Graph.buildG` (filterValid nl . instancesToEdges $ il))
(nodesToBounds nl)
mkRebootNodeGraph :: List -> List -> Instance.List -> Maybe Graph.Graph
mkRebootNodeGraph allnodes nl il =
liftM (`Graph.buildG` filterValid nl edges) (nodesToBounds nl)
where
edges = instancesToEdges il `union`
(Container.elems allnodes >>= nodeToSharedSecondaryEdge il)
showField :: Node
-> String
-> String
showField t field =
case field of
"idx" -> printf "%4d" $ idx t
"name" -> alias t
"fqdn" -> name t
"status" -> case () of
_ | offline t -> "-"
| failN1 t -> "*"
| otherwise -> " "
"tmem" -> printf "%5.0f" $ tMem t
"nmem" -> printf "%5d" $ nMem t
"xmem" -> printf "%5d" $ xMem t
"fmem" -> printf "%5d" $ fMem t
"umem" -> printf "%5d" $ unallocatedMem t
"imem" -> printf "%5d" $ iMem t
"rmem" -> printf "%5d" $ rMem t
"amem" -> printf "%5d" $ availMem t
"tdsk" -> printf "%5.0f" $ tDsk t / 1024
"fdsk" -> printf "%5d" $ fDsk t `div` 1024
"tcpu" -> printf "%4.0f" $ tCpu t
"ucpu" -> printf "%4d" $ uCpu t
"pcnt" -> printf "%3d" $ length (pList t)
"scnt" -> printf "%3d" $ length (sList t)
"plist" -> show $ pList t
"slist" -> show $ sList t
"pfmem" -> printf "%6.4f" $ pMem t
"pfdsk" -> printf "%6.4f" $ pDsk t
"rcpu" -> printf "%5.2f" $ pCpu t
"cload" -> printf "%5.3f" uC
"mload" -> printf "%5.3f" uM
"dload" -> printf "%5.3f" uD
"nload" -> printf "%5.3f" uN
"ptags" -> intercalate "," . map (uncurry (printf "%s=%d")) .
Map.toList $ pTags t
"peermap" -> show $ peers t
"spindle_count" -> show $ tSpindles t
"hi_spindles" -> show $ hiSpindles t
"inst_spindles" -> show $ instSpindles t
_ -> T.unknownField
where
T.DynUtil { T.cpuWeight = uC, T.memWeight = uM,
T.dskWeight = uD, T.netWeight = uN } = utilLoad t
showHeader :: String -> (String, Bool)
showHeader field =
case field of
"idx" -> ("Index", True)
"name" -> ("Name", False)
"fqdn" -> ("Name", False)
"status" -> ("F", False)
"tmem" -> ("t_mem", True)
"nmem" -> ("n_mem", True)
"xmem" -> ("x_mem", True)
"fmem" -> ("f_mem", True)
"umem" -> ("u_mem", True)
"amem" -> ("a_mem", True)
"imem" -> ("i_mem", True)
"rmem" -> ("r_mem", True)
"tdsk" -> ("t_dsk", True)
"fdsk" -> ("f_dsk", True)
"tcpu" -> ("pcpu", True)
"ucpu" -> ("vcpu", True)
"pcnt" -> ("pcnt", True)
"scnt" -> ("scnt", True)
"plist" -> ("primaries", True)
"slist" -> ("secondaries", True)
"pfmem" -> ("p_fmem", True)
"pfdsk" -> ("p_fdsk", True)
"rcpu" -> ("r_cpu", True)
"cload" -> ("lCpu", True)
"mload" -> ("lMem", True)
"dload" -> ("lDsk", True)
"nload" -> ("lNet", True)
"ptags" -> ("PrimaryTags", False)
"peermap" -> ("PeerMap", False)
"spindle_count" -> ("NodeSpindles", True)
"hi_spindles" -> ("MaxSpindles", True)
"inst_spindles" -> ("InstSpindles", True)
_ -> (T.unknownField, False)
list :: [String] -> Node -> [String]
list fields t = map (showField t) fields
genOpSetOffline :: (MonadFail m) => Node -> Bool -> m OpCodes.OpCode
genOpSetOffline node offlineStatus = do
nodeName <- mkNonEmpty (name node)
return OpCodes.OpNodeSetParams
{ OpCodes.opNodeName = nodeName
, OpCodes.opNodeUuid = Nothing
, OpCodes.opForce = False
, OpCodes.opHvState = Nothing
, OpCodes.opDiskState = Nothing
, OpCodes.opMasterCandidate = Nothing
, OpCodes.opOffline = Just offlineStatus
, OpCodes.opDrained = Nothing
, OpCodes.opAutoPromote = False
, OpCodes.opMasterCapable = Nothing
, OpCodes.opVmCapable = Nothing
, OpCodes.opSecondaryIp = Nothing
, OpCodes.opgenericNdParams = Nothing
, OpCodes.opPowered = Nothing
}
genOobCommand :: (MonadFail m) => [Node] -> OobCommand -> m OpCodes.OpCode
genOobCommand nodes command = do
names <- mapM (mkNonEmpty . name) nodes
return OpCodes.OpOobCommand
{ OpCodes.opNodeNames = names
, OpCodes.opNodeUuids = Nothing
, OpCodes.opOobCommand = command
, OpCodes.opOobTimeout = C.oobTimeout
, OpCodes.opIgnoreStatus = False
, OpCodes.opPowerDelay = C.oobPowerDelay
}
genPowerOnOpCodes :: (MonadFail m) => [Node] -> m [OpCodes.OpCode]
genPowerOnOpCodes nodes = do
opSetParams <- mapM (`genOpSetOffline` False) nodes
oobCommand <- genOobCommand nodes OobPowerOn
return $ opSetParams ++ [oobCommand]
genPowerOffOpCodes :: (MonadFail m) => [Node] -> m [OpCodes.OpCode]
genPowerOffOpCodes nodes = do
opSetParams <- mapM (`genOpSetOffline` True) nodes
oobCommand <- genOobCommand nodes OobPowerOff
return $ opSetParams ++ [oobCommand]
genAddTagsOpCode :: Node -> [String] -> OpCodes.OpCode
genAddTagsOpCode node tags = OpCodes.OpTagsSet
{ OpCodes.opKind = TagKindNode
, OpCodes.opTagsList = tags
, OpCodes.opTagsGetName = Just $ name node
}
defaultFields :: [String]
defaultFields =
[ "status", "name", "tmem", "nmem", "imem", "xmem", "fmem", "umem"
, "rmem", "tdsk", "fdsk", "tcpu", "ucpu", "pcnt", "scnt"
, "pfmem", "pfdsk", "rcpu"
, "cload", "mload", "dload", "nload" ]
computeGroups :: [Node] -> [(T.Gdx, [Node])]
computeGroups nodes =
let nodes' = sortBy (comparing group) nodes
nodes'' = groupBy ((==) `on` group) nodes'
in map (\nl -> (group (head nl), nl)) nodes''