{-# LANGUAGE OverloadedStrings, QuasiQuotes, RecordWildCards #-} -- | /register handlers. module Handler.RegisterR where import Import import Data.List import Data.Maybe -- import Data.Text (Text) import qualified Data.Text as T import Safe import Handler.AddForm import Handler.Common import Handler.Utils import Hledger.Data import Hledger.Query import Hledger.Reports import Hledger.Utils import Hledger.Cli.CliOptions import Hledger.Web.WebOptions -- | The main journal/account register view, with accounts sidebar. getRegisterR :: Handler Html getRegisterR = do vd@VD{..} <- getViewData -- staticRootUrl <- (staticRoot . settings) <$> getYesod let -- injournal = isNothing inacct filtering = m /= Any -- title = "Transactions in "++a++s1++s2 title = T.unpack a++s1++s2 where (a,inclsubs) = fromMaybe ("all accounts",True) $ inAccount qopts s1 = if inclsubs then "" else " (excluding subaccounts)" s2 = if filtering then ", filtered" else "" maincontent = registerReportHtml opts vd $ accountTransactionsReport (reportopts_ $ cliopts_ opts) j m $ fromMaybe Any $ inAccountQuery qopts hledgerLayout vd "register" [hamlet|

#{title} ^{maincontent} |] postRegisterR :: Handler Html postRegisterR = postAddForm -- Generate html for an account register, including a balance chart and transaction list. registerReportHtml :: WebOpts -> ViewData -> TransactionsReport -> HtmlUrl AppRoute registerReportHtml opts vd r = [hamlet|
^{registerChartHtml $ transactionsReportByCommodity r} ^{registerItemsHtml opts vd r} |] -- Generate html for a transaction list from an "TransactionsReport". registerItemsHtml :: WebOpts -> ViewData -> TransactionsReport -> HtmlUrl AppRoute registerItemsHtml _ vd (balancelabel,items) = [hamlet|
Date Description To/From Account(s) Amount Out/In #{balancelabel'} $forall i <- numberTransactionsReportItems items ^{itemAsHtml vd i} |] where insomeacct = isJust $ inAccount $ qopts vd balancelabel' = if insomeacct then balancelabel else "Total" -- filtering = m /= Any itemAsHtml :: ViewData -> (Int, Bool, Bool, Bool, TransactionsReportItem) -> HtmlUrl AppRoute itemAsHtml VD{..} (n, newd, newm, _, (torig, tacct, split, acct, amt, bal)) = [hamlet| #{date} #{textElideRight 30 desc} #{elideRight 40 acct} $if showamt \#{mixedAmountAsHtml amt} #{mixedAmountAsHtml bal} |] where evenodd = if even n then "even" else "odd" :: String datetransition | newm = "newmonth" | newd = "newday" | otherwise = "" :: String (firstposting, date, desc) = (False, show $ tdate tacct, tdescription tacct) -- acctquery = (here, [("q", pack $ accountQuery acct)]) showamt = not split || not (isZeroMixedAmount amt) -- | Generate javascript/html for a register balance line chart based on -- the provided "TransactionsReportItem"s. -- registerChartHtml :: forall t (t1 :: * -> *) t2 t3 t4 t5. -- Data.Foldable.Foldable t1 => -- t1 (Transaction, t2, t3, t4, t5, MixedAmount) -- -> t -> Text.Blaze.Internal.HtmlM () registerChartHtml :: [(CommoditySymbol, (String, [TransactionsReportItem]))] -> HtmlUrl AppRoute registerChartHtml percommoditytxnreports = -- have to make sure plot is not called when our container (maincontent) -- is hidden, eg with add form toggled [hamlet|