{-# LANGUAGE FlexibleContexts #-} module Villefort.Util (getHeader ,makeRow ,makeTable ,D(..) ,unpackStringToDate ,getDay ,getDateD ,getDate ,total) where import Control.Monad.Reader (MonadReader,MonadIO,liftIO) import Villefort.Definitions (VConfig(..)) import Paths_Villefort (getDataFileName) import Data.List (intercalate) import Data.Time (Day(..),fromGregorian,getZonedTime) import Data.Time.Calendar.OrdinalDate (mondayStartWeek) import Data.List.Split as S (splitOn) -- | Returns header of Villefortx 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)) ++ "
" -- | toatals minutes on row total :: [[String]] -> Int total row = sum $ map (\x -> read $ x !! 1 :: Int) row -- | Date representation data D = D { year :: Int, month :: Int, day :: Int} deriving (Show) -- | Convert from string to Day datatype fromZonedTimeToDay :: String -> Day fromZonedTimeToDay x = fromGregorian (toInteger (year up) ) (month up ) (day up) where up = unpackStringToDate x -- | get Current local time getDate :: IO Day getDate = fromZonedTimeToDay <$> show <$> getZonedTime -- | get Local Date getDateD :: IO D getDateD = unpackStringToDate <$> show <$> getZonedTime -- | convert from String to internal Day representation unpackStringToDate :: [Char] -> D unpackStringToDate x = D (read (nums !! 0) :: Int) (read (nums !! 1) :: Int) (read (nums !! 2) :: Int) where nums = S.splitOn "-" $ take 10 x -- | Get local day of week as number getDay :: IO Int getDay = do z <- getDate return $ snd $mondayStartWeek z