lib: Remove unused label on TranspactionReport and AccountTransactionsReport.
This commit is contained in:
parent
5752f1c5cb
commit
7e44b89bb4
@ -65,10 +65,7 @@ import Hledger.Utils
|
|||||||
-- posts to the current account), most recent first.
|
-- posts to the current account), most recent first.
|
||||||
-- Reporting intervals are currently ignored.
|
-- Reporting intervals are currently ignored.
|
||||||
--
|
--
|
||||||
type AccountTransactionsReport =
|
type AccountTransactionsReport = [AccountTransactionsReportItem] -- line items, one per transaction
|
||||||
(String -- label for the balance column, eg "balance" or "total"
|
|
||||||
,[AccountTransactionsReportItem] -- line items, one per transaction
|
|
||||||
)
|
|
||||||
|
|
||||||
type AccountTransactionsReportItem =
|
type AccountTransactionsReportItem =
|
||||||
(
|
(
|
||||||
@ -80,11 +77,8 @@ type AccountTransactionsReportItem =
|
|||||||
,MixedAmount -- the register's running total or the current account(s)'s historical balance, after this transaction
|
,MixedAmount -- the register's running total or the current account(s)'s historical balance, after this transaction
|
||||||
)
|
)
|
||||||
|
|
||||||
totallabel = "Period Total"
|
|
||||||
balancelabel = "Historical Total"
|
|
||||||
|
|
||||||
accountTransactionsReport :: ReportSpec -> Journal -> Query -> Query -> AccountTransactionsReport
|
accountTransactionsReport :: ReportSpec -> Journal -> Query -> Query -> AccountTransactionsReport
|
||||||
accountTransactionsReport rspec@ReportSpec{rsOpts=ropts} j reportq thisacctq = (label, items)
|
accountTransactionsReport rspec@ReportSpec{rsOpts=ropts} j reportq thisacctq = items
|
||||||
where
|
where
|
||||||
-- a depth limit should not affect the account transactions report
|
-- a depth limit should not affect the account transactions report
|
||||||
-- seems unnecessary for some reason XXX
|
-- seems unnecessary for some reason XXX
|
||||||
@ -130,9 +124,9 @@ accountTransactionsReport rspec@ReportSpec{rsOpts=ropts} j reportq thisacctq = (
|
|||||||
ptraceAtWith 5 (("ts5:\n"++).pshowTransactions) $
|
ptraceAtWith 5 (("ts5:\n"++).pshowTransactions) $
|
||||||
sortBy (comparing (transactionRegisterDate reportq' thisacctq)) ts4
|
sortBy (comparing (transactionRegisterDate reportq' thisacctq)) ts4
|
||||||
|
|
||||||
(startbal,label)
|
startbal
|
||||||
| balancetype_ ropts == HistoricalBalance = (sumPostings priorps, balancelabel)
|
| balancetype_ ropts == HistoricalBalance = sumPostings priorps
|
||||||
| otherwise = (nullmixedamt, totallabel)
|
| otherwise = nullmixedamt
|
||||||
where
|
where
|
||||||
priorps = dbg5 "priorps" $
|
priorps = dbg5 "priorps" $
|
||||||
filter (matchesPosting
|
filter (matchesPosting
|
||||||
|
|||||||
@ -40,9 +40,7 @@ import Hledger.Utils
|
|||||||
-- them) with or without a notion of current account(s).
|
-- them) with or without a notion of current account(s).
|
||||||
-- Two kinds of report use this data structure, see transactionsReport
|
-- Two kinds of report use this data structure, see transactionsReport
|
||||||
-- and accountTransactionsReport below for details.
|
-- and accountTransactionsReport below for details.
|
||||||
type TransactionsReport = (String -- label for the balance column, eg "balance" or "total"
|
type TransactionsReport = [TransactionsReportItem] -- line items, one per transaction
|
||||||
,[TransactionsReportItem] -- line items, one per transaction
|
|
||||||
)
|
|
||||||
type TransactionsReportItem = (Transaction -- the original journal transaction, unmodified
|
type TransactionsReportItem = (Transaction -- the original journal transaction, unmodified
|
||||||
,Transaction -- the transaction as seen from a particular account, with postings maybe filtered
|
,Transaction -- the transaction as seen from a particular account, with postings maybe filtered
|
||||||
,Bool -- is this a split, ie more than one other account posting
|
,Bool -- is this a split, ie more than one other account posting
|
||||||
@ -60,14 +58,12 @@ triBalance (_,_,_,_,_,a) = a
|
|||||||
triCommodityAmount c = filterMixedAmountByCommodity c . triAmount
|
triCommodityAmount c = filterMixedAmountByCommodity c . triAmount
|
||||||
triCommodityBalance c = filterMixedAmountByCommodity c . triBalance
|
triCommodityBalance c = filterMixedAmountByCommodity c . triBalance
|
||||||
|
|
||||||
totallabel = "Period Total"
|
|
||||||
|
|
||||||
-- | Select transactions from the whole journal. This is similar to a
|
-- | Select transactions from the whole journal. This is similar to a
|
||||||
-- "postingsReport" except with transaction-based report items which
|
-- "postingsReport" except with transaction-based report items which
|
||||||
-- are ordered most recent first. XXX Or an EntriesReport - use that instead ?
|
-- are ordered most recent first. XXX Or an EntriesReport - use that instead ?
|
||||||
-- This is used by hledger-web's journal view.
|
-- This is used by hledger-web's journal view.
|
||||||
transactionsReport :: ReportOpts -> Journal -> Query -> TransactionsReport
|
transactionsReport :: ReportOpts -> Journal -> Query -> TransactionsReport
|
||||||
transactionsReport opts j q = (totallabel, items)
|
transactionsReport opts j q = items
|
||||||
where
|
where
|
||||||
-- XXX items' first element should be the full transaction with all postings
|
-- XXX items' first element should be the full transaction with all postings
|
||||||
items = reverse $ accountTransactionsReportItems q None nullmixedamt id ts
|
items = reverse $ accountTransactionsReportItems q None nullmixedamt id ts
|
||||||
@ -80,15 +76,14 @@ transactionsReportByCommodity :: TransactionsReport -> [(CommoditySymbol, Transa
|
|||||||
transactionsReportByCommodity tr =
|
transactionsReportByCommodity tr =
|
||||||
[(c, filterTransactionsReportByCommodity c tr) | c <- transactionsReportCommodities tr]
|
[(c, filterTransactionsReportByCommodity c tr) | c <- transactionsReportCommodities tr]
|
||||||
where
|
where
|
||||||
transactionsReportCommodities (_,items) =
|
transactionsReportCommodities = nubSort . map acommodity . concatMap (amounts . triAmount)
|
||||||
nubSort . map acommodity $ concatMap (amounts . triAmount) items
|
|
||||||
|
|
||||||
-- Remove transaction report items and item amount (and running
|
-- Remove transaction report items and item amount (and running
|
||||||
-- balance amount) components that don't involve the specified
|
-- balance amount) components that don't involve the specified
|
||||||
-- commodity. Other item fields such as the transaction are left unchanged.
|
-- commodity. Other item fields such as the transaction are left unchanged.
|
||||||
filterTransactionsReportByCommodity :: CommoditySymbol -> TransactionsReport -> TransactionsReport
|
filterTransactionsReportByCommodity :: CommoditySymbol -> TransactionsReport -> TransactionsReport
|
||||||
filterTransactionsReportByCommodity c (label,items) =
|
filterTransactionsReportByCommodity c =
|
||||||
(label, fixTransactionsReportItemBalances $ concat [filterTransactionsReportItemByCommodity c i | i <- items])
|
fixTransactionsReportItemBalances . concatMap (filterTransactionsReportItemByCommodity c)
|
||||||
where
|
where
|
||||||
filterTransactionsReportItemByCommodity c (t,t2,s,o,a,bal)
|
filterTransactionsReportItemByCommodity c (t,t2,s,o,a,bal)
|
||||||
| c `elem` cs = [item']
|
| c `elem` cs = [item']
|
||||||
|
|||||||
@ -79,7 +79,7 @@ rsInit d reset ui@UIState{aopts=_uopts@UIOpts{cliopts_=CliOpts{reportspec_=rspec
|
|||||||
,Not generatedTransactionTag
|
,Not generatedTransactionTag
|
||||||
]
|
]
|
||||||
|
|
||||||
(_label,items) = accountTransactionsReport rspec' j q thisacctq
|
items = accountTransactionsReport rspec' j q thisacctq
|
||||||
items' = (if empty_ ropts then id else filter (not . mixedAmountLooksZero . fifth6)) $ -- without --empty, exclude no-change txns
|
items' = (if empty_ ropts then id else filter (not . mixedAmountLooksZero . fifth6)) $ -- without --empty, exclude no-change txns
|
||||||
reverse -- most recent last
|
reverse -- most recent last
|
||||||
items
|
items
|
||||||
|
|||||||
@ -208,7 +208,7 @@ regenerateTransactions rspec j s acct i ui =
|
|||||||
let
|
let
|
||||||
q = filterQuery (not . queryIsDepth) $ rsQuery rspec
|
q = filterQuery (not . queryIsDepth) $ rsQuery rspec
|
||||||
thisacctq = Acct $ accountNameToAccountRegex acct -- includes subs
|
thisacctq = Acct $ accountNameToAccountRegex acct -- includes subs
|
||||||
items = reverse $ snd $ accountTransactionsReport rspec j q thisacctq
|
items = reverse $ accountTransactionsReport rspec j q thisacctq
|
||||||
ts = map first6 items
|
ts = map first6 items
|
||||||
numberedts = zip [1..] ts
|
numberedts = zip [1..] ts
|
||||||
-- select the best current transaction from the new list
|
-- select the best current transaction from the new list
|
||||||
|
|||||||
@ -27,7 +27,7 @@ getJournalR = do
|
|||||||
Just (a, inclsubs) -> "Transactions in " <> a <> if inclsubs then "" else " (excluding subaccounts)"
|
Just (a, inclsubs) -> "Transactions in " <> a <> if inclsubs then "" else " (excluding subaccounts)"
|
||||||
title' = title <> if m /= Any then ", filtered" else ""
|
title' = title <> if m /= Any then ", filtered" else ""
|
||||||
acctlink a = (RegisterR, [("q", replaceInacct q $ accountQuery a)])
|
acctlink a = (RegisterR, [("q", replaceInacct q $ accountQuery a)])
|
||||||
(_, items) = transactionsReport (rsOpts . reportspec_ $ cliopts_ opts) j m
|
items = transactionsReport (rsOpts . reportspec_ $ cliopts_ opts) j m
|
||||||
transactionFrag = transactionFragment j
|
transactionFrag = transactionFragment j
|
||||||
|
|
||||||
defaultLayout $ do
|
defaultLayout $ do
|
||||||
|
|||||||
@ -44,8 +44,11 @@ getRegisterR = do
|
|||||||
zip xs $
|
zip xs $
|
||||||
zip (map (T.unpack . accountSummarisedName . paccount) xs) $
|
zip (map (T.unpack . accountSummarisedName . paccount) xs) $
|
||||||
tail $ (", "<$xs) ++ [""]
|
tail $ (", "<$xs) ++ [""]
|
||||||
r@(balancelabel,items) = accountTransactionsReport rspec j m acctQuery
|
items = accountTransactionsReport rspec j m acctQuery
|
||||||
balancelabel' = if isJust (inAccount qopts) then balancelabel else "Total"
|
balancelabel
|
||||||
|
| isJust (inAccount qopts), balancetype_ (rsOpts rspec) == HistoricalBalance = "Historical Total"
|
||||||
|
| isJust (inAccount qopts) = "Period Total"
|
||||||
|
| otherwise = "Total"
|
||||||
transactionFrag = transactionFragment j
|
transactionFrag = transactionFragment j
|
||||||
defaultLayout $ do
|
defaultLayout $ do
|
||||||
setTitle "register - hledger-web"
|
setTitle "register - hledger-web"
|
||||||
@ -96,14 +99,12 @@ decorateLinks =
|
|||||||
|
|
||||||
-- | Generate javascript/html for a register balance line chart based on
|
-- | Generate javascript/html for a register balance line chart based on
|
||||||
-- the provided "TransactionsReportItem"s.
|
-- the provided "TransactionsReportItem"s.
|
||||||
registerChartHtml :: [(CommoditySymbol, (String, [TransactionsReportItem]))] -> HtmlUrl AppRoute
|
registerChartHtml :: String -> [(CommoditySymbol, [TransactionsReportItem])] -> HtmlUrl AppRoute
|
||||||
registerChartHtml percommoditytxnreports = $(hamletFile "templates/chart.hamlet")
|
registerChartHtml title percommoditytxnreports = $(hamletFile "templates/chart.hamlet")
|
||||||
-- have to make sure plot is not called when our container (maincontent)
|
-- have to make sure plot is not called when our container (maincontent)
|
||||||
-- is hidden, eg with add form toggled
|
-- is hidden, eg with add form toggled
|
||||||
where
|
where
|
||||||
charttitle = case maybe "" (fst . snd) $ listToMaybe percommoditytxnreports of
|
charttitle = if null title then "" else title ++ ":"
|
||||||
"" -> ""
|
|
||||||
s -> s <> ":"
|
|
||||||
colorForCommodity = fromMaybe 0 . flip lookup commoditiesIndex
|
colorForCommodity = fromMaybe 0 . flip lookup commoditiesIndex
|
||||||
commoditiesIndex = zip (map fst percommoditytxnreports) [0..] :: [(CommoditySymbol,Int)]
|
commoditiesIndex = zip (map fst percommoditytxnreports) [0..] :: [(CommoditySymbol,Int)]
|
||||||
simpleMixedAmountQuantity = maybe 0 aquantity . listToMaybe . amounts
|
simpleMixedAmountQuantity = maybe 0 aquantity . listToMaybe . amounts
|
||||||
|
|||||||
@ -6,7 +6,7 @@
|
|||||||
if ($chartdiv.is(':visible')) {
|
if ($chartdiv.is(':visible')) {
|
||||||
\$('#register-chart-label').text('#{charttitle}');
|
\$('#register-chart-label').text('#{charttitle}');
|
||||||
var seriesData = [
|
var seriesData = [
|
||||||
$forall (c,(_,items)) <- percommoditytxnreports
|
$forall (c,items) <- percommoditytxnreports
|
||||||
/* we render each commodity using two series:
|
/* we render each commodity using two series:
|
||||||
* one with extra data points added to show a stepped balance line */
|
* one with extra data points added to show a stepped balance line */
|
||||||
{
|
{
|
||||||
|
|||||||
@ -2,7 +2,7 @@
|
|||||||
#{header}
|
#{header}
|
||||||
|
|
||||||
<div .hidden-xs>
|
<div .hidden-xs>
|
||||||
^{registerChartHtml $ transactionsReportByCommodity r}
|
^{registerChartHtml balancelabel $ transactionsReportByCommodity items}
|
||||||
|
|
||||||
<div.table-responsive>
|
<div.table-responsive>
|
||||||
<table .table.table-striped.table-condensed>
|
<table .table.table-striped.table-condensed>
|
||||||
@ -15,7 +15,7 @@
|
|||||||
<th style="text-align:left;">To/From Account(s)
|
<th style="text-align:left;">To/From Account(s)
|
||||||
<th style="text-align:right; white-space:normal;">Amount Out/In
|
<th style="text-align:right; white-space:normal;">Amount Out/In
|
||||||
<th style="text-align:right; white-space:normal;">
|
<th style="text-align:right; white-space:normal;">
|
||||||
#{balancelabel'}
|
#{balancelabel}
|
||||||
|
|
||||||
<tbody>
|
<tbody>
|
||||||
$forall (torig, tacct, split, _acct, amt, bal) <- items
|
$forall (torig, tacct, split, _acct, amt, bal) <- items
|
||||||
|
|||||||
@ -108,7 +108,7 @@ aregister opts@CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do
|
|||||||
]
|
]
|
||||||
-- run the report
|
-- run the report
|
||||||
-- TODO: need to also pass the queries so we can choose which date to render - move them into the report ?
|
-- TODO: need to also pass the queries so we can choose which date to render - move them into the report ?
|
||||||
(balancelabel,items) = accountTransactionsReport rspec' j reportq thisacctq
|
items = accountTransactionsReport rspec' j reportq thisacctq
|
||||||
items' = (if empty_ ropts then id else filter (not . mixedAmountLooksZero . fifth6)) $
|
items' = (if empty_ ropts then id else filter (not . mixedAmountLooksZero . fifth6)) $
|
||||||
reverse items
|
reverse items
|
||||||
-- select renderer
|
-- select renderer
|
||||||
@ -119,10 +119,10 @@ aregister opts@CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do
|
|||||||
where
|
where
|
||||||
fmt = outputFormatFromOpts opts
|
fmt = outputFormatFromOpts opts
|
||||||
|
|
||||||
writeOutputLazyText opts $ render (balancelabel,items')
|
writeOutputLazyText opts $ render items'
|
||||||
|
|
||||||
accountTransactionsReportAsCsv :: Query -> Query -> AccountTransactionsReport -> CSV
|
accountTransactionsReportAsCsv :: Query -> Query -> AccountTransactionsReport -> CSV
|
||||||
accountTransactionsReportAsCsv reportq thisacctq (_,is) =
|
accountTransactionsReportAsCsv reportq thisacctq is =
|
||||||
["txnidx","date","code","description","otheraccounts","change","balance"]
|
["txnidx","date","code","description","otheraccounts","change","balance"]
|
||||||
: map (accountTransactionsReportItemAsCsvRecord reportq thisacctq) is
|
: map (accountTransactionsReportItemAsCsvRecord reportq thisacctq) is
|
||||||
|
|
||||||
@ -141,7 +141,7 @@ accountTransactionsReportItemAsCsvRecord
|
|||||||
|
|
||||||
-- | Render a register report as plain text suitable for console output.
|
-- | Render a register report as plain text suitable for console output.
|
||||||
accountTransactionsReportAsText :: CliOpts -> Query -> Query -> AccountTransactionsReport -> TL.Text
|
accountTransactionsReportAsText :: CliOpts -> Query -> Query -> AccountTransactionsReport -> TL.Text
|
||||||
accountTransactionsReportAsText copts reportq thisacctq (_balancelabel, items)
|
accountTransactionsReportAsText copts reportq thisacctq items
|
||||||
= TB.toLazyText . mconcat . intersperse (TB.fromText "\n") $
|
= TB.toLazyText . mconcat . intersperse (TB.fromText "\n") $
|
||||||
title :
|
title :
|
||||||
map (accountTransactionsReportItemAsText copts reportq thisacctq amtwidth balwidth) items
|
map (accountTransactionsReportItemAsText copts reportq thisacctq amtwidth balwidth) items
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user