Skip to content
Snippets Groups Projects
Commit aa8d2e71 authored by Iustin Pop's avatar Iustin Pop
Browse files

Add loading and processing of utilisation data

This patch adds loading and processing the utilisation data during
instance moves. While the data is not yet used, it is correctly modified
by instance changes between nodes.

hbal has the new ‘-U’ command line argument for this. The format of the
file is simply instance name and the four stats, space-separated.
parent 4f83a560
No related branches found
No related tags found
No related merge requests found
...@@ -52,6 +52,7 @@ import qualified Ganeti.HTools.Node as Node ...@@ -52,6 +52,7 @@ import qualified Ganeti.HTools.Node as Node
import Ganeti.HTools.Types import Ganeti.HTools.Types
import Ganeti.HTools.CLI import Ganeti.HTools.CLI
import Ganeti.HTools.Utils (sepSplit, tryRead)
-- | Parse the environment and return the node\/instance names. -- | Parse the environment and return the node\/instance names.
-- --
...@@ -66,6 +67,20 @@ parseEnv () = do ...@@ -66,6 +67,20 @@ parseEnv () = do
wrapIO :: IO (Result a) -> IO (Result a) wrapIO :: IO (Result a) -> IO (Result a)
wrapIO = flip catch (return . Bad . show) wrapIO = flip catch (return . Bad . show)
parseUtilisation :: String -> Result (String, DynUtil)
parseUtilisation line =
let columns = sepSplit ' ' line
in case columns of
[name, cpu, mem, dsk, net] -> do
rcpu <- tryRead name cpu
rmem <- tryRead name mem
rdsk <- tryRead name dsk
rnet <- tryRead name net
let du = DynUtil { cpuWeight = rcpu, memWeight = rmem
, dskWeight = rdsk, netWeight = rnet }
return (name, du)
_ -> Bad $ "Cannot parse line " ++ line
-- | External tool data loader from a variety of sources. -- | External tool data loader from a variety of sources.
loadExternalData :: Options loadExternalData :: Options
-> IO (Node.List, Instance.List, String) -> IO (Node.List, Instance.List, String)
...@@ -89,6 +104,16 @@ loadExternalData opts = do ...@@ -89,6 +104,16 @@ loadExternalData opts = do
" files options should be given.") " files options should be given.")
exitWith $ ExitFailure 1 exitWith $ ExitFailure 1
util_contents <- (case optDynuFile opts of
Just path -> readFile path
Nothing -> return "")
let util_data = mapM parseUtilisation $ lines util_contents
util_data' <- (case util_data of
Ok x -> return x
Bad y -> do
hPutStrLn stderr ("Error: can't parse utilisation" ++
" data: " ++ show y)
exitWith $ ExitFailure 1)
input_data <- input_data <-
case () of case () of
_ | setRapi -> _ | setRapi ->
...@@ -101,7 +126,7 @@ loadExternalData opts = do ...@@ -101,7 +126,7 @@ loadExternalData opts = do
| setSim -> Simu.loadData $ fromJust simdata | setSim -> Simu.loadData $ fromJust simdata
| otherwise -> wrapIO $ Text.loadData nodef instf | otherwise -> wrapIO $ Text.loadData nodef instf
let ldresult = input_data >>= Loader.mergeData let ldresult = input_data >>= Loader.mergeData util_data'
(loaded_nl, il, csf) <- (loaded_nl, il, csf) <-
(case ldresult of (case ldresult of
Ok x -> return x Ok x -> return x
......
...@@ -110,7 +110,7 @@ parseData body = do ...@@ -110,7 +110,7 @@ parseData body = do
let idata = fromJSObject ilist let idata = fromJSObject ilist
iobj <- mapM (\(x,y) -> asJSObject y >>= parseInstance ktn x) idata iobj <- mapM (\(x,y) -> asJSObject y >>= parseInstance ktn x) idata
let (kti, il) = assignIndices iobj let (kti, il) = assignIndices iobj
(map_n, map_i, csf) <- mergeData (nl, il) (map_n, map_i, csf) <- mergeData [] (nl, il)
req_nodes <- fromObj "required_nodes" request req_nodes <- fromObj "required_nodes" request
optype <- fromObj "type" request optype <- fromObj "type" request
rqtype <- rqtype <-
......
...@@ -37,6 +37,7 @@ module Ganeti.HTools.Loader ...@@ -37,6 +37,7 @@ module Ganeti.HTools.Loader
, Request(..) , Request(..)
) where ) where
import Control.Monad (foldM)
import Data.Function (on) import Data.Function (on)
import Data.List import Data.List
import Data.Maybe (fromJust) import Data.Maybe (fromJust)
...@@ -96,9 +97,9 @@ assocEqual = (==) `on` fst ...@@ -96,9 +97,9 @@ assocEqual = (==) `on` fst
-- | For each instance, add its index to its primary and secondary nodes. -- | For each instance, add its index to its primary and secondary nodes.
fixNodes :: [(Ndx, Node.Node)] fixNodes :: [(Ndx, Node.Node)]
-> (Idx, Instance.Instance) -> Instance.Instance
-> [(Ndx, Node.Node)] -> [(Ndx, Node.Node)]
fixNodes accu (_, inst) = fixNodes accu inst =
let let
pdx = Instance.pNode inst pdx = Instance.pNode inst
sdx = Instance.sNode inst sdx = Instance.sNode inst
...@@ -130,15 +131,21 @@ stripSuffix sflen name = take (length name - sflen) name ...@@ -130,15 +131,21 @@ stripSuffix sflen name = take (length name - sflen) name
-- | Initializer function that loads the data from a node and instance -- | Initializer function that loads the data from a node and instance
-- list and massages it into the correct format. -- list and massages it into the correct format.
mergeData :: (Node.AssocList, mergeData :: [(String, DynUtil)] -- ^ Instance utilisation data
-> (Node.AssocList,
Instance.AssocList) -- ^ Data from either Text.loadData Instance.AssocList) -- ^ Data from either Text.loadData
-- or Rapi.loadData -- or Rapi.loadData
-> Result (Node.List, Instance.List, String) -> Result (Node.List, Instance.List, String)
mergeData (nl, il) = do mergeData um (nl, il) = do
let let il2 = Container.fromAssocList il
nl2 = foldl' fixNodes nl il il3 <- foldM (\im (name, n_util) -> do
il3 = Container.fromAssocList il idx <- Container.findByName im name
nl3 = Container.fromAssocList let inst = Container.find idx im
new_i = inst { Instance.util = n_util }
return $ Container.add idx new_i im
) il2 um
let nl2 = foldl' fixNodes nl (Container.elems il3)
let nl3 = Container.fromAssocList
(map (\ (k, v) -> (k, Node.buildPeers v il3)) nl2) (map (\ (k, v) -> (k, Node.buildPeers v il3)) nl2)
node_names = map Node.name $ Container.elems nl3 node_names = map Node.name $ Container.elems nl3
inst_names = map Instance.name $ Container.elems il3 inst_names = map Instance.name $ Container.elems il3
......
...@@ -26,13 +26,7 @@ Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA ...@@ -26,13 +26,7 @@ Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
-} -}
module Ganeti.HTools.Node module Ganeti.HTools.Node
( Node(failN1, name, idx, ( Node(..)
tMem, nMem, fMem, rMem, xMem,
tDsk, fDsk,
tCpu, uCpu,
pMem, pDsk, pRem, pCpu,
mDsk, mCpu, loDsk, hiCpu,
pList, sList, offline)
, List , List
-- * Constructor -- * Constructor
, create , create
...@@ -217,16 +211,22 @@ buildPeers t il = ...@@ -217,16 +211,22 @@ buildPeers t il =
in t {peers=pmap, failN1 = new_failN1, rMem = new_rmem, pRem = new_prem} in t {peers=pmap, failN1 = new_failN1, rMem = new_rmem, pRem = new_prem}
-- | Assigns an instance to a node as primary and update the used VCPU -- | Assigns an instance to a node as primary and update the used VCPU
-- count. -- count and utilisation data.
setPri :: Node -> Instance.Instance -> Node setPri :: Node -> Instance.Instance -> Node
setPri t inst = t { pList = (Instance.idx inst):pList t setPri t inst = t { pList = Instance.idx inst:pList t
, uCpu = new_count , uCpu = new_count
, pCpu = fromIntegral new_count / tCpu t } , pCpu = fromIntegral new_count / tCpu t
, utilLoad = utilLoad t `T.addUtil` Instance.util inst
}
where new_count = uCpu t + Instance.vcpus inst where new_count = uCpu t + Instance.vcpus inst
-- | Assigns an instance to a node as secondary without other updates. -- | Assigns an instance to a node as secondary without other updates.
setSec :: Node -> Instance.Instance -> Node setSec :: Node -> Instance.Instance -> Node
setSec t inst = t { sList = (Instance.idx inst):sList t } setSec t inst = t { sList = Instance.idx inst:sList t
, utilLoad = old_load { T.dskWeight = T.dskWeight old_load +
T.dskWeight (Instance.util inst) }
}
where old_load = utilLoad t
-- * Update functions -- * Update functions
...@@ -250,9 +250,10 @@ removePri t inst = ...@@ -250,9 +250,10 @@ removePri t inst =
new_failn1 = new_mem <= rMem t new_failn1 = new_mem <= rMem t
new_ucpu = uCpu t - Instance.vcpus inst new_ucpu = uCpu t - Instance.vcpus inst
new_rcpu = fromIntegral new_ucpu / tCpu t new_rcpu = fromIntegral new_ucpu / tCpu t
new_load = utilLoad t `T.subUtil` Instance.util inst
in t {pList = new_plist, fMem = new_mem, fDsk = new_dsk, in t {pList = new_plist, fMem = new_mem, fDsk = new_dsk,
failN1 = new_failn1, pMem = new_mp, pDsk = new_dp, failN1 = new_failn1, pMem = new_mp, pDsk = new_dp,
uCpu = new_ucpu, pCpu = new_rcpu} uCpu = new_ucpu, pCpu = new_rcpu, utilLoad = new_load}
-- | Removes a secondary instance. -- | Removes a secondary instance.
removeSec :: Node -> Instance.Instance -> Node removeSec :: Node -> Instance.Instance -> Node
...@@ -273,9 +274,12 @@ removeSec t inst = ...@@ -273,9 +274,12 @@ removeSec t inst =
new_prem = fromIntegral new_rmem / tMem t new_prem = fromIntegral new_rmem / tMem t
new_failn1 = fMem t <= new_rmem new_failn1 = fMem t <= new_rmem
new_dp = fromIntegral new_dsk / tDsk t new_dp = fromIntegral new_dsk / tDsk t
old_load = utilLoad t
new_load = old_load { T.dskWeight = T.dskWeight old_load -
T.dskWeight (Instance.util inst) }
in t {sList = new_slist, fDsk = new_dsk, peers = new_peers, in t {sList = new_slist, fDsk = new_dsk, peers = new_peers,
failN1 = new_failn1, rMem = new_rmem, pDsk = new_dp, failN1 = new_failn1, rMem = new_rmem, pDsk = new_dp,
pRem = new_prem} pRem = new_prem, utilLoad = new_load}
-- | Adds a primary instance. -- | Adds a primary instance.
addPri :: Node -> Instance.Instance -> T.OpResult Node addPri :: Node -> Instance.Instance -> T.OpResult Node
...@@ -288,6 +292,7 @@ addPri t inst = ...@@ -288,6 +292,7 @@ addPri t inst =
new_pcpu = fromIntegral new_ucpu / tCpu t new_pcpu = fromIntegral new_ucpu / tCpu t
new_dp = fromIntegral new_dsk / tDsk t new_dp = fromIntegral new_dsk / tDsk t
l_cpu = mCpu t l_cpu = mCpu t
new_load = utilLoad t `T.addUtil` Instance.util inst
in if new_mem <= 0 then T.OpFail T.FailMem in if new_mem <= 0 then T.OpFail T.FailMem
else if new_dsk <= 0 || mDsk t > new_dp then T.OpFail T.FailDisk else if new_dsk <= 0 || mDsk t > new_dp then T.OpFail T.FailDisk
else if new_failn1 && not (failN1 t) then T.OpFail T.FailMem else if new_failn1 && not (failN1 t) then T.OpFail T.FailMem
...@@ -297,7 +302,7 @@ addPri t inst = ...@@ -297,7 +302,7 @@ addPri t inst =
new_mp = fromIntegral new_mem / tMem t new_mp = fromIntegral new_mem / tMem t
r = t { pList = new_plist, fMem = new_mem, fDsk = new_dsk, r = t { pList = new_plist, fMem = new_mem, fDsk = new_dsk,
failN1 = new_failn1, pMem = new_mp, pDsk = new_dp, failN1 = new_failn1, pMem = new_mp, pDsk = new_dp,
uCpu = new_ucpu, pCpu = new_pcpu } uCpu = new_ucpu, pCpu = new_pcpu, utilLoad = new_load }
in T.OpGood r in T.OpGood r
-- | Adds a secondary instance. -- | Adds a secondary instance.
...@@ -313,13 +318,16 @@ addSec t inst pdx = ...@@ -313,13 +318,16 @@ addSec t inst pdx =
new_prem = fromIntegral new_rmem / tMem t new_prem = fromIntegral new_rmem / tMem t
new_failn1 = old_mem <= new_rmem new_failn1 = old_mem <= new_rmem
new_dp = fromIntegral new_dsk / tDsk t new_dp = fromIntegral new_dsk / tDsk t
old_load = utilLoad t
new_load = old_load { T.dskWeight = T.dskWeight old_load +
T.dskWeight (Instance.util inst) }
in if new_dsk <= 0 || mDsk t > new_dp then T.OpFail T.FailDisk in if new_dsk <= 0 || mDsk t > new_dp then T.OpFail T.FailDisk
else if new_failn1 && not (failN1 t) then T.OpFail T.FailMem else if new_failn1 && not (failN1 t) then T.OpFail T.FailMem
else let new_slist = iname:sList t else let new_slist = iname:sList t
r = t { sList = new_slist, fDsk = new_dsk, r = t { sList = new_slist, fDsk = new_dsk,
peers = new_peers, failN1 = new_failn1, peers = new_peers, failN1 = new_failn1,
rMem = new_rmem, pDsk = new_dp, rMem = new_rmem, pDsk = new_dp,
pRem = new_prem } pRem = new_prem, utilLoad = new_load }
in T.OpGood r in T.OpGood r
-- * Stats functions -- * Stats functions
......
...@@ -72,6 +72,7 @@ options = ...@@ -72,6 +72,7 @@ options =
, oMaxCpu , oMaxCpu
, oMinDisk , oMinDisk
, oDiskMoves , oDiskMoves
, oDynuFile
, oShowVer , oShowVer
, oShowHelp , oShowHelp
] ]
......
...@@ -135,7 +135,7 @@ main = do ...@@ -135,7 +135,7 @@ main = do
printf "%-*s " nlen name printf "%-*s " nlen name
hFlush stdout hFlush stdout
input_data <- Rapi.loadData name input_data <- Rapi.loadData name
let ldresult = input_data >>= Loader.mergeData let ldresult = input_data >>= Loader.mergeData []
(case ldresult of (case ldresult of
Bad err -> printf "\nError: failed to load data. \ Bad err -> printf "\nError: failed to load data. \
\Details:\n%s\n" err \Details:\n%s\n" err
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment