{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Hledger.Reports.BalanceReport (
BalanceReport,
BalanceReportItem,
balanceReport,
flatShowsExclusiveBalance,
tests_BalanceReport
)
where
import Data.Time.Calendar
import Hledger.Data
import Hledger.Query
import Hledger.Utils
import Hledger.Reports.MultiBalanceReport (multiBalanceReport)
import Hledger.Reports.ReportOptions
import Hledger.Reports.ReportTypes
type BalanceReport = ([BalanceReportItem], MixedAmount)
type BalanceReportItem = (AccountName, AccountName, Int, MixedAmount)
instance HasAmounts BalanceReportItem where
styleAmounts :: Map CommoditySymbol AmountStyle
-> BalanceReportItem -> BalanceReportItem
styleAmounts Map CommoditySymbol AmountStyle
styles (CommoditySymbol
a,CommoditySymbol
b,Int
c,MixedAmount
d) = (CommoditySymbol
a,CommoditySymbol
b,Int
c,Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount
forall a. HasAmounts a => Map CommoditySymbol AmountStyle -> a -> a
styleAmounts Map CommoditySymbol AmountStyle
styles MixedAmount
d)
flatShowsExclusiveBalance :: Bool
flatShowsExclusiveBalance = Bool
True
balanceReport :: ReportSpec -> Journal -> BalanceReport
balanceReport :: ReportSpec -> Journal -> BalanceReport
balanceReport ReportSpec
rspec Journal
j = ([BalanceReportItem]
rows, MixedAmount
total)
where
report :: MultiBalanceReport
report = ReportSpec -> Journal -> MultiBalanceReport
multiBalanceReport ReportSpec
rspec Journal
j
rows :: [BalanceReportItem]
rows = [( PeriodicReportRow DisplayName MixedAmount -> CommoditySymbol
forall a. PeriodicReportRow DisplayName a -> CommoditySymbol
prrFullName PeriodicReportRow DisplayName MixedAmount
row
, PeriodicReportRow DisplayName MixedAmount -> CommoditySymbol
forall a. PeriodicReportRow DisplayName a -> CommoditySymbol
prrDisplayName PeriodicReportRow DisplayName MixedAmount
row
, PeriodicReportRow DisplayName MixedAmount -> Int
forall a. PeriodicReportRow DisplayName a -> Int
prrIndent PeriodicReportRow DisplayName MixedAmount
row
, PeriodicReportRow DisplayName MixedAmount -> MixedAmount
forall a b. PeriodicReportRow a b -> b
prrTotal PeriodicReportRow DisplayName MixedAmount
row
) | PeriodicReportRow DisplayName MixedAmount
row <- MultiBalanceReport -> [PeriodicReportRow DisplayName MixedAmount]
forall a b. PeriodicReport a b -> [PeriodicReportRow a b]
prRows MultiBalanceReport
report]
total :: MixedAmount
total = PeriodicReportRow () MixedAmount -> MixedAmount
forall a b. PeriodicReportRow a b -> b
prrTotal (PeriodicReportRow () MixedAmount -> MixedAmount)
-> PeriodicReportRow () MixedAmount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ MultiBalanceReport -> PeriodicReportRow () MixedAmount
forall a b. PeriodicReport a b -> PeriodicReportRow () b
prTotals MultiBalanceReport
report
Right Journal
samplejournal2 =
BalancingOpts -> Journal -> Either String Journal
journalBalanceTransactions BalancingOpts
defbalancingopts
Journal
nulljournal{
jtxns = [
txnTieKnot Transaction{
tindex=0,
tsourcepos=nullsourcepospair,
tdate=fromGregorian 2008 01 01,
tdate2=Just $ fromGregorian 2009 01 01,
tstatus=Unmarked,
tcode="",
tdescription="income",
tcomment="",
ttags=[],
tpostings=
[posting {paccount="assets:bank:checking", pamount=mixedAmount (usd 1)}
,posting {paccount="income:salary", pamount=missingmixedamt}
],
tprecedingcomment=""
}
]
}
tests_BalanceReport :: TestTree
tests_BalanceReport = String -> [TestTree] -> TestTree
testGroup String
"BalanceReport" [
let
(ReportSpec
rspec,Journal
journal) gives :: (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives` BalanceReport
r = do
let opts' :: ReportSpec
opts' = ReportSpec
rspec{_rsQuery=And [queryFromFlags $ _rsReportOpts rspec, _rsQuery rspec]}
([BalanceReportItem]
eitems, MixedAmount
etotal) = BalanceReport
r
([BalanceReportItem]
aitems, MixedAmount
atotal) = ReportSpec -> Journal -> BalanceReport
balanceReport ReportSpec
opts' Journal
journal
showw :: (a, b, c, MixedAmount) -> (a, b, c, String)
showw (a
acct,b
acct',c
indent,MixedAmount
amt) = (a
acct, b
acct', c
indent, MixedAmount -> String
showMixedAmountDebug MixedAmount
amt)
((BalanceReportItem
-> (CommoditySymbol, CommoditySymbol, Int, String))
-> [BalanceReportItem]
-> [(CommoditySymbol, CommoditySymbol, Int, String)]
forall a b. (a -> b) -> [a] -> [b]
map BalanceReportItem
-> (CommoditySymbol, CommoditySymbol, Int, String)
forall {a} {b} {c}. (a, b, c, MixedAmount) -> (a, b, c, String)
showw [BalanceReportItem]
aitems) [(CommoditySymbol, CommoditySymbol, Int, String)]
-> [(CommoditySymbol, CommoditySymbol, Int, String)] -> IO ()
forall a. (Eq a, Show a, HasCallStack) => a -> a -> IO ()
@?= ((BalanceReportItem
-> (CommoditySymbol, CommoditySymbol, Int, String))
-> [BalanceReportItem]
-> [(CommoditySymbol, CommoditySymbol, Int, String)]
forall a b. (a -> b) -> [a] -> [b]
map BalanceReportItem
-> (CommoditySymbol, CommoditySymbol, Int, String)
forall {a} {b} {c}. (a, b, c, MixedAmount) -> (a, b, c, String)
showw [BalanceReportItem]
eitems)
(MixedAmount -> String
showMixedAmountDebug MixedAmount
atotal) String -> String -> IO ()
forall a. (Eq a, Show a, HasCallStack) => a -> a -> IO ()
@?= (MixedAmount -> String
showMixedAmountDebug MixedAmount
etotal)
in
String -> [TestTree] -> TestTree
testGroup String
"balanceReport" [
String -> IO () -> TestTree
testCase String
"no args, null journal" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
(ReportSpec
defreportspec, Journal
nulljournal) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives` ([], MixedAmount
nullmixedamt)
,String -> IO () -> TestTree
testCase String
"no args, sample journal" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
(ReportSpec
defreportspec, Journal
samplejournal) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives`
([
(CommoditySymbol
"assets:bank:checking",CommoditySymbol
"assets:bank:checking",Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
1))
,(CommoditySymbol
"assets:bank:saving",CommoditySymbol
"assets:bank:saving",Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
1))
,(CommoditySymbol
"assets:cash",CommoditySymbol
"assets:cash",Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd (-DecimalRaw Integer
2)))
,(CommoditySymbol
"expenses:food",CommoditySymbol
"expenses:food",Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
1))
,(CommoditySymbol
"expenses:supplies",CommoditySymbol
"expenses:supplies",Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
1))
,(CommoditySymbol
"income:gifts",CommoditySymbol
"income:gifts",Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd (-DecimalRaw Integer
1)))
,(CommoditySymbol
"income:salary",CommoditySymbol
"income:salary",Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd (-DecimalRaw Integer
1)))
],
Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
0))
,String -> IO () -> TestTree
testCase String
"with --tree" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
(ReportSpec
defreportspec{_rsReportOpts=defreportopts{accountlistmode_=ALTree}}, Journal
samplejournal) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives`
([
(CommoditySymbol
"assets",CommoditySymbol
"assets",Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
0))
,(CommoditySymbol
"assets:bank",CommoditySymbol
"bank",Int
1, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
2))
,(CommoditySymbol
"assets:bank:checking",CommoditySymbol
"checking",Int
2, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
1))
,(CommoditySymbol
"assets:bank:saving",CommoditySymbol
"saving",Int
2, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
1))
,(CommoditySymbol
"assets:cash",CommoditySymbol
"cash",Int
1, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd (-DecimalRaw Integer
2)))
,(CommoditySymbol
"expenses",CommoditySymbol
"expenses",Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
2))
,(CommoditySymbol
"expenses:food",CommoditySymbol
"food",Int
1, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
1))
,(CommoditySymbol
"expenses:supplies",CommoditySymbol
"supplies",Int
1, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
1))
,(CommoditySymbol
"income",CommoditySymbol
"income",Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd (-DecimalRaw Integer
2)))
,(CommoditySymbol
"income:gifts",CommoditySymbol
"gifts",Int
1, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd (-DecimalRaw Integer
1)))
,(CommoditySymbol
"income:salary",CommoditySymbol
"salary",Int
1, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd (-DecimalRaw Integer
1)))
],
Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
0))
,String -> IO () -> TestTree
testCase String
"with --depth=N" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
(ReportSpec
defreportspec{_rsReportOpts=defreportopts{depth_=DepthSpec (Just 1) []}}, Journal
samplejournal) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives`
([
(CommoditySymbol
"expenses", CommoditySymbol
"expenses", Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
2))
,(CommoditySymbol
"income", CommoditySymbol
"income", Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd (-DecimalRaw Integer
2)))
],
Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
0))
,String -> IO () -> TestTree
testCase String
"with depth:N" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
(ReportSpec
defreportspec{_rsQuery=Depth 1}, Journal
samplejournal) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives`
([
(CommoditySymbol
"expenses", CommoditySymbol
"expenses", Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
2))
,(CommoditySymbol
"income", CommoditySymbol
"income", Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd (-DecimalRaw Integer
2)))
],
Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
0))
,String -> IO () -> TestTree
testCase String
"with date:" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
(ReportSpec
defreportspec{_rsQuery=Date $ DateSpan (Just $ Exact $ fromGregorian 2009 01 01) (Just $ Exact $ fromGregorian 2010 01 01)}, Journal
samplejournal2) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives`
([], MixedAmount
nullmixedamt)
,String -> IO () -> TestTree
testCase String
"with date2:" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
(ReportSpec
defreportspec{_rsQuery=Date2 $ DateSpan (Just $ Exact $ fromGregorian 2009 01 01) (Just $ Exact $ fromGregorian 2010 01 01)}, Journal
samplejournal2) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives`
([
(CommoditySymbol
"assets:bank:checking",CommoditySymbol
"assets:bank:checking",Int
0,Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
1))
,(CommoditySymbol
"income:salary",CommoditySymbol
"income:salary",Int
0,Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd (-DecimalRaw Integer
1)))
],
Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
0))
,String -> IO () -> TestTree
testCase String
"with desc:" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
(ReportSpec
defreportspec{_rsQuery=Desc $ toRegexCI' "income"}, Journal
samplejournal) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives`
([
(CommoditySymbol
"assets:bank:checking",CommoditySymbol
"assets:bank:checking",Int
0,Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
1))
,(CommoditySymbol
"income:salary",CommoditySymbol
"income:salary",Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd (-DecimalRaw Integer
1)))
],
Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
0))
,String -> IO () -> TestTree
testCase String
"with not:desc:" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
(ReportSpec
defreportspec{_rsQuery=Not . Desc $ toRegexCI' "income"}, Journal
samplejournal) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives`
([
(CommoditySymbol
"assets:bank:saving",CommoditySymbol
"assets:bank:saving",Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
1))
,(CommoditySymbol
"assets:cash",CommoditySymbol
"assets:cash",Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd (-DecimalRaw Integer
2)))
,(CommoditySymbol
"expenses:food",CommoditySymbol
"expenses:food",Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
1))
,(CommoditySymbol
"expenses:supplies",CommoditySymbol
"expenses:supplies",Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
1))
,(CommoditySymbol
"income:gifts",CommoditySymbol
"income:gifts",Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd (-DecimalRaw Integer
1)))
],
Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
0))
,String -> IO () -> TestTree
testCase String
"with period on a populated period" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
(ReportSpec
defreportspec{_rsReportOpts=defreportopts{period_= PeriodBetween (fromGregorian 2008 1 1) (fromGregorian 2008 1 2)}}, Journal
samplejournal) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives`
(
[
(CommoditySymbol
"assets:bank:checking",CommoditySymbol
"assets:bank:checking",Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
1))
,(CommoditySymbol
"income:salary",CommoditySymbol
"income:salary",Int
0, Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd (-DecimalRaw Integer
1)))
],
Amount -> MixedAmount
mixedAmount (DecimalRaw Integer -> Amount
usd DecimalRaw Integer
0))
,String -> IO () -> TestTree
testCase String
"with period on an unpopulated period" (IO () -> TestTree) -> IO () -> TestTree
forall a b. (a -> b) -> a -> b
$
(ReportSpec
defreportspec{_rsReportOpts=defreportopts{period_= PeriodBetween (fromGregorian 2008 1 2) (fromGregorian 2008 1 3)}}, Journal
samplejournal) (ReportSpec, Journal) -> BalanceReport -> IO ()
`gives`
([], MixedAmount
nullmixedamt)
]
]