2014-03-20 04:11:48 +04:00
|
|
|
{-# LANGUAGE RecordWildCards, DeriveDataTypeable, FlexibleInstances #-}
|
|
|
|
{-|
|
|
|
|
|
2014-06-13 03:14:41 +04:00
|
|
|
Here are several variants of a transactions report.
|
|
|
|
Transactions reports are like a postings report, but more
|
|
|
|
transaction-oriented, and (in the account-centric variant) relative to
|
|
|
|
a some base account. They are used by hledger-web.
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
-}
|
|
|
|
|
|
|
|
module Hledger.Reports.TransactionsReports (
|
|
|
|
TransactionsReport,
|
|
|
|
TransactionsReportItem,
|
2015-08-20 21:05:42 +03:00
|
|
|
AccountTransactionsReport,
|
|
|
|
AccountTransactionsReportItem,
|
2014-07-19 03:45:46 +04:00
|
|
|
triOrigTransaction,
|
2014-03-20 04:11:48 +04:00
|
|
|
triDate,
|
2014-07-19 03:45:46 +04:00
|
|
|
triAmount,
|
2014-03-20 04:11:48 +04:00
|
|
|
triBalance,
|
2014-07-19 03:45:46 +04:00
|
|
|
triCommodityAmount,
|
|
|
|
triCommodityBalance,
|
2014-03-20 04:11:48 +04:00
|
|
|
journalTransactionsReport,
|
|
|
|
accountTransactionsReport,
|
2016-07-27 22:07:48 +03:00
|
|
|
transactionsReportByCommodity,
|
|
|
|
transactionRegisterDate
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
-- -- * Tests
|
|
|
|
-- tests_Hledger_Reports_TransactionsReports
|
|
|
|
)
|
|
|
|
where
|
|
|
|
|
|
|
|
import Data.List
|
|
|
|
import Data.Ord
|
lib: textification begins! account names
The first of several conversions from String to (strict) Text, hopefully
reducing space and time usage.
This one shows a small improvement, with GHC 7.10.3 and text-1.2.2.1:
hledger -f data/100x100x10.journal stats
string: <<ghc: 39471064 bytes, 77 GCs, 198421/275048 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.001 elapsed), 0.015 MUT (0.020 elapsed), 0.010 GC (0.014 elapsed) :ghc>>
text: <<ghc: 39268024 bytes, 77 GCs, 197018/270840 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.002 elapsed), 0.016 MUT (0.022 elapsed), 0.009 GC (0.011 elapsed) :ghc>>
hledger -f data/1000x100x10.journal stats
string: <<ghc: 318555920 bytes, 617 GCs, 2178997/7134472 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.001 elapsed), 0.129 MUT (0.136 elapsed), 0.067 GC (0.077 elapsed) :ghc>>
text: <<ghc: 314248496 bytes, 612 GCs, 2074045/6617960 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.003 elapsed), 0.137 MUT (0.145 elapsed), 0.067 GC (0.079 elapsed) :ghc>>
hledger -f data/10000x100x10.journal stats
string: <<ghc: 3114763608 bytes, 6026 GCs, 18858950/75552024 avg/max bytes residency (11 samples), 201M in use, 0.000 INIT (0.000 elapsed), 1.331 MUT (1.372 elapsed), 0.699 GC (0.812 elapsed) :ghc>>
text: <<ghc: 3071468920 bytes, 5968 GCs, 14120344/62951360 avg/max bytes residency (9 samples), 124M in use, 0.000 INIT (0.003 elapsed), 1.272 MUT (1.349 elapsed), 0.513 GC (0.578 elapsed) :ghc>>
hledger -f data/100000x100x10.journal stats
string: <<ghc: 31186579432 bytes, 60278 GCs, 135332581/740228992 avg/max bytes residency (13 samples), 1697M in use, 0.000 INIT (0.008 elapsed), 14.677 MUT (15.508 elapsed), 7.081 GC (8.074 elapsed) :ghc>>
text: <<ghc: 30753427672 bytes, 59763 GCs, 117595958/666457240 avg/max bytes residency (14 samples), 1588M in use, 0.000 INIT (0.008 elapsed), 13.713 MUT (13.966 elapsed), 6.220 GC (7.108 elapsed) :ghc>>
2016-05-24 04:16:21 +03:00
|
|
|
-- import Data.Text (Text)
|
|
|
|
import qualified Data.Text as T
|
2016-07-27 22:07:48 +03:00
|
|
|
import Data.Time.Calendar
|
2014-03-22 04:41:54 +04:00
|
|
|
-- import Test.HUnit
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
import Hledger.Data
|
|
|
|
import Hledger.Query
|
|
|
|
import Hledger.Reports.ReportOptions
|
2016-09-06 18:43:25 +03:00
|
|
|
import Hledger.Utils.Debug
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
|
|
|
|
-- | A transactions report includes a list of transactions
|
|
|
|
-- (posting-filtered and unfiltered variants), a running balance, and some
|
|
|
|
-- other information helpful for rendering a register view (a flag
|
|
|
|
-- indicating multiple other accounts and a display string describing
|
|
|
|
-- them) with or without a notion of current account(s).
|
|
|
|
-- Two kinds of report use this data structure, see journalTransactionsReport
|
|
|
|
-- and accountTransactionsReport below for detais.
|
|
|
|
type TransactionsReport = (String -- label for the balance column, eg "balance" or "total"
|
|
|
|
,[TransactionsReportItem] -- line items, one per transaction
|
|
|
|
)
|
2014-07-18 03:20:34 +04:00
|
|
|
type TransactionsReportItem = (Transaction -- the original journal transaction, unmodified
|
2016-06-02 17:03:00 +03:00
|
|
|
,Transaction -- the transaction as seen from a particular account, with postings maybe filtered
|
2014-03-20 04:11:48 +04:00
|
|
|
,Bool -- is this a split, ie more than one other account posting
|
|
|
|
,String -- a display string describing the other account(s), if any
|
2016-06-02 17:03:00 +03:00
|
|
|
,MixedAmount -- the amount posted to the current account(s) by the filtered postings (or total amount posted)
|
2016-08-13 03:26:34 +03:00
|
|
|
,MixedAmount -- the running total of item amounts, starting from zero;
|
|
|
|
-- or with --historical, the running total including items
|
|
|
|
-- (matched by the report query) preceding the report period
|
2014-03-20 04:11:48 +04:00
|
|
|
)
|
|
|
|
|
2014-07-19 03:45:46 +04:00
|
|
|
triOrigTransaction (torig,_,_,_,_,_) = torig
|
|
|
|
triDate (_,tacct,_,_,_,_) = tdate tacct
|
2014-03-20 04:11:48 +04:00
|
|
|
triAmount (_,_,_,_,a,_) = a
|
|
|
|
triBalance (_,_,_,_,_,a) = a
|
2014-07-19 03:45:46 +04:00
|
|
|
triCommodityAmount c = filterMixedAmountByCommodity c . triAmount
|
|
|
|
triCommodityBalance c = filterMixedAmountByCommodity c . triBalance
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
-------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
-- | Select transactions from the whole journal. This is similar to a
|
|
|
|
-- "postingsReport" except with transaction-based report items which
|
2014-06-13 03:14:41 +04:00
|
|
|
-- are ordered most recent first. XXX Or an EntriesReport - use that instead ?
|
|
|
|
-- This is used by hledger-web's journal view.
|
2014-03-20 04:11:48 +04:00
|
|
|
journalTransactionsReport :: ReportOpts -> Journal -> Query -> TransactionsReport
|
2014-06-13 03:14:41 +04:00
|
|
|
journalTransactionsReport opts j q = (totallabel, items)
|
2014-03-20 04:11:48 +04:00
|
|
|
where
|
|
|
|
-- XXX items' first element should be the full transaction with all postings
|
2014-07-18 03:20:34 +04:00
|
|
|
items = reverse $ accountTransactionsReportItems q None nullmixedamt id ts
|
2014-06-13 03:14:41 +04:00
|
|
|
ts = sortBy (comparing date) $ filter (q `matchesTransaction`) $ jtxns $ journalSelectingAmountFromOpts opts j
|
|
|
|
date = transactionDateFn opts
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
-------------------------------------------------------------------------------
|
|
|
|
|
2014-07-18 03:20:34 +04:00
|
|
|
-- | An account transactions report represents transactions affecting
|
|
|
|
-- a particular account (or possibly several accounts, but we don't
|
2016-07-27 22:07:48 +03:00
|
|
|
-- use that). It is used eg by hledger-ui's and hledger-web's account
|
|
|
|
-- register view, where we want to show one row per transaction, in
|
|
|
|
-- the context of the current account. Report items consist of:
|
2014-03-20 04:11:48 +04:00
|
|
|
--
|
2016-07-27 22:07:48 +03:00
|
|
|
-- - the transaction, unmodified
|
|
|
|
--
|
|
|
|
-- - the transaction as seen in the context of the current account and query,
|
|
|
|
-- which means:
|
|
|
|
--
|
|
|
|
-- - the transaction date is set to the "transaction context date",
|
|
|
|
-- which can be different from the transaction's general date:
|
|
|
|
-- if postings to the current account (and matched by the report query)
|
|
|
|
-- have their own dates, it's the earliest of these dates.
|
2014-03-20 04:11:48 +04:00
|
|
|
--
|
2016-07-27 22:07:48 +03:00
|
|
|
-- - the transaction's postings are filtered, excluding any which are not
|
|
|
|
-- matched by the report query
|
2014-03-20 04:11:48 +04:00
|
|
|
--
|
2016-07-27 22:07:48 +03:00
|
|
|
-- - a text description of the other account(s) posted to/from
|
|
|
|
--
|
|
|
|
-- - a flag indicating whether there's more than one other account involved
|
|
|
|
--
|
|
|
|
-- - the total increase/decrease to the current account
|
2014-07-18 03:20:34 +04:00
|
|
|
--
|
2016-08-13 03:26:34 +03:00
|
|
|
-- - the report transactions' running total after this transaction;
|
2016-09-06 18:43:25 +03:00
|
|
|
-- or if historical balance is requested (-H), the historical running total.
|
|
|
|
-- The historical running total includes transactions from before the
|
|
|
|
-- report start date if one is specified, filtered by the report query.
|
|
|
|
-- The historical running total may or may not be the account's historical
|
|
|
|
-- running balance, depending on the report query.
|
2016-07-27 22:07:48 +03:00
|
|
|
--
|
2016-09-06 18:43:25 +03:00
|
|
|
-- Items are sorted by transaction register date (the earliest date the transaction
|
|
|
|
-- posts to the current account), most recent first.
|
2016-07-27 22:07:48 +03:00
|
|
|
-- Reporting intervals are currently ignored.
|
2014-07-18 03:20:34 +04:00
|
|
|
--
|
|
|
|
type AccountTransactionsReport =
|
|
|
|
(String -- label for the balance column, eg "balance" or "total"
|
|
|
|
,[AccountTransactionsReportItem] -- line items, one per transaction
|
|
|
|
)
|
|
|
|
|
|
|
|
type AccountTransactionsReportItem =
|
|
|
|
(
|
2016-07-27 22:07:48 +03:00
|
|
|
Transaction -- the transaction, unmodified
|
|
|
|
,Transaction -- the transaction, as seen from the current account
|
|
|
|
,Bool -- is this a split (more than one posting to other accounts) ?
|
2014-07-18 03:20:34 +04:00
|
|
|
,String -- a display string describing the other account(s), if any
|
|
|
|
,MixedAmount -- the amount posted to the current account(s) (or total amount posted)
|
2016-07-27 22:07:48 +03:00
|
|
|
,MixedAmount -- the register's running total or the current account(s)'s historical balance, after this transaction
|
2014-07-18 03:20:34 +04:00
|
|
|
)
|
|
|
|
|
|
|
|
accountTransactionsReport :: ReportOpts -> Journal -> Query -> Query -> AccountTransactionsReport
|
2016-07-27 22:07:48 +03:00
|
|
|
accountTransactionsReport opts j reportq thisacctq = (label, items)
|
2016-06-02 17:03:00 +03:00
|
|
|
where
|
2016-06-12 17:18:03 +03:00
|
|
|
-- a depth limit does not affect the account transactions report
|
2016-09-06 18:43:25 +03:00
|
|
|
-- seems unnecessary for some reason XXX
|
|
|
|
reportq' = -- filterQuery (not . queryIsDepth)
|
|
|
|
reportq
|
2016-06-02 17:03:00 +03:00
|
|
|
-- get all transactions, with amounts converted to cost basis if -B
|
|
|
|
ts1 = jtxns $ journalSelectingAmountFromOpts opts j
|
2016-09-06 18:43:25 +03:00
|
|
|
-- apply any cur:SYM filters in reportq'
|
|
|
|
symq = filterQuery queryIsSym reportq'
|
2016-06-02 17:03:00 +03:00
|
|
|
ts2 = (if queryIsNull symq then id else map (filterTransactionAmounts symq)) ts1
|
2016-06-04 03:51:10 +03:00
|
|
|
-- keep just the transactions affecting this account (via possibly realness or status-filtered postings)
|
2016-09-06 18:43:25 +03:00
|
|
|
realq = filterQuery queryIsReal reportq'
|
|
|
|
statusq = filterQuery queryIsStatus reportq'
|
2016-07-27 22:07:48 +03:00
|
|
|
ts3 = filter (matchesTransaction thisacctq . filterTransactionPostings (And [realq, statusq])) ts2
|
2016-09-06 18:43:25 +03:00
|
|
|
-- sort by the transaction's register date, for accurate starting balance
|
|
|
|
ts = sortBy (comparing (transactionRegisterDate reportq' thisacctq)) ts3
|
2016-06-02 17:03:00 +03:00
|
|
|
|
2016-08-13 03:26:34 +03:00
|
|
|
(startbal,label)
|
|
|
|
| balancetype_ opts == HistoricalBalance = (sumPostings priorps, balancelabel)
|
|
|
|
| otherwise = (nullmixedamt, totallabel)
|
|
|
|
where
|
2016-09-06 18:43:25 +03:00
|
|
|
priorps = dbg1 "priorps" $
|
2016-08-13 03:26:34 +03:00
|
|
|
filter (matchesPosting
|
2016-09-06 18:43:25 +03:00
|
|
|
(dbg1 "priorq" $
|
|
|
|
And [thisacctq, tostartdateq, datelessreportq]))
|
2016-08-13 03:26:34 +03:00
|
|
|
$ transactionsPostings ts
|
2016-09-06 18:43:25 +03:00
|
|
|
tostartdateq =
|
2016-09-06 00:44:16 +03:00
|
|
|
case mstartdate of
|
|
|
|
Just _ -> Date (DateSpan Nothing mstartdate)
|
2016-09-06 18:43:25 +03:00
|
|
|
Nothing -> None -- no start date specified, there are no prior postings
|
|
|
|
mstartdate = queryStartDate (date2_ opts) reportq'
|
|
|
|
datelessreportq = filterQuery (not . queryIsDateOrDate2) reportq'
|
2016-06-02 17:03:00 +03:00
|
|
|
|
|
|
|
items = reverse $ -- see also registerChartHtml
|
2016-09-06 18:43:25 +03:00
|
|
|
accountTransactionsReportItems reportq' thisacctq startbal negate ts
|
2014-07-18 03:20:34 +04:00
|
|
|
|
2016-08-13 03:26:34 +03:00
|
|
|
totallabel = "Period Total"
|
|
|
|
balancelabel = "Historical Total"
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
-- | Generate transactions report items from a list of transactions,
|
2016-06-02 17:03:00 +03:00
|
|
|
-- using the provided user-specified report query, a query specifying
|
|
|
|
-- which account to use as the focus, a starting balance, a sign-setting
|
|
|
|
-- function and a balance-summing function. Or with a None current account
|
|
|
|
-- query, this can also be used for the journalTransactionsReport.
|
2014-07-18 03:20:34 +04:00
|
|
|
accountTransactionsReportItems :: Query -> Query -> MixedAmount -> (MixedAmount -> MixedAmount) -> [Transaction] -> [TransactionsReportItem]
|
2014-03-20 04:11:48 +04:00
|
|
|
accountTransactionsReportItems _ _ _ _ [] = []
|
2016-06-02 17:03:00 +03:00
|
|
|
accountTransactionsReportItems reportq thisacctq bal signfn (torig:ts) =
|
2014-03-20 04:11:48 +04:00
|
|
|
case i of Just i' -> i':is
|
|
|
|
Nothing -> is
|
2016-06-02 17:03:00 +03:00
|
|
|
-- 201403: This is used for both accountTransactionsReport and journalTransactionsReport, which makes it a bit overcomplicated
|
|
|
|
-- 201407: I've lost my grip on this, let's just hope for the best
|
|
|
|
-- 201606: we now calculate change and balance from filtered postings, check this still works well for all callers XXX
|
2014-03-20 04:11:48 +04:00
|
|
|
where
|
2016-07-27 22:07:48 +03:00
|
|
|
tfiltered@Transaction{tpostings=reportps} = filterTransactionPostings reportq torig
|
|
|
|
tacct = tfiltered{tdate=transactionRegisterDate reportq thisacctq tfiltered}
|
2016-06-02 17:03:00 +03:00
|
|
|
(i,bal') = case reportps of
|
|
|
|
[] -> (Nothing,bal) -- no matched postings in this transaction, skip it
|
2014-07-18 03:20:34 +04:00
|
|
|
_ -> (Just (torig, tacct, numotheraccts > 1, otheracctstr, a, b), b)
|
2014-03-20 04:11:48 +04:00
|
|
|
where
|
2016-06-02 17:03:00 +03:00
|
|
|
(thisacctps, otheracctps) = partition (matchesPosting thisacctq) reportps
|
|
|
|
numotheraccts = length $ nub $ map paccount otheracctps
|
|
|
|
otheracctstr | thisacctq == None = summarisePostingAccounts reportps -- no current account ? summarise all matched postings
|
|
|
|
| numotheraccts == 0 = summarisePostingAccounts thisacctps -- only postings to current account ? summarise those
|
|
|
|
| otherwise = summarisePostingAccounts otheracctps -- summarise matched postings to other account(s)
|
|
|
|
a = signfn $ negate $ sum $ map pamount thisacctps
|
2014-03-20 04:11:48 +04:00
|
|
|
b = bal + a
|
2016-06-02 17:03:00 +03:00
|
|
|
is = accountTransactionsReportItems reportq thisacctq bal' signfn ts
|
2014-03-20 04:11:48 +04:00
|
|
|
|
2016-07-27 22:07:48 +03:00
|
|
|
-- | What is the transaction's date in the context of a particular account
|
|
|
|
-- (specified with a query) and report query, as in an account register ?
|
|
|
|
-- It's normally the transaction's general date, but if any posting(s)
|
|
|
|
-- matched by the report query and affecting the matched account(s) have
|
|
|
|
-- their own earlier dates, it's the earliest of these dates.
|
|
|
|
-- Secondary transaction/posting dates are ignored.
|
|
|
|
transactionRegisterDate :: Query -> Query -> Transaction -> Day
|
|
|
|
transactionRegisterDate reportq thisacctq t
|
|
|
|
| null thisacctps = tdate t
|
|
|
|
| otherwise = minimum $ map postingDate thisacctps
|
|
|
|
where
|
|
|
|
reportps = tpostings $ filterTransactionPostings reportq t
|
|
|
|
thisacctps = filter (matchesPosting thisacctq) reportps
|
|
|
|
|
2014-06-13 03:21:26 +04:00
|
|
|
-- -- | Generate a short readable summary of some postings, like
|
|
|
|
-- -- "from (negatives) to (positives)".
|
|
|
|
-- summarisePostings :: [Posting] -> String
|
|
|
|
-- summarisePostings ps =
|
|
|
|
-- case (summarisePostingAccounts froms, summarisePostingAccounts tos) of
|
|
|
|
-- ("",t) -> "to "++t
|
|
|
|
-- (f,"") -> "from "++f
|
|
|
|
-- (f,t) -> "from "++f++" to "++t
|
|
|
|
-- where
|
|
|
|
-- (froms,tos) = partition (fromMaybe False . isNegativeMixedAmount . pamount) ps
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
-- | Generate a simplified summary of some postings' accounts.
|
2015-08-28 21:58:57 +03:00
|
|
|
-- To reduce noise, if there are both real and virtual postings, show only the real ones.
|
2014-03-20 04:11:48 +04:00
|
|
|
summarisePostingAccounts :: [Posting] -> String
|
2015-08-28 21:58:57 +03:00
|
|
|
summarisePostingAccounts ps =
|
lib: textification begins! account names
The first of several conversions from String to (strict) Text, hopefully
reducing space and time usage.
This one shows a small improvement, with GHC 7.10.3 and text-1.2.2.1:
hledger -f data/100x100x10.journal stats
string: <<ghc: 39471064 bytes, 77 GCs, 198421/275048 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.001 elapsed), 0.015 MUT (0.020 elapsed), 0.010 GC (0.014 elapsed) :ghc>>
text: <<ghc: 39268024 bytes, 77 GCs, 197018/270840 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.002 elapsed), 0.016 MUT (0.022 elapsed), 0.009 GC (0.011 elapsed) :ghc>>
hledger -f data/1000x100x10.journal stats
string: <<ghc: 318555920 bytes, 617 GCs, 2178997/7134472 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.001 elapsed), 0.129 MUT (0.136 elapsed), 0.067 GC (0.077 elapsed) :ghc>>
text: <<ghc: 314248496 bytes, 612 GCs, 2074045/6617960 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.003 elapsed), 0.137 MUT (0.145 elapsed), 0.067 GC (0.079 elapsed) :ghc>>
hledger -f data/10000x100x10.journal stats
string: <<ghc: 3114763608 bytes, 6026 GCs, 18858950/75552024 avg/max bytes residency (11 samples), 201M in use, 0.000 INIT (0.000 elapsed), 1.331 MUT (1.372 elapsed), 0.699 GC (0.812 elapsed) :ghc>>
text: <<ghc: 3071468920 bytes, 5968 GCs, 14120344/62951360 avg/max bytes residency (9 samples), 124M in use, 0.000 INIT (0.003 elapsed), 1.272 MUT (1.349 elapsed), 0.513 GC (0.578 elapsed) :ghc>>
hledger -f data/100000x100x10.journal stats
string: <<ghc: 31186579432 bytes, 60278 GCs, 135332581/740228992 avg/max bytes residency (13 samples), 1697M in use, 0.000 INIT (0.008 elapsed), 14.677 MUT (15.508 elapsed), 7.081 GC (8.074 elapsed) :ghc>>
text: <<ghc: 30753427672 bytes, 59763 GCs, 117595958/666457240 avg/max bytes residency (14 samples), 1588M in use, 0.000 INIT (0.008 elapsed), 13.713 MUT (13.966 elapsed), 6.220 GC (7.108 elapsed) :ghc>>
2016-05-24 04:16:21 +03:00
|
|
|
(intercalate ", " . map (T.unpack . accountSummarisedName) . nub . map paccount) displayps -- XXX pack
|
2015-08-28 21:58:57 +03:00
|
|
|
where
|
|
|
|
realps = filter isReal ps
|
|
|
|
displayps | null realps = ps
|
|
|
|
| otherwise = realps
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
-------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
-- | Split a transactions report whose items may involve several commodities,
|
|
|
|
-- into one or more single-commodity transactions reports.
|
2016-05-08 02:18:04 +03:00
|
|
|
transactionsReportByCommodity :: TransactionsReport -> [(CommoditySymbol, TransactionsReport)]
|
2014-03-20 04:11:48 +04:00
|
|
|
transactionsReportByCommodity tr =
|
2014-07-18 05:09:02 +04:00
|
|
|
[(c, filterTransactionsReportByCommodity c tr) | c <- transactionsReportCommodities tr]
|
2014-03-20 04:11:48 +04:00
|
|
|
where
|
|
|
|
transactionsReportCommodities (_,items) =
|
|
|
|
nub $ sort $ map acommodity $ concatMap (amounts . triAmount) items
|
|
|
|
|
|
|
|
-- Remove transaction report items and item amount (and running
|
|
|
|
-- balance amount) components that don't involve the specified
|
|
|
|
-- commodity. Other item fields such as the transaction are left unchanged.
|
2016-05-08 02:18:04 +03:00
|
|
|
filterTransactionsReportByCommodity :: CommoditySymbol -> TransactionsReport -> TransactionsReport
|
2014-03-20 04:11:48 +04:00
|
|
|
filterTransactionsReportByCommodity c (label,items) =
|
|
|
|
(label, fixTransactionsReportItemBalances $ concat [filterTransactionsReportItemByCommodity c i | i <- items])
|
|
|
|
where
|
|
|
|
filterTransactionsReportItemByCommodity c (t,t2,s,o,a,bal)
|
|
|
|
| c `elem` cs = [item']
|
|
|
|
| otherwise = []
|
|
|
|
where
|
|
|
|
cs = map acommodity $ amounts a
|
|
|
|
item' = (t,t2,s,o,a',bal)
|
|
|
|
a' = filterMixedAmountByCommodity c a
|
|
|
|
|
|
|
|
fixTransactionsReportItemBalances [] = []
|
|
|
|
fixTransactionsReportItemBalances [i] = [i]
|
|
|
|
fixTransactionsReportItemBalances items = reverse $ i:(go startbal is)
|
|
|
|
where
|
|
|
|
i:is = reverse items
|
|
|
|
startbal = filterMixedAmountByCommodity c $ triBalance i
|
|
|
|
go _ [] = []
|
|
|
|
go bal ((t,t2,s,o,amt,_):is) = (t,t2,s,o,amt,bal'):go bal' is
|
|
|
|
where bal' = bal + amt
|
|
|
|
|
|
|
|
-------------------------------------------------------------------------------
|
|
|
|
|