aboutsummaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
authorSean Whitton <spwhitton@spwhitton.name>2015-03-21 19:06:08 +0900
committerSean Whitton <spwhitton@spwhitton.name>2015-03-21 19:06:08 +0900
commit6b57ba33b60fb9aef9b6b3a2553dbb2c2c5c14c0 (patch)
treed681e7479e88a8aaff290c378cb0bbfbf42087ef
parent9a1e75719481e68259e79b7bed6c6f500f0da86e (diff)
downloadsariulclocks-6b57ba33b60fb9aef9b6b3a2553dbb2c2c5c14c0.tar.gz
weeklyCron filled out
-rw-r--r--src/sariulccron.hs18
1 files changed, 17 insertions, 1 deletions
diff --git a/src/sariulccron.hs b/src/sariulccron.hs
index 3adaf5a..b58599d 100644
--- a/src/sariulccron.hs
+++ b/src/sariulccron.hs
@@ -1,8 +1,12 @@
{-# LANGUAGE OverloadedStrings #-}
+
+import Control.Applicative ((<$>))
import Control.Monad (liftM, when)
import Control.Monad.SariulClocks
import Control.Monad.Trans (liftIO)
import Data.Classes
+import Data.Function (on)
+import Data.List (sortBy)
import Data.Maybe (fromJust)
import Text.PrettyPrint.Boxes
import Types.Classes
@@ -12,7 +16,19 @@ import Utils.ScoresFile
--- meaty functions
weeklyCron :: ScoresList -> ScoresList
-weeklyCron scores = undefined
+weeklyCron scores = (resetTime . deductPoints 10) <$> take 3 sortedScores
+ ++ drop 3 sortedScores
+ where
+ sortedScores = sortBy (compare `on` (scoreTimeWasted . snd)) scores
+
+scoreTimeWasted :: Score -> Int
+scoreTimeWasted (Score _ x) = x
+
+deductPoints :: Int -> (Class, Score) -> (Class, Score)
+deductPoints n (c, Score x y) = (c, Score (x - n) y)
+
+resetTime :: (Class, Score) -> (Class, Score)
+resetTime (c, Score x _) = (c, Score x 0)
main :: IO ()
main = runSariulClocksIO $ do