{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
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
type AccountTransactionsReport = [AccountTransactionsReportItem]
type AccountTransactionsReportItem =
(
Transaction
,Transaction
,Bool
,Text
,MixedAmount
,MixedAmount
)
instance HasAmounts AccountTransactionsReportItem where
styleAmounts :: Map Text AmountStyle
-> AccountTransactionsReportItem -> AccountTransactionsReportItem
styleAmounts Map Text AmountStyle
styles (Transaction
torig,Transaction
tacct,Bool
b,Text
c,MixedAmount
a1,MixedAmount
a2) =
(Map Text AmountStyle -> Transaction -> Transaction
forall a. HasAmounts a => Map Text AmountStyle -> a -> a
styleAmounts Map Text AmountStyle
styles Transaction
torig,Map Text AmountStyle -> Transaction -> Transaction
forall a. HasAmounts a => Map Text AmountStyle -> a -> a
styleAmounts Map Text AmountStyle
styles Transaction
tacct,Bool
b,Text
c,Map Text AmountStyle -> MixedAmount -> MixedAmount
forall a. HasAmounts a => Map Text AmountStyle -> a -> a
styleAmounts Map Text AmountStyle
styles MixedAmount
a1,Map Text AmountStyle -> MixedAmount -> MixedAmount
forall a. HasAmounts a => Map Text AmountStyle -> a -> a
styleAmounts Map Text AmountStyle
styles MixedAmount
a2)
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 :: Text -> (a, b, c, d, MixedAmount, f) -> MixedAmount
triCommodityAmount Text
c = Text -> MixedAmount -> MixedAmount
filterMixedAmountByCommodity Text
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 :: Text -> (a, b, c, d, e, MixedAmount) -> MixedAmount
triCommodityBalance Text
c = Text -> MixedAmount -> MixedAmount
filterMixedAmountByCommodity Text
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
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
wd :: WhichDate
wd = ReportOpts -> WhichDate
whichDate ReportOpts
ropts
acctJournal :: Journal
acctJournal =
(if ReportOpts -> Bool
show_costs_ ReportOpts
ropts then Journal -> Journal
forall a. a -> a
id else (MixedAmount -> MixedAmount) -> Journal -> Journal
journalMapPostingAmounts MixedAmount -> MixedAmount
mixedAmountStripCosts)
(Journal -> Journal) -> (Journal -> Journal) -> Journal -> Journal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> (Journal -> String) -> Journal -> Journal
forall a. Int -> (a -> String) -> a -> a
traceOrLogAtWith 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)
(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. Int -> (a -> String) -> a -> a
traceOrLogAtWith 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)
(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)
(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
traceOrLogAt 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. Int -> (a -> String) -> a -> a
traceOrLogAtWith 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 = filter (matchesTransaction thisacctq . relevantPostings) $ jtxns 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 EFDay -> Maybe EFDay -> DateSpan
DateSpan Maybe EFDay
forall a. Maybe a
Nothing (Day -> EFDay
Exact (Day -> EFDay) -> Maybe Day -> Maybe EFDay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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
items :: AccountTransactionsReport
items =
Query
-> Query
-> MixedAmount
-> (MixedAmount -> MixedAmount)
-> (Text -> Maybe AccountType)
-> [(Day, Transaction)]
-> AccountTransactionsReport
accountTransactionsReportItems Query
reportq Query
thisacctq MixedAmount
startbal MixedAmount -> MixedAmount
maNegate (Journal -> Text -> Maybe AccountType
journalAccountType Journal
j)
([(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. Int -> (a -> String) -> a -> a
traceAtWith 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 -> (WhichDate -> Query -> Query -> Transaction -> Day
transactionRegisterDate WhichDate
wd Query
reportq Query
thisacctq Transaction
t, Transaction
t))
([Transaction] -> [(Day, Transaction)])
-> ([Transaction] -> [Transaction])
-> [Transaction]
-> [(Day, Transaction)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Transaction -> Transaction) -> [Transaction] -> [Transaction]
forall a b. (a -> b) -> [a] -> [b]
map (if ReportOpts -> Bool
invert_ ReportOpts
ropts then (\Transaction
t -> Transaction
t{tpostings = map postingNegateMainAmount $ tpostings t}) else Transaction -> Transaction
forall a. a -> a
id)
([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, Text -> String
T.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ Transaction -> Text
tdescription Transaction
t])
accountTransactionsReportItems :: Query -> Query -> MixedAmount -> (MixedAmount -> MixedAmount)
-> (AccountName -> Maybe AccountType) -> [(Day, Transaction)]
-> [AccountTransactionsReportItem]
accountTransactionsReportItems :: Query
-> Query
-> MixedAmount
-> (MixedAmount -> MixedAmount)
-> (Text -> Maybe AccountType)
-> [(Day, Transaction)]
-> AccountTransactionsReport
accountTransactionsReportItems Query
reportq Query
thisacctq MixedAmount
bal MixedAmount -> MixedAmount
signfn Text -> Maybe AccountType
accttypefn =
[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 :: * -> *) s a b.
Traversable t =>
(s -> a -> (s, b)) -> s -> t a -> (s, t b)
mapAccumR (Query
-> Query
-> (MixedAmount -> MixedAmount)
-> (Text -> Maybe AccountType)
-> MixedAmount
-> (Day, Transaction)
-> (MixedAmount, Maybe AccountTransactionsReportItem)
accountTransactionsReportItem Query
reportq Query
thisacctq MixedAmount -> MixedAmount
signfn Text -> Maybe AccountType
accttypefn) MixedAmount
bal
accountTransactionsReportItem :: Query -> Query -> (MixedAmount -> MixedAmount)
-> (AccountName -> Maybe AccountType) -> MixedAmount -> (Day, Transaction)
-> (MixedAmount, Maybe AccountTransactionsReportItem)
accountTransactionsReportItem :: Query
-> Query
-> (MixedAmount -> MixedAmount)
-> (Text -> Maybe AccountType)
-> MixedAmount
-> (Day, Transaction)
-> (MixedAmount, Maybe AccountTransactionsReportItem)
accountTransactionsReportItem Query
reportq Query
thisacctq MixedAmount -> MixedAmount
signfn Text -> Maybe AccountType
accttypefn MixedAmount
bal (Day
d, Transaction
t)
| [Posting] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Posting]
reportps = (MixedAmount
bal, Maybe AccountTransactionsReportItem
forall a. Maybe a
Nothing)
| Bool
otherwise = (MixedAmount
bal', AccountTransactionsReportItem
-> Maybe AccountTransactionsReportItem
forall a. a -> Maybe a
Just (Transaction
t, Transaction
tacct{tdate=d}, Int
numotheraccts Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1, Text
otheracctstr, MixedAmount
amt, MixedAmount
bal'))
where
tacct :: Transaction
tacct@Transaction{tpostings :: Transaction -> [Posting]
tpostings=[Posting]
reportps} = (Text -> Maybe AccountType) -> Query -> Transaction -> Transaction
filterTransactionPostingsExtra Text -> Maybe AccountType
accttypefn Query
reportq Transaction
t
([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 = [Text] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Text] -> Int) -> [Text] -> Int
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text]
forall a. Eq a => [a] -> [a]
nub ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ (Posting -> Text) -> [Posting] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> Text
paccount [Posting]
otheracctps
otheracctstr :: Text
otheracctstr | Query
thisacctq Query -> Query -> Bool
forall a. Eq a => a -> a -> Bool
== Query
None = [Posting] -> Text
summarisePostingAccounts [Posting]
reportps
| Int
numotheraccts Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = [Posting] -> Text
summarisePostingAccounts [Posting]
thisacctps
| Bool
otherwise = [Posting] -> Text
summarisePostingAccounts [Posting]
otheracctps
amt :: MixedAmount
amt
| [Posting] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Posting]
thisacctps = MixedAmount -> MixedAmount
signfn (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ [Posting] -> MixedAmount
sumPostings [Posting]
otheracctps
| Bool
otherwise = 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
bal' :: MixedAmount
bal' = MixedAmount
bal MixedAmount -> MixedAmount -> MixedAmount
`maPlus` MixedAmount
amt
transactionRegisterDate :: WhichDate -> Query -> Query -> Transaction -> Day
transactionRegisterDate :: WhichDate -> Query -> Query -> Transaction -> Day
transactionRegisterDate WhichDate
wd Query
reportq Query
thisacctq Transaction
t
| Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [Posting] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Posting]
thisacctps = [Day] -> Day
forall a. Ord a => [a] -> a
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 (WhichDate -> Posting -> Day
postingDateOrDate2 WhichDate
wd) [Posting]
thisacctps
| Bool
otherwise = WhichDate -> Transaction -> Day
transactionDateOrDate2 WhichDate
wd Transaction
t
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] -> Text
summarisePostingAccounts [Posting]
ps =
Text -> [Text] -> Text
T.intercalate Text
", " ([Text] -> Text) -> ([Text] -> [Text]) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Text
accountSummarisedName ([Text] -> [Text]) -> ([Text] -> [Text]) -> [Text] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [Text]
forall a. Eq a => [a] -> [a]
nub ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Posting -> Text) -> [Posting] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> Text
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 a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Posting]
realps = [Posting]
ps
| Bool
otherwise = [Posting]
realps
accountTransactionsReportByCommodity :: AccountTransactionsReport -> [(CommoditySymbol, AccountTransactionsReport)]
accountTransactionsReportByCommodity :: AccountTransactionsReport -> [(Text, AccountTransactionsReport)]
accountTransactionsReportByCommodity AccountTransactionsReport
tr =
[(Text
c, Text -> AccountTransactionsReport -> AccountTransactionsReport
filterAccountTransactionsReportByCommodity Text
c AccountTransactionsReport
tr) | Text
c <- AccountTransactionsReport -> [Text]
forall {a} {b} {c} {d} {f}.
[(a, b, c, d, MixedAmount, f)] -> [Text]
commodities AccountTransactionsReport
tr]
where
commodities :: [(a, b, c, d, MixedAmount, f)] -> [Text]
commodities = [Text] -> [Text]
forall a. Ord a => [a] -> [a]
nubSort ([Text] -> [Text])
-> ([(a, b, c, d, MixedAmount, f)] -> [Text])
-> [(a, b, c, d, MixedAmount, f)]
-> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Amount -> Text) -> [Amount] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Amount -> Text
acommodity ([Amount] -> [Text])
-> ([(a, b, c, d, MixedAmount, f)] -> [Amount])
-> [(a, b, c, d, MixedAmount, f)]
-> [Text]
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)
filterAccountTransactionsReportByCommodity :: CommoditySymbol -> AccountTransactionsReport -> AccountTransactionsReport
filterAccountTransactionsReportByCommodity :: Text -> AccountTransactionsReport -> AccountTransactionsReport
filterAccountTransactionsReportByCommodity Text
comm =
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 (Text -> AccountTransactionsReportItem -> AccountTransactionsReport
forall {a} {b} {c} {d} {f}.
Text
-> (a, b, c, d, MixedAmount, f) -> [(a, b, c, d, MixedAmount, f)]
filterTransactionsReportItemByCommodity Text
comm)
where
filterTransactionsReportItemByCommodity :: Text
-> (a, b, c, d, MixedAmount, f) -> [(a, b, c, d, MixedAmount, f)]
filterTransactionsReportItemByCommodity Text
c (a
t,b
t2,c
s,d
o,MixedAmount
a,f
bal)
| Text
c Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
cs = [(a, b, c, d, MixedAmount, f)
item']
| Bool
otherwise = []
where
cs :: [Text]
cs = (Amount -> Text) -> [Amount] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Amount -> Text
acommodity ([Amount] -> [Text]) -> [Amount] -> [Text]
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' = Text -> MixedAmount -> MixedAmount
filterMixedAmountByCommodity Text
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 = Text -> MixedAmount -> MixedAmount
filterMixedAmountByCommodity Text
comm (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_AccountTransactionsReport :: TestTree
tests_AccountTransactionsReport = String -> [TestTree] -> TestTree
testGroup String
"AccountTransactionsReport" [
]