hledger/hledger-web/Handler/RegisterR.hs
Simon Michael 90c9735b7a lib: textification: descriptions & codes
Slightly higher (with small files) and lower (with large files) maximum
residency, and slightly quicker for all.

hledger -f data/100x100x10.journal stats
<<ghc: 42858472 bytes, 84 GCs, 193712/269608 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.015 elapsed), 0.016 MUT (0.042 elapsed), 0.011 GC (0.119 elapsed) :ghc>>
<<ghc: 42891776 bytes, 84 GCs, 190816/260920 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.004 elapsed), 0.017 MUT (0.025 elapsed), 0.010 GC (0.015 elapsed) :ghc>>

hledger -f data/1000x1000x10.journal stats
<<ghc: 349575240 bytes, 681 GCs, 1396425/4091680 avg/max bytes residency (7 samples), 11M in use, 0.000 INIT (0.000 elapsed), 0.137 MUT (0.146 elapsed), 0.050 GC (0.057 elapsed) :ghc>>
<<ghc: 349927568 bytes, 681 GCs, 1397825/4097248 avg/max bytes residency (7 samples), 11M in use, 0.000 INIT (0.000 elapsed), 0.126 MUT (0.133 elapsed), 0.050 GC (0.057 elapsed) :ghc>>

hledger -f data/10000x1000x10.journal stats
<<ghc: 3424029496 bytes, 6658 GCs, 11403141/41077288 avg/max bytes residency (11 samples), 111M in use, 0.000 INIT (0.000 elapsed), 1.278 MUT (1.310 elapsed), 0.493 GC (0.546 elapsed) :ghc>>
<<ghc: 3427418064 bytes, 6665 GCs, 11127869/37790168 avg/max bytes residency (11 samples), 109M in use, 0.000 INIT (0.001 elapsed), 1.212 MUT (1.229 elapsed), 0.466 GC (0.519 elapsed) :ghc>>

hledger -f data/100000x1000x10.journal stats
<<ghc: 34306546248 bytes, 66727 GCs, 77030638/414617944 avg/max bytes residency (14 samples), 1012M in use, 0.000 INIT (0.000 elapsed), 12.965 MUT (13.164 elapsed), 4.771 GC (5.447 elapsed) :ghc>>
<<ghc: 34340246056 bytes, 66779 GCs, 76983178/416011480 avg/max bytes residency (14 samples), 1011M in use, 0.000 INIT (0.008 elapsed), 12.666 MUT (12.836 elapsed), 4.595 GC (5.175 elapsed) :ghc>>
2016-05-24 19:00:58 -07:00

179 lines
6.7 KiB
Haskell

{-# 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|
<h2#contenttitle>#{title}
<!-- p>Transactions affecting this account, with running balance. -->
^{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|
<table.registerreport>
<tr.headings>
<th.date style="text-align:left;">
Date
<span .glyphicon .glyphicon-chevron-up>
<th.description style="text-align:left;">Description
<th.account style="text-align:left;">To/From Account(s)
<th.amount style="text-align:right; white-space:normal;">Amount Out/In
<th.balance style="text-align:right; white-space:normal;">#{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|
<tr ##{tindex torig} .item.#{evenodd}.#{firstposting}.#{datetransition} title="#{show torig}" style="vertical-align:top;">
<td.date>
<a href="@{JournalR}##{tindex torig}">#{date}
<td.description title="#{show torig}">#{textElideRight 30 desc}
<td.account>#{elideRight 40 acct}
<td.amount style="text-align:right; white-space:nowrap;">
$if showamt
\#{mixedAmountAsHtml amt}
<td.balance style="text-align:right;">#{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|
<label#register-chart-label style=""><br>
<div#register-chart style="width:85%; height:150px; margin-bottom:1em; display:block;">
<script type=text/javascript>
\$(document).ready(function() {
var $chartdiv = $('#register-chart');
if ($chartdiv.is(':visible')) {
\$('#register-chart-label').text('#{charttitle}');
var seriesData = [
$forall (c,(_,items)) <- percommoditytxnreports
/* we render each commodity using two series:
* one with extra data points added to show a stepped balance line */
{
data: [
$forall i <- reverse items
[
#{dayToJsTimestamp $ triDate i},
#{simpleMixedAmountQuantity $ triCommodityBalance c i}
],
/* [] */
],
label: '#{shownull $ T.unpack c}',
color: #{colorForCommodity c},
lines: {
show: true,
steps: true,
},
points: {
show: false,
},
clickable: false,
hoverable: false,
},
/* and one with the original data, showing one clickable, hoverable point per transaction */
{
data: [
$forall i <- reverse items
[
#{dayToJsTimestamp $ triDate i},
#{simpleMixedAmountQuantity $ triCommodityBalance c i},
'#{showMixedAmountWithZeroCommodity $ triCommodityAmount c i}',
'#{showMixedAmountWithZeroCommodity $ triCommodityBalance c i}',
'#{concat $ intersperse "\\n" $ lines $ show $ triOrigTransaction i}',
#{tindex $ triOrigTransaction i}
],
/* [] */
],
label: '',
color: #{colorForCommodity c},
lines: {
show: false,
},
points: {
show: true,
},
},
]
var plot = registerChart($chartdiv, seriesData);
\$chartdiv.bind("plotclick", registerChartClick);
};
});
|]
-- [#{dayToJsTimestamp $ ltrace "\ndate" $ triDate i}, #{ltrace "balancequantity" $ simpleMixedAmountQuantity $ triCommodityBalance c i}, '#{ltrace "balance" $ show $ triCommodityBalance c i}, '#{ltrace "amount" $ show $ triCommodityAmount c i}''],
where
charttitle = case maybe "" (fst.snd) $ headMay percommoditytxnreports
of "" -> ""
s -> s++":"
colorForCommodity = fromMaybe 0 . flip lookup commoditiesIndex
commoditiesIndex = zip (map fst percommoditytxnreports) [0..] :: [(CommoditySymbol,Int)]
simpleMixedAmountQuantity = maybe 0 aquantity . headMay . amounts
shownull c = if null c then " " else c