module Ganeti.HTools.Cluster.MetricsTH
( MetricComponent(..)
, declareStatistics
) where
import Data.List (partition)
import Data.Maybe (mapMaybe)
import Language.Haskell.TH
import Text.Printf (printf)
import qualified Ganeti.HTools.Node as Node
import Ganeti.Utils (printTable)
import Ganeti.Utils.Statistics
data MetricComponent = MetricComponent
{ name :: String
, weight :: Q Exp
, fromNode :: Q Exp
, fromNodeType :: Q Type
, statisticsType :: Q Type
, forOnlineNodes :: Bool
, optimalValue :: Maybe ExpQ
}
declareStatistics :: [MetricComponent] -> Q [Dec]
declareStatistics components = do
nodeValues <- nodeValuesDecl components
getNodeValues <- getNodeValuesDecl components
clusterStatistics <- clusterStatisticsDecl components
compClusterStatistics <- compClusterStatisticsDecl components
updateClusterStatistics <- updateClusterStatisticsDecl components
compCVfromStats <- compCVfromStatsDecl components
showClusterStatistics <- showClusterStatisticsDecl components
optimalCVScore <- optimalCVScoreDecl components
return $ nodeValues ++ getNodeValues ++ clusterStatistics ++
compClusterStatistics ++ updateClusterStatistics ++
compCVfromStats ++ showClusterStatistics ++
optimalCVScore
getVarStrictTypeQ :: (String, Q Type) -> VarStrictTypeQ
getVarStrictTypeQ (n, t) = do
t' <- t
return (mkName n, NotStrict, t')
nodeValuesDecl :: [MetricComponent] -> Q [Dec]
nodeValuesDecl components = do
let names = map (("nv_" ++ ) . name ) components
types = map fromNodeType components
strict_types <- mapM getVarStrictTypeQ $ zip names types
return [DataD [] (mkName "NodeValues") []
[RecC (mkName "NodeValues") strict_types] []]
clusterStatisticsDecl :: [MetricComponent] -> Q [Dec]
clusterStatisticsDecl components = do
let names = map (("cs_" ++ ) . name ) components
types = map statisticsType components
strict_types <- mapM getVarStrictTypeQ $ zip names types
return [DataD [] (mkName "ClusterStatistics") []
[RecC (mkName "ClusterStatistics") strict_types] []]
getNodeValuesDecl :: [MetricComponent] -> Q [Dec]
getNodeValuesDecl components = do
extract_functions <- mapM fromNode components
x <- newName "node"
node_t <- [t| Node.Node |]
let names = map (mkName . ("nv_" ++) . name) components
values = map (\f -> AppE f (VarE x)) extract_functions
body_exp = RecConE (mkName "NodeValues") $ zip names values
fname = mkName "getNodeValues"
nv_t = ConT $ mkName "NodeValues"
sig_d = SigD fname (ArrowT `AppT` node_t `AppT` nv_t)
fun_d = FunD fname [Clause [VarP x] (NormalB body_exp) []]
return [sig_d, fun_d]
appTwice :: Q Exp -> Q Exp -> Q Exp -> Q Exp
appTwice fun arg1 = appE $ appE fun arg1
getQNameExp :: String -> Q Exp -> Q (Name, Exp)
getQNameExp n e = do
e' <- e
return (mkName n, e')
compClusterStatisticsDecl :: [MetricComponent] -> Q [Dec]
compClusterStatisticsDecl components = do
nl_i <- newName "nl"
let splitted = appTwice [| partition |] [| Node.offline |] (varE nl_i)
(nl_off, nl_on) = (appE [| fst |] splitted, appE [| snd |] splitted)
(online, offline) = partition forOnlineNodes components
nv_f nm = varE . mkName $ "nv_" ++ nm
nvl_f = appTwice [| map |] (varE (mkName "getNodeValues"))
nv_field nm = appTwice [| map |] $ nv_f nm
cs_field nm nvl = appE [| calculate |] $ nv_field nm nvl
(online_names, offline_names) = (map name online, map name offline)
offline_f = map (\nm -> getQNameExp ("cs_" ++ nm) .
cs_field nm $ nvl_f nl_off) offline_names
online_f = map (\nm -> getQNameExp ("cs_" ++ nm) .
cs_field nm $ nvl_f nl_on ) online_names
body = recConE (mkName "ClusterStatistics") $ offline_f ++ online_f
cls_stat_t = conT $ mkName "ClusterStatistics"
fname = mkName "compClusterStatistics"
sig_d <- sigD fname ((arrowT `appT` [t| [Node.Node] |]) `appT` cls_stat_t)
fun_d <- funD fname [clause [varP nl_i] (normalB body) []]
return [sig_d, fun_d]
updateClusterStatisticsDecl :: [MetricComponent] -> Q [Dec]
updateClusterStatisticsDecl components = do
old_s <- newName "old_s"
n <- newName "n"
n' <- newName "n'"
let (online, offline) = partition forOnlineNodes components
pattern = [varP old_s, tupP [varP n, varP n']]
is_node_online = appE [| not . Node.offline |] $ varE n
get_nv nd = appE (varE $ mkName "getNodeValues") $ varE nd
nv_get_field nm nd = appE (varE . mkName $ "nv_" ++ nm) $ get_nv nd
cs_cur_field nm = appE (varE . mkName $ "cs_" ++ nm) $ varE old_s
update_field nm = appTwice (appE [| update |] $ cs_cur_field nm)
(nv_get_field nm n) (nv_get_field nm n')
(online_names, offline_names) = (map name online, map name offline)
offline_f = map (\nm -> getQNameExp ("cs_" ++ nm) $
cs_cur_field nm) offline_names
online_f = map (\nm -> getQNameExp ("cs_" ++ nm) $
update_field nm) online_names
body = condE is_node_online
(recConE (mkName "ClusterStatistics") $ offline_f ++ online_f)
(varE old_s)
fname = mkName "updateClusterStatistics"
cs_t = conT $ mkName "ClusterStatistics"
sig_d <- sigD fname ((arrowT `appT` cs_t) `appT`
((arrowT `appT` [t| (Node.Node, Node.Node) |]) `appT`
cs_t))
fun_d <- funD fname [clause pattern (normalB body) []]
return [sig_d, fun_d]
compCVfromStatsDecl :: [MetricComponent] -> Q [Dec]
compCVfromStatsDecl components = do
cs <- newName "cs"
let get_comp c = appE (varE . mkName $ "cs_" ++ name c) $ varE cs
get_val c = appE [| getValue |] $ get_comp c
term c = appTwice [| (*) :: Double -> Double -> Double |]
(get_val c) (weight c)
stat = appE [| sum :: [Double] -> Double |] . listE $ map term components
fname = mkName "compCVfromStats"
cs_t = conT $ mkName "ClusterStatistics"
sig_d <- sigD fname ((arrowT `appT` cs_t) `appT` [t| Double |])
fun_d <- funD fname [clause [varP cs] (normalB stat) []]
return [sig_d, fun_d]
showClusterStatisticsDecl :: [MetricComponent] -> Q [Dec]
showClusterStatisticsDecl components = do
lp <- newName "lp"
cs <- newName "cs"
let get_comp c = appE (varE . mkName $ "cs_" ++ name c) $ varE cs
get_val c = appE [| getValue |] $ get_comp c
format w h val = listE [ h
, appE [| printf "%.8f" |] val
, appE [| printf "x%.2f"|] w
]
print_line c = format (weight c) (litE . StringL $ name c) (get_val c)
header = [| [ "Field", "Value", "Weight" ] |]
printed = listE $ map print_line components
result = appTwice (appTwice [| printTable |] (varE lp) header)
printed [| False:repeat True |]
fname = mkName "showClusterStatistics"
cs_t = conT $ mkName "ClusterStatistics"
sig_d <- sigD fname ((arrowT `appT` [t| String |]) `appT`
((arrowT `appT` cs_t) `appT` [t| String |]))
fun_d <- funD fname [clause [varP lp, varP cs] (normalB result) []]
return [sig_d, fun_d]
optimalCVScoreDecl :: [MetricComponent] -> Q [Dec]
optimalCVScoreDecl components = do
nl <- newName "nl"
let stat =
foldl (addVal nl) [| 0 :: Double |] $ mapMaybe optimalValue components
fname = mkName "optimalCVScore"
sig_d <- sigD fname ((arrowT `appT` [t| Node.List |]) `appT` [t| Double |])
fun_d <- funD fname [clause [varP nl] (normalB stat) []]
return [sig_d, fun_d]
where
addVal :: Name -> ExpQ -> ExpQ -> ExpQ
addVal nl cur f = appTwice [| (+) :: Double -> Double -> Double |]
cur . appE f $ varE nl