{-# LANGUAGE FlexibleInstances, RecordWildCards, ScopedTypeVariables, OverloadedStrings #-}
module Hledger.Reports.BalanceReport (
BalanceReport,
BalanceReportItem,
balanceReport,
flatShowsExclusiveBalance,
sortAccountItemsLike,
unifyMixedAmount,
perdivide,
tests_BalanceReport
)
where
import Data.List
import Data.Ord
import Data.Maybe
import Data.Time.Calendar
import Hledger.Data
import Hledger.Read (mamountp')
import Hledger.Query
import Hledger.Utils
import Hledger.Reports.ReportOptions
type BalanceReport = ([BalanceReportItem], MixedAmount)
type BalanceReportItem = (AccountName, AccountName, Int, MixedAmount)
flatShowsExclusiveBalance = True
balanceReport :: ReportOpts -> Query -> Journal -> BalanceReport
balanceReport ropts@ReportOpts{..} q j@Journal{..} =
(if invert_ then brNegate else id) $
(mappedsorteditems, mappedtotal)
where
dbg1 s = let p = "balanceReport" in Hledger.Utils.dbg1 (p++" "++s)
accttree = ledgerRootAccount $ ledgerFromJournal q $ journalSelectingAmountFromOpts ropts j
valuedaccttree = mapAccounts avalue accttree
where
avalue a@Account{..} = a{aebalance=bvalue aebalance, aibalance=bvalue aibalance}
where
bvalue = maybe id (mixedAmountApplyValuation (journalPriceOracle j) (journalCommodityStyles j) periodlast mreportlast today multiperiod) value_
where
periodlast =
fromMaybe (error' "balanceReport: expected a non-empty journal") $
reportPeriodOrJournalLastDay ropts j
mreportlast = reportPeriodLastDay ropts
today = fromMaybe (error' "balanceReport: could not pick a valuation date, ReportOpts today_ is unset") today_
multiperiod = interval_ /= NoInterval
displayaccts :: [Account]
| queryDepth q == 0 =
dbg1 "displayaccts" $
take 1 $ clipAccountsAndAggregate (queryDepth q) $ flattenAccounts valuedaccttree
| flat_ ropts = dbg1 "displayaccts" $
filterzeros $
filterempty $
drop 1 $ clipAccountsAndAggregate (queryDepth q) $ flattenAccounts valuedaccttree
| otherwise = dbg1 "displayaccts" $
filter (not.aboring) $
drop 1 $ flattenAccounts $
markboring $
prunezeros $
sortAccountTreeByAmount (fromMaybe NormallyPositive normalbalance_) $
clipAccounts (queryDepth q) valuedaccttree
where
balance = if flat_ ropts then aebalance else aibalance
filterzeros = if empty_ then id else filter (not . isZeroMixedAmount . balance)
filterempty = filter (\a -> anumpostings a > 0 || not (isZeroMixedAmount (balance a)))
prunezeros = if empty_ then id else fromMaybe nullacct . pruneAccounts (isZeroMixedAmount . balance)
markboring = if no_elide_ then id else markBoringParentAccounts
items = dbg1 "items" $ map (balanceReportItem ropts q) displayaccts
sorteditems
| sort_amount_ && tree_ ropts = items
| sort_amount_ = sortFlatBRByAmount items
| otherwise = sortBRByAccountDeclaration items
where
sortFlatBRByAmount :: [BalanceReportItem] -> [BalanceReportItem]
sortFlatBRByAmount = sortBy (maybeflip $ comparing (normaliseMixedAmountSquashPricesForDisplay . fourth4))
where
maybeflip = if normalbalance_ == Just NormallyNegative then id else flip
sortBRByAccountDeclaration :: [BalanceReportItem] -> [BalanceReportItem]
sortBRByAccountDeclaration rows = sortedrows
where
anamesandrows = [(first4 r, r) | r <- rows]
anames = map fst anamesandrows
sortedanames = sortAccountNamesByDeclaration j (tree_ ropts) anames
sortedrows = sortAccountItemsLike sortedanames anamesandrows
total | not (flat_ ropts) = dbg1 "total" $ sum [amt | (_,_,indent,amt) <- items, indent == 0]
| otherwise = dbg1 "total" $
if flatShowsExclusiveBalance
then sum $ map fourth4 items
else sum $ map aebalance $ clipAccountsAndAggregate 1 displayaccts
mappedtotal | percent_ = dbg1 "mappedtotal" $ total `perdivide` total
| otherwise = total
mappedsorteditems | percent_ =
dbg1 "mappedsorteditems" $
map (\(fname, sname, indent, amount) -> (fname, sname, indent, amount `perdivide` total)) sorteditems
| otherwise = sorteditems
sortAccountItemsLike :: [AccountName] -> [(AccountName, b)] -> [b]
sortAccountItemsLike sortedas items =
concatMap (\a -> maybe [] (:[]) $ lookup a items) sortedas
markBoringParentAccounts :: Account -> Account
markBoringParentAccounts = tieAccountParents . mapAccounts mark
where
mark a | length (asubs a) == 1 && isZeroMixedAmount (aebalance a) = a{aboring=True}
| otherwise = a
balanceReportItem :: ReportOpts -> Query -> Account -> BalanceReportItem
balanceReportItem opts q a
| flat_ opts = (name, name, 0, (if flatShowsExclusiveBalance then aebalance else aibalance) a)
| otherwise = (name, elidedname, indent, aibalance a)
where
name | queryDepth q > 0 = aname a
| otherwise = "..."
elidedname = accountNameFromComponents (adjacentboringparentnames ++ [accountLeafName name])
adjacentboringparentnames = reverse $ map (accountLeafName.aname) $ takeWhile aboring parents
indent = length $ filter (not.aboring) parents
parents = case parentAccounts a of [] -> []
as -> init as
brNegate :: BalanceReport -> BalanceReport
brNegate (is, tot) = (map brItemNegate is, -tot)
where
brItemNegate (a, a', d, amt) = (a, a', d, -amt)
unifyMixedAmount :: MixedAmount -> Amount
unifyMixedAmount mixedAmount = foldl combine (num 0) (amounts mixedAmount)
where
combine amount result =
if isReallyZeroAmount amount
then result
else if isReallyZeroAmount result
then amount
else if acommodity amount == acommodity result
then amount + result
else error' "Cannot calculate percentages for accounts with multiple commodities. (Hint: Try --cost, -V or similar flags.)"
perdivide :: MixedAmount -> MixedAmount -> MixedAmount
perdivide a b =
let a' = unifyMixedAmount a
b' = unifyMixedAmount b
in if isReallyZeroAmount a' || isReallyZeroAmount b' || acommodity a' == acommodity b'
then mixed [per $ if aquantity b' == 0 then 0 else (aquantity a' / abs (aquantity b') * 100)]
else error' "Cannot calculate percentages if accounts have different commodities. (Hint: Try --cost, -V or similar flags.)"
Right samplejournal2 =
journalBalanceTransactions False
nulljournal{
jtxns = [
txnTieKnot Transaction{
tindex=0,
tsourcepos=nullsourcepos,
tdate=parsedate "2008/01/01",
tdate2=Just $ parsedate "2009/01/01",
tstatus=Unmarked,
tcode="",
tdescription="income",
tcomment="",
ttags=[],
tpostings=
[posting {paccount="assets:bank:checking", pamount=Mixed [usd 1]}
,posting {paccount="income:salary", pamount=missingmixedamt}
],
tprecedingcomment=""
}
]
}
tests_BalanceReport = tests "BalanceReport" [
let
(opts,journal) `gives` r = do
let (eitems, etotal) = r
(aitems, atotal) = balanceReport opts (queryFromOpts nulldate opts) journal
showw (acct,acct',indent,amt) = (acct, acct', indent, showMixedAmountDebug amt)
(map showw eitems) @?= (map showw aitems)
(showMixedAmountDebug etotal) @?= (showMixedAmountDebug atotal)
in
tests "balanceReport" [
test "no args, null journal" $
(defreportopts, nulljournal) `gives` ([], Mixed [nullamt])
,test "no args, sample journal" $
(defreportopts, samplejournal) `gives`
([
("assets","assets",0, mamountp' "$0.00")
,("assets:bank","bank",1, mamountp' "$2.00")
,("assets:bank:checking","checking",2, mamountp' "$1.00")
,("assets:bank:saving","saving",2, mamountp' "$1.00")
,("assets:cash","cash",1, mamountp' "$-2.00")
,("expenses","expenses",0, mamountp' "$2.00")
,("expenses:food","food",1, mamountp' "$1.00")
,("expenses:supplies","supplies",1, mamountp' "$1.00")
,("income","income",0, mamountp' "$-2.00")
,("income:gifts","gifts",1, mamountp' "$-1.00")
,("income:salary","salary",1, mamountp' "$-1.00")
],
Mixed [usd 0])
,test "with --depth=N" $
(defreportopts{depth_=Just 1}, samplejournal) `gives`
([
("expenses", "expenses", 0, mamountp' "$2.00")
,("income", "income", 0, mamountp' "$-2.00")
],
Mixed [usd 0])
,test "with depth:N" $
(defreportopts{query_="depth:1"}, samplejournal) `gives`
([
("expenses", "expenses", 0, mamountp' "$2.00")
,("income", "income", 0, mamountp' "$-2.00")
],
Mixed [usd 0])
,test "with date:" $
(defreportopts{query_="date:'in 2009'"}, samplejournal2) `gives`
([],
Mixed [nullamt])
,test "with date2:" $
(defreportopts{query_="date2:'in 2009'"}, samplejournal2) `gives`
([
("assets:bank:checking","assets:bank:checking",0,mamountp' "$1.00")
,("income:salary","income:salary",0,mamountp' "$-1.00")
],
Mixed [usd 0])
,test "with desc:" $
(defreportopts{query_="desc:income"}, samplejournal) `gives`
([
("assets:bank:checking","assets:bank:checking",0,mamountp' "$1.00")
,("income:salary","income:salary",0, mamountp' "$-1.00")
],
Mixed [usd 0])
,test "with not:desc:" $
(defreportopts{query_="not:desc:income"}, samplejournal) `gives`
([
("assets","assets",0, mamountp' "$-1.00")
,("assets:bank:saving","bank:saving",1, mamountp' "$1.00")
,("assets:cash","cash",1, mamountp' "$-2.00")
,("expenses","expenses",0, mamountp' "$2.00")
,("expenses:food","food",1, mamountp' "$1.00")
,("expenses:supplies","supplies",1, mamountp' "$1.00")
,("income:gifts","income:gifts",0, mamountp' "$-1.00")
],
Mixed [usd 0])
,test "with period on a populated period" $
(defreportopts{period_= PeriodBetween (fromGregorian 2008 1 1) (fromGregorian 2008 1 2)}, samplejournal) `gives`
(
[
("assets:bank:checking","assets:bank:checking",0, mamountp' "$1.00")
,("income:salary","income:salary",0, mamountp' "$-1.00")
],
Mixed [usd 0])
,test "with period on an unpopulated period" $
(defreportopts{period_= PeriodBetween (fromGregorian 2008 1 2) (fromGregorian 2008 1 3)}, samplejournal) `gives`
([],Mixed [nullamt])
]
]