2017-07-06 19:53:59 +03:00
{- # LANGUAGE FlexibleInstances, ScopedTypeVariables, OverloadedStrings # -}
2014-03-20 04:11:48 +04:00
{- |
Multi - column balance reports , used by the balance command .
- }
module Hledger.Reports.MultiBalanceReports (
MultiBalanceReport ( .. ) ,
MultiBalanceReportRow ,
2015-08-26 20:38:45 +03:00
multiBalanceReport ,
2018-01-23 22:32:24 +03:00
balanceReportFromMultiBalanceReport ,
2018-01-16 04:58:14 +03:00
-- mbrNegate,
-- mbrNormaliseSign,
2014-03-20 04:11:48 +04:00
-- -- * Tests
2017-07-06 19:53:59 +03:00
tests_Hledger_Reports_MultiBalanceReport
2014-03-20 04:11:48 +04:00
)
where
import Data.List
import Data.Maybe
import Data.Ord
2015-08-26 20:38:45 +03:00
import Data.Time.Calendar
2014-04-19 19:40:16 +04:00
import Safe
2017-07-06 19:53:59 +03:00
import Test.HUnit
2014-03-20 04:11:48 +04:00
import Hledger.Data
import Hledger.Query
import Hledger.Utils
2017-07-06 19:53:59 +03:00
import Hledger.Read ( mamountp' )
2014-03-20 04:11:48 +04:00
import Hledger.Reports.ReportOptions
import Hledger.Reports.BalanceReport
-- | A multi balance report is a balance report with one or more columns. It has:
--
2016-08-09 01:56:50 +03:00
-- 1. a list of each column's period (date span)
2014-03-20 04:11:48 +04:00
--
2017-07-26 05:43:45 +03:00
-- 2. a list of rows, each containing:
2014-03-20 04:11:48 +04:00
--
2016-08-09 01:56:50 +03:00
-- * the full account name
2014-03-20 04:11:48 +04:00
--
2016-08-09 01:56:50 +03:00
-- * the leaf account name
2014-03-20 04:11:48 +04:00
--
2016-08-09 01:56:50 +03:00
-- * the account's depth
2014-03-20 04:11:48 +04:00
--
2017-07-26 05:43:45 +03:00
-- * a list of amounts, one for each column
2014-12-26 22:04:23 +03:00
--
2016-08-09 01:56:50 +03:00
-- * the total of the row's amounts
2014-12-26 22:04:23 +03:00
--
2016-08-09 01:56:50 +03:00
-- * the average of the row's amounts
--
-- 3. the column totals and the overall total and average
--
-- The meaning of the amounts depends on the type of multi balance
-- report, of which there are three: periodic, cumulative and historical
2017-09-12 19:12:45 +03:00
-- (see 'BalanceType' and "Hledger.Cli.Commands.Balance").
2016-08-09 01:56:50 +03:00
newtype MultiBalanceReport =
MultiBalanceReport ( [ DateSpan ]
, [ MultiBalanceReportRow ]
, MultiBalanceReportTotals
)
type MultiBalanceReportRow = ( AccountName , AccountName , Int , [ MixedAmount ] , MixedAmount , MixedAmount )
2017-07-06 19:44:44 +03:00
type MultiBalanceReportTotals = ( [ MixedAmount ] , MixedAmount , MixedAmount ) -- (Totals list, sum of totals, average of totals)
2014-03-20 04:11:48 +04:00
instance Show MultiBalanceReport where
-- use ppShow to break long lists onto multiple lines
2014-03-26 06:27:18 +04:00
-- we add some bogus extra shows here to help ppShow parse the output
2014-03-20 04:11:48 +04:00
-- and wrap tuples and lists properly
show ( MultiBalanceReport ( spans , items , totals ) ) =
" MultiBalanceReport (ignore extra quotes): \ n " ++ ppShow ( show spans , map show items , totals )
2014-03-26 06:27:18 +04:00
-- type alias just to remind us which AccountNames might be depth-clipped, below.
type ClippedAccountName = AccountName
2014-04-13 22:07:39 +04:00
-- | Generate a multicolumn balance report for the matched accounts,
-- showing the change of balance, accumulated balance, or historical balance
2018-01-23 22:32:24 +03:00
-- in each of the specified periods. Does not support tree-mode boring parent eliding.
-- If the normalbalance_ option is set, it adjusts the sorting and sign of amounts
-- (see ReportOpts and CompoundBalanceCommand).
2014-04-13 22:07:39 +04:00
multiBalanceReport :: ReportOpts -> Query -> Journal -> MultiBalanceReport
2017-09-30 05:19:07 +03:00
multiBalanceReport opts q j = MultiBalanceReport ( displayspans , sorteditems , totalsrow )
2014-03-20 04:11:48 +04:00
where
2015-05-14 22:49:17 +03:00
symq = dbg1 " symq " $ filterQuery queryIsSym $ dbg1 " requested q " q
depthq = dbg1 " depthq " $ filterQuery queryIsDepth q
2014-04-15 00:10:34 +04:00
depth = queryDepth depthq
2015-05-14 22:49:17 +03:00
depthless = dbg1 " depthless " . filterQuery ( not . queryIsDepth )
datelessq = dbg1 " datelessq " $ filterQuery ( not . queryIsDateOrDate2 ) q
2014-05-01 04:20:02 +04:00
dateqcons = if date2_ opts then Date2 else Date
2015-05-14 22:49:17 +03:00
precedingq = dbg1 " precedingq " $ And [ datelessq , dateqcons $ DateSpan Nothing ( spanStart reportspan ) ]
requestedspan = dbg1 " requestedspan " $ queryDateSpan ( date2_ opts ) q -- span specified by -b/-e/-p options and query args
requestedspan' = dbg1 " requestedspan' " $ requestedspan ` spanDefaultsFrom ` journalDateSpan ( date2_ opts ) j -- if open-ended, close it using the journal's end dates
2016-07-30 05:19:44 +03:00
intervalspans = dbg1 " intervalspans " $ splitSpan ( interval_ opts ) requestedspan' -- interval spans enclosing it
2015-05-14 22:49:17 +03:00
reportspan = dbg1 " reportspan " $ DateSpan ( maybe Nothing spanStart $ headMay intervalspans ) -- the requested span enlarged to a whole number of intervals
2014-04-19 19:40:16 +04:00
( maybe Nothing spanEnd $ lastMay intervalspans )
2015-05-14 22:49:17 +03:00
newdatesq = dbg1 " newdateq " $ dateqcons reportspan
reportq = dbg1 " reportq " $ depthless $ And [ datelessq , newdatesq ] -- user's query enlarged to whole intervals and with no depth limit
2014-03-26 06:27:18 +04:00
ps :: [ Posting ] =
2015-05-14 22:49:17 +03:00
dbg1 " ps " $
2014-04-15 00:10:34 +04:00
journalPostings $
2014-05-24 00:10:36 +04:00
filterJournalAmounts symq $ -- remove amount parts excluded by cur:
2014-04-15 00:10:34 +04:00
filterJournalPostings reportq $ -- remove postings not matched by (adjusted) query
journalSelectingAmountFromOpts opts j
2014-03-20 04:11:48 +04:00
2016-07-30 05:19:44 +03:00
displayspans = dbg1 " displayspans " $ splitSpan ( interval_ opts ) displayspan
2014-04-19 19:40:16 +04:00
where
displayspan
2016-08-08 18:31:01 +03:00
| empty_ opts = dbg1 " displayspan (-E) " reportspan -- all the requested intervals
2015-05-14 22:49:17 +03:00
| otherwise = dbg1 " displayspan " $ requestedspan ` spanIntersect ` matchedspan -- exclude leading/trailing empty intervals
matchedspan = dbg1 " matchedspan " $ postingsDateSpan' ( whichDateFromOpts opts ) ps
2014-03-26 06:27:18 +04:00
2014-04-13 22:07:39 +04:00
psPerSpan :: [ [ Posting ] ] =
2016-08-08 18:31:01 +03:00
dbg1 " psPerSpan "
2014-04-19 19:40:16 +04:00
[ filter ( isPostingInDateSpan' ( whichDateFromOpts opts ) s ) ps | s <- displayspans ]
2014-03-26 06:27:18 +04:00
2014-04-13 22:07:39 +04:00
postedAcctBalChangesPerSpan :: [ [ ( ClippedAccountName , MixedAmount ) ] ] =
2015-05-14 22:49:17 +03:00
dbg1 " postedAcctBalChangesPerSpan " $
2014-04-13 22:07:39 +04:00
map postingAcctBals psPerSpan
2014-03-26 06:27:18 +04:00
where
postingAcctBals :: [ Posting ] -> [ ( ClippedAccountName , MixedAmount ) ]
2014-04-07 08:56:47 +04:00
postingAcctBals ps = [ ( aname a , ( if tree_ opts then aibalance else aebalance ) a ) | a <- as ]
2014-03-26 06:27:18 +04:00
where
2014-09-11 00:07:53 +04:00
as = depthLimit $
2014-04-07 08:56:47 +04:00
( if tree_ opts then id else filter ( ( > 0 ) . anumpostings ) ) $
2014-03-26 06:27:18 +04:00
drop 1 $ accountsFromPostings ps
depthLimit
2014-04-07 08:56:47 +04:00
| tree_ opts = filter ( ( depthq ` matchesAccount ` ) . aname ) -- exclude deeper balances
| otherwise = clipAccountsAndAggregate depth -- aggregate deeper balances at the depth limit
2014-03-26 06:27:18 +04:00
2015-05-14 22:49:17 +03:00
postedAccts :: [ AccountName ] = dbg1 " postedAccts " $ sort $ accountNamesFromPostings ps
2014-07-18 02:18:40 +04:00
-- starting balances and accounts from transactions before the report start date
2016-08-09 01:56:50 +03:00
startacctbals = dbg1 " startacctbals " $ map ( \ ( a , _ , _ , b ) -> ( a , b ) ) startbalanceitems
2014-07-18 02:18:40 +04:00
where
2015-05-14 22:49:17 +03:00
( startbalanceitems , _ ) = dbg1 " starting balance report " $ balanceReport opts' precedingq j
2014-07-18 02:18:40 +04:00
where
opts' | tree_ opts = opts { no_elide_ = True }
2014-12-05 23:56:33 +03:00
| otherwise = opts { accountlistmode_ = ALFlat }
2014-07-18 02:18:40 +04:00
startingBalanceFor a = fromMaybe nullmixedamt $ lookup a startacctbals
2015-05-14 22:49:17 +03:00
startAccts = dbg1 " startAccts " $ map fst startacctbals
2014-03-26 06:27:18 +04:00
2014-04-13 22:07:39 +04:00
displayedAccts :: [ ClippedAccountName ] =
2015-05-14 22:49:17 +03:00
dbg1 " displayedAccts " $
2014-04-13 22:07:39 +04:00
( if tree_ opts then expandAccountNames else id ) $
2014-10-20 04:53:20 +04:00
nub $ map ( clipOrEllipsifyAccountName depth ) $
2017-07-11 20:49:08 +03:00
if empty_ opts || ( balancetype_ opts ) == HistoricalBalance then nub $ sort $ startAccts ++ postedAccts else postedAccts
2014-03-26 06:27:18 +04:00
2014-04-13 22:07:39 +04:00
acctBalChangesPerSpan :: [ [ ( ClippedAccountName , MixedAmount ) ] ] =
2016-08-08 18:31:01 +03:00
dbg1 " acctBalChangesPerSpan "
2014-04-13 22:07:39 +04:00
[ sortBy ( comparing fst ) $ unionBy ( \ ( a , _ ) ( a' , _ ) -> a == a' ) postedacctbals zeroes
| postedacctbals <- postedAcctBalChangesPerSpan ]
where zeroes = [ ( a , nullmixedamt ) | a <- displayedAccts ]
2014-03-26 06:27:18 +04:00
2014-04-13 22:07:39 +04:00
acctBalChanges :: [ ( ClippedAccountName , [ MixedAmount ] ) ] =
2016-08-08 18:31:01 +03:00
dbg1 " acctBalChanges "
2014-04-13 22:07:39 +04:00
[ ( a , map snd abs ) | abs @ ( ( a , _ ) : _ ) <- transpose acctBalChangesPerSpan ] -- never null, or used when null...
2014-03-26 06:27:18 +04:00
2014-04-13 22:07:39 +04:00
items :: [ MultiBalanceReportRow ] =
2017-09-25 19:17:46 +03:00
dbg1 " items " $
2016-08-09 01:56:50 +03:00
[ ( a , accountLeafName a , accountNameLevel a , displayedBals , rowtot , rowavg )
2014-04-13 22:07:39 +04:00
| ( a , changes ) <- acctBalChanges
, let displayedBals = case balancetype_ opts of
HistoricalBalance -> drop 1 $ scanl ( + ) ( startingBalanceFor a ) changes
2016-08-12 19:44:31 +03:00
CumulativeChange -> drop 1 $ scanl ( + ) nullmixedamt changes
2014-04-13 22:07:39 +04:00
_ -> changes
2014-12-26 22:04:23 +03:00
, let rowtot = sum displayedBals
, let rowavg = averageMixedAmounts displayedBals
2014-10-20 04:53:20 +04:00
, empty_ opts || depth == 0 || any ( not . isZeroMixedAmount ) displayedBals
2014-04-13 22:07:39 +04:00
]
2017-09-30 05:19:07 +03:00
sorteditems :: [ MultiBalanceReportRow ] =
dbg1 " sorteditems " $
2018-01-21 06:42:05 +03:00
sortitems items
2017-09-30 05:19:07 +03:00
where
2018-01-21 06:42:05 +03:00
sortitems
| sort_amount_ opts && accountlistmode_ opts == ALTree = sortTreeMultiBalanceReportRowsByAmount
| sort_amount_ opts = sortFlatMultiBalanceReportRowsByAmount
| not ( sort_amount_ opts ) && accountlistmode_ opts == ALTree = sortTreeMultiBalanceReportRowsByAccountCodeAndName
| otherwise = sortFlatMultiBalanceReportRowsByAccountCodeAndName
2017-09-30 05:19:07 +03:00
where
-- Sort the report rows, representing a flat account list, by row total.
sortFlatMultiBalanceReportRowsByAmount = sortBy ( maybeflip $ comparing fifth6 )
where
2018-01-16 00:05:20 +03:00
maybeflip = if normalbalance_ opts == Just NormallyNegative then id else flip
2017-09-30 05:19:07 +03:00
-- Sort the report rows, representing a tree of accounts, by row total at each level.
-- To do this we recreate an Account tree with the row totals as balances,
-- so we can do a hierarchical sort, flatten again, and then reorder the
-- report rows similarly. Yes this is pretty long winded.
sortTreeMultiBalanceReportRowsByAmount rows = sortedrows
where
anamesandrows = [ ( first6 r , r ) | r <- rows ]
anames = map fst anamesandrows
atotals = [ ( a , tot ) | ( a , _ , _ , _ , tot , _ ) <- rows ]
nametree = treeFromPaths $ map expandAccountName anames
accounttree = nameTreeToAccount " root " nametree
accounttreewithbals = mapAccounts setibalance accounttree
where
-- this error should not happen, but it's ugly TODO
setibalance a = a { aibalance = fromMaybe ( error " sortTreeMultiBalanceReportRowsByAmount 1 " ) $ lookup ( aname a ) atotals }
2018-01-16 00:05:20 +03:00
sortedaccounttree = sortAccountTreeByAmount ( fromMaybe NormallyPositive $ normalbalance_ opts ) accounttreewithbals
2017-09-30 05:19:07 +03:00
sortedaccounts = drop 1 $ flattenAccounts sortedaccounttree
2018-01-21 06:42:05 +03:00
-- dropped the root account, also ignore any parent accounts not in rows
sortedrows = concatMap ( \ a -> maybe [] ( : [] ) $ lookup ( aname a ) anamesandrows ) sortedaccounts
-- Sort the report rows by account code if any, with the empty account code coming last, then account name.
sortFlatMultiBalanceReportRowsByAccountCodeAndName = sortBy ( comparing acodeandname )
where
acodeandname r = ( acode' , aname )
where
aname = first6 r
macode = fromMaybe Nothing $ lookup aname $ jaccounts j
acode' = fromMaybe maxBound macode
-- Sort the report rows, representing a tree of accounts, by account code and then account name at each level.
-- Convert a tree of account names, look up the account codes, sort and flatten the tree, reorder the rows.
sortTreeMultiBalanceReportRowsByAccountCodeAndName rows = sortedrows
where
anamesandrows = [ ( first6 r , r ) | r <- rows ]
anames = map fst anamesandrows
nametree = treeFromPaths $ map expandAccountName anames
accounttree = nameTreeToAccount " root " nametree
accounttreewithcodes = mapAccounts ( accountSetCodeFrom j ) accounttree
sortedaccounttree = sortAccountTreeByAccountCodeAndName accounttreewithcodes
sortedaccounts = drop 1 $ flattenAccounts sortedaccounttree
-- dropped the root account, also ignore any parent accounts not in rows
sortedrows = concatMap ( \ a -> maybe [] ( : [] ) $ lookup ( aname a ) anamesandrows ) sortedaccounts
2014-04-13 22:07:39 +04:00
totals :: [ MixedAmount ] =
2015-05-14 22:49:17 +03:00
-- dbg1 "totals" $
2014-04-13 22:07:39 +04:00
map sum balsbycol
2014-03-20 04:11:48 +04:00
where
2017-09-30 05:19:07 +03:00
balsbycol = transpose [ bs | ( a , _ , _ , bs , _ , _ ) <- sorteditems , not ( tree_ opts ) || a ` elem ` highestlevelaccts ]
2014-03-26 06:27:18 +04:00
highestlevelaccts =
2016-08-08 18:31:01 +03:00
dbg1 " highestlevelaccts "
2014-04-13 22:07:39 +04:00
[ a | a <- displayedAccts , not $ any ( ` elem ` displayedAccts ) $ init $ expandAccountName a ]
2014-04-19 22:26:01 +04:00
2016-08-09 01:56:50 +03:00
totalsrow :: MultiBalanceReportTotals =
2016-08-08 18:31:01 +03:00
dbg1 " totalsrow "
2014-12-26 22:04:23 +03:00
( totals , sum totals , averageMixedAmounts totals )
2015-05-14 22:49:17 +03:00
dbg1 s = let p = " multiBalanceReport " in Hledger . Utils . dbg1 ( p ++ " " ++ s ) -- add prefix in this function's debug output
-- dbg1 = const id -- exclude this function from debug output
2014-04-19 22:26:01 +04:00
2018-01-23 22:32:24 +03:00
-- | Generates a simple non-columnar BalanceReport, but using multiBalanceReport,
-- in order to support --historical. Does not support tree-mode boring parent eliding.
-- If the normalbalance_ option is set, it adjusts the sorting and sign of amounts
-- (see ReportOpts and CompoundBalanceCommand).
balanceReportFromMultiBalanceReport :: ReportOpts -> Query -> Journal -> BalanceReport
balanceReportFromMultiBalanceReport opts q j = ( rows' , total )
where
MultiBalanceReport ( _ , rows , ( totals , _ , _ ) ) = multiBalanceReport opts q j
rows' = [ ( a
, if flat_ opts then a else a' -- BalanceReport expects full account name here with --flat
, if tree_ opts then d - 1 else 0 -- BalanceReport uses 0-based account depths
, headDef nullmixedamt amts -- 0 columns is illegal, should not happen, return zeroes if it does
) | ( a , a' , d , amts , _ , _ ) <- rows ]
total = headDef nullmixedamt totals
2015-08-26 20:38:45 +03:00
2017-07-06 19:53:59 +03:00
tests_multiBalanceReport =
let
( opts , journal ) ` gives ` r = do
let ( eitems , etotal ) = r
( MultiBalanceReport ( _ , aitems , atotal ) ) = multiBalanceReport opts ( queryFromOpts nulldate opts ) journal
showw ( acct , acct' , indent , lAmt , amt , amt' ) = ( acct , acct' , indent , map showMixedAmountDebug lAmt , showMixedAmountDebug amt , showMixedAmountDebug amt' )
assertEqual " items " ( map showw eitems ) ( map showw aitems )
assertEqual " total " ( showMixedAmountDebug etotal ) ( ( \ ( _ , b , _ ) -> showMixedAmountDebug b ) atotal ) -- we only check the sum of the totals
usd0 = usd 0
amount0 = Amount { acommodity = " $ " , aquantity = 0 , aprice = NoPrice , astyle = AmountStyle { ascommodityside = L , ascommodityspaced = False , asprecision = 2 , asdecimalpoint = Just '.' , asdigitgroups = Nothing } , amultiplier = False }
in [
" multiBalanceReport with no args on null journal " ~: do
( defreportopts , nulljournal ) ` gives ` ( [] , Mixed [ nullamt ] )
, " multiBalanceReport with -H on a populated period " ~: do
( defreportopts { period_ = PeriodBetween ( fromGregorian 2008 1 1 ) ( fromGregorian 2008 1 2 ) , balancetype_ = HistoricalBalance } , samplejournal ) ` gives `
(
[
( " assets:bank:checking " , " checking " , 3 , [ mamountp' " $1.00 " ] , mamountp' " $1.00 " , Mixed [ amount0 { aquantity = 1 } ] )
, ( " income:salary " , " salary " , 2 , [ mamountp' " $-1.00 " ] , mamountp' " $-1.00 " , Mixed [ amount0 { aquantity = ( - 1 ) } ] )
] ,
Mixed [ usd0 ] )
, " multiBalanceReport tests the ability to have a valid history on an empty period " ~: do
( defreportopts { period_ = PeriodBetween ( fromGregorian 2008 1 2 ) ( fromGregorian 2008 1 3 ) , balancetype_ = HistoricalBalance } , samplejournal ) ` gives `
(
[
( " assets:bank:checking " , " checking " , 3 , [ mamountp' " $1.00 " ] , mamountp' " $1.00 " , Mixed [ amount0 { aquantity = 1 } ] )
, ( " income:salary " , " salary " , 2 , [ mamountp' " $-1.00 " ] , mamountp' " $-1.00 " , Mixed [ amount0 { aquantity = ( - 1 ) } ] )
] ,
Mixed [ usd0 ] )
2017-07-10 19:47:51 +03:00
, " multiBalanceReport tests the ability to have a valid history on an empty period (More complex) " ~: do
( defreportopts { period_ = PeriodBetween ( fromGregorian 2009 1 1 ) ( fromGregorian 2009 1 2 ) , balancetype_ = HistoricalBalance } , samplejournal ) ` gives `
(
[
( " assets:bank:checking " , " checking " , 3 , [ mamountp' " $1.00 " ] , mamountp' " $1.00 " , Mixed [ amount0 { aquantity = 1 } ] )
, ( " assets:bank:saving " , " saving " , 3 , [ mamountp' " $1.00 " ] , mamountp' " $1.00 " , Mixed [ amount0 { aquantity = 1 } ] )
, ( " assets:cash " , " cash " , 2 , [ mamountp' " $-2.00 " ] , mamountp' " $-2.00 " , Mixed [ amount0 { aquantity = ( - 2 ) } ] )
, ( " expenses:food " , " food " , 2 , [ mamountp' " $1.00 " ] , mamountp' " $1.00 " , Mixed [ amount0 { aquantity = ( 1 ) } ] )
, ( " expenses:supplies " , " supplies " , 2 , [ mamountp' " $1.00 " ] , mamountp' " $1.00 " , Mixed [ amount0 { aquantity = ( 1 ) } ] )
, ( " income:gifts " , " gifts " , 2 , [ mamountp' " $-1.00 " ] , mamountp' " $-1.00 " , Mixed [ amount0 { aquantity = ( - 1 ) } ] )
, ( " income:salary " , " salary " , 2 , [ mamountp' " $-1.00 " ] , mamountp' " $-1.00 " , Mixed [ amount0 { aquantity = ( - 1 ) } ] )
] ,
Mixed [ usd0 ] )
2017-07-06 19:53:59 +03:00
]
tests_Hledger_Reports_MultiBalanceReport :: Test
tests_Hledger_Reports_MultiBalanceReport = TestList
tests_multiBalanceReport