-- | /journal handlers. module Handler.JournalR where import Import import Handler.Common import Handler.Post import Hledger.Data import Hledger.Query import Hledger.Reports import Hledger.Utils import Hledger.Cli.Options import Hledger.Web.Options -- | The formatted journal view, with sidebar. getJournalR :: Handler Html getJournalR = do vd@VD{..} <- getViewData let -- XXX like registerReportAsHtml inacct = inAccount qopts -- injournal = isNothing inacct filtering = m /= Any -- showlastcolumn = if injournal && not filtering then False else True title = case inacct of Nothing -> "General Journal"++s2 Just (a,inclsubs) -> "Transactions in "++a++s1++s2 where s1 = if inclsubs then "" else " (excluding subaccounts)" where s2 = if filtering then ", filtered" else "" maincontent = journalTransactionsReportAsHtml opts vd $ journalTransactionsReport (reportopts_ $ cliopts_ opts) j m hledgerLayout vd "journal" [hamlet| #{title} Add a transaction ^{maincontent} |] postJournalR :: Handler Html postJournalR = handlePost -- | Render a "TransactionsReport" as html for the formatted journal view. journalTransactionsReportAsHtml :: WebOpts -> ViewData -> TransactionsReport -> HtmlUrl AppRoute journalTransactionsReportAsHtml _ vd (_,items) = [hamlet| Date Description Account Amount $forall i <- numberTransactionsReportItems items ^{itemAsHtml vd i} |] where -- .#{datetransition} itemAsHtml :: ViewData -> (Int, Bool, Bool, Bool, TransactionsReportItem) -> HtmlUrl AppRoute itemAsHtml VD{..} (n, _, _, _, (t, _, split, _, amt, _)) = [hamlet| #{date} #{elideRight 60 desc} $if showamt \#{mixedAmountAsHtml amt} $forall p' <- tpostings t   #{elideAccountName 40 $ paccount p'} #{mixedAmountAsHtml $ pamount p'}   |] where evenodd = if even n then "even" else "odd" :: String -- datetransition | newm = "newmonth" -- | newd = "newday" -- | otherwise = "" :: String (firstposting, date, desc) = (False, show $ tdate t, tdescription t) -- acctquery = (here, [("q", pack $ accountQuery acct)]) showamt = not split || not (isZeroMixedAmount amt)