1{-# LANGUAGE OverloadedStrings, RecordWildCards, FlexibleInstances #-}
2{-|
3
4An account-centric transactions report.
5
6-}
7
8module Hledger.Reports.AccountTransactionsReport (
9  AccountTransactionsReport,
10  AccountTransactionsReportItem,
11  accountTransactionsReport,
12  accountTransactionsReportItems,
13  transactionRegisterDate,
14  tests_AccountTransactionsReport
15)
16where
17
18import Data.List
19import Data.Ord
20import Data.Maybe
21import qualified Data.Text as T
22import Data.Time.Calendar
23
24import Hledger.Data
25import Hledger.Query
26import Hledger.Reports.ReportOptions
27import Hledger.Utils
28
29
30-- | An account transactions report represents transactions affecting
31-- a particular account (or possibly several accounts, but we don't
32-- use that). It is used eg by hledger-ui's and hledger-web's register
33-- view, and hledger's aregister report, where we want to show one row
34-- per transaction, in the context of the current account. Report
35-- items consist of:
36--
37-- - the transaction, unmodified
38--
39-- - the transaction as seen in the context of the current account and query,
40--   which means:
41--
42--   - the transaction date is set to the "transaction context date",
43--     which can be different from the transaction's general date:
44--     if postings to the current account (and matched by the report query)
45--     have their own dates, it's the earliest of these dates.
46--
47--   - the transaction's postings are filtered, excluding any which are not
48--     matched by the report query
49--
50-- - a text description of the other account(s) posted to/from
51--
52-- - a flag indicating whether there's more than one other account involved
53--
54-- - the total increase/decrease to the current account
55--
56-- - the report transactions' running total after this transaction;
57--   or if historical balance is requested (-H), the historical running total.
58--   The historical running total includes transactions from before the
59--   report start date if one is specified, filtered by the report query.
60--   The historical running total may or may not be the account's historical
61--   running balance, depending on the report query.
62--
63-- Items are sorted by transaction register date (the earliest date the transaction
64-- posts to the current account), most recent first.
65-- Reporting intervals are currently ignored.
66--
67type AccountTransactionsReport =
68  (String                          -- label for the balance column, eg "balance" or "total"
69  ,[AccountTransactionsReportItem] -- line items, one per transaction
70  )
71
72type AccountTransactionsReportItem =
73  (
74   Transaction -- the transaction, unmodified
75  ,Transaction -- the transaction, as seen from the current account
76  ,Bool        -- is this a split (more than one posting to other accounts) ?
77  ,String      -- a display string describing the other account(s), if any
78  ,MixedAmount -- the amount posted to the current account(s) (or total amount posted)
79  ,MixedAmount -- the register's running total or the current account(s)'s historical balance, after this transaction
80  )
81
82totallabel   = "Period Total"
83balancelabel = "Historical Total"
84
85accountTransactionsReport :: ReportOpts -> Journal -> Query -> Query -> AccountTransactionsReport
86accountTransactionsReport ropts j reportq thisacctq = (label, items)
87  where
88    -- a depth limit should not affect the account transactions report
89    -- seems unnecessary for some reason XXX
90    reportq' = -- filterQuery (not . queryIsDepth)
91               reportq
92
93    -- get all transactions
94    ts1 =
95      -- ptraceAtWith 5 (("ts1:\n"++).pshowTransactions) $
96      jtxns j
97
98    -- apply any cur:SYM filters in reportq'
99    symq  = filterQuery queryIsSym reportq'
100    ts2 =
101      ptraceAtWith 5 (("ts2:\n"++).pshowTransactions) $
102      (if queryIsNull symq then id else map (filterTransactionAmounts symq)) ts1
103
104    -- keep just the transactions affecting this account (via possibly realness or status-filtered postings)
105    realq = filterQuery queryIsReal reportq'
106    statusq = filterQuery queryIsStatus reportq'
107    ts3 =
108      traceAt 3 ("thisacctq: "++show thisacctq) $
109      ptraceAtWith 5 (("ts3:\n"++).pshowTransactions) $
110      filter (matchesTransaction thisacctq . filterTransactionPostings (And [realq, statusq])) ts2
111
112    -- maybe convert these transactions to cost or value
113    -- PARTIAL:
114    prices = journalPriceOracle (infer_value_ ropts) j
115    styles = journalCommodityStyles j
116    periodlast =
117      fromMaybe (error' "journalApplyValuation: expected a non-empty journal") $ -- XXX shouldn't happen
118      reportPeriodOrJournalLastDay ropts j
119    mreportlast = reportPeriodLastDay ropts
120    today = fromMaybe (error' "journalApplyValuation: could not pick a valuation date, ReportOpts today_ is unset") $ today_ ropts -- XXX shouldn't happen
121    multiperiod = interval_ ropts /= NoInterval
122    tval = case value_ ropts of
123             Just v  -> \t -> transactionApplyValuation prices styles periodlast mreportlast today multiperiod t v
124             Nothing -> id
125    ts4 =
126      ptraceAtWith 5 (("ts4:\n"++).pshowTransactions) $
127      map tval ts3
128
129    -- sort by the transaction's register date, for accurate starting balance
130    -- these are not yet filtered by tdate, we want to search them all for priorps
131    ts5 =
132      ptraceAtWith 5 (("ts5:\n"++).pshowTransactions) $
133      sortBy (comparing (transactionRegisterDate reportq' thisacctq)) ts4
134
135    (startbal,label)
136      | balancetype_ ropts == HistoricalBalance = (sumPostings priorps, balancelabel)
137      | otherwise                               = (nullmixedamt,        totallabel)
138      where
139        priorps = dbg5 "priorps" $
140                  filter (matchesPosting
141                          (dbg5 "priorq" $
142                           And [thisacctq, tostartdateq, datelessreportq]))
143                         $ transactionsPostings ts5
144        tostartdateq =
145          case mstartdate of
146            Just _  -> Date (DateSpan Nothing mstartdate)
147            Nothing -> None  -- no start date specified, there are no prior postings
148        mstartdate = queryStartDate (date2_ ropts) reportq'
149        datelessreportq = filterQuery (not . queryIsDateOrDate2) reportq'
150
151    -- accountTransactionsReportItem will keep transactions of any date which have any posting inside the report period.
152    -- Should we also require that transaction date is inside the report period ?
153    -- Should we be filtering by reportq here to apply other query terms (?)
154    -- Make it an option for now.
155    filtertxns = txn_dates_ ropts
156
157    items = reverse $
158            accountTransactionsReportItems reportq' thisacctq startbal negate $
159            (if filtertxns then filter (reportq' `matchesTransaction`) else id) $
160            ts5
161
162pshowTransactions :: [Transaction] -> String
163pshowTransactions = pshow . map (\t -> unwords [show $ tdate t, T.unpack $ tdescription t])
164
165-- | Generate transactions report items from a list of transactions,
166-- using the provided user-specified report query, a query specifying
167-- which account to use as the focus, a starting balance, a sign-setting
168-- function and a balance-summing function. Or with a None current account
169-- query, this can also be used for the transactionsReport.
170accountTransactionsReportItems :: Query -> Query -> MixedAmount -> (MixedAmount -> MixedAmount) -> [Transaction] -> [AccountTransactionsReportItem]
171accountTransactionsReportItems reportq thisacctq bal signfn =
172    catMaybes . snd .
173    mapAccumL (accountTransactionsReportItem reportq thisacctq signfn) bal
174
175accountTransactionsReportItem :: Query -> Query -> (MixedAmount -> MixedAmount) -> MixedAmount -> Transaction -> (MixedAmount, Maybe AccountTransactionsReportItem)
176accountTransactionsReportItem reportq thisacctq signfn bal torig = balItem
177    -- 201403: This is used for both accountTransactionsReport and transactionsReport, which makes it a bit overcomplicated
178    -- 201407: I've lost my grip on this, let's just hope for the best
179    -- 201606: we now calculate change and balance from filtered postings, check this still works well for all callers XXX
180    where
181      tfiltered@Transaction{tpostings=reportps} = filterTransactionPostings reportq torig
182      tacct = tfiltered{tdate=transactionRegisterDate reportq thisacctq tfiltered}
183      balItem = case reportps of
184           [] -> (bal, Nothing)  -- no matched postings in this transaction, skip it
185           _  -> (b, Just (torig, tacct, numotheraccts > 1, otheracctstr, a, b))
186                 where
187                  (thisacctps, otheracctps) = partition (matchesPosting thisacctq) reportps
188                  numotheraccts = length $ nub $ map paccount otheracctps
189                  otheracctstr | thisacctq == None  = summarisePostingAccounts reportps     -- no current account ? summarise all matched postings
190                               | numotheraccts == 0 = summarisePostingAccounts thisacctps   -- only postings to current account ? summarise those
191                               | otherwise          = summarisePostingAccounts otheracctps  -- summarise matched postings to other account(s)
192                  a = signfn $ negate $ sum $ map pamount thisacctps
193                  b = bal + a
194
195-- | What is the transaction's date in the context of a particular account
196-- (specified with a query) and report query, as in an account register ?
197-- It's normally the transaction's general date, but if any posting(s)
198-- matched by the report query and affecting the matched account(s) have
199-- their own earlier dates, it's the earliest of these dates.
200-- Secondary transaction/posting dates are ignored.
201transactionRegisterDate :: Query -> Query -> Transaction -> Day
202transactionRegisterDate reportq thisacctq t
203  | null thisacctps = tdate t
204  | otherwise       = minimum $ map postingDate thisacctps
205  where
206    reportps   = tpostings $ filterTransactionPostings reportq t
207    thisacctps = filter (matchesPosting thisacctq) reportps
208
209-- -- | Generate a short readable summary of some postings, like
210-- -- "from (negatives) to (positives)".
211-- summarisePostings :: [Posting] -> String
212-- summarisePostings ps =
213--     case (summarisePostingAccounts froms, summarisePostingAccounts tos) of
214--        ("",t) -> "to "++t
215--        (f,"") -> "from "++f
216--        (f,t)  -> "from "++f++" to "++t
217--     where
218--       (froms,tos) = partition (fromMaybe False . isNegativeMixedAmount . pamount) ps
219
220-- | Generate a simplified summary of some postings' accounts.
221-- To reduce noise, if there are both real and virtual postings, show only the real ones.
222summarisePostingAccounts :: [Posting] -> String
223summarisePostingAccounts ps =
224  (intercalate ", " . map (T.unpack . accountSummarisedName) . nub . map paccount) displayps -- XXX pack
225  where
226    realps = filter isReal ps
227    displayps | null realps = ps
228              | otherwise   = realps
229
230-- tests
231
232tests_AccountTransactionsReport = tests "AccountTransactionsReport" [
233 ]
234