{-# LANGUAGE FlexibleContexts #-} module Villefort.Util where import Control.Monad.Reader import Villefort.Definitions import Paths_Villefort import Data.List getHeader :: (MonadReader VConfig m, MonadIO m) => m String getHeader = do headerPath <- liftIO $ getDataFileName "templates/header" liftIO $ readFile headerPath -- | Helper function to generate row of table makeRow :: [String] -> String makeRow x = " " ++ (intercalate " " x )++ " " -- | Generate Table makeTable ::[String] -> [[String]] -> String makeTable tableData stats = " " ++ "" ++ ( makeRow tableData) ++ "" ++ (mconcat (map makeRow stats)) ++ "
" total :: [[String]] -> Int total row = sum $ map (\x -> read $ x !! 1 :: Int) row