{-# LANGUAGE TemplateHaskell, QuasiQuotes, OverloadedStrings #-} module Handlers where import Control.Applicative ((<$>)) --, (<*>)) import Data.Text(Text,pack,unpack) import System.FilePath (takeFileName) --()) import System.IO.Storage (putValue, getValue) import Text.Hamlet import Text.ParserCombinators.Parsec hiding (string) import Hledger.Cli.Balance import Hledger.Cli.Print import Hledger.Cli.Register import Hledger.Cli.Options hiding (value) import Hledger.Cli.Utils import Hledger.Cli.Version (version) import Hledger.Data hiding (insert, today) import App import Settings import StaticFiles ---------------------------------------------------------------------- -- handlers/views ---------------------------------------------------------------------- getRootR :: Handler RepHtml getRootR = redirect RedirectTemporary defaultroute where defaultroute = JournalR -- defaultLayout $ do -- h2id <- lift newIdent -- setTitle "hledger-web homepage" -- addWidget $(widgetFile "homepage") ---------------------------------------------------------------------- -- | A combined accounts and journal view. getJournalR :: Handler RepHtml getJournalR = do (a, p, opts, fspec, j, msg, here) <- getHandlerData today <- liftIO getCurrentDay -- app <- getYesod -- t <- liftIO $ getCurrentLocalTime let -- args = appArgs app -- fspec' = optsToFilterSpec opts args t sidecontent = balanceReportAsHtml opts td $ balanceReport opts fspec j maincontent = journalReportAsHtml opts td $ journalReport opts fspec j td = mktd{here=here, title="hledger journal", msg=msg, a=a, p=p, j=j, today=today} editform' = editform td hamletToRepHtml $ pageLayout td [hamlet| TemplateData -> BalanceReport -> Hamlet AppRoute balanceReportAsHtml _ td@TD{here=here,a=a,p=p} (items,total) = [hamlet| ^{accountsheading} $forall i <- items ^{itemAsHtml' i} #{mixedAmountAsHtml total} |] where accountsheading = [hamlet| ^{showmore} ^{showall}|] :: Hamlet AppRoute showmore = case (filteringaccts, items) of -- cunning parent account logic (True, ((acct, _, _, _):_)) -> let a' = if isAccountRegex a then a else acct a'' = accountNameToAccountRegex $ parentAccountName $ accountRegexToAccountName a' parenturl = (here, [("a",pack a''), ("p",pack p)]) in [hamlet| \ | # show more ↑ |] _ -> nulltemplate showall = if filteringaccts then [hamlet| \ | # show all |] else nulltemplate where allurl = (here, [("p",pack p)]) itemAsHtml' = itemAsHtml td itemAsHtml :: TemplateData -> BalanceReportItem -> Hamlet AppRoute itemAsHtml TD{p=p} (acct, adisplay, adepth, abal) = [hamlet| #{adisplay} #{mixedAmountAsHtml abal} |] where indent = preEscapedString $ concat $ replicate (2 * adepth) " " acctpat = accountNameToAccountRegex acct pparam = if null p then "" else "&p="++p accountNameToAccountRegex :: String -> String accountNameToAccountRegex "" = "" accountNameToAccountRegex a = printf "^%s(:|$)" a accountRegexToAccountName :: String -> String accountRegexToAccountName = gsubRegexPR "^\\^(.*?)\\(:\\|\\$\\)$" "\\1" isAccountRegex :: String -> Bool isAccountRegex s = take 1 s == "^" && (take 5 $ reverse s) == ")$|:(" ---------------------------------------------------------------------- -- | A basic journal view, like hledger print, with editing. getJournalOnlyR :: Handler RepHtml getJournalOnlyR = do (a, p, opts, fspec, j, msg, here) <- getHandlerData today <- liftIO getCurrentDay let td = mktd{here=here, title="hledger journal", msg=msg, a=a, p=p, j=j, today=today} editform' = editform td txns = journalReportAsHtml opts td $ journalReport opts fspec j hamletToRepHtml $ pageLayout td [hamlet| TemplateData -> JournalReport -> Hamlet AppRoute journalReportAsHtml _ td items = [hamlet| $forall i <- number items ^{itemAsHtml' i} |] where number = zip [1..] itemAsHtml' = itemAsHtml td itemAsHtml :: TemplateData -> (Int, JournalReportItem) -> Hamlet AppRoute itemAsHtml _ (n, t) = [hamlet|
 #{txn}
     |] where
       evenodd = if even n then "even" else "odd" :: String
       txn = trimnl $ showTransaction t where trimnl = reverse . dropWhile (=='\n') . reverse

addform :: TemplateData -> Hamlet AppRoute
addform td = [hamlet|