{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-|

An account-centric transactions report.

-}

module Hledger.Reports.AccountTransactionsReport (
  AccountTransactionsReport,
  AccountTransactionsReportItem,
  accountTransactionsReport,
  accountTransactionsReportItems,
  transactionRegisterDate,
  triOrigTransaction,
  triDate,
  triAmount,
  triBalance,
  triCommodityAmount,
  triCommodityBalance,
  accountTransactionsReportByCommodity,
  tests_AccountTransactionsReport
)
where

import Data.List (mapAccumR, nub, partition, sortBy)
import Data.List.Extra (nubSort)
import Data.Maybe (catMaybes)
import Data.Ord (Down(..), comparing)
import Data.Text (Text)
import qualified Data.Text as T
import Data.Time.Calendar (Day)

import Hledger.Data
import Hledger.Query
import Hledger.Reports.ReportOptions
import Hledger.Utils


-- | An account transactions report represents transactions affecting
-- a particular account (or possibly several accounts, but we don't
-- use that). It is used eg by hledger-ui's and hledger-web's register
-- view, and hledger's aregister report, where we want to show one row
-- per transaction, in the context of the current account. Report
-- items consist of:
--
-- - 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":
--     the earliest of the transaction date and any other posting dates
--     of postings to the current account (matched by the report query).
--
--   - the transaction's postings are filtered, excluding any which are not
--     matched by the report query
--
-- - 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
--
-- - the report transactions' running total after this transaction;
--   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.
--
-- Items are sorted by transaction register date (the earliest date the transaction
-- posts to the current account), most recent first.
-- Reporting intervals are currently ignored.
--
type AccountTransactionsReport = [AccountTransactionsReportItem] -- line items, one per transaction

type AccountTransactionsReportItem =
  (
   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) ?
  ,Text        -- a display string describing the other account(s), if any
  ,MixedAmount -- the amount posted to the current account(s) (or total amount posted)
  ,MixedAmount -- the register's running total or the current account(s)'s historical balance, after this transaction
  )

triOrigTransaction :: (a, b, c, d, e, f) -> a
triOrigTransaction (a
torig,b
_,c
_,d
_,e
_,f
_) = a
torig
triDate :: (a, Transaction, c, d, e, f) -> Day
triDate (a
_,Transaction
tacct,c
_,d
_,e
_,f
_) = Transaction -> Day
tdate Transaction
tacct
triAmount :: (a, b, c, d, e, f) -> e
triAmount (a
_,b
_,c
_,d
_,e
a,f
_) = e
a
triBalance :: (a, b, c, d, e, f) -> f
triBalance (a
_,b
_,c
_,d
_,e
_,f
a) = f
a
triCommodityAmount :: CommoditySymbol -> (a, b, c, d, MixedAmount, f) -> MixedAmount
triCommodityAmount CommoditySymbol
c = CommoditySymbol -> MixedAmount -> MixedAmount
filterMixedAmountByCommodity CommoditySymbol
c  (MixedAmount -> MixedAmount)
-> ((a, b, c, d, MixedAmount, f) -> MixedAmount)
-> (a, b, c, d, MixedAmount, f)
-> MixedAmount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b, c, d, MixedAmount, f) -> MixedAmount
forall a b c d e f. (a, b, c, d, e, f) -> e
triAmount
triCommodityBalance :: CommoditySymbol -> (a, b, c, d, e, MixedAmount) -> MixedAmount
triCommodityBalance CommoditySymbol
c = CommoditySymbol -> MixedAmount -> MixedAmount
filterMixedAmountByCommodity CommoditySymbol
c  (MixedAmount -> MixedAmount)
-> ((a, b, c, d, e, MixedAmount) -> MixedAmount)
-> (a, b, c, d, e, MixedAmount)
-> MixedAmount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b, c, d, e, MixedAmount) -> MixedAmount
forall a b c d e f. (a, b, c, d, e, f) -> f
triBalance

accountTransactionsReport :: ReportSpec -> Journal -> Query -> AccountTransactionsReport
accountTransactionsReport :: ReportSpec -> Journal -> Query -> AccountTransactionsReport
accountTransactionsReport rspec :: ReportSpec
rspec@ReportSpec{_rsReportOpts :: ReportSpec -> ReportOpts
_rsReportOpts=ReportOpts
ropts} Journal
j Query
thisacctq = AccountTransactionsReport
items
  where
    -- A depth limit should not affect the account transactions report; it should show all transactions in/below this account.
    -- Queries on currency or amount are also ignored at this stage; they are handled earlier, before valuation.
    reportq :: Query
reportq = Query -> Query
simplifyQuery (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ [Query] -> Query
And [Query
aregisterq, Query
periodq]
      where
        aregisterq :: Query
aregisterq = (Query -> Bool) -> Query -> Query
filterQuery (Bool -> Bool
not (Bool -> Bool) -> (Query -> Bool) -> Query -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Query -> Bool
queryIsCurOrAmt) (Query -> Query) -> (Query -> Query) -> Query -> Query
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Query -> Bool) -> Query -> Query
filterQuery (Bool -> Bool
not (Bool -> Bool) -> (Query -> Bool) -> Query -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Query -> Bool
queryIsDepth) (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ ReportSpec -> Query
_rsQuery ReportSpec
rspec
        periodq :: Query
periodq = DateSpan -> Query
Date (DateSpan -> Query) -> (Period -> DateSpan) -> Period -> Query
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Period -> DateSpan
periodAsDateSpan (Period -> Query) -> Period -> Query
forall a b. (a -> b) -> a -> b
$ ReportOpts -> Period
period_ ReportOpts
ropts
    amtq :: Query
amtq = (Query -> Bool) -> Query -> Query
filterQuery Query -> Bool
queryIsCurOrAmt (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ ReportSpec -> Query
_rsQuery ReportSpec
rspec
    queryIsCurOrAmt :: Query -> Bool
queryIsCurOrAmt Query
q = Query -> Bool
queryIsSym Query
q Bool -> Bool -> Bool
|| Query -> Bool
queryIsAmt Query
q

    -- Note that within this functions, we are only allowed limited
    -- transformation of the transaction postings: this is due to the need to
    -- pass the original transactions into accountTransactionsReportItem.
    -- Generally, we either include a transaction in full, or not at all.
    -- Do some limited filtering and valuing of the journal's transactions:
    -- - filter them by the account query if any,
    -- - discard amounts not matched by the currency and amount query if any,
    -- - then apply valuation if any.
    acctJournal :: Journal
acctJournal =
          Int -> (Journal -> String) -> Journal -> Journal
forall a. Show a => Int -> (a -> String) -> a -> a
ptraceAtWith Int
5 ((String
"ts3:\n"String -> String -> String
forall a. [a] -> [a] -> [a]
++)(String -> String) -> (Journal -> String) -> Journal -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.[Transaction] -> String
pshowTransactions([Transaction] -> String)
-> (Journal -> [Transaction]) -> Journal -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Journal -> [Transaction]
jtxns)
        -- maybe convert these transactions to cost or value
        (Journal -> Journal) -> (Journal -> Journal) -> Journal -> Journal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReportSpec -> Journal -> Journal
journalApplyValuationFromOpts ReportSpec
rspec
        (Journal -> Journal) -> (Journal -> Journal) -> Journal -> Journal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> (Journal -> String) -> Journal -> Journal
forall a. Show a => Int -> (a -> String) -> a -> a
ptraceAtWith Int
5 ((String
"ts2:\n"String -> String -> String
forall a. [a] -> [a] -> [a]
++)(String -> String) -> (Journal -> String) -> Journal -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.[Transaction] -> String
pshowTransactions([Transaction] -> String)
-> (Journal -> [Transaction]) -> Journal -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Journal -> [Transaction]
jtxns)
        -- apply any cur:SYM filters in reportq
        (Journal -> Journal) -> (Journal -> Journal) -> Journal -> Journal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if Query -> Bool
queryIsNull Query
amtq then Journal -> Journal
forall a. a -> a
id else Query -> Journal -> Journal
filterJournalAmounts Query
amtq)
        -- only consider transactions which match thisacctq (possibly excluding postings
        -- which are not real or have the wrong status)
        (Journal -> Journal) -> (Journal -> Journal) -> Journal -> Journal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> Journal -> Journal
forall a. Int -> String -> a -> a
traceAt Int
3 (String
"thisacctq: "String -> String -> String
forall a. [a] -> [a] -> [a]
++Query -> String
forall a. Show a => a -> String
show Query
thisacctq)
        (Journal -> Journal) -> Journal -> Journal
forall a b. (a -> b) -> a -> b
$ Int -> (Journal -> String) -> Journal -> Journal
forall a. Show a => Int -> (a -> String) -> a -> a
ptraceAtWith Int
5 ((String
"ts1:\n"String -> String -> String
forall a. [a] -> [a] -> [a]
++)(String -> String) -> (Journal -> String) -> Journal -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.[Transaction] -> String
pshowTransactions([Transaction] -> String)
-> (Journal -> [Transaction]) -> Journal -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Journal -> [Transaction]
jtxns)
          Journal
j{jtxns :: [Transaction]
jtxns = (Transaction -> Bool) -> [Transaction] -> [Transaction]
forall a. (a -> Bool) -> [a] -> [a]
filter (Query -> Transaction -> Bool
matchesTransaction Query
thisacctq (Transaction -> Bool)
-> (Transaction -> Transaction) -> Transaction -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> Transaction
relevantPostings) ([Transaction] -> [Transaction]) -> [Transaction] -> [Transaction]
forall a b. (a -> b) -> a -> b
$ Journal -> [Transaction]
jtxns Journal
j}
      where
        relevantPostings :: Transaction -> Transaction
relevantPostings
          | Query -> Bool
queryIsNull Query
realq Bool -> Bool -> Bool
&& Query -> Bool
queryIsNull Query
statusq = Transaction -> Transaction
forall a. a -> a
id
          | Bool
otherwise = Query -> Transaction -> Transaction
filterTransactionPostings (Query -> Transaction -> Transaction)
-> (Query -> Query) -> Query -> Transaction -> Transaction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Query -> Query
simplifyQuery (Query -> Transaction -> Transaction)
-> Query -> Transaction -> Transaction
forall a b. (a -> b) -> a -> b
$ [Query] -> Query
And [Query
realq, Query
statusq]
        realq :: Query
realq   = (Query -> Bool) -> Query -> Query
filterQuery Query -> Bool
queryIsReal Query
reportq
        statusq :: Query
statusq = (Query -> Bool) -> Query -> Query
filterQuery Query -> Bool
queryIsStatus Query
reportq

    startbal :: MixedAmount
startbal
      | ReportOpts -> BalanceAccumulation
balanceaccum_ ReportOpts
ropts BalanceAccumulation -> BalanceAccumulation -> Bool
forall a. Eq a => a -> a -> Bool
== BalanceAccumulation
Historical = [Posting] -> MixedAmount
sumPostings [Posting]
priorps
      | Bool
otherwise                         = MixedAmount
nullmixedamt
      where
        priorps :: [Posting]
priorps = String -> [Posting] -> [Posting]
forall a. Show a => String -> a -> a
dbg5 String
"priorps" ([Posting] -> [Posting])
-> (Journal -> [Posting]) -> Journal -> [Posting]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Journal -> [Posting]
journalPostings (Journal -> [Posting]) -> Journal -> [Posting]
forall a b. (a -> b) -> a -> b
$ Query -> Journal -> Journal
filterJournalPostings Query
priorq Journal
acctJournal
        priorq :: Query
priorq = String -> Query -> Query
forall a. Show a => String -> a -> a
dbg5 String
"priorq" (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ [Query] -> Query
And [Query
thisacctq, Query
tostartdateq, Query
datelessreportq]
        tostartdateq :: Query
tostartdateq =
          case Maybe Day
mstartdate of
            Just Day
_  -> DateSpan -> Query
Date (Maybe Day -> Maybe Day -> DateSpan
DateSpan Maybe Day
forall a. Maybe a
Nothing Maybe Day
mstartdate)
            Maybe Day
Nothing -> Query
None  -- no start date specified, there are no prior postings
        mstartdate :: Maybe Day
mstartdate = Bool -> Query -> Maybe Day
queryStartDate (ReportOpts -> Bool
date2_ ReportOpts
ropts) Query
reportq
        datelessreportq :: Query
datelessreportq = (Query -> Bool) -> Query -> Query
filterQuery (Bool -> Bool
not (Bool -> Bool) -> (Query -> Bool) -> Query -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Query -> Bool
queryIsDateOrDate2) Query
reportq

    items :: AccountTransactionsReport
items =
        Query
-> Query
-> MixedAmount
-> (MixedAmount -> MixedAmount)
-> [(Day, Transaction)]
-> AccountTransactionsReport
accountTransactionsReportItems Query
reportq Query
thisacctq MixedAmount
startbal MixedAmount -> MixedAmount
maNegate
      -- sort by the transaction's register date, then index, for accurate starting balance
      ([(Day, Transaction)] -> AccountTransactionsReport)
-> ([Transaction] -> [(Day, Transaction)])
-> [Transaction]
-> AccountTransactionsReport
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int
-> ([(Day, Transaction)] -> String)
-> [(Day, Transaction)]
-> [(Day, Transaction)]
forall a. Show a => Int -> (a -> String) -> a -> a
ptraceAtWith Int
5 ((String
"ts4:\n"String -> String -> String
forall a. [a] -> [a] -> [a]
++)(String -> String)
-> ([(Day, Transaction)] -> String)
-> [(Day, Transaction)]
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.[Transaction] -> String
pshowTransactions([Transaction] -> String)
-> ([(Day, Transaction)] -> [Transaction])
-> [(Day, Transaction)]
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.((Day, Transaction) -> Transaction)
-> [(Day, Transaction)] -> [Transaction]
forall a b. (a -> b) -> [a] -> [b]
map (Day, Transaction) -> Transaction
forall a b. (a, b) -> b
snd)
      ([(Day, Transaction)] -> [(Day, Transaction)])
-> ([Transaction] -> [(Day, Transaction)])
-> [Transaction]
-> [(Day, Transaction)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Day, Transaction) -> (Day, Transaction) -> Ordering)
-> [(Day, Transaction)] -> [(Day, Transaction)]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (((Day, Transaction) -> Down Day)
-> (Day, Transaction) -> (Day, Transaction) -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing (Day -> Down Day
forall a. a -> Down a
Down (Day -> Down Day)
-> ((Day, Transaction) -> Day) -> (Day, Transaction) -> Down Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Day, Transaction) -> Day
forall a b. (a, b) -> a
fst) ((Day, Transaction) -> (Day, Transaction) -> Ordering)
-> ((Day, Transaction) -> (Day, Transaction) -> Ordering)
-> (Day, Transaction)
-> (Day, Transaction)
-> Ordering
forall a. Semigroup a => a -> a -> a
<> ((Day, Transaction) -> Down Integer)
-> (Day, Transaction) -> (Day, Transaction) -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing (Integer -> Down Integer
forall a. a -> Down a
Down (Integer -> Down Integer)
-> ((Day, Transaction) -> Integer)
-> (Day, Transaction)
-> Down Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> Integer
tindex (Transaction -> Integer)
-> ((Day, Transaction) -> Transaction)
-> (Day, Transaction)
-> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Day, Transaction) -> Transaction
forall a b. (a, b) -> b
snd))
      ([(Day, Transaction)] -> [(Day, Transaction)])
-> ([Transaction] -> [(Day, Transaction)])
-> [Transaction]
-> [(Day, Transaction)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Transaction -> (Day, Transaction))
-> [Transaction] -> [(Day, Transaction)]
forall a b. (a -> b) -> [a] -> [b]
map (\Transaction
t -> (Query -> Query -> Transaction -> Day
transactionRegisterDate Query
reportq Query
thisacctq Transaction
t, Transaction
t))
      ([Transaction] -> AccountTransactionsReport)
-> [Transaction] -> AccountTransactionsReport
forall a b. (a -> b) -> a -> b
$ Journal -> [Transaction]
jtxns Journal
acctJournal

pshowTransactions :: [Transaction] -> String
pshowTransactions :: [Transaction] -> String
pshowTransactions = [String] -> String
forall a. Show a => a -> String
pshow ([String] -> String)
-> ([Transaction] -> [String]) -> [Transaction] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Transaction -> String) -> [Transaction] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (\Transaction
t -> [String] -> String
unwords [Day -> String
forall a. Show a => a -> String
show (Day -> String) -> Day -> String
forall a b. (a -> b) -> a -> b
$ Transaction -> Day
tdate Transaction
t, CommoditySymbol -> String
T.unpack (CommoditySymbol -> String) -> CommoditySymbol -> String
forall a b. (a -> b) -> a -> b
$ Transaction -> CommoditySymbol
tdescription Transaction
t])

-- | Generate transactions report items from a list of transactions,
-- using the provided user-specified report query, a query specifying
-- which account to use as the focus, a starting balance, and a sign-setting
-- function.
-- Each transaction is accompanied by the date that should be shown for it
-- in the report, which is not necessarily the transaction date; it is
-- the earliest of the posting dates which match both thisacctq and reportq,
-- otherwise the transaction's date if there are no matching postings.
accountTransactionsReportItems :: Query -> Query -> MixedAmount -> (MixedAmount -> MixedAmount)
                               -> [(Day, Transaction)] -> [AccountTransactionsReportItem]
accountTransactionsReportItems :: Query
-> Query
-> MixedAmount
-> (MixedAmount -> MixedAmount)
-> [(Day, Transaction)]
-> AccountTransactionsReport
accountTransactionsReportItems Query
reportq Query
thisacctq MixedAmount
bal MixedAmount -> MixedAmount
signfn =
    [Maybe AccountTransactionsReportItem] -> AccountTransactionsReport
forall a. [Maybe a] -> [a]
catMaybes ([Maybe AccountTransactionsReportItem]
 -> AccountTransactionsReport)
-> ([(Day, Transaction)] -> [Maybe AccountTransactionsReportItem])
-> [(Day, Transaction)]
-> AccountTransactionsReport
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (MixedAmount, [Maybe AccountTransactionsReportItem])
-> [Maybe AccountTransactionsReportItem]
forall a b. (a, b) -> b
snd ((MixedAmount, [Maybe AccountTransactionsReportItem])
 -> [Maybe AccountTransactionsReportItem])
-> ([(Day, Transaction)]
    -> (MixedAmount, [Maybe AccountTransactionsReportItem]))
-> [(Day, Transaction)]
-> [Maybe AccountTransactionsReportItem]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (MixedAmount
 -> (Day, Transaction)
 -> (MixedAmount, Maybe AccountTransactionsReportItem))
-> MixedAmount
-> [(Day, Transaction)]
-> (MixedAmount, [Maybe AccountTransactionsReportItem])
forall (t :: * -> *) a b c.
Traversable t =>
(a -> b -> (a, c)) -> a -> t b -> (a, t c)
mapAccumR (Query
-> Query
-> (MixedAmount -> MixedAmount)
-> MixedAmount
-> (Day, Transaction)
-> (MixedAmount, Maybe AccountTransactionsReportItem)
accountTransactionsReportItem Query
reportq Query
thisacctq MixedAmount -> MixedAmount
signfn) MixedAmount
bal

accountTransactionsReportItem :: Query -> Query -> (MixedAmount -> MixedAmount) -> MixedAmount
                              -> (Day, Transaction) -> (MixedAmount, Maybe AccountTransactionsReportItem)
accountTransactionsReportItem :: Query
-> Query
-> (MixedAmount -> MixedAmount)
-> MixedAmount
-> (Day, Transaction)
-> (MixedAmount, Maybe AccountTransactionsReportItem)
accountTransactionsReportItem Query
reportq Query
thisacctq MixedAmount -> MixedAmount
signfn MixedAmount
bal (Day
d, Transaction
torig)
    -- 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
    | [Posting] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Posting]
reportps = (MixedAmount
bal, Maybe AccountTransactionsReportItem
forall a. Maybe a
Nothing)  -- no matched postings in this transaction, skip it
    | Bool
otherwise     = (MixedAmount
b, AccountTransactionsReportItem
-> Maybe AccountTransactionsReportItem
forall a. a -> Maybe a
Just (Transaction
torig, Transaction
tacct{tdate :: Day
tdate=Day
d}, Int
numotheraccts Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1, CommoditySymbol
otheracctstr, MixedAmount
a, MixedAmount
b))
    where
      tacct :: Transaction
tacct@Transaction{tpostings :: Transaction -> [Posting]
tpostings=[Posting]
reportps} = Query -> Transaction -> Transaction
filterTransactionPostings Query
reportq Transaction
torig
      ([Posting]
thisacctps, [Posting]
otheracctps) = (Posting -> Bool) -> [Posting] -> ([Posting], [Posting])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition (Query -> Posting -> Bool
matchesPosting Query
thisacctq) [Posting]
reportps
      numotheraccts :: Int
numotheraccts = [CommoditySymbol] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([CommoditySymbol] -> Int) -> [CommoditySymbol] -> Int
forall a b. (a -> b) -> a -> b
$ [CommoditySymbol] -> [CommoditySymbol]
forall a. Eq a => [a] -> [a]
nub ([CommoditySymbol] -> [CommoditySymbol])
-> [CommoditySymbol] -> [CommoditySymbol]
forall a b. (a -> b) -> a -> b
$ (Posting -> CommoditySymbol) -> [Posting] -> [CommoditySymbol]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> CommoditySymbol
paccount [Posting]
otheracctps
      otheracctstr :: CommoditySymbol
otheracctstr | Query
thisacctq Query -> Query -> Bool
forall a. Eq a => a -> a -> Bool
== Query
None  = [Posting] -> CommoditySymbol
summarisePostingAccounts [Posting]
reportps     -- no current account ? summarise all matched postings
                   | Int
numotheraccts Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = [Posting] -> CommoditySymbol
summarisePostingAccounts [Posting]
thisacctps   -- only postings to current account ? summarise those
                   | Bool
otherwise          = [Posting] -> CommoditySymbol
summarisePostingAccounts [Posting]
otheracctps  -- summarise matched postings to other account(s)
      a :: MixedAmount
a = MixedAmount -> MixedAmount
signfn (MixedAmount -> MixedAmount)
-> (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MixedAmount -> MixedAmount
maNegate (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ [Posting] -> MixedAmount
sumPostings [Posting]
thisacctps
      b :: MixedAmount
b = MixedAmount
bal MixedAmount -> MixedAmount -> MixedAmount
`maPlus` MixedAmount
a

-- | 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 :: Query -> Query -> Transaction -> Day
transactionRegisterDate Query
reportq Query
thisacctq Transaction
t
  | [Posting] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Posting]
thisacctps = Transaction -> Day
tdate Transaction
t
  | Bool
otherwise       = [Day] -> Day
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum ([Day] -> Day) -> [Day] -> Day
forall a b. (a -> b) -> a -> b
$ (Posting -> Day) -> [Posting] -> [Day]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> Day
postingDate [Posting]
thisacctps
  where
    reportps :: [Posting]
reportps   = Transaction -> [Posting]
tpostings (Transaction -> [Posting]) -> Transaction -> [Posting]
forall a b. (a -> b) -> a -> b
$ Query -> Transaction -> Transaction
filterTransactionPostings Query
reportq Transaction
t
    thisacctps :: [Posting]
thisacctps = (Posting -> Bool) -> [Posting] -> [Posting]
forall a. (a -> Bool) -> [a] -> [a]
filter (Query -> Posting -> Bool
matchesPosting Query
thisacctq) [Posting]
reportps

-- -- | 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

-- | Generate a simplified summary of some postings' accounts.
-- To reduce noise, if there are both real and virtual postings, show only the real ones.
summarisePostingAccounts :: [Posting] -> Text
summarisePostingAccounts :: [Posting] -> CommoditySymbol
summarisePostingAccounts [Posting]
ps =
    CommoditySymbol -> [CommoditySymbol] -> CommoditySymbol
T.intercalate CommoditySymbol
", " ([CommoditySymbol] -> CommoditySymbol)
-> ([CommoditySymbol] -> [CommoditySymbol])
-> [CommoditySymbol]
-> CommoditySymbol
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CommoditySymbol -> CommoditySymbol)
-> [CommoditySymbol] -> [CommoditySymbol]
forall a b. (a -> b) -> [a] -> [b]
map CommoditySymbol -> CommoditySymbol
accountSummarisedName ([CommoditySymbol] -> [CommoditySymbol])
-> ([CommoditySymbol] -> [CommoditySymbol])
-> [CommoditySymbol]
-> [CommoditySymbol]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [CommoditySymbol] -> [CommoditySymbol]
forall a. Eq a => [a] -> [a]
nub ([CommoditySymbol] -> CommoditySymbol)
-> [CommoditySymbol] -> CommoditySymbol
forall a b. (a -> b) -> a -> b
$ (Posting -> CommoditySymbol) -> [Posting] -> [CommoditySymbol]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> CommoditySymbol
paccount [Posting]
displayps
  where
    realps :: [Posting]
realps = (Posting -> Bool) -> [Posting] -> [Posting]
forall a. (a -> Bool) -> [a] -> [a]
filter Posting -> Bool
isReal [Posting]
ps
    displayps :: [Posting]
displayps | [Posting] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Posting]
realps = [Posting]
ps
              | Bool
otherwise   = [Posting]
realps

-- | Split an  account transactions report whose items may involve several commodities,
-- into one or more single-commodity account transactions reports.
accountTransactionsReportByCommodity :: AccountTransactionsReport -> [(CommoditySymbol, AccountTransactionsReport)]
accountTransactionsReportByCommodity :: AccountTransactionsReport
-> [(CommoditySymbol, AccountTransactionsReport)]
accountTransactionsReportByCommodity AccountTransactionsReport
tr =
  [(CommoditySymbol
c, CommoditySymbol
-> AccountTransactionsReport -> AccountTransactionsReport
filterAccountTransactionsReportByCommodity CommoditySymbol
c AccountTransactionsReport
tr) | CommoditySymbol
c <- AccountTransactionsReport -> [CommoditySymbol]
forall a b c d f.
[(a, b, c, d, MixedAmount, f)] -> [CommoditySymbol]
commodities AccountTransactionsReport
tr]
  where
    commodities :: [(a, b, c, d, MixedAmount, f)] -> [CommoditySymbol]
commodities = [CommoditySymbol] -> [CommoditySymbol]
forall a. Ord a => [a] -> [a]
nubSort ([CommoditySymbol] -> [CommoditySymbol])
-> ([(a, b, c, d, MixedAmount, f)] -> [CommoditySymbol])
-> [(a, b, c, d, MixedAmount, f)]
-> [CommoditySymbol]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Amount -> CommoditySymbol) -> [Amount] -> [CommoditySymbol]
forall a b. (a -> b) -> [a] -> [b]
map Amount -> CommoditySymbol
acommodity ([Amount] -> [CommoditySymbol])
-> ([(a, b, c, d, MixedAmount, f)] -> [Amount])
-> [(a, b, c, d, MixedAmount, f)]
-> [CommoditySymbol]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, b, c, d, MixedAmount, f) -> [Amount])
-> [(a, b, c, d, MixedAmount, f)] -> [Amount]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (MixedAmount -> [Amount]
amounts (MixedAmount -> [Amount])
-> ((a, b, c, d, MixedAmount, f) -> MixedAmount)
-> (a, b, c, d, MixedAmount, f)
-> [Amount]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b, c, d, MixedAmount, f) -> MixedAmount
forall a b c d e f. (a, b, c, d, e, f) -> e
triAmount)

-- | Remove account 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.
filterAccountTransactionsReportByCommodity :: CommoditySymbol -> AccountTransactionsReport -> AccountTransactionsReport
filterAccountTransactionsReportByCommodity :: CommoditySymbol
-> AccountTransactionsReport -> AccountTransactionsReport
filterAccountTransactionsReportByCommodity CommoditySymbol
c =
    AccountTransactionsReport -> AccountTransactionsReport
forall a b c d.
[(a, b, c, d, MixedAmount, MixedAmount)]
-> [(a, b, c, d, MixedAmount, MixedAmount)]
fixTransactionsReportItemBalances (AccountTransactionsReport -> AccountTransactionsReport)
-> (AccountTransactionsReport -> AccountTransactionsReport)
-> AccountTransactionsReport
-> AccountTransactionsReport
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (AccountTransactionsReportItem -> AccountTransactionsReport)
-> AccountTransactionsReport -> AccountTransactionsReport
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (CommoditySymbol
-> AccountTransactionsReportItem -> AccountTransactionsReport
forall a b c d f.
CommoditySymbol
-> (a, b, c, d, MixedAmount, f) -> [(a, b, c, d, MixedAmount, f)]
filterTransactionsReportItemByCommodity CommoditySymbol
c)
  where
    filterTransactionsReportItemByCommodity :: CommoditySymbol
-> (a, b, c, d, MixedAmount, f) -> [(a, b, c, d, MixedAmount, f)]
filterTransactionsReportItemByCommodity CommoditySymbol
c (a
t,b
t2,c
s,d
o,MixedAmount
a,f
bal)
      | CommoditySymbol
c CommoditySymbol -> [CommoditySymbol] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [CommoditySymbol]
cs = [(a, b, c, d, MixedAmount, f)
item']
      | Bool
otherwise   = []
      where
        cs :: [CommoditySymbol]
cs = (Amount -> CommoditySymbol) -> [Amount] -> [CommoditySymbol]
forall a b. (a -> b) -> [a] -> [b]
map Amount -> CommoditySymbol
acommodity ([Amount] -> [CommoditySymbol]) -> [Amount] -> [CommoditySymbol]
forall a b. (a -> b) -> a -> b
$ MixedAmount -> [Amount]
amounts MixedAmount
a
        item' :: (a, b, c, d, MixedAmount, f)
item' = (a
t,b
t2,c
s,d
o,MixedAmount
a',f
bal)
        a' :: MixedAmount
a' = CommoditySymbol -> MixedAmount -> MixedAmount
filterMixedAmountByCommodity CommoditySymbol
c MixedAmount
a

    fixTransactionsReportItemBalances :: [(a, b, c, d, MixedAmount, MixedAmount)]
-> [(a, b, c, d, MixedAmount, MixedAmount)]
fixTransactionsReportItemBalances [] = []
    fixTransactionsReportItemBalances [(a, b, c, d, MixedAmount, MixedAmount)
i] = [(a, b, c, d, MixedAmount, MixedAmount)
i]
    fixTransactionsReportItemBalances [(a, b, c, d, MixedAmount, MixedAmount)]
items = [(a, b, c, d, MixedAmount, MixedAmount)]
-> [(a, b, c, d, MixedAmount, MixedAmount)]
forall a. [a] -> [a]
reverse ([(a, b, c, d, MixedAmount, MixedAmount)]
 -> [(a, b, c, d, MixedAmount, MixedAmount)])
-> [(a, b, c, d, MixedAmount, MixedAmount)]
-> [(a, b, c, d, MixedAmount, MixedAmount)]
forall a b. (a -> b) -> a -> b
$ (a, b, c, d, MixedAmount, MixedAmount)
i(a, b, c, d, MixedAmount, MixedAmount)
-> [(a, b, c, d, MixedAmount, MixedAmount)]
-> [(a, b, c, d, MixedAmount, MixedAmount)]
forall a. a -> [a] -> [a]
:(MixedAmount
-> [(a, b, c, d, MixedAmount, MixedAmount)]
-> [(a, b, c, d, MixedAmount, MixedAmount)]
forall a b c d f.
MixedAmount
-> [(a, b, c, d, MixedAmount, f)]
-> [(a, b, c, d, MixedAmount, MixedAmount)]
go MixedAmount
startbal [(a, b, c, d, MixedAmount, MixedAmount)]
is)
      where
        (a, b, c, d, MixedAmount, MixedAmount)
i:[(a, b, c, d, MixedAmount, MixedAmount)]
is = [(a, b, c, d, MixedAmount, MixedAmount)]
-> [(a, b, c, d, MixedAmount, MixedAmount)]
forall a. [a] -> [a]
reverse [(a, b, c, d, MixedAmount, MixedAmount)]
items
        startbal :: MixedAmount
startbal = CommoditySymbol -> MixedAmount -> MixedAmount
filterMixedAmountByCommodity CommoditySymbol
c (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ (a, b, c, d, MixedAmount, MixedAmount) -> MixedAmount
forall a b c d e f. (a, b, c, d, e, f) -> f
triBalance (a, b, c, d, MixedAmount, MixedAmount)
i
        go :: MixedAmount
-> [(a, b, c, d, MixedAmount, f)]
-> [(a, b, c, d, MixedAmount, MixedAmount)]
go MixedAmount
_ [] = []
        go MixedAmount
bal ((a
t,b
t2,c
s,d
o,MixedAmount
amt,f
_):[(a, b, c, d, MixedAmount, f)]
is) = (a
t,b
t2,c
s,d
o,MixedAmount
amt,MixedAmount
bal')(a, b, c, d, MixedAmount, MixedAmount)
-> [(a, b, c, d, MixedAmount, MixedAmount)]
-> [(a, b, c, d, MixedAmount, MixedAmount)]
forall a. a -> [a] -> [a]
:MixedAmount
-> [(a, b, c, d, MixedAmount, f)]
-> [(a, b, c, d, MixedAmount, MixedAmount)]
go MixedAmount
bal' [(a, b, c, d, MixedAmount, f)]
is
          where bal' :: MixedAmount
bal' = MixedAmount
bal MixedAmount -> MixedAmount -> MixedAmount
`maPlus` MixedAmount
amt

-- tests

tests_AccountTransactionsReport :: TestTree
tests_AccountTransactionsReport = String -> [TestTree] -> TestTree
testGroup String
"AccountTransactionsReport" [
 ]