{-# LANGUAGE OverloadedStrings, RecordWildCards, FlexibleInstances #-}
module Hledger.Reports.TransactionsReport (
TransactionsReport,
TransactionsReportItem,
transactionsReport,
transactionsReportByCommodity,
triOrigTransaction,
triDate,
triAmount,
triBalance,
triCommodityAmount,
triCommodityBalance,
tests_TransactionsReport
)
where
import Data.List
import Data.List.Extra (nubSort)
import Data.Text (Text)
import Data.Ord
import Hledger.Data
import Hledger.Query
import Hledger.Reports.ReportOptions
import Hledger.Reports.AccountTransactionsReport
import Hledger.Utils
type TransactionsReport = [TransactionsReportItem]
type TransactionsReportItem = (Transaction
,Transaction
,Bool
,Text
,MixedAmount
,MixedAmount
)
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
transactionsReport :: ReportOpts -> Journal -> Query -> TransactionsReport
transactionsReport :: ReportOpts -> Journal -> Query -> TransactionsReport
transactionsReport ReportOpts
opts Journal
j Query
q = TransactionsReport
items
where
items :: TransactionsReport
items = TransactionsReport -> TransactionsReport
forall a. [a] -> [a]
reverse (TransactionsReport -> TransactionsReport)
-> TransactionsReport -> TransactionsReport
forall a b. (a -> b) -> a -> b
$ Query
-> Query
-> MixedAmount
-> (MixedAmount -> MixedAmount)
-> [Transaction]
-> TransactionsReport
accountTransactionsReportItems Query
q Query
None MixedAmount
nullmixedamt MixedAmount -> MixedAmount
forall a. a -> a
id [Transaction]
ts
ts :: [Transaction]
ts = (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 Transaction -> Day
date) ([Transaction] -> [Transaction]) -> [Transaction] -> [Transaction]
forall a b. (a -> b) -> a -> b
$ (Transaction -> Bool) -> [Transaction] -> [Transaction]
forall a. (a -> Bool) -> [a] -> [a]
filter (Query
q Query -> Transaction -> Bool
`matchesTransaction`) ([Transaction] -> [Transaction]) -> [Transaction] -> [Transaction]
forall a b. (a -> b) -> a -> b
$ Journal -> [Transaction]
jtxns (Journal -> [Transaction]) -> Journal -> [Transaction]
forall a b. (a -> b) -> a -> b
$ ReportOpts -> Journal -> Journal
journalSelectingAmountFromOpts ReportOpts
opts Journal
j
date :: Transaction -> Day
date = ReportOpts -> Transaction -> Day
transactionDateFn ReportOpts
opts
transactionsReportByCommodity :: TransactionsReport -> [(CommoditySymbol, TransactionsReport)]
transactionsReportByCommodity :: TransactionsReport -> [(CommoditySymbol, TransactionsReport)]
transactionsReportByCommodity TransactionsReport
tr =
[(CommoditySymbol
c, CommoditySymbol -> TransactionsReport -> TransactionsReport
filterTransactionsReportByCommodity CommoditySymbol
c TransactionsReport
tr) | CommoditySymbol
c <- TransactionsReport -> [CommoditySymbol]
forall a b c d f.
[(a, b, c, d, MixedAmount, f)] -> [CommoditySymbol]
transactionsReportCommodities TransactionsReport
tr]
where
transactionsReportCommodities :: [(a, b, c, d, MixedAmount, f)] -> [CommoditySymbol]
transactionsReportCommodities = [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)
filterTransactionsReportByCommodity :: CommoditySymbol -> TransactionsReport -> TransactionsReport
filterTransactionsReportByCommodity :: CommoditySymbol -> TransactionsReport -> TransactionsReport
filterTransactionsReportByCommodity CommoditySymbol
c =
TransactionsReport -> TransactionsReport
forall a b c d.
[(a, b, c, d, MixedAmount, MixedAmount)]
-> [(a, b, c, d, MixedAmount, MixedAmount)]
fixTransactionsReportItemBalances (TransactionsReport -> TransactionsReport)
-> (TransactionsReport -> TransactionsReport)
-> TransactionsReport
-> TransactionsReport
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Transaction, Transaction, Bool, CommoditySymbol, MixedAmount,
MixedAmount)
-> TransactionsReport)
-> TransactionsReport -> TransactionsReport
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (CommoditySymbol
-> (Transaction, Transaction, Bool, CommoditySymbol, MixedAmount,
MixedAmount)
-> TransactionsReport
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 t a b c d f.
Num t =>
t -> [(a, b, c, d, t, f)] -> [(a, b, c, d, t, t)]
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 :: t -> [(a, b, c, d, t, f)] -> [(a, b, c, d, t, t)]
go t
_ [] = []
go t
bal ((a
t,b
t2,c
s,d
o,t
amt,f
_):[(a, b, c, d, t, f)]
is) = (a
t,b
t2,c
s,d
o,t
amt,t
bal')(a, b, c, d, t, t) -> [(a, b, c, d, t, t)] -> [(a, b, c, d, t, t)]
forall a. a -> [a] -> [a]
:t -> [(a, b, c, d, t, f)] -> [(a, b, c, d, t, t)]
go t
bal' [(a, b, c, d, t, f)]
is
where bal' :: t
bal' = t
bal t -> t -> t
forall a. Num a => a -> a -> a
+ t
amt
tests_TransactionsReport :: TestTree
tests_TransactionsReport = String -> [TestTree] -> TestTree
tests String
"TransactionsReport" [
]