{-# LANGUAGE OverloadedStrings, RecordWildCards, FlexibleInstances #-}
module Hledger.Reports.AccountTransactionsReport (
AccountTransactionsReport,
AccountTransactionsReportItem,
accountTransactionsReport,
accountTransactionsReportItems,
transactionRegisterDate,
tests_AccountTransactionsReport
)
where
import Data.List
import Data.Ord
import Data.Maybe
import Data.Text (Text)
import qualified Data.Text as T
import Data.Time.Calendar
import Hledger.Data
import Hledger.Query
import Hledger.Reports.ReportOptions
import Hledger.Utils
type AccountTransactionsReport = [AccountTransactionsReportItem]
type AccountTransactionsReportItem =
(
Transaction
,Transaction
,Bool
,Text
,MixedAmount
,MixedAmount
)
accountTransactionsReport :: ReportSpec -> Journal -> Query -> Query -> AccountTransactionsReport
accountTransactionsReport :: ReportSpec
-> Journal -> Query -> Query -> AccountTransactionsReport
accountTransactionsReport rspec :: ReportSpec
rspec@ReportSpec{rsOpts :: ReportSpec -> ReportOpts
rsOpts=ReportOpts
ropts} Journal
j Query
reportq Query
thisacctq = AccountTransactionsReport
items
where
reportq' :: Query
reportq' =
Query
reportq
ts1 :: [Transaction]
ts1 =
Journal -> [Transaction]
jtxns Journal
j
symq :: Query
symq = (Query -> Bool) -> Query -> Query
filterQuery Query -> Bool
queryIsSym Query
reportq'
ts2 :: [Transaction]
ts2 =
Int -> ([Transaction] -> String) -> [Transaction] -> [Transaction]
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)
-> ([Transaction] -> String) -> [Transaction] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.[Transaction] -> String
pshowTransactions) ([Transaction] -> [Transaction]) -> [Transaction] -> [Transaction]
forall a b. (a -> b) -> a -> b
$
(if Query -> Bool
queryIsNull Query
symq then [Transaction] -> [Transaction]
forall a. a -> a
id else (Transaction -> Transaction) -> [Transaction] -> [Transaction]
forall a b. (a -> b) -> [a] -> [b]
map (Query -> Transaction -> Transaction
filterTransactionAmounts Query
symq)) [Transaction]
ts1
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'
ts3 :: [Transaction]
ts3 =
Int -> String -> [Transaction] -> [Transaction]
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) ([Transaction] -> [Transaction]) -> [Transaction] -> [Transaction]
forall a b. (a -> b) -> a -> b
$
Int -> ([Transaction] -> String) -> [Transaction] -> [Transaction]
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)
-> ([Transaction] -> String) -> [Transaction] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.[Transaction] -> String
pshowTransactions) ([Transaction] -> [Transaction]) -> [Transaction] -> [Transaction]
forall a b. (a -> b) -> a -> b
$
(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
. Query -> Transaction -> Transaction
filterTransactionPostings ([Query] -> Query
And [Query
realq, Query
statusq])) [Transaction]
ts2
prices :: PriceOracle
prices = Bool -> Journal -> PriceOracle
journalPriceOracle (ReportOpts -> Bool
infer_value_ ReportOpts
ropts) Journal
j
styles :: Map CommoditySymbol AmountStyle
styles = Journal -> Map CommoditySymbol AmountStyle
journalCommodityStyles Journal
j
periodlast :: Day
periodlast =
Day -> Maybe Day -> Day
forall a. a -> Maybe a -> a
fromMaybe (String -> Day
forall a. String -> a
error' String
"journalApplyValuation: expected a non-empty journal") (Maybe Day -> Day) -> Maybe Day -> Day
forall a b. (a -> b) -> a -> b
$
ReportSpec -> Journal -> Maybe Day
reportPeriodOrJournalLastDay ReportSpec
rspec Journal
j
tval :: Transaction -> Transaction
tval = PriceOracle
-> Map CommoditySymbol AmountStyle
-> Day
-> Day
-> Costing
-> Maybe ValuationType
-> Transaction
-> Transaction
transactionApplyCostValuation PriceOracle
prices Map CommoditySymbol AmountStyle
styles Day
periodlast (ReportSpec -> Day
rsToday ReportSpec
rspec) (ReportOpts -> Costing
cost_ ReportOpts
ropts) (Maybe ValuationType -> Transaction -> Transaction)
-> Maybe ValuationType -> Transaction -> Transaction
forall a b. (a -> b) -> a -> b
$ ReportOpts -> Maybe ValuationType
value_ ReportOpts
ropts
ts4 :: [Transaction]
ts4 =
Int -> ([Transaction] -> String) -> [Transaction] -> [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)
-> ([Transaction] -> String) -> [Transaction] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.[Transaction] -> String
pshowTransactions) ([Transaction] -> [Transaction]) -> [Transaction] -> [Transaction]
forall a b. (a -> b) -> a -> b
$
(Transaction -> Transaction) -> [Transaction] -> [Transaction]
forall a b. (a -> b) -> [a] -> [b]
map Transaction -> Transaction
tval [Transaction]
ts3
ts5 :: [Transaction]
ts5 =
Int -> ([Transaction] -> String) -> [Transaction] -> [Transaction]
forall a. Show a => Int -> (a -> String) -> a -> a
ptraceAtWith Int
5 ((String
"ts5:\n"String -> String -> String
forall a. [a] -> [a] -> [a]
++)(String -> String)
-> ([Transaction] -> String) -> [Transaction] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.[Transaction] -> String
pshowTransactions) ([Transaction] -> [Transaction]) -> [Transaction] -> [Transaction]
forall a b. (a -> b) -> a -> b
$
(Transaction -> Transaction -> Ordering)
-> [Transaction] -> [Transaction]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy ((Transaction -> Day) -> Transaction -> Transaction -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing (Query -> Query -> Transaction -> Day
transactionRegisterDate Query
reportq' Query
thisacctq)) [Transaction]
ts4
startbal :: MixedAmount
startbal
| ReportOpts -> BalanceType
balancetype_ ReportOpts
ropts BalanceType -> BalanceType -> Bool
forall a. Eq a => a -> a -> Bool
== BalanceType
HistoricalBalance = [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]) -> [Posting] -> [Posting]
forall a b. (a -> b) -> a -> b
$
(Posting -> Bool) -> [Posting] -> [Posting]
forall a. (a -> Bool) -> [a] -> [a]
filter (Query -> Posting -> Bool
matchesPosting
(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]))
([Posting] -> [Posting]) -> [Posting] -> [Posting]
forall a b. (a -> b) -> a -> b
$ [Transaction] -> [Posting]
transactionsPostings [Transaction]
ts5
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
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'
filtertxns :: Bool
filtertxns = ReportOpts -> Bool
txn_dates_ ReportOpts
ropts
items :: AccountTransactionsReport
items = AccountTransactionsReport -> AccountTransactionsReport
forall a. [a] -> [a]
reverse (AccountTransactionsReport -> AccountTransactionsReport)
-> AccountTransactionsReport -> AccountTransactionsReport
forall a b. (a -> b) -> a -> b
$
Query
-> Query
-> MixedAmount
-> (MixedAmount -> MixedAmount)
-> [Transaction]
-> AccountTransactionsReport
accountTransactionsReportItems Query
reportq' Query
thisacctq MixedAmount
startbal MixedAmount -> MixedAmount
forall a. Num a => a -> a
negate ([Transaction] -> AccountTransactionsReport)
-> [Transaction] -> AccountTransactionsReport
forall a b. (a -> b) -> a -> b
$
(if Bool
filtertxns then (Transaction -> Bool) -> [Transaction] -> [Transaction]
forall a. (a -> Bool) -> [a] -> [a]
filter (Query
reportq' Query -> Transaction -> Bool
`matchesTransaction`) else [Transaction] -> [Transaction]
forall a. a -> a
id) ([Transaction] -> [Transaction]) -> [Transaction] -> [Transaction]
forall a b. (a -> b) -> a -> b
$
[Transaction]
ts5
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])
accountTransactionsReportItems :: Query -> Query -> MixedAmount -> (MixedAmount -> MixedAmount) -> [Transaction] -> [AccountTransactionsReportItem]
accountTransactionsReportItems :: Query
-> Query
-> MixedAmount
-> (MixedAmount -> MixedAmount)
-> [Transaction]
-> AccountTransactionsReport
accountTransactionsReportItems Query
reportq Query
thisacctq MixedAmount
bal MixedAmount -> MixedAmount
signfn =
[Maybe AccountTransactionsReportItem] -> AccountTransactionsReport
forall a. [Maybe a] -> [a]
catMaybes ([Maybe AccountTransactionsReportItem]
-> AccountTransactionsReport)
-> ([Transaction] -> [Maybe AccountTransactionsReportItem])
-> [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])
-> ([Transaction]
-> (MixedAmount, [Maybe AccountTransactionsReportItem]))
-> [Transaction]
-> [Maybe AccountTransactionsReportItem]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(MixedAmount
-> Transaction
-> (MixedAmount, Maybe AccountTransactionsReportItem))
-> MixedAmount
-> [Transaction]
-> (MixedAmount, [Maybe AccountTransactionsReportItem])
forall (t :: * -> *) a b c.
Traversable t =>
(a -> b -> (a, c)) -> a -> t b -> (a, t c)
mapAccumL (Query
-> Query
-> (MixedAmount -> MixedAmount)
-> MixedAmount
-> Transaction
-> (MixedAmount, Maybe AccountTransactionsReportItem)
accountTransactionsReportItem Query
reportq Query
thisacctq MixedAmount -> MixedAmount
signfn) MixedAmount
bal
accountTransactionsReportItem :: Query -> Query -> (MixedAmount -> MixedAmount) -> MixedAmount -> Transaction -> (MixedAmount, Maybe AccountTransactionsReportItem)
accountTransactionsReportItem :: Query
-> Query
-> (MixedAmount -> MixedAmount)
-> MixedAmount
-> Transaction
-> (MixedAmount, Maybe AccountTransactionsReportItem)
accountTransactionsReportItem Query
reportq Query
thisacctq MixedAmount -> MixedAmount
signfn MixedAmount
bal Transaction
torig = (MixedAmount, Maybe AccountTransactionsReportItem)
balItem
where
tfiltered :: Transaction
tfiltered@Transaction{tpostings :: Transaction -> [Posting]
tpostings=[Posting]
reportps} = Query -> Transaction -> Transaction
filterTransactionPostings Query
reportq Transaction
torig
tacct :: Transaction
tacct = Transaction
tfiltered{tdate :: Day
tdate=Query -> Query -> Transaction -> Day
transactionRegisterDate Query
reportq Query
thisacctq Transaction
tfiltered}
balItem :: (MixedAmount, Maybe AccountTransactionsReportItem)
balItem = case [Posting]
reportps of
[] -> (MixedAmount
bal, Maybe AccountTransactionsReportItem
forall a. Maybe a
Nothing)
[Posting]
_ -> (MixedAmount
b, AccountTransactionsReportItem
-> Maybe AccountTransactionsReportItem
forall a. a -> Maybe a
Just (Transaction
torig, Transaction
tacct, Int
numotheraccts Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1, CommoditySymbol
otheracctstr, MixedAmount
a, MixedAmount
b))
where
([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
| Int
numotheraccts Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = [Posting] -> CommoditySymbol
summarisePostingAccounts [Posting]
thisacctps
| Bool
otherwise = [Posting] -> CommoditySymbol
summarisePostingAccounts [Posting]
otheracctps
a :: MixedAmount
a = MixedAmount -> MixedAmount
signfn (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ MixedAmount -> MixedAmount
forall a. Num a => a -> a
negate (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ [MixedAmount] -> MixedAmount
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([MixedAmount] -> MixedAmount) -> [MixedAmount] -> MixedAmount
forall a b. (a -> b) -> a -> b
$ (Posting -> MixedAmount) -> [Posting] -> [MixedAmount]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> MixedAmount
pamount [Posting]
thisacctps
b :: MixedAmount
b = MixedAmount
bal MixedAmount -> MixedAmount -> MixedAmount
forall a. Num a => a -> a -> a
+ MixedAmount
a
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
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
tests_AccountTransactionsReport :: TestTree
tests_AccountTransactionsReport = String -> [TestTree] -> TestTree
tests String
"AccountTransactionsReport" [
]