aboutsummaryrefslogtreecommitdiffhomepage
path: root/src/sariulccron.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/sariulccron.hs')
-rw-r--r--src/sariulccron.hs56
1 files changed, 41 insertions, 15 deletions
diff --git a/src/sariulccron.hs b/src/sariulccron.hs
index 87b5e30..d36258e 100644
--- a/src/sariulccron.hs
+++ b/src/sariulccron.hs
@@ -1,23 +1,49 @@
--- import Control.Monad.SariulClocks
-import Utils.ScoresFile
-import Types.Scores
-import Types.Classes
-import Control.Monad (liftM, when)
-import Text.PrettyPrint.Boxes
+{-# LANGUAGE OverloadedStrings #-}
+import Control.Monad (liftM, when)
+import Control.Monad.SariulClocks
+import Control.Monad.Trans (liftIO)
+import Data.Classes
+import Data.Maybe (fromJust)
+import Text.PrettyPrint.Boxes
+import Types.Classes
+import Types.Scores
+import Utils.ScoresFile
-scoresBox :: ScoresList -> Box
-scoresBox = undefined
+--- meaty functions
weeklyCron :: ScoresList -> ScoresList
weeklyCron scores = undefined
--- main :: IO ()
--- main = runSariulClocksIO $ do
--- scores <- readScoresFile
--- when (isJust scores) $ do
--- modifyScores weeklyCron
--- shouldModify <- liftM (((/=) scores) . Just) getScores
--- when shouldModify writeScoresFile
+main :: IO ()
+main = runSariulClocksIO $ do
+ scores <- readScoresFile
+ when (isJust scores) $ do
+ modifyScores weeklyCron
+ shouldModify <- liftM (((/=) scores) . Just) getScores
+ liftIO $ putStrLn "Scores before:\n"
+ liftIO $ putStrLn . ppScores $ fromJust scores
+ liftIO $ putStrLn "Scores after:\n"
+ scores' <- getScores
+ liftIO $ putStrLn . ppScores $ scores'
+ when shouldModify writeScoresFile
+
+--- utility functions
+
+ppScores :: ScoresList -> String
+ppScores x = render $
+ hsep 3 center1 [ alignHoriz center2 7 "Class"
+ , alignHoriz center1 7 "Points"
+ , alignHoriz center1 12 "Time wasted"]
+ // "--------------------------------"
+ // foldr step nullBox x
+ where
+ step b bs = classBox b // bs
+
+classBox :: (Class, Score) -> Box
+classBox (c, (Score x y)) = hsep 3 left
+ [ alignHoriz center1 7 $ (text . show) c
+ , alignHoriz center1 7 $ (text . show) x
+ , alignHoriz center1 12 $ (text . show) y]
isJust :: Maybe a -> Bool
isJust (Just _) = True