ref: bal: rename some report types to clarify/sync with docs
ReportType -> BalanceCalculation ChangeReport -> CalcChange BudgetReport -> CalcBudget ValueChangeReport -> CalcValueChange BalanceType -> BalanceAccumulation PeriodChange -> PerPeriod CumulativeChange -> Cumulative HistoricalBalance -> Historical ReportOpts: reporttype_ -> balancecalc_ balancetype_ -> balanceaccum_ CompoundBalanceCommandSpec: cbctype -> cbcaccum Hledger.Reports.ReportOptions: balanceTypeOverride -> balanceAccumulationOverride
This commit is contained in:
parent
f54e645dbf
commit
87f575e643
@ -107,8 +107,8 @@ accountTransactionsReport rspec@ReportSpec{rsOpts=ropts} j reportq thisacctq = i
|
|||||||
$ journalApplyValuationFromOpts rspec j
|
$ journalApplyValuationFromOpts rspec j
|
||||||
|
|
||||||
startbal
|
startbal
|
||||||
| balancetype_ ropts == HistoricalBalance = sumPostings priorps
|
| balanceaccum_ ropts == Historical = sumPostings priorps
|
||||||
| otherwise = nullmixedamt
|
| otherwise = nullmixedamt
|
||||||
where
|
where
|
||||||
priorps = dbg5 "priorps" $
|
priorps = dbg5 "priorps" $
|
||||||
filter (matchesPosting
|
filter (matchesPosting
|
||||||
|
|||||||
@ -280,7 +280,7 @@ budgetReportAsText ropts@ReportOpts{..} budgetr = TB.toLazyText $
|
|||||||
-- | Build a 'Table' from a multi-column balance report.
|
-- | Build a 'Table' from a multi-column balance report.
|
||||||
budgetReportAsTable :: ReportOpts -> BudgetReport -> Table Text Text (Maybe MixedAmount, Maybe MixedAmount)
|
budgetReportAsTable :: ReportOpts -> BudgetReport -> Table Text Text (Maybe MixedAmount, Maybe MixedAmount)
|
||||||
budgetReportAsTable
|
budgetReportAsTable
|
||||||
ropts@ReportOpts{balancetype_}
|
ropts@ReportOpts{balanceaccum_}
|
||||||
(PeriodicReport spans rows (PeriodicReportRow _ coltots grandtot grandavg)) =
|
(PeriodicReport spans rows (PeriodicReportRow _ coltots grandtot grandavg)) =
|
||||||
addtotalrow $
|
addtotalrow $
|
||||||
Table
|
Table
|
||||||
@ -288,7 +288,7 @@ budgetReportAsTable
|
|||||||
(Tab.Group NoLine $ map Header colheadings)
|
(Tab.Group NoLine $ map Header colheadings)
|
||||||
(map rowvals rows)
|
(map rowvals rows)
|
||||||
where
|
where
|
||||||
colheadings = map (reportPeriodName balancetype_ spans) spans
|
colheadings = map (reportPeriodName balanceaccum_ spans) spans
|
||||||
++ [" Total" | row_total_ ropts]
|
++ [" Total" | row_total_ ropts]
|
||||||
++ ["Average" | average_ ropts]
|
++ ["Average" | average_ ropts]
|
||||||
|
|
||||||
|
|||||||
@ -292,17 +292,17 @@ calculateReportMatrix rspec@ReportSpec{rsOpts=ropts} j priceoracle startbals col
|
|||||||
-- The valued row amounts to be displayed: per-period changes,
|
-- The valued row amounts to be displayed: per-period changes,
|
||||||
-- zero-based cumulative totals, or
|
-- zero-based cumulative totals, or
|
||||||
-- starting-balance-based historical balances.
|
-- starting-balance-based historical balances.
|
||||||
rowbals name changes = dbg5 "rowbals" $ case balancetype_ ropts of
|
rowbals name changes = dbg5 "rowbals" $ case balanceaccum_ ropts of
|
||||||
PeriodChange -> changeamts
|
PerPeriod -> changeamts
|
||||||
CumulativeChange -> cumulative
|
Cumulative -> cumulative
|
||||||
HistoricalBalance -> historical
|
Historical -> historical
|
||||||
where
|
where
|
||||||
-- changes to report on: usually just the changes itself, but use the
|
-- changes to report on: usually just the changes itself, but use the
|
||||||
-- differences in the historical amount for ValueChangeReports.
|
-- differences in the historical amount for ValueChangeReports.
|
||||||
changeamts = case reporttype_ ropts of
|
changeamts = case balancecalc_ ropts of
|
||||||
ChangeReport -> M.mapWithKey avalue changes
|
CalcChange -> M.mapWithKey avalue changes
|
||||||
BudgetReport -> M.mapWithKey avalue changes
|
CalcBudget -> M.mapWithKey avalue changes
|
||||||
ValueChangeReport -> periodChanges valuedStart historical
|
CalcValueChange -> periodChanges valuedStart historical
|
||||||
cumulative = cumulativeSum avalue nullacct changeamts
|
cumulative = cumulativeSum avalue nullacct changeamts
|
||||||
historical = cumulativeSum avalue startingBalance changes
|
historical = cumulativeSum avalue startingBalance changes
|
||||||
startingBalance = HM.lookupDefault nullacct name startbals
|
startingBalance = HM.lookupDefault nullacct name startbals
|
||||||
@ -368,9 +368,9 @@ buildReportRows ropts displaynames =
|
|||||||
-- The total and average for the row.
|
-- The total and average for the row.
|
||||||
-- These are always simply the sum/average of the displayed row amounts.
|
-- These are always simply the sum/average of the displayed row amounts.
|
||||||
-- Total for a cumulative/historical report is always the last column.
|
-- Total for a cumulative/historical report is always the last column.
|
||||||
rowtot = case balancetype_ ropts of
|
rowtot = case balanceaccum_ ropts of
|
||||||
PeriodChange -> maSum rowbals
|
PerPeriod -> maSum rowbals
|
||||||
_ -> lastDef nullmixedamt rowbals
|
_ -> lastDef nullmixedamt rowbals
|
||||||
rowavg = averageMixedAmounts rowbals
|
rowavg = averageMixedAmounts rowbals
|
||||||
balance = case accountlistmode_ ropts of ALTree -> aibalance; ALFlat -> aebalance
|
balance = case accountlistmode_ ropts of ALTree -> aibalance; ALFlat -> aebalance
|
||||||
|
|
||||||
@ -476,9 +476,9 @@ calculateTotalsRow ropts rows =
|
|||||||
-- Calculate the grand total and average. These are always the sum/average
|
-- Calculate the grand total and average. These are always the sum/average
|
||||||
-- of the column totals.
|
-- of the column totals.
|
||||||
-- Total for a cumulative/historical report is always the last column.
|
-- Total for a cumulative/historical report is always the last column.
|
||||||
grandtotal = case balancetype_ ropts of
|
grandtotal = case balanceaccum_ ropts of
|
||||||
PeriodChange -> maSum coltotals
|
PerPeriod -> maSum coltotals
|
||||||
_ -> lastDef nullmixedamt coltotals
|
_ -> lastDef nullmixedamt coltotals
|
||||||
grandaverage = averageMixedAmounts coltotals
|
grandaverage = averageMixedAmounts coltotals
|
||||||
|
|
||||||
-- | Map the report rows to percentages if needed
|
-- | Map the report rows to percentages if needed
|
||||||
@ -574,7 +574,7 @@ tests_MultiBalanceReport = tests "MultiBalanceReport" [
|
|||||||
(defreportspec, nulljournal) `gives` ([], nullmixedamt)
|
(defreportspec, nulljournal) `gives` ([], nullmixedamt)
|
||||||
|
|
||||||
,test "with -H on a populated period" $
|
,test "with -H on a populated period" $
|
||||||
(defreportspec{rsOpts=defreportopts{period_= PeriodBetween (fromGregorian 2008 1 1) (fromGregorian 2008 1 2), balancetype_=HistoricalBalance}}, samplejournal) `gives`
|
(defreportspec{rsOpts=defreportopts{period_= PeriodBetween (fromGregorian 2008 1 1) (fromGregorian 2008 1 2), balanceaccum_=Historical}}, samplejournal) `gives`
|
||||||
(
|
(
|
||||||
[ PeriodicReportRow (flatDisplayName "assets:bank:checking") [mamountp' "$1.00"] (mamountp' "$1.00") (mixedAmount amt0{aquantity=1})
|
[ PeriodicReportRow (flatDisplayName "assets:bank:checking") [mamountp' "$1.00"] (mamountp' "$1.00") (mixedAmount amt0{aquantity=1})
|
||||||
, PeriodicReportRow (flatDisplayName "income:salary") [mamountp' "$-1.00"] (mamountp' "$-1.00") (mixedAmount amt0{aquantity=(-1)})
|
, PeriodicReportRow (flatDisplayName "income:salary") [mamountp' "$-1.00"] (mamountp' "$-1.00") (mixedAmount amt0{aquantity=(-1)})
|
||||||
@ -582,7 +582,7 @@ tests_MultiBalanceReport = tests "MultiBalanceReport" [
|
|||||||
mamountp' "$0.00")
|
mamountp' "$0.00")
|
||||||
|
|
||||||
-- ,test "a valid history on an empty period" $
|
-- ,test "a valid history on an empty period" $
|
||||||
-- (defreportopts{period_= PeriodBetween (fromGregorian 2008 1 2) (fromGregorian 2008 1 3), balancetype_=HistoricalBalance}, samplejournal) `gives`
|
-- (defreportopts{period_= PeriodBetween (fromGregorian 2008 1 2) (fromGregorian 2008 1 3), balanceaccum_=Historical}, samplejournal) `gives`
|
||||||
-- (
|
-- (
|
||||||
-- [
|
-- [
|
||||||
-- ("assets:bank:checking","checking",3, [mamountp' "$1.00"], mamountp' "$1.00",mixedAmount amt0 {aquantity=1})
|
-- ("assets:bank:checking","checking",3, [mamountp' "$1.00"], mamountp' "$1.00",mixedAmount amt0 {aquantity=1})
|
||||||
@ -591,7 +591,7 @@ tests_MultiBalanceReport = tests "MultiBalanceReport" [
|
|||||||
-- mixedAmount usd0)
|
-- mixedAmount usd0)
|
||||||
|
|
||||||
-- ,test "a valid history on an empty period (more complex)" $
|
-- ,test "a valid history on an empty period (more complex)" $
|
||||||
-- (defreportopts{period_= PeriodBetween (fromGregorian 2009 1 1) (fromGregorian 2009 1 2), balancetype_=HistoricalBalance}, samplejournal) `gives`
|
-- (defreportopts{period_= PeriodBetween (fromGregorian 2009 1 1) (fromGregorian 2009 1 2), balanceaccum_=Historical}, samplejournal) `gives`
|
||||||
-- (
|
-- (
|
||||||
-- [
|
-- [
|
||||||
-- ("assets:bank:checking","checking",3, [mamountp' "$1.00"], mamountp' "$1.00",mixedAmount amt0 {aquantity=1})
|
-- ("assets:bank:checking","checking",3, [mamountp' "$1.00"], mamountp' "$1.00",mixedAmount amt0 {aquantity=1})
|
||||||
|
|||||||
@ -90,7 +90,7 @@ postingsReport rspec@ReportSpec{rsOpts=ropts@ReportOpts{..}} j = items
|
|||||||
-- may be converting to value per hledger_options.m4.md "Effect
|
-- may be converting to value per hledger_options.m4.md "Effect
|
||||||
-- of --value on reports".
|
-- of --value on reports".
|
||||||
-- XXX balance report doesn't value starting balance.. should this ?
|
-- XXX balance report doesn't value starting balance.. should this ?
|
||||||
historical = balancetype_ == HistoricalBalance
|
historical = balanceaccum_ == Historical
|
||||||
startbal | average_ = if historical then precedingavg else nullmixedamt
|
startbal | average_ = if historical then precedingavg else nullmixedamt
|
||||||
| otherwise = if historical then precedingsum else nullmixedamt
|
| otherwise = if historical then precedingsum else nullmixedamt
|
||||||
where
|
where
|
||||||
|
|||||||
@ -11,8 +11,8 @@ Options common to most hledger reports.
|
|||||||
module Hledger.Reports.ReportOptions (
|
module Hledger.Reports.ReportOptions (
|
||||||
ReportOpts(..),
|
ReportOpts(..),
|
||||||
ReportSpec(..),
|
ReportSpec(..),
|
||||||
ReportType(..),
|
BalanceCalculation(..),
|
||||||
BalanceType(..),
|
BalanceAccumulation(..),
|
||||||
AccountListMode(..),
|
AccountListMode(..),
|
||||||
ValuationType(..),
|
ValuationType(..),
|
||||||
defreportopts,
|
defreportopts,
|
||||||
@ -22,7 +22,7 @@ module Hledger.Reports.ReportOptions (
|
|||||||
updateReportSpec,
|
updateReportSpec,
|
||||||
updateReportSpecWith,
|
updateReportSpecWith,
|
||||||
rawOptsToReportSpec,
|
rawOptsToReportSpec,
|
||||||
balanceTypeOverride,
|
balanceAccumulationOverride,
|
||||||
flat_,
|
flat_,
|
||||||
tree_,
|
tree_,
|
||||||
reportOptsToggleStatus,
|
reportOptsToggleStatus,
|
||||||
@ -65,23 +65,26 @@ import Hledger.Query
|
|||||||
import Hledger.Utils
|
import Hledger.Utils
|
||||||
|
|
||||||
|
|
||||||
-- | What is calculated and shown in each cell in a balance report.
|
-- | What to calculate for each cell in a balance report.
|
||||||
data ReportType = ChangeReport -- ^ The sum of posting amounts.
|
-- "Balance report types -> Calculation type" in the hledger manual.
|
||||||
| BudgetReport -- ^ The sum of posting amounts and the goal.
|
data BalanceCalculation =
|
||||||
| ValueChangeReport -- ^ The change of value of period-end historical values.
|
CalcChange -- ^ Sum of posting amounts in the period.
|
||||||
|
| CalcBudget -- ^ Sum of posting amounts and the goal for the period.
|
||||||
|
| CalcValueChange -- ^ Change from previous period's historical end value to this period's historical end value.
|
||||||
deriving (Eq, Show)
|
deriving (Eq, Show)
|
||||||
|
|
||||||
instance Default ReportType where def = ChangeReport
|
instance Default BalanceCalculation where def = CalcChange
|
||||||
|
|
||||||
-- | Which "accumulation method" is being shown in a balance report.
|
-- | How to accumulate calculated values across periods (columns) in a balance report.
|
||||||
data BalanceType = PeriodChange -- ^ The accumulate change over a single period.
|
-- "Balance report types -> Accumulation type" in the hledger manual.
|
||||||
| CumulativeChange -- ^ The accumulated change across multiple periods.
|
data BalanceAccumulation =
|
||||||
| HistoricalBalance -- ^ The historical ending balance, including the effect of
|
PerPeriod -- ^ No accumulation. Eg, shows the change of balance in each period.
|
||||||
-- all postings before the report period. Unless altered by,
|
| Cumulative -- ^ Accumulate changes across periods, starting from zero at report start.
|
||||||
-- a query, this is what you would see on a bank statement.
|
| Historical -- ^ Accumulate changes across periods, including any from before report start.
|
||||||
|
-- Eg, shows the historical end balance of each period.
|
||||||
deriving (Eq,Show)
|
deriving (Eq,Show)
|
||||||
|
|
||||||
instance Default BalanceType where def = PeriodChange
|
instance Default BalanceAccumulation where def = PerPeriod
|
||||||
|
|
||||||
-- | Should accounts be displayed: in the command's default style, hierarchically, or as a flat list ?
|
-- | Should accounts be displayed: in the command's default style, hierarchically, or as a flat list ?
|
||||||
data AccountListMode = ALFlat | ALTree deriving (Eq, Show)
|
data AccountListMode = ALFlat | ALTree deriving (Eq, Show)
|
||||||
@ -114,8 +117,8 @@ data ReportOpts = ReportOpts {
|
|||||||
-- for account transactions reports (aregister)
|
-- for account transactions reports (aregister)
|
||||||
,txn_dates_ :: Bool
|
,txn_dates_ :: Bool
|
||||||
-- for balance reports (bal, bs, cf, is)
|
-- for balance reports (bal, bs, cf, is)
|
||||||
,reporttype_ :: ReportType
|
,balancecalc_ :: BalanceCalculation
|
||||||
,balancetype_ :: BalanceType
|
,balanceaccum_ :: BalanceAccumulation
|
||||||
,accountlistmode_ :: AccountListMode
|
,accountlistmode_ :: AccountListMode
|
||||||
,drop_ :: Int
|
,drop_ :: Int
|
||||||
,row_total_ :: Bool
|
,row_total_ :: Bool
|
||||||
@ -162,8 +165,8 @@ defreportopts = ReportOpts
|
|||||||
, average_ = False
|
, average_ = False
|
||||||
, related_ = False
|
, related_ = False
|
||||||
, txn_dates_ = False
|
, txn_dates_ = False
|
||||||
, reporttype_ = def
|
, balancecalc_ = def
|
||||||
, balancetype_ = def
|
, balanceaccum_ = def
|
||||||
, accountlistmode_ = ALFlat
|
, accountlistmode_ = ALFlat
|
||||||
, drop_ = 0
|
, drop_ = 0
|
||||||
, row_total_ = False
|
, row_total_ = False
|
||||||
@ -209,8 +212,8 @@ rawOptsToReportOpts rawopts = do
|
|||||||
,average_ = boolopt "average" rawopts
|
,average_ = boolopt "average" rawopts
|
||||||
,related_ = boolopt "related" rawopts
|
,related_ = boolopt "related" rawopts
|
||||||
,txn_dates_ = boolopt "txn-dates" rawopts
|
,txn_dates_ = boolopt "txn-dates" rawopts
|
||||||
,reporttype_ = reporttypeopt rawopts
|
,balancecalc_ = balancecalcopt rawopts
|
||||||
,balancetype_ = balancetypeopt rawopts
|
,balanceaccum_ = balanceaccumopt rawopts
|
||||||
,accountlistmode_ = accountlistmodeopt rawopts
|
,accountlistmode_ = accountlistmodeopt rawopts
|
||||||
,drop_ = posintopt "drop" rawopts
|
,drop_ = posintopt "drop" rawopts
|
||||||
,row_total_ = boolopt "row-total" rawopts
|
,row_total_ = boolopt "row-total" rawopts
|
||||||
@ -286,29 +289,29 @@ accountlistmodeopt =
|
|||||||
"flat" -> Just ALFlat
|
"flat" -> Just ALFlat
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
|
|
||||||
reporttypeopt :: RawOpts -> ReportType
|
balancecalcopt :: RawOpts -> BalanceCalculation
|
||||||
reporttypeopt =
|
balancecalcopt =
|
||||||
fromMaybe ChangeReport . choiceopt parse where
|
fromMaybe CalcChange . choiceopt parse where
|
||||||
parse = \case
|
parse = \case
|
||||||
"sum" -> Just ChangeReport
|
"sum" -> Just CalcChange
|
||||||
"valuechange" -> Just ValueChangeReport
|
"valuechange" -> Just CalcValueChange
|
||||||
"budget" -> Just BudgetReport
|
"budget" -> Just CalcBudget
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
|
|
||||||
balancetypeopt :: RawOpts -> BalanceType
|
balanceaccumopt :: RawOpts -> BalanceAccumulation
|
||||||
balancetypeopt = fromMaybe PeriodChange . balanceTypeOverride
|
balanceaccumopt = fromMaybe PerPeriod . balanceAccumulationOverride
|
||||||
|
|
||||||
balanceTypeOverride :: RawOpts -> Maybe BalanceType
|
balanceAccumulationOverride :: RawOpts -> Maybe BalanceAccumulation
|
||||||
balanceTypeOverride rawopts = choiceopt parse rawopts <|> reportbal
|
balanceAccumulationOverride rawopts = choiceopt parse rawopts <|> reportbal
|
||||||
where
|
where
|
||||||
parse = \case
|
parse = \case
|
||||||
"historical" -> Just HistoricalBalance
|
"historical" -> Just Historical
|
||||||
"cumulative" -> Just CumulativeChange
|
"cumulative" -> Just Cumulative
|
||||||
"change" -> Just PeriodChange
|
"change" -> Just PerPeriod
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
reportbal = case reporttypeopt rawopts of
|
reportbal = case balancecalcopt rawopts of
|
||||||
ValueChangeReport -> Just PeriodChange
|
CalcValueChange -> Just PerPeriod
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
|
|
||||||
-- Get the period specified by any -b/--begin, -e/--end and/or -p/--period
|
-- Get the period specified by any -b/--begin, -e/--end and/or -p/--period
|
||||||
-- options appearing in the command line.
|
-- options appearing in the command line.
|
||||||
@ -321,8 +324,7 @@ periodFromRawOpts d rawopts =
|
|||||||
(Nothing, Nothing) -> PeriodAll
|
(Nothing, Nothing) -> PeriodAll
|
||||||
(Just b, Nothing) -> PeriodFrom b
|
(Just b, Nothing) -> PeriodFrom b
|
||||||
(Nothing, Just e) -> PeriodTo e
|
(Nothing, Just e) -> PeriodTo e
|
||||||
(Just b, Just e) -> simplifyPeriod $
|
(Just b, Just e) -> simplifyPeriod $ PeriodBetween b e
|
||||||
PeriodBetween b e
|
|
||||||
where
|
where
|
||||||
mlastb = case beginDatesFromRawOpts d rawopts of
|
mlastb = case beginDatesFromRawOpts d rawopts of
|
||||||
[] -> Nothing
|
[] -> Nothing
|
||||||
@ -439,8 +441,8 @@ valuationTypeFromRawOpts :: RawOpts -> (Costing, Maybe ValuationType)
|
|||||||
valuationTypeFromRawOpts rawopts = (costing, valuation)
|
valuationTypeFromRawOpts rawopts = (costing, valuation)
|
||||||
where
|
where
|
||||||
costing = if (any ((Cost==) . fst) valuationopts) then Cost else NoCost
|
costing = if (any ((Cost==) . fst) valuationopts) then Cost else NoCost
|
||||||
valuation = case reporttypeopt rawopts of
|
valuation = case balancecalcopt rawopts of
|
||||||
ValueChangeReport -> case directval of
|
CalcValueChange -> case directval of
|
||||||
Nothing -> Just $ AtEnd Nothing -- If no valuation requested for valuechange, use AtEnd
|
Nothing -> Just $ AtEnd Nothing -- If no valuation requested for valuechange, use AtEnd
|
||||||
Just (AtEnd _) -> directval -- If AtEnd valuation requested, use it
|
Just (AtEnd _) -> directval -- If AtEnd valuation requested, use it
|
||||||
Just _ -> usageError "--valuechange only produces sensible results with --value=end"
|
Just _ -> usageError "--valuechange only produces sensible results with --value=end"
|
||||||
@ -544,8 +546,8 @@ valuationAfterSum :: ReportOpts -> Maybe (Maybe CommoditySymbol)
|
|||||||
valuationAfterSum ropts = case value_ ropts of
|
valuationAfterSum ropts = case value_ ropts of
|
||||||
Just (AtEnd mc) | valueAfterSum -> Just mc
|
Just (AtEnd mc) | valueAfterSum -> Just mc
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
where valueAfterSum = reporttype_ ropts == ValueChangeReport
|
where valueAfterSum = balancecalc_ ropts == CalcValueChange
|
||||||
|| balancetype_ ropts /= PeriodChange
|
|| balanceaccum_ ropts /= PerPeriod
|
||||||
|
|
||||||
|
|
||||||
-- | Convert report options to a query, ignoring any non-flag command line arguments.
|
-- | Convert report options to a query, ignoring any non-flag command line arguments.
|
||||||
@ -652,10 +654,10 @@ reportPeriodOrJournalLastDay rspec j = reportPeriodLastDay rspec <|> journalOrPr
|
|||||||
--
|
--
|
||||||
-- - all other balance change reports: a description of the datespan,
|
-- - all other balance change reports: a description of the datespan,
|
||||||
-- abbreviated to compact form if possible (see showDateSpan).
|
-- abbreviated to compact form if possible (see showDateSpan).
|
||||||
reportPeriodName :: BalanceType -> [DateSpan] -> DateSpan -> T.Text
|
reportPeriodName :: BalanceAccumulation -> [DateSpan] -> DateSpan -> T.Text
|
||||||
reportPeriodName balancetype spans =
|
reportPeriodName balanceaccumulation spans =
|
||||||
case balancetype of
|
case balanceaccumulation of
|
||||||
PeriodChange -> if multiyear then showDateSpan else showDateSpanMonthAbbrev
|
PerPeriod -> if multiyear then showDateSpan else showDateSpanMonthAbbrev
|
||||||
where
|
where
|
||||||
multiyear = (>1) $ length $ nubSort $ map spanStartYear spans
|
multiyear = (>1) $ length $ nubSort $ map spanStartYear spans
|
||||||
_ -> maybe "" (showDate . prevday) . spanEnd
|
_ -> maybe "" (showDate . prevday) . spanEnd
|
||||||
|
|||||||
@ -64,7 +64,7 @@ type Average = MixedAmount -- ^ The average of 'Change's or 'Balance's in a rep
|
|||||||
--
|
--
|
||||||
-- * A list of amounts, one for each column. Depending on the value type,
|
-- * A list of amounts, one for each column. Depending on the value type,
|
||||||
-- these can represent balance changes, ending balances, budget
|
-- these can represent balance changes, ending balances, budget
|
||||||
-- performance, etc. (for example, see 'BalanceType' and
|
-- performance, etc. (for example, see 'BalanceAccumulation' and
|
||||||
-- "Hledger.Cli.Commands.Balance").
|
-- "Hledger.Cli.Commands.Balance").
|
||||||
--
|
--
|
||||||
-- * the total of the row's amounts for a periodic report,
|
-- * the total of the row's amounts for a periodic report,
|
||||||
|
|||||||
@ -153,7 +153,7 @@ asDraw UIState{aopts=_uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec}}
|
|||||||
|
|
||||||
where
|
where
|
||||||
ropts = rsOpts rspec
|
ropts = rsOpts rspec
|
||||||
ishistorical = balancetype_ ropts == HistoricalBalance
|
ishistorical = balanceaccum_ ropts == Historical
|
||||||
|
|
||||||
toplabel =
|
toplabel =
|
||||||
withAttr ("border" <> "filename") files
|
withAttr ("border" <> "filename") files
|
||||||
|
|||||||
@ -109,7 +109,7 @@ runBrickUi uopts@UIOpts{cliopts_=copts@CliOpts{inputopts_=_iopts,reportspec_=rsp
|
|||||||
period_=periodfromoptsandargs, -- query's date part
|
period_=periodfromoptsandargs, -- query's date part
|
||||||
no_elide_=True, -- avoid squashing boring account names, for a more regular tree (unlike hledger)
|
no_elide_=True, -- avoid squashing boring account names, for a more regular tree (unlike hledger)
|
||||||
empty_=not $ empty_ ropts, -- show zero items by default, hide them with -E (unlike hledger)
|
empty_=not $ empty_ ropts, -- show zero items by default, hide them with -E (unlike hledger)
|
||||||
balancetype_=HistoricalBalance -- show historical balances by default (unlike hledger)
|
balanceaccum_=Historical -- show historical balances by default (unlike hledger)
|
||||||
}
|
}
|
||||||
}
|
}
|
||||||
}
|
}
|
||||||
|
|||||||
@ -70,7 +70,7 @@ rsInit d reset ui@UIState{aopts=_uopts@UIOpts{cliopts_=CliOpts{reportspec_=rspec
|
|||||||
depth_=Nothing
|
depth_=Nothing
|
||||||
-- XXX aregister also has this, needed ?
|
-- XXX aregister also has this, needed ?
|
||||||
-- always show historical balance
|
-- always show historical balance
|
||||||
-- , balancetype_= HistoricalBalance
|
-- , balanceaccum_= Historical
|
||||||
}
|
}
|
||||||
rspec' =
|
rspec' =
|
||||||
either (error "rsInit: adjusting the query for register, should not have failed") id $ -- PARTIAL:
|
either (error "rsInit: adjusting the query for register, should not have failed") id $ -- PARTIAL:
|
||||||
@ -201,7 +201,7 @@ rsDraw UIState{aopts=_uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec}}
|
|||||||
|
|
||||||
where
|
where
|
||||||
ropts = rsOpts rspec
|
ropts = rsOpts rspec
|
||||||
ishistorical = balancetype_ ropts == HistoricalBalance
|
ishistorical = balanceaccum_ ropts == Historical
|
||||||
-- inclusive = tree_ ropts || rsForceInclusive
|
-- inclusive = tree_ ropts || rsForceInclusive
|
||||||
|
|
||||||
toplabel =
|
toplabel =
|
||||||
|
|||||||
@ -146,10 +146,10 @@ toggleTree ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspe
|
|||||||
-- | Toggle between historical balances and period balances.
|
-- | Toggle between historical balances and period balances.
|
||||||
toggleHistorical :: UIState -> UIState
|
toggleHistorical :: UIState -> UIState
|
||||||
toggleHistorical ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{rsOpts=ropts}}}} =
|
toggleHistorical ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{rsOpts=ropts}}}} =
|
||||||
ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{rsOpts=ropts{balancetype_=b}}}}}
|
ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{rsOpts=ropts{balanceaccum_=b}}}}}
|
||||||
where
|
where
|
||||||
b | balancetype_ ropts == HistoricalBalance = PeriodChange
|
b | balanceaccum_ ropts == Historical = PerPeriod
|
||||||
| otherwise = HistoricalBalance
|
| otherwise = Historical
|
||||||
|
|
||||||
-- | Toggle hledger-ui's "forecast/future mode". When this mode is enabled,
|
-- | Toggle hledger-ui's "forecast/future mode". When this mode is enabled,
|
||||||
-- hledger-shows regular transactions which have future dates, and
|
-- hledger-shows regular transactions which have future dates, and
|
||||||
|
|||||||
@ -46,7 +46,7 @@ getRegisterR = do
|
|||||||
tail $ (", "<$xs) ++ [""]
|
tail $ (", "<$xs) ++ [""]
|
||||||
items = accountTransactionsReport rspec j m acctQuery
|
items = accountTransactionsReport rspec j m acctQuery
|
||||||
balancelabel
|
balancelabel
|
||||||
| isJust (inAccount qopts), balancetype_ (rsOpts rspec) == HistoricalBalance = "Historical Total"
|
| isJust (inAccount qopts), balanceaccum_ (rsOpts rspec) == Historical = "Historical Total"
|
||||||
| isJust (inAccount qopts) = "Period Total"
|
| isJust (inAccount qopts) = "Period Total"
|
||||||
| otherwise = "Total"
|
| otherwise = "Total"
|
||||||
transactionFrag = transactionFragment j
|
transactionFrag = transactionFragment j
|
||||||
|
|||||||
@ -86,7 +86,7 @@ aregister opts@CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do
|
|||||||
-- ignore any depth limit, as in postingsReport; allows register's total to match balance reports (cf #1468)
|
-- ignore any depth limit, as in postingsReport; allows register's total to match balance reports (cf #1468)
|
||||||
depth_=Nothing
|
depth_=Nothing
|
||||||
-- always show historical balance
|
-- always show historical balance
|
||||||
, balancetype_= HistoricalBalance
|
, balanceaccum_= Historical
|
||||||
}
|
}
|
||||||
-- and regenerate the ReportSpec, making sure to use the above
|
-- and regenerate the ReportSpec, making sure to use the above
|
||||||
rspec' = rspec{ rsQuery=simplifyQuery $ And [queryFromFlags ropts', argsquery]
|
rspec' = rspec{ rsQuery=simplifyQuery $ And [queryFromFlags ropts', argsquery]
|
||||||
|
|||||||
@ -310,8 +310,8 @@ balancemode = hledgerCommandMode
|
|||||||
|
|
||||||
-- | The balance command, prints a balance report.
|
-- | The balance command, prints a balance report.
|
||||||
balance :: CliOpts -> Journal -> IO ()
|
balance :: CliOpts -> Journal -> IO ()
|
||||||
balance opts@CliOpts{reportspec_=rspec} j = case reporttype_ of
|
balance opts@CliOpts{reportspec_=rspec} j = case balancecalc_ of
|
||||||
BudgetReport -> do -- single or multi period budget report
|
CalcBudget -> do -- single or multi period budget report
|
||||||
let reportspan = reportSpan j rspec
|
let reportspan = reportSpan j rspec
|
||||||
budgetreport = budgetReport rspec (balancingopts_ $ inputopts_ opts) reportspan j
|
budgetreport = budgetReport rspec (balancingopts_ $ inputopts_ opts) reportspan j
|
||||||
render = case fmt of
|
render = case fmt of
|
||||||
@ -586,12 +586,12 @@ multiBalanceReportAsText ropts@ReportOpts{..} r = TB.toLazyText $
|
|||||||
where
|
where
|
||||||
title = mtitle <> " in " <> showDateSpan (periodicReportSpan r) <> valuationdesc <> ":"
|
title = mtitle <> " in " <> showDateSpan (periodicReportSpan r) <> valuationdesc <> ":"
|
||||||
|
|
||||||
mtitle = case (reporttype_, balancetype_) of
|
mtitle = case (balancecalc_, balanceaccum_) of
|
||||||
(ValueChangeReport, PeriodChange ) -> "Period-end value changes"
|
(CalcValueChange, PerPeriod ) -> "Period-end value changes"
|
||||||
(ValueChangeReport, CumulativeChange ) -> "Cumulative period-end value changes"
|
(CalcValueChange, Cumulative ) -> "Cumulative period-end value changes"
|
||||||
(_, PeriodChange ) -> "Balance changes"
|
(_, PerPeriod ) -> "Balance changes"
|
||||||
(_, CumulativeChange ) -> "Ending balances (cumulative)"
|
(_, Cumulative ) -> "Ending balances (cumulative)"
|
||||||
(_, HistoricalBalance) -> "Ending balances (historical)"
|
(_, Historical) -> "Ending balances (historical)"
|
||||||
valuationdesc =
|
valuationdesc =
|
||||||
(case cost_ of
|
(case cost_ of
|
||||||
Cost -> ", converted to cost"
|
Cost -> ", converted to cost"
|
||||||
@ -604,14 +604,14 @@ multiBalanceReportAsText ropts@ReportOpts{..} r = TB.toLazyText $
|
|||||||
Just (AtDate d _mc) -> ", valued at " <> showDate d
|
Just (AtDate d _mc) -> ", valued at " <> showDate d
|
||||||
Nothing -> "")
|
Nothing -> "")
|
||||||
|
|
||||||
changingValuation = case (reporttype_, balancetype_) of
|
changingValuation = case (balancecalc_, balanceaccum_) of
|
||||||
(ValueChangeReport, PeriodChange) -> True
|
(CalcValueChange, PerPeriod) -> True
|
||||||
(ValueChangeReport, CumulativeChange) -> True
|
(CalcValueChange, Cumulative) -> True
|
||||||
_ -> False
|
_ -> False
|
||||||
|
|
||||||
-- | Build a 'Table' from a multi-column balance report.
|
-- | Build a 'Table' from a multi-column balance report.
|
||||||
balanceReportAsTable :: ReportOpts -> MultiBalanceReport -> Table T.Text T.Text MixedAmount
|
balanceReportAsTable :: ReportOpts -> MultiBalanceReport -> Table T.Text T.Text MixedAmount
|
||||||
balanceReportAsTable opts@ReportOpts{average_, row_total_, balancetype_}
|
balanceReportAsTable opts@ReportOpts{average_, row_total_, balanceaccum_}
|
||||||
(PeriodicReport spans items (PeriodicReportRow _ coltotals tot avg)) =
|
(PeriodicReport spans items (PeriodicReportRow _ coltotals tot avg)) =
|
||||||
maybetranspose $
|
maybetranspose $
|
||||||
addtotalrow $
|
addtotalrow $
|
||||||
@ -620,8 +620,8 @@ balanceReportAsTable opts@ReportOpts{average_, row_total_, balancetype_}
|
|||||||
(Tab.Group NoLine $ map Header colheadings)
|
(Tab.Group NoLine $ map Header colheadings)
|
||||||
(map rowvals items)
|
(map rowvals items)
|
||||||
where
|
where
|
||||||
totalscolumn = row_total_ && balancetype_ `notElem` [CumulativeChange, HistoricalBalance]
|
totalscolumn = row_total_ && balanceaccum_ `notElem` [Cumulative, Historical]
|
||||||
colheadings = map (reportPeriodName balancetype_ spans) spans
|
colheadings = map (reportPeriodName balanceaccum_ spans) spans
|
||||||
++ [" Total" | totalscolumn]
|
++ [" Total" | totalscolumn]
|
||||||
++ ["Average" | average_]
|
++ ["Average" | average_]
|
||||||
accts = map renderacct items
|
accts = map renderacct items
|
||||||
|
|||||||
@ -37,7 +37,7 @@ balancesheetSpec = CompoundBalanceCommandSpec {
|
|||||||
,cbcsubreportincreasestotal=False
|
,cbcsubreportincreasestotal=False
|
||||||
}
|
}
|
||||||
],
|
],
|
||||||
cbctype = HistoricalBalance
|
cbcaccum = Historical
|
||||||
}
|
}
|
||||||
|
|
||||||
balancesheetmode :: Mode RawOpts
|
balancesheetmode :: Mode RawOpts
|
||||||
|
|||||||
@ -45,7 +45,7 @@ balancesheetequitySpec = CompoundBalanceCommandSpec {
|
|||||||
,cbcsubreportincreasestotal=False
|
,cbcsubreportincreasestotal=False
|
||||||
}
|
}
|
||||||
],
|
],
|
||||||
cbctype = HistoricalBalance
|
cbcaccum = Historical
|
||||||
}
|
}
|
||||||
|
|
||||||
balancesheetequitymode :: Mode RawOpts
|
balancesheetequitymode :: Mode RawOpts
|
||||||
|
|||||||
@ -34,7 +34,7 @@ cashflowSpec = CompoundBalanceCommandSpec {
|
|||||||
,cbcsubreportincreasestotal=True
|
,cbcsubreportincreasestotal=True
|
||||||
}
|
}
|
||||||
],
|
],
|
||||||
cbctype = PeriodChange
|
cbcaccum = PerPeriod
|
||||||
}
|
}
|
||||||
|
|
||||||
cashflowmode :: Mode RawOpts
|
cashflowmode :: Mode RawOpts
|
||||||
|
|||||||
@ -102,7 +102,7 @@ close CliOpts{rawopts_=rawopts, reportspec_=rspec} j = do
|
|||||||
explicit = boolopt "explicit" rawopts
|
explicit = boolopt "explicit" rawopts
|
||||||
|
|
||||||
-- the balances to close
|
-- the balances to close
|
||||||
ropts = (rsOpts rspec){balancetype_=HistoricalBalance, accountlistmode_=ALFlat}
|
ropts = (rsOpts rspec){balanceaccum_=Historical, accountlistmode_=ALFlat}
|
||||||
rspec_ = rspec{rsOpts=ropts}
|
rspec_ = rspec{rsOpts=ropts}
|
||||||
(acctbals',_) = balanceReport rspec_ j
|
(acctbals',_) = balanceReport rspec_ j
|
||||||
acctbals = map (\(a,_,_,b) -> (a, if show_costs_ ropts then b else mixedAmountStripPrices b)) acctbals'
|
acctbals = map (\(a,_,_,b) -> (a, if show_costs_ ropts then b else mixedAmountStripPrices b)) acctbals'
|
||||||
|
|||||||
@ -35,7 +35,7 @@ incomestatementSpec = CompoundBalanceCommandSpec {
|
|||||||
,cbcsubreportincreasestotal=False
|
,cbcsubreportincreasestotal=False
|
||||||
}
|
}
|
||||||
],
|
],
|
||||||
cbctype = PeriodChange
|
cbcaccum = PerPeriod
|
||||||
}
|
}
|
||||||
|
|
||||||
incomestatementmode :: Mode RawOpts
|
incomestatementmode :: Mode RawOpts
|
||||||
|
|||||||
@ -47,8 +47,8 @@ data CompoundBalanceCommandSpec = CompoundBalanceCommandSpec {
|
|||||||
cbcdoc :: CommandDoc, -- ^ the command's name(s) and documentation
|
cbcdoc :: CommandDoc, -- ^ the command's name(s) and documentation
|
||||||
cbctitle :: String, -- ^ overall report title
|
cbctitle :: String, -- ^ overall report title
|
||||||
cbcqueries :: [CBCSubreportSpec DisplayName], -- ^ subreport details
|
cbcqueries :: [CBCSubreportSpec DisplayName], -- ^ subreport details
|
||||||
cbctype :: BalanceType -- ^ the "balance" type (change, cumulative, historical)
|
cbcaccum :: BalanceAccumulation -- ^ how to accumulate balances (per-period, cumulative, historical)
|
||||||
-- this report shows (overrides command line flags)
|
-- (overrides command line flags)
|
||||||
}
|
}
|
||||||
|
|
||||||
-- | Generate a cmdargs option-parsing mode from a compound balance command
|
-- | Generate a cmdargs option-parsing mode from a compound balance command
|
||||||
@ -66,13 +66,13 @@ compoundBalanceCommandMode CompoundBalanceCommandSpec{..} =
|
|||||||
|
|
||||||
,flagNone ["change"] (setboolopt "change")
|
,flagNone ["change"] (setboolopt "change")
|
||||||
("accumulate amounts from column start to column end (in multicolumn reports)"
|
("accumulate amounts from column start to column end (in multicolumn reports)"
|
||||||
++ defType PeriodChange)
|
++ defaultMarker PerPeriod)
|
||||||
,flagNone ["cumulative"] (setboolopt "cumulative")
|
,flagNone ["cumulative"] (setboolopt "cumulative")
|
||||||
("accumulate amounts from report start (specified by e.g. -b/--begin) to column end"
|
("accumulate amounts from report start (specified by e.g. -b/--begin) to column end"
|
||||||
++ defType CumulativeChange)
|
++ defaultMarker Cumulative)
|
||||||
,flagNone ["historical","H"] (setboolopt "historical")
|
,flagNone ["historical","H"] (setboolopt "historical")
|
||||||
("accumulate amounts from journal start to column end (includes postings before report start date)"
|
("accumulate amounts from journal start to column end (includes postings before report start date)"
|
||||||
++ defType HistoricalBalance ++ "\n ")
|
++ defaultMarker Historical ++ "\n ")
|
||||||
]
|
]
|
||||||
++ flattreeflags True ++
|
++ flattreeflags True ++
|
||||||
[flagReq ["drop"] (\s opts -> Right $ setopt "drop" s opts) "N" "flat mode: omit N leading account name parts"
|
[flagReq ["drop"] (\s opts -> Right $ setopt "drop" s opts) "N" "flat mode: omit N leading account name parts"
|
||||||
@ -91,9 +91,9 @@ compoundBalanceCommandMode CompoundBalanceCommandSpec{..} =
|
|||||||
hiddenflags
|
hiddenflags
|
||||||
([], Just $ argsFlag "[QUERY]")
|
([], Just $ argsFlag "[QUERY]")
|
||||||
where
|
where
|
||||||
defType :: BalanceType -> String
|
defaultMarker :: BalanceAccumulation -> String
|
||||||
defType bt | bt == cbctype = " (default)"
|
defaultMarker bacc | bacc == cbcaccum = " (default)"
|
||||||
| otherwise = ""
|
| otherwise = ""
|
||||||
|
|
||||||
-- | Generate a runnable command from a compound balance command specification.
|
-- | Generate a runnable command from a compound balance command specification.
|
||||||
compoundBalanceCommand :: CompoundBalanceCommandSpec -> (CliOpts -> Journal -> IO ())
|
compoundBalanceCommand :: CompoundBalanceCommandSpec -> (CliOpts -> Journal -> IO ())
|
||||||
@ -102,10 +102,10 @@ compoundBalanceCommand CompoundBalanceCommandSpec{..} opts@CliOpts{reportspec_=r
|
|||||||
where
|
where
|
||||||
ropts@ReportOpts{..} = rsOpts rspec
|
ropts@ReportOpts{..} = rsOpts rspec
|
||||||
-- use the default balance type for this report, unless the user overrides
|
-- use the default balance type for this report, unless the user overrides
|
||||||
mBalanceTypeOverride = balanceTypeOverride rawopts
|
mbalanceAccumulationOverride = balanceAccumulationOverride rawopts
|
||||||
balancetype = fromMaybe cbctype mBalanceTypeOverride
|
balanceaccumulation = fromMaybe cbcaccum mbalanceAccumulationOverride
|
||||||
-- Set balance type in the report options.
|
-- Set balance type in the report options.
|
||||||
ropts' = ropts{balancetype_=balancetype}
|
ropts' = ropts{balanceaccum_=balanceaccumulation}
|
||||||
|
|
||||||
title =
|
title =
|
||||||
T.pack cbctitle
|
T.pack cbctitle
|
||||||
@ -116,24 +116,24 @@ compoundBalanceCommand CompoundBalanceCommandSpec{..} opts@CliOpts{reportspec_=r
|
|||||||
where
|
where
|
||||||
|
|
||||||
-- XXX #1078 the title of ending balance reports
|
-- XXX #1078 the title of ending balance reports
|
||||||
-- (HistoricalBalance) should mention the end date(s) shown as
|
-- (Historical) should mention the end date(s) shown as
|
||||||
-- column heading(s) (not the date span of the transactions).
|
-- column heading(s) (not the date span of the transactions).
|
||||||
-- Also the dates should not be simplified (it should show
|
-- Also the dates should not be simplified (it should show
|
||||||
-- "2008/01/01-2008/12/31", not "2008").
|
-- "2008/01/01-2008/12/31", not "2008").
|
||||||
titledatestr = case balancetype of
|
titledatestr = case balanceaccumulation of
|
||||||
HistoricalBalance -> showEndDates enddates
|
Historical -> showEndDates enddates
|
||||||
_ -> showDateSpan requestedspan
|
_ -> showDateSpan requestedspan
|
||||||
where
|
where
|
||||||
enddates = map (addDays (-1)) . mapMaybe spanEnd $ cbrDates cbr -- these spans will always have a definite end date
|
enddates = map (addDays (-1)) . mapMaybe spanEnd $ cbrDates cbr -- these spans will always have a definite end date
|
||||||
requestedspan = reportSpan j rspec
|
requestedspan = reportSpan j rspec
|
||||||
|
|
||||||
-- when user overrides, add an indication to the report title
|
-- when user overrides, add an indication to the report title
|
||||||
-- Do we need to deal with overridden ReportType?
|
-- Do we need to deal with overridden BalanceCalculation?
|
||||||
mtitleclarification = flip fmap mBalanceTypeOverride $ \case
|
mtitleclarification = flip fmap mbalanceAccumulationOverride $ \case
|
||||||
PeriodChange | changingValuation -> "(Period-End Value Changes)"
|
PerPeriod | changingValuation -> "(Period-End Value Changes)"
|
||||||
PeriodChange -> "(Balance Changes)"
|
PerPeriod -> "(Balance Changes)"
|
||||||
CumulativeChange -> "(Cumulative Ending Balances)"
|
Cumulative -> "(Cumulative Ending Balances)"
|
||||||
HistoricalBalance -> "(Historical Ending Balances)"
|
Historical -> "(Historical Ending Balances)"
|
||||||
|
|
||||||
valuationdesc =
|
valuationdesc =
|
||||||
(case cost_ of
|
(case cost_ of
|
||||||
@ -147,9 +147,9 @@ compoundBalanceCommand CompoundBalanceCommandSpec{..} opts@CliOpts{reportspec_=r
|
|||||||
Just (AtDate today _mc) -> ", valued at " <> showDate today
|
Just (AtDate today _mc) -> ", valued at " <> showDate today
|
||||||
Nothing -> "")
|
Nothing -> "")
|
||||||
|
|
||||||
changingValuation = case (reporttype_, balancetype_) of
|
changingValuation = case (balancecalc_, balanceaccum_) of
|
||||||
(ValueChangeReport, PeriodChange) -> True
|
(CalcValueChange, PerPeriod) -> True
|
||||||
(ValueChangeReport, CumulativeChange) -> True
|
(CalcValueChange, Cumulative) -> True
|
||||||
_ -> False
|
_ -> False
|
||||||
|
|
||||||
-- make a CompoundBalanceReport.
|
-- make a CompoundBalanceReport.
|
||||||
@ -239,7 +239,7 @@ compoundBalanceReportAsCsv ropts (CompoundPeriodicReport title colspans subrepor
|
|||||||
addtotals $
|
addtotals $
|
||||||
padRow title
|
padRow title
|
||||||
: ( "Account"
|
: ( "Account"
|
||||||
: map (reportPeriodName (balancetype_ ropts) colspans) colspans
|
: map (reportPeriodName (balanceaccum_ ropts) colspans) colspans
|
||||||
++ (if row_total_ ropts then ["Total"] else [])
|
++ (if row_total_ ropts then ["Total"] else [])
|
||||||
++ (if average_ ropts then ["Average"] else [])
|
++ (if average_ ropts then ["Average"] else [])
|
||||||
)
|
)
|
||||||
@ -284,7 +284,7 @@ compoundBalanceReportAsHtml ropts cbr =
|
|||||||
[tr_ $ th_ [colspanattr, leftattr] $ h2_ $ toHtml title]
|
[tr_ $ th_ [colspanattr, leftattr] $ h2_ $ toHtml title]
|
||||||
++ [thRow $
|
++ [thRow $
|
||||||
"" :
|
"" :
|
||||||
map (reportPeriodName (balancetype_ ropts) colspans) colspans
|
map (reportPeriodName (balanceaccum_ ropts) colspans) colspans
|
||||||
++ (if row_total_ ropts then ["Total"] else [])
|
++ (if row_total_ ropts then ["Total"] else [])
|
||||||
++ (if average_ ropts then ["Average"] else [])
|
++ (if average_ ropts then ["Average"] else [])
|
||||||
]
|
]
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user