2019-04-26 17:37:27 +03:00
|
|
|
{-# LANGUAGE FlexibleInstances, RecordWildCards, 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-30 01:52:03 +03:00
|
|
|
mbrNegate,
|
|
|
|
mbrNormaliseSign,
|
2018-04-03 15:07:13 +03:00
|
|
|
multiBalanceReportSpan,
|
|
|
|
tableAsText,
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
-- -- * Tests
|
2018-09-06 23:08:26 +03:00
|
|
|
tests_MultiBalanceReports
|
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
|
2018-04-03 15:07:13 +03:00
|
|
|
import Text.Tabular as T
|
|
|
|
import Text.Tabular.AsciiWide
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
import Hledger.Data
|
|
|
|
import Hledger.Query
|
2018-09-04 23:52:36 +03:00
|
|
|
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
|
2018-07-16 14:47:37 +03:00
|
|
|
-- use pshow (pretty-show's ppShow) to break long lists onto multiple lines
|
|
|
|
-- we add some bogus extra shows here to help it parse the output
|
2014-03-20 04:11:48 +04:00
|
|
|
-- and wrap tuples and lists properly
|
|
|
|
show (MultiBalanceReport (spans, items, totals)) =
|
2018-07-16 14:47:37 +03:00
|
|
|
"MultiBalanceReport (ignore extra quotes):\n" ++ pshow (show spans, map show items, totals)
|
2014-03-20 04:11:48 +04:00
|
|
|
|
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).
|
2019-05-09 17:58:45 +03:00
|
|
|
-- hledger's most powerful and useful report, used by the balance
|
|
|
|
-- command (in multiperiod mode) and by the bs/cf/is commands.
|
2014-04-13 22:07:39 +04:00
|
|
|
multiBalanceReport :: ReportOpts -> Query -> Journal -> MultiBalanceReport
|
2019-05-04 22:34:59 +03:00
|
|
|
multiBalanceReport ropts@ReportOpts{..} q j =
|
|
|
|
(if invert_ then mbrNegate else id) $
|
2019-05-09 17:58:45 +03:00
|
|
|
MultiBalanceReport (colspans, sortedrowsvalued, totalsrow)
|
2014-03-20 04:11:48 +04:00
|
|
|
where
|
2019-05-09 17:58:45 +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
|
|
|
|
|
|
|
|
----------------------------------------------------------------------
|
|
|
|
-- 1. Queries, report/column dates.
|
|
|
|
|
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
|
2019-05-04 22:34:59 +03:00
|
|
|
dateqcons = if date2_ then Date2 else Date
|
2018-10-17 23:10:49 +03:00
|
|
|
-- The date span specified by -b/-e/-p options and query args if any.
|
2019-05-04 22:34:59 +03:00
|
|
|
requestedspan = dbg1 "requestedspan" $ queryDateSpan date2_ q
|
2018-10-17 23:10:49 +03:00
|
|
|
-- If the requested span is open-ended, close it using the journal's end dates.
|
|
|
|
-- This can still be the null (open) span if the journal is empty.
|
2019-05-04 22:34:59 +03:00
|
|
|
requestedspan' = dbg1 "requestedspan'" $ requestedspan `spanDefaultsFrom` journalDateSpan date2_ j
|
2018-10-17 23:10:49 +03:00
|
|
|
-- The list of interval spans enclosing the requested span.
|
|
|
|
-- This list can be empty if the journal was empty,
|
|
|
|
-- or if hledger-ui has added its special date:-tomorrow to the query
|
|
|
|
-- and all txns are in the future.
|
2019-05-04 22:34:59 +03:00
|
|
|
intervalspans = dbg1 "intervalspans" $ splitSpan interval_ requestedspan'
|
2018-10-17 23:10:49 +03:00
|
|
|
-- The requested span enlarged to enclose a whole number of intervals.
|
|
|
|
-- This can be the null span if there were no intervals.
|
|
|
|
reportspan = dbg1 "reportspan" $ DateSpan (maybe Nothing spanStart $ headMay intervalspans)
|
|
|
|
(maybe Nothing spanEnd $ lastMay intervalspans)
|
2019-05-09 17:58:45 +03:00
|
|
|
mreportstart = spanStart reportspan
|
2018-10-17 23:10:49 +03:00
|
|
|
-- The user's query with no depth limit, and expanded to the report span
|
|
|
|
-- if there is one (otherwise any date queries are left as-is, which
|
|
|
|
-- handles the hledger-ui+future txns case above).
|
|
|
|
reportq = dbg1 "reportq" $ depthless $
|
|
|
|
if reportspan == nulldatespan
|
|
|
|
then q
|
|
|
|
else And [datelessq, reportspandatesq]
|
|
|
|
where
|
|
|
|
reportspandatesq = dbg1 "reportspandatesq" $ dateqcons reportspan
|
2019-05-09 17:58:45 +03:00
|
|
|
-- The date spans to be included as report columns.
|
|
|
|
colspans :: [DateSpan] = dbg1 "colspans" $ splitSpan interval_ displayspan
|
2014-04-19 19:40:16 +04:00
|
|
|
where
|
|
|
|
displayspan
|
2019-05-04 22:34:59 +03:00
|
|
|
| empty_ = dbg1 "displayspan (-E)" reportspan -- all the requested intervals
|
|
|
|
| otherwise = dbg1 "displayspan" $ requestedspan `spanIntersect` matchedspan -- exclude leading/trailing empty intervals
|
|
|
|
matchedspan = dbg1 "matchedspan" $ postingsDateSpan' (whichDateFromOpts ropts) ps
|
2019-05-09 17:58:45 +03:00
|
|
|
|
|
|
|
----------------------------------------------------------------------
|
|
|
|
-- 2. Things we'll need for valuation, if -V/--value-at are present.
|
|
|
|
-- Valuation complicates this report quite a lot.
|
|
|
|
|
|
|
|
-- Here's the current intended effect of --value-at on each part of the report:
|
2019-05-08 02:19:49 +03:00
|
|
|
-- -H starting balances:
|
|
|
|
-- transaction: sum of values of previous postings on their posting dates
|
|
|
|
-- period: value -H starting balances at day before report start
|
|
|
|
-- date: value -H starting balances at date
|
|
|
|
-- table cells:
|
|
|
|
-- transaction: value each posting before calculating table cell amounts
|
|
|
|
-- period: value each table cell amount at subperiod end
|
|
|
|
-- date: value each table cell amount at date
|
|
|
|
-- column totals:
|
|
|
|
-- transaction: sum/average the valued cell amounts
|
|
|
|
-- period: sum/average the unvalued amounts and value at subperiod end
|
|
|
|
-- date: sum/average the unvalued amounts and value at date
|
|
|
|
-- row totals & averages, grand total & average:
|
|
|
|
-- transaction: sum/average the valued amounts
|
|
|
|
-- period: sum/average the unvalued amounts and value at report period end
|
|
|
|
-- date: sum/average the unvalued amounts and value at date
|
2019-05-10 01:36:26 +03:00
|
|
|
mvalueat = valueTypeFromOpts ropts
|
2019-05-05 19:30:01 +03:00
|
|
|
today = fromMaybe (error' "postingsReport: ReportOpts today_ is unset so could not satisfy --value-at=now") today_
|
2019-05-09 17:58:45 +03:00
|
|
|
-- Market prices. Sort into date then parse order,
|
|
|
|
-- & reverse for quick lookup of the latest price.
|
|
|
|
prices = reverse $ sortOn mpdate $ jmarketprices j
|
|
|
|
-- A helper for valuing amounts according to --value-at.
|
|
|
|
maybevalue :: Day -> MixedAmount -> MixedAmount
|
|
|
|
maybevalue periodlastday amt = case mvalueat of
|
|
|
|
Nothing -> amt
|
|
|
|
Just AtTransaction -> amt -- assume --value-at=transaction was handled earlier
|
|
|
|
Just AtPeriod -> mixedAmountValue prices periodlastday amt
|
|
|
|
Just AtNow -> mixedAmountValue prices today amt
|
|
|
|
Just (AtDate d) -> mixedAmountValue prices d amt
|
|
|
|
-- The last day of each column subperiod.
|
|
|
|
lastdays :: [Day] =
|
|
|
|
map ((maybe
|
|
|
|
(error' "multiBalanceReport: expected all spans to have an end date") -- XXX should not happen
|
|
|
|
(addDays (-1)))
|
|
|
|
. spanEnd) colspans
|
|
|
|
-- The last day of the overall report period.
|
|
|
|
reportlastday =
|
|
|
|
fromMaybe (error' "multiBalanceReport: expected a non-empty journal") -- XXX might happen ? :(
|
|
|
|
$ reportPeriodOrJournalLastDay ropts j
|
|
|
|
|
|
|
|
----------------------------------------------------------------------
|
|
|
|
-- 3. Calculate starting balances (both unvalued and valued), if needed for -H
|
|
|
|
|
|
|
|
-- Balances at report start date, unvalued, from all earlier postings which otherwise match the query.
|
|
|
|
startbals :: [(AccountName, MixedAmount)] = dbg1 "startbals" $ map (\(a,_,_,b) -> (a,b)) startbalanceitems
|
|
|
|
where
|
|
|
|
(startbalanceitems,_) = dbg1 "starting balance report" $ balanceReport ropts''{value_=False} startbalq j
|
|
|
|
where
|
|
|
|
ropts' | tree_ ropts = ropts{no_elide_=True}
|
|
|
|
| otherwise = ropts{accountlistmode_=ALFlat}
|
|
|
|
ropts'' = ropts'{period_ = precedingperiod}
|
|
|
|
where
|
|
|
|
precedingperiod = dateSpanAsPeriod $ spanIntersect (DateSpan Nothing mreportstart) $ periodAsDateSpan period_
|
|
|
|
-- q projected back before the report start date.
|
|
|
|
-- When there's no report start date, in case there are future txns (the hledger-ui case above),
|
|
|
|
-- we use emptydatespan to make sure they aren't counted as starting balance.
|
|
|
|
startbalq = dbg1 "startbalq" $ And [datelessq, dateqcons precedingspan]
|
|
|
|
where
|
|
|
|
precedingspan = case mreportstart of
|
|
|
|
Just d -> DateSpan Nothing (Just d)
|
|
|
|
Nothing -> emptydatespan
|
|
|
|
-- Balances at report start date, maybe valued according to --value-at. XXX duplication
|
|
|
|
startbalsmaybevalued :: [(AccountName, MixedAmount)] = dbg1 "startbalsmaybevalued" $ map (\(a,_,_,b) -> (a,b)) startbalanceitems
|
|
|
|
where
|
|
|
|
(startbalanceitems,_) = dbg1 "starting balance report (maybe valued)" $ balanceReport ropts'' startbalq j
|
|
|
|
where
|
|
|
|
ropts' | tree_ ropts = ropts{no_elide_=True}
|
|
|
|
| otherwise = ropts{accountlistmode_=ALFlat}
|
|
|
|
ropts'' = ropts'{period_ = precedingperiod}
|
|
|
|
where
|
|
|
|
precedingperiod = dateSpanAsPeriod $ spanIntersect (DateSpan Nothing mreportstart) $ periodAsDateSpan period_
|
|
|
|
-- q projected back before the report start date.
|
|
|
|
-- When there's no report start date, in case there are future txns (the hledger-ui case above),
|
|
|
|
-- we use emptydatespan to make sure they aren't counted as starting balance.
|
|
|
|
startbalq = dbg1 "startbalq" $ And [datelessq, dateqcons precedingspan]
|
|
|
|
where
|
|
|
|
precedingspan = case mreportstart of
|
|
|
|
Just d -> DateSpan Nothing (Just d)
|
|
|
|
Nothing -> emptydatespan
|
|
|
|
-- The matched accounts with a starting balance. All of these should appear
|
|
|
|
-- in the report even if they have no postings during the report period.
|
|
|
|
startaccts = dbg1 "startaccts" $ map fst startbals
|
|
|
|
-- Helpers to look up an account's starting balance.
|
|
|
|
startingBalanceFor a = fromMaybe nullmixedamt $ lookup a startbals
|
|
|
|
valuedStartingBalanceFor a = fromMaybe nullmixedamt $ lookup a startbalsmaybevalued
|
|
|
|
|
|
|
|
----------------------------------------------------------------------
|
|
|
|
-- 4. Gather postings for each column.
|
|
|
|
|
|
|
|
-- Postings matching the query within the report period.
|
|
|
|
ps :: [Posting] =
|
|
|
|
dbg1 "ps" $
|
|
|
|
journalPostings $
|
|
|
|
filterJournalAmounts symq $ -- remove amount parts excluded by cur:
|
|
|
|
filterJournalPostings reportq $ -- remove postings not matched by (adjusted) query
|
|
|
|
journalSelectingAmountFromOpts ropts j
|
|
|
|
-- Group postings into their columns, with the column end dates.
|
|
|
|
colps :: [([Posting], Maybe Day)] =
|
|
|
|
dbg1 "colps"
|
|
|
|
[(filter (isPostingInDateSpan' (whichDateFromOpts ropts) s) ps, spanEnd s) | s <- colspans]
|
2019-05-05 19:30:01 +03:00
|
|
|
-- If --value-at=transaction is in effect, convert the postings to value before summing.
|
2019-05-09 17:58:45 +03:00
|
|
|
colpsmaybevalued :: [([Posting], Maybe Day)] =
|
2019-05-05 19:30:01 +03:00
|
|
|
case mvalueat of
|
2019-05-09 17:58:45 +03:00
|
|
|
Just AtTransaction -> [([postingValueAtDate j (postingDate p) p | p <- ps], periodend) | (ps,periodend) <- colps]
|
|
|
|
_ -> colps
|
|
|
|
|
|
|
|
----------------------------------------------------------------------
|
|
|
|
-- 5. Calculate account balance changes in each column.
|
|
|
|
|
|
|
|
-- In each column, gather the accounts that have postings and their change amount.
|
|
|
|
-- Do this for the unvalued postings, and if needed the posting-date-valued postings.
|
|
|
|
acctChangesFromPostings :: [Posting] -> [(ClippedAccountName, MixedAmount)]
|
|
|
|
acctChangesFromPostings ps = [(aname a, (if tree_ ropts then aibalance else aebalance) a) | a <- as]
|
2014-07-18 02:18:40 +04:00
|
|
|
where
|
2019-05-09 17:58:45 +03:00
|
|
|
as = depthLimit $
|
|
|
|
(if tree_ ropts then id else filter ((>0).anumpostings)) $
|
|
|
|
drop 1 $ accountsFromPostings ps
|
|
|
|
depthLimit
|
|
|
|
| tree_ ropts = filter ((depthq `matchesAccount`).aname) -- exclude deeper balances
|
|
|
|
| otherwise = clipAccountsAndAggregate depth -- aggregate deeper balances at the depth limit
|
|
|
|
-- colacctchanges :: [[(ClippedAccountName, MixedAmount)]] =
|
|
|
|
-- dbg1 "colacctchanges" $ map (acctChangesFromPostings . fst) colps
|
|
|
|
colacctchangesmaybevalued :: [[(ClippedAccountName, MixedAmount)]] =
|
|
|
|
dbg1 "colacctchangesmaybevalued" $ map (acctChangesFromPostings . fst) colpsmaybevalued
|
|
|
|
|
|
|
|
----------------------------------------------------------------------
|
|
|
|
-- 6. Gather the account balance changes into a regular matrix including the accounts
|
|
|
|
-- from all columns (and with -H, accounts with starting balances), adding zeroes where needed.
|
|
|
|
|
2019-05-05 03:46:52 +03:00
|
|
|
-- All account names that will be displayed, possibly depth-clipped.
|
2019-05-09 17:58:45 +03:00
|
|
|
displayaccts :: [ClippedAccountName] =
|
|
|
|
dbg1 "displayaccts" $
|
2019-05-04 22:34:59 +03:00
|
|
|
(if tree_ ropts then expandAccountNames else id) $
|
2014-10-20 04:53:20 +04:00
|
|
|
nub $ map (clipOrEllipsifyAccountName depth) $
|
2019-05-09 17:58:45 +03:00
|
|
|
if empty_ || balancetype_ == HistoricalBalance
|
|
|
|
then nub $ sort $ startaccts ++ allpostedaccts
|
|
|
|
else allpostedaccts
|
|
|
|
where
|
|
|
|
allpostedaccts :: [AccountName] = dbg1 "allpostedaccts" $ sort $ accountNamesFromPostings ps
|
|
|
|
-- Each column's balance changes for each account, adding zeroes where needed.
|
|
|
|
colallacctchanges :: [[(ClippedAccountName, MixedAmount)]] =
|
|
|
|
dbg1 "colallacctchanges"
|
|
|
|
[sortBy (comparing fst) $
|
|
|
|
unionBy (\(a,_) (a',_) -> a == a') postedacctchanges zeroes
|
|
|
|
| postedacctchanges <- colacctchangesmaybevalued]
|
|
|
|
where zeroes = [(a, nullmixedamt) | a <- displayaccts]
|
|
|
|
-- Transpose to get each account's balance changes across all columns.
|
|
|
|
acctchanges :: [(ClippedAccountName, [MixedAmount])] =
|
|
|
|
dbg1 "acctchanges"
|
|
|
|
[(a, map snd abs) | abs@((a,_):_) <- transpose colallacctchanges] -- never null, or used when null...
|
|
|
|
|
|
|
|
----------------------------------------------------------------------
|
|
|
|
-- 7. Build the report rows.
|
|
|
|
|
|
|
|
-- One row per account, with account name info, column amounts, row total and row average.
|
|
|
|
-- Calculate them two ways: unvalued for calculating column/grand totals, and valued for display.
|
|
|
|
rows :: [MultiBalanceReportRow] =
|
|
|
|
dbg1 "rows" $
|
|
|
|
[(a, accountLeafName a, accountNameLevel a, unvaluedbals, rowtot, rowavg)
|
|
|
|
| (a,changes) <- acctchanges
|
|
|
|
-- The amounts to be displayed (period changes, cumulative totals, or historical balances).
|
|
|
|
, let unvaluedbals = case balancetype_ of
|
|
|
|
HistoricalBalance -> drop 1 $ scanl (+) (startingBalanceFor a) changes
|
|
|
|
CumulativeChange -> drop 1 $ scanl (+) 0 changes
|
|
|
|
_ -> changes
|
|
|
|
-- The total and average for the row.
|
|
|
|
, let rowtot = sum unvaluedbals
|
|
|
|
, let rowavg = averageMixedAmounts unvaluedbals
|
|
|
|
, empty_ || depth == 0 || any (not . isZeroMixedAmount) unvaluedbals
|
|
|
|
]
|
|
|
|
rowsvalued :: [MultiBalanceReportRow] =
|
|
|
|
dbg1 "rowsvalued" $
|
|
|
|
[(a, accountLeafName a, accountNameLevel a, valuedbals, valuedrowtot, valuedrowavg)
|
|
|
|
| (a,changes) <- acctchanges
|
|
|
|
-- The amounts to be displayed (period changes, cumulative totals, or historical balances).
|
|
|
|
, let unvaluedbals = case balancetype_ of
|
|
|
|
HistoricalBalance -> drop 1 $ scanl (+) (startingBalanceFor a) changes
|
|
|
|
CumulativeChange -> drop 1 $ scanl (+) 0 changes
|
|
|
|
_ -> changes
|
|
|
|
-- The amounts valued according to --value-at, if needed.
|
|
|
|
, let valuedbals1 = case balancetype_ of
|
|
|
|
HistoricalBalance -> drop 1 $ scanl (+) (valuedStartingBalanceFor a) changes
|
|
|
|
CumulativeChange -> drop 1 $ scanl (+) 0 changes
|
|
|
|
_ -> changes
|
|
|
|
, let valuedbals = case mvalueat of
|
|
|
|
Just AtTransaction -> valuedbals1
|
|
|
|
Just AtPeriod -> [mixedAmountValue prices periodlastday amt | (amt,periodlastday) <- zip unvaluedbals lastdays]
|
|
|
|
Just AtNow -> [mixedAmountValue prices today amt | amt <- valuedbals1]
|
|
|
|
Just (AtDate d) -> [mixedAmountValue prices d amt | amt <- valuedbals1]
|
|
|
|
_ -> unvaluedbals --value-at=transaction was handled earlier
|
|
|
|
-- The total and average for the row, and their values.
|
|
|
|
, let rowtot = sum unvaluedbals
|
|
|
|
, let rowavg = averageMixedAmounts unvaluedbals
|
|
|
|
, let valuedrowtot = case mvalueat of
|
|
|
|
Just AtPeriod -> mixedAmountValue prices reportlastday rowtot
|
|
|
|
Just AtNow -> mixedAmountValue prices today rowtot
|
|
|
|
Just (AtDate d) -> mixedAmountValue prices d rowtot
|
|
|
|
_ -> rowtot
|
|
|
|
, let valuedrowavg = case mvalueat of
|
|
|
|
Just AtPeriod -> mixedAmountValue prices reportlastday rowavg
|
|
|
|
Just AtNow -> mixedAmountValue prices today rowavg
|
|
|
|
Just (AtDate d) -> mixedAmountValue prices d rowavg
|
|
|
|
_ -> rowavg
|
|
|
|
, empty_ || depth == 0 || any (not . isZeroMixedAmount) valuedbals
|
2014-04-13 22:07:39 +04:00
|
|
|
]
|
2019-05-09 17:58:45 +03:00
|
|
|
|
|
|
|
----------------------------------------------------------------------
|
2019-05-09 22:22:48 +03:00
|
|
|
-- 8. Sort the report rows.
|
2019-05-09 17:58:45 +03:00
|
|
|
|
|
|
|
-- Sort the rows by amount or by account declaration order. This is a bit tricky.
|
|
|
|
-- TODO: is it always ok to sort report rows after report has been generated, as a separate step ?
|
|
|
|
sortedrowsvalued :: [MultiBalanceReportRow] =
|
|
|
|
dbg1 "sortedrowsvalued" $
|
|
|
|
sortrows rowsvalued
|
2017-09-30 05:19:07 +03:00
|
|
|
where
|
2019-05-09 17:58:45 +03:00
|
|
|
sortrows
|
2019-05-04 22:34:59 +03:00
|
|
|
| sort_amount_ && accountlistmode_ == ALTree = sortTreeMBRByAmount
|
|
|
|
| sort_amount_ = sortFlatMBRByAmount
|
|
|
|
| otherwise = sortMBRByAccountDeclaration
|
2017-09-30 05:19:07 +03:00
|
|
|
where
|
|
|
|
-- Sort the report rows, representing a tree of accounts, by row total at each level.
|
journal: a new account sorting mechanism, and a bunch of sorting fixes
A bunch of account sorting changes that got intermingled.
First, account codes have been dropped. They can still be parsed and
will be ignored, for now. I don't know if anyone used them.
Instead, account display order is now controlled by the order of account
directives, if any. From the mail list:
I'd like to drop account codes, introduced in hledger 1.9 to control
the display order of accounts. In my experience,
- they are tedious to maintain
- they duplicate/compete with the natural tendency to arrange account
directives to match your mental chart of accounts
- they duplicate/compete with the tree structure created by account
names
and it gets worse if you think about using them more extensively,
eg to classify accounts by type.
Instead, I plan to just let the position (parse order) of account
directives determine the display order of those declared accounts.
Undeclared accounts will be displayed after declared accounts,
sorted alphabetically as usual.
Second, the various account sorting modes have been implemented more
widely and more correctly. All sorting modes (alphabetically, by account
declaration, by amount) should now work correctly in almost all commands
and modes (non-tabular and tabular balance reports, tree and flat modes,
the accounts command). Sorting bugs have been fixed, eg #875.
Only the budget report (balance --budget) does not yet support sorting.
Comprehensive functional tests for sorting in the accounts and balance
commands have been added. If you are confused by some sorting behaviour,
studying these tests is recommended, as sorting gets tricky.
2018-09-23 10:45:07 +03:00
|
|
|
-- Similar to sortMBRByAccountDeclaration/sortAccountNamesByDeclaration.
|
|
|
|
sortTreeMBRByAmount rows = sortedrows
|
2017-09-30 05:19:07 +03:00
|
|
|
where
|
|
|
|
anamesandrows = [(first6 r, r) | r <- rows]
|
|
|
|
anames = map fst anamesandrows
|
|
|
|
atotals = [(a,tot) | (a,_,_,_,tot,_) <- rows]
|
journal: a new account sorting mechanism, and a bunch of sorting fixes
A bunch of account sorting changes that got intermingled.
First, account codes have been dropped. They can still be parsed and
will be ignored, for now. I don't know if anyone used them.
Instead, account display order is now controlled by the order of account
directives, if any. From the mail list:
I'd like to drop account codes, introduced in hledger 1.9 to control
the display order of accounts. In my experience,
- they are tedious to maintain
- they duplicate/compete with the natural tendency to arrange account
directives to match your mental chart of accounts
- they duplicate/compete with the tree structure created by account
names
and it gets worse if you think about using them more extensively,
eg to classify accounts by type.
Instead, I plan to just let the position (parse order) of account
directives determine the display order of those declared accounts.
Undeclared accounts will be displayed after declared accounts,
sorted alphabetically as usual.
Second, the various account sorting modes have been implemented more
widely and more correctly. All sorting modes (alphabetically, by account
declaration, by amount) should now work correctly in almost all commands
and modes (non-tabular and tabular balance reports, tree and flat modes,
the accounts command). Sorting bugs have been fixed, eg #875.
Only the budget report (balance --budget) does not yet support sorting.
Comprehensive functional tests for sorting in the accounts and balance
commands have been added. If you are confused by some sorting behaviour,
studying these tests is recommended, as sorting gets tricky.
2018-09-23 10:45:07 +03:00
|
|
|
accounttree = accountTree "root" anames
|
2017-09-30 05:19:07 +03:00
|
|
|
accounttreewithbals = mapAccounts setibalance accounttree
|
|
|
|
where
|
journal: a new account sorting mechanism, and a bunch of sorting fixes
A bunch of account sorting changes that got intermingled.
First, account codes have been dropped. They can still be parsed and
will be ignored, for now. I don't know if anyone used them.
Instead, account display order is now controlled by the order of account
directives, if any. From the mail list:
I'd like to drop account codes, introduced in hledger 1.9 to control
the display order of accounts. In my experience,
- they are tedious to maintain
- they duplicate/compete with the natural tendency to arrange account
directives to match your mental chart of accounts
- they duplicate/compete with the tree structure created by account
names
and it gets worse if you think about using them more extensively,
eg to classify accounts by type.
Instead, I plan to just let the position (parse order) of account
directives determine the display order of those declared accounts.
Undeclared accounts will be displayed after declared accounts,
sorted alphabetically as usual.
Second, the various account sorting modes have been implemented more
widely and more correctly. All sorting modes (alphabetically, by account
declaration, by amount) should now work correctly in almost all commands
and modes (non-tabular and tabular balance reports, tree and flat modes,
the accounts command). Sorting bugs have been fixed, eg #875.
Only the budget report (balance --budget) does not yet support sorting.
Comprehensive functional tests for sorting in the accounts and balance
commands have been added. If you are confused by some sorting behaviour,
studying these tests is recommended, as sorting gets tricky.
2018-09-23 10:45:07 +03:00
|
|
|
-- should not happen, but it's dangerous; TODO
|
|
|
|
setibalance a = a{aibalance=fromMaybe (error "sortTreeMBRByAmount 1") $ lookup (aname a) atotals}
|
2019-05-04 22:34:59 +03:00
|
|
|
sortedaccounttree = sortAccountTreeByAmount (fromMaybe NormallyPositive normalbalance_) accounttreewithbals
|
journal: a new account sorting mechanism, and a bunch of sorting fixes
A bunch of account sorting changes that got intermingled.
First, account codes have been dropped. They can still be parsed and
will be ignored, for now. I don't know if anyone used them.
Instead, account display order is now controlled by the order of account
directives, if any. From the mail list:
I'd like to drop account codes, introduced in hledger 1.9 to control
the display order of accounts. In my experience,
- they are tedious to maintain
- they duplicate/compete with the natural tendency to arrange account
directives to match your mental chart of accounts
- they duplicate/compete with the tree structure created by account
names
and it gets worse if you think about using them more extensively,
eg to classify accounts by type.
Instead, I plan to just let the position (parse order) of account
directives determine the display order of those declared accounts.
Undeclared accounts will be displayed after declared accounts,
sorted alphabetically as usual.
Second, the various account sorting modes have been implemented more
widely and more correctly. All sorting modes (alphabetically, by account
declaration, by amount) should now work correctly in almost all commands
and modes (non-tabular and tabular balance reports, tree and flat modes,
the accounts command). Sorting bugs have been fixed, eg #875.
Only the budget report (balance --budget) does not yet support sorting.
Comprehensive functional tests for sorting in the accounts and balance
commands have been added. If you are confused by some sorting behaviour,
studying these tests is recommended, as sorting gets tricky.
2018-09-23 10:45:07 +03:00
|
|
|
sortedanames = map aname $ drop 1 $ flattenAccounts sortedaccounttree
|
|
|
|
sortedrows = sortAccountItemsLike sortedanames anamesandrows
|
2018-01-21 06:42:05 +03:00
|
|
|
|
journal: a new account sorting mechanism, and a bunch of sorting fixes
A bunch of account sorting changes that got intermingled.
First, account codes have been dropped. They can still be parsed and
will be ignored, for now. I don't know if anyone used them.
Instead, account display order is now controlled by the order of account
directives, if any. From the mail list:
I'd like to drop account codes, introduced in hledger 1.9 to control
the display order of accounts. In my experience,
- they are tedious to maintain
- they duplicate/compete with the natural tendency to arrange account
directives to match your mental chart of accounts
- they duplicate/compete with the tree structure created by account
names
and it gets worse if you think about using them more extensively,
eg to classify accounts by type.
Instead, I plan to just let the position (parse order) of account
directives determine the display order of those declared accounts.
Undeclared accounts will be displayed after declared accounts,
sorted alphabetically as usual.
Second, the various account sorting modes have been implemented more
widely and more correctly. All sorting modes (alphabetically, by account
declaration, by amount) should now work correctly in almost all commands
and modes (non-tabular and tabular balance reports, tree and flat modes,
the accounts command). Sorting bugs have been fixed, eg #875.
Only the budget report (balance --budget) does not yet support sorting.
Comprehensive functional tests for sorting in the accounts and balance
commands have been added. If you are confused by some sorting behaviour,
studying these tests is recommended, as sorting gets tricky.
2018-09-23 10:45:07 +03:00
|
|
|
-- Sort the report rows, representing a flat account list, by row total.
|
|
|
|
sortFlatMBRByAmount = sortBy (maybeflip $ comparing (normaliseMixedAmountSquashPricesForDisplay . fifth6))
|
2018-01-21 06:42:05 +03:00
|
|
|
where
|
2019-05-04 22:34:59 +03:00
|
|
|
maybeflip = if normalbalance_ == Just NormallyNegative then id else flip
|
2018-01-21 06:42:05 +03:00
|
|
|
|
journal: a new account sorting mechanism, and a bunch of sorting fixes
A bunch of account sorting changes that got intermingled.
First, account codes have been dropped. They can still be parsed and
will be ignored, for now. I don't know if anyone used them.
Instead, account display order is now controlled by the order of account
directives, if any. From the mail list:
I'd like to drop account codes, introduced in hledger 1.9 to control
the display order of accounts. In my experience,
- they are tedious to maintain
- they duplicate/compete with the natural tendency to arrange account
directives to match your mental chart of accounts
- they duplicate/compete with the tree structure created by account
names
and it gets worse if you think about using them more extensively,
eg to classify accounts by type.
Instead, I plan to just let the position (parse order) of account
directives determine the display order of those declared accounts.
Undeclared accounts will be displayed after declared accounts,
sorted alphabetically as usual.
Second, the various account sorting modes have been implemented more
widely and more correctly. All sorting modes (alphabetically, by account
declaration, by amount) should now work correctly in almost all commands
and modes (non-tabular and tabular balance reports, tree and flat modes,
the accounts command). Sorting bugs have been fixed, eg #875.
Only the budget report (balance --budget) does not yet support sorting.
Comprehensive functional tests for sorting in the accounts and balance
commands have been added. If you are confused by some sorting behaviour,
studying these tests is recommended, as sorting gets tricky.
2018-09-23 10:45:07 +03:00
|
|
|
-- Sort the report rows by account declaration order then account name.
|
|
|
|
sortMBRByAccountDeclaration rows = sortedrows
|
|
|
|
where
|
2018-01-21 06:42:05 +03:00
|
|
|
anamesandrows = [(first6 r, r) | r <- rows]
|
|
|
|
anames = map fst anamesandrows
|
2019-05-04 22:34:59 +03:00
|
|
|
sortedanames = sortAccountNamesByDeclaration j (tree_ ropts) anames
|
journal: a new account sorting mechanism, and a bunch of sorting fixes
A bunch of account sorting changes that got intermingled.
First, account codes have been dropped. They can still be parsed and
will be ignored, for now. I don't know if anyone used them.
Instead, account display order is now controlled by the order of account
directives, if any. From the mail list:
I'd like to drop account codes, introduced in hledger 1.9 to control
the display order of accounts. In my experience,
- they are tedious to maintain
- they duplicate/compete with the natural tendency to arrange account
directives to match your mental chart of accounts
- they duplicate/compete with the tree structure created by account
names
and it gets worse if you think about using them more extensively,
eg to classify accounts by type.
Instead, I plan to just let the position (parse order) of account
directives determine the display order of those declared accounts.
Undeclared accounts will be displayed after declared accounts,
sorted alphabetically as usual.
Second, the various account sorting modes have been implemented more
widely and more correctly. All sorting modes (alphabetically, by account
declaration, by amount) should now work correctly in almost all commands
and modes (non-tabular and tabular balance reports, tree and flat modes,
the accounts command). Sorting bugs have been fixed, eg #875.
Only the budget report (balance --budget) does not yet support sorting.
Comprehensive functional tests for sorting in the accounts and balance
commands have been added. If you are confused by some sorting behaviour,
studying these tests is recommended, as sorting gets tricky.
2018-09-23 10:45:07 +03:00
|
|
|
sortedrows = sortAccountItemsLike sortedanames anamesandrows
|
2014-12-26 22:04:23 +03:00
|
|
|
|
2019-05-09 17:58:45 +03:00
|
|
|
----------------------------------------------------------------------
|
|
|
|
-- 9. Build the report totals row.
|
|
|
|
|
|
|
|
-- Calculate and maybe value the column totals.
|
|
|
|
highestlevelaccts = [a | a <- displayaccts, not $ any (`elem` displayaccts) $ init $ expandAccountName a]
|
|
|
|
colamts = transpose [bs | (a,_,_,bs,_,_) <- rows , not (tree_ ropts) || a `elem` highestlevelaccts]
|
|
|
|
colamtsvalued = transpose [bs | (a,_,_,bs,_,_) <- rowsvalued, not (tree_ ropts) || a `elem` highestlevelaccts]
|
|
|
|
coltotals :: [MixedAmount] =
|
|
|
|
dbg1 "coltotals" $
|
|
|
|
case mvalueat of
|
|
|
|
Nothing -> map sum colamts
|
|
|
|
Just AtTransaction -> map sum colamtsvalued
|
|
|
|
Just AtPeriod -> map (\(amts,periodlastday) -> maybevalue periodlastday $ sum amts) $ zip colamts lastdays
|
|
|
|
Just AtNow -> map (maybevalue today . sum) colamts
|
|
|
|
Just (AtDate d) -> map (maybevalue d . sum) colamts
|
|
|
|
-- Calculate and maybe value the grand total and average.
|
|
|
|
[grandtotal,grandaverage] =
|
|
|
|
let amts = map ($ map sum colamts) [sum, averageMixedAmounts]
|
|
|
|
in case mvalueat of
|
|
|
|
Nothing -> amts
|
|
|
|
Just AtTransaction -> amts
|
|
|
|
Just AtPeriod -> map (maybevalue reportlastday) amts
|
|
|
|
Just AtNow -> map (maybevalue today) amts
|
|
|
|
Just (AtDate d) -> map (maybevalue d) amts
|
|
|
|
-- Totals row.
|
|
|
|
totalsrow :: MultiBalanceReportTotals =
|
|
|
|
dbg1 "totalsrow" (coltotals, grandtotal, grandaverage)
|
2014-04-19 22:26:01 +04:00
|
|
|
|
2018-01-30 01:52:03 +03:00
|
|
|
-- | Given a MultiBalanceReport and its normal balance sign,
|
|
|
|
-- if it is known to be normally negative, convert it to normally positive.
|
|
|
|
mbrNormaliseSign :: NormalSign -> MultiBalanceReport -> MultiBalanceReport
|
|
|
|
mbrNormaliseSign NormallyNegative = mbrNegate
|
|
|
|
mbrNormaliseSign _ = id
|
|
|
|
|
|
|
|
-- | Flip the sign of all amounts in a MultiBalanceReport.
|
|
|
|
mbrNegate (MultiBalanceReport (colspans, rows, totalsrow)) =
|
|
|
|
MultiBalanceReport (colspans, map mbrRowNegate rows, mbrTotalsRowNegate totalsrow)
|
|
|
|
where
|
|
|
|
mbrRowNegate (acct,shortacct,indent,amts,tot,avg) = (acct,shortacct,indent,map negate amts,-tot,-avg)
|
|
|
|
mbrTotalsRowNegate (amts,tot,avg) = (map negate amts,-tot,-avg)
|
|
|
|
|
2018-04-03 15:07:13 +03:00
|
|
|
-- | Figure out the overall date span of a multicolumn balance report.
|
|
|
|
multiBalanceReportSpan :: MultiBalanceReport -> DateSpan
|
|
|
|
multiBalanceReportSpan (MultiBalanceReport ([], _, _)) = DateSpan Nothing Nothing
|
|
|
|
multiBalanceReportSpan (MultiBalanceReport (colspans, _, _)) = DateSpan (spanStart $ head colspans) (spanEnd $ last colspans)
|
|
|
|
|
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
|
|
|
|
2018-04-03 15:07:13 +03:00
|
|
|
-- common rendering helper, XXX here for now
|
|
|
|
|
|
|
|
tableAsText :: ReportOpts -> (a -> String) -> Table String String a -> String
|
|
|
|
tableAsText (ReportOpts{pretty_tables_ = pretty}) showcell =
|
|
|
|
unlines
|
|
|
|
. trimborder
|
|
|
|
. lines
|
|
|
|
. render pretty id id showcell
|
|
|
|
. align
|
|
|
|
where
|
|
|
|
trimborder = drop 1 . init . map (drop 1 . init)
|
|
|
|
align (Table l t d) = Table l' t d
|
|
|
|
where
|
|
|
|
acctswidth = maximum' $ map strWidth (headerContents l)
|
|
|
|
l' = padRightWide acctswidth <$> l
|
|
|
|
|
2018-09-04 22:23:07 +03:00
|
|
|
-- tests
|
|
|
|
|
2018-09-06 23:08:26 +03:00
|
|
|
tests_MultiBalanceReports = tests "MultiBalanceReports" [
|
2018-09-04 22:23:07 +03:00
|
|
|
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')
|
|
|
|
(map showw aitems) `is` (map showw eitems)
|
|
|
|
((\(_, b, _) -> showMixedAmountDebug b) atotal) `is` (showMixedAmountDebug etotal) -- we only check the sum of the totals
|
|
|
|
usd0 = usd 0
|
2019-01-04 21:54:52 +03:00
|
|
|
amount0 = Amount {acommodity="$", aquantity=0, aprice=NoPrice, astyle=AmountStyle {ascommodityside = L, ascommodityspaced = False, asprecision = 2, asdecimalpoint = Just '.', asdigitgroups = Nothing}, aismultiplier=False}
|
2018-09-04 22:23:07 +03:00
|
|
|
in
|
|
|
|
tests "multiBalanceReport" [
|
|
|
|
test "null journal" $
|
|
|
|
(defreportopts, nulljournal) `gives` ([], Mixed [nullamt])
|
|
|
|
|
|
|
|
,test "with -H on a populated period" $
|
|
|
|
(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])
|
|
|
|
|
2019-05-09 17:58:45 +03:00
|
|
|
,_test "a valid history on an empty period" $
|
2018-09-04 22:23:07 +03:00
|
|
|
(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])
|
|
|
|
|
2019-05-09 17:58:45 +03:00
|
|
|
,_test "a valid history on an empty period (more complex)" $
|
2018-09-04 22:23:07 +03:00
|
|
|
(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])
|
|
|
|
]
|
|
|
|
]
|