2016-08-08 18:31:01 +03:00
{- # LANGUAGE FlexibleInstances, ScopedTypeVariables # -}
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 ,
multiBalanceReportValue
2014-03-20 04:11:48 +04:00
-- -- * Tests
-- tests_Hledger_Reports_MultiBalanceReport
)
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
2014-03-22 04:41:54 +04:00
-- import Test.HUnit
2014-03-20 04:11:48 +04:00
import Hledger.Data
import Hledger.Query
import Hledger.Utils
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
--
2016-08-09 01:56:50 +03:00
-- 2. a list of row items, 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
--
2016-08-09 01:56:50 +03:00
-- * the amounts to show in 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
-- (see 'BalanceType' and "Hledger.Cli.Balance").
newtype MultiBalanceReport =
MultiBalanceReport ( [ DateSpan ]
, [ MultiBalanceReportRow ]
, MultiBalanceReportTotals
)
type MultiBalanceReportRow = ( AccountName , AccountName , Int , [ MixedAmount ] , MixedAmount , MixedAmount )
type MultiBalanceReportTotals = ( [ MixedAmount ] , MixedAmount , MixedAmount )
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
-- in each of the specified periods.
multiBalanceReport :: ReportOpts -> Query -> Journal -> MultiBalanceReport
2014-12-26 22:04:23 +03:00
multiBalanceReport opts q j = MultiBalanceReport ( displayspans , items , 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 ) $
2014-07-18 02:18:40 +04:00
if empty_ opts 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 ] =
2016-08-08 18:31:01 +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
CumulativeBalance -> drop 1 $ scanl ( + ) nullmixedamt changes
_ -> 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
]
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
2016-08-09 01:56:50 +03:00
balsbycol = transpose [ bs | ( a , _ , _ , bs , _ , _ ) <- items , 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
2015-08-26 20:38:45 +03:00
-- | Convert all the amounts in a multi-column balance report to their
-- value on the given date in their default valuation commodities
-- (which are determined as of that date, not the report interval dates).
multiBalanceReportValue :: Journal -> Day -> MultiBalanceReport -> MultiBalanceReport
multiBalanceReportValue j d r = r'
where
MultiBalanceReport ( spans , rows , ( coltotals , rowtotaltotal , rowavgtotal ) ) = r
r' = MultiBalanceReport
( spans ,
2016-08-09 01:56:50 +03:00
[ ( acct , acct' , depth , map convert rowamts , convert rowtotal , convert rowavg ) | ( acct , acct' , depth , rowamts , rowtotal , rowavg ) <- rows ] ,
2015-08-26 20:38:45 +03:00
( map convert coltotals , convert rowtotaltotal , convert rowavgtotal ) )
convert = mixedAmountValue j d