summaryrefslogtreecommitdiff
path: root/Handler/Vacation.hs
blob: e6c95f9c5a458cd7dd07baf8257bb68b213ca157 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
{-# LANGUAGE TupleSections, OverloadedStrings #-}
module Handler.Vacation where

import Import hiding (get)
import Control.Monad (when, guard)
import Control.Monad.Trans.RWS.Lazy (ask, tell, get, put, execRWST)
import qualified Data.Text as T
import Data.Time.Clock (getCurrentTime, UTCTime, utctDay)
import Yesod.Auth (maybeAuth)
import PTO

getVacationR :: UserId -> Handler Html
getVacationR cid = do
    user <- runDB $ get404 cid
    ma <- maybeAuth
    today <- fmap utctDay (liftIO getCurrentTime)
    (e':es) <- runDB $ fmap (map entityVal) (selectList [EmploymentUser ==. cid] [])
    let twoyear = twoYearsFrom $ employmentStartDate e'
        username = userIdent user
        (currentyear, currentmonth) = monthOf today
        months = [2005 .. currentyear] >>= \ x -> [1 .. 12] >>= \ y -> guard ((x, y) < (currentyear, currentmonth)) >> return (x, y)
    (_, transacts') <- execRWST' (cid, twoyear) 0 $ mapM anotherMonth months
    let transacts = reverse $ map (fmap fromRational) transacts'
    defaultLayout $ do
        aDomId <- newIdent
        (setTitle . toHtml) ("Vacation report for " `T.append` username)
        $(widgetFile "vacationpage")
    where
        execRWST' = flip .  flip execRWST

-- anotherMonth :: UserId -> (Integer,Int) -> WriterT [Change]
anotherMonth (y,m) = do
    currentval <- get
    (u, twoyear) <- ask
    (plus, minus) <- lift . runDB $ monthlyTransactions u (y,m)
    when (plus > 0) (add plus)
    when (minus > 0) (subtract (toRational minus))
    when ((snd . monthOf) twoyear == m) kneecap
    where
        add x = get >>= \o -> tell [(show y ++ "-" ++ show m ++ ": adding " ++ show (fromRational x) ++ " hours", o + x)] >> put (o + x)
        subtract x = get >>= \o -> tell [(show y ++ "-" ++ show m ++ ": subtracting " ++ show (fromRational x) ++ " hours", o - x)] >> put (o - x)
	kneecap = get >>= \o -> when (o > 160) (tell [(show y ++ "-" ++ show m ++ ": over anniversary max, subtracting " ++ show (fromRational o - 160) ++ " hours", 160)] >> put 160)