mirror of
https://github.com/simonmichael/hledger.git
synced 2024-12-26 20:02:27 +03:00
lib: BudgetReport uses new renderTable inteface, now has more compact output.
This changes showMixedAmountElided so that the width to elide to is given as an argument, rather than fixed at 22 characters. This actually uses the new renderTable interface. Mostly this is just an internal change, but since we have more information about the widths of things, we can actually get rid of some superfluous spaces in the budget report output, previously there to make sure it stayed aligned with the largest reasonable contents.
This commit is contained in:
parent
33369dfa6c
commit
162a936360
@ -640,11 +640,11 @@ showMixedAmountWithoutPrice c = fst . showMixed showAmountWithoutPrice Nothing N
|
||||
showMixedAmountOneLineWithoutPrice :: Bool -> MixedAmount -> String
|
||||
showMixedAmountOneLineWithoutPrice c = fst . showMixedOneLine showAmountWithoutPrice Nothing Nothing c
|
||||
|
||||
-- | Like showMixedAmountOneLineWithoutPrice, but show at most width 22
|
||||
-- | Like showMixedAmountOneLineWithoutPrice, but show at most the given width,
|
||||
-- with an elision indicator if there are more.
|
||||
-- With a True argument, adds ANSI codes to show negative amounts in red.
|
||||
showMixedAmountElided :: Bool -> MixedAmount -> String
|
||||
showMixedAmountElided c = fst . showMixedOneLine showAmountWithoutPrice Nothing (Just 22) c
|
||||
showMixedAmountElided :: Int -> Bool -> MixedAmount -> String
|
||||
showMixedAmountElided w c = fst . showMixedOneLine showAmountWithoutPrice Nothing (Just w) c
|
||||
|
||||
-- | Get an unambiguous string representation of a mixed amount for debugging.
|
||||
showMixedAmountDebug :: MixedAmount -> String
|
||||
|
@ -1,11 +1,12 @@
|
||||
{- |
|
||||
-}
|
||||
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE NamedFieldPuns #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE NamedFieldPuns #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
|
||||
module Hledger.Reports.BudgetReport (
|
||||
BudgetGoal,
|
||||
@ -62,6 +63,8 @@ type BudgetCell = (Maybe Change, Maybe BudgetGoal)
|
||||
type BudgetReportRow = PeriodicReportRow DisplayName BudgetCell
|
||||
type BudgetReport = PeriodicReport DisplayName BudgetCell
|
||||
|
||||
type BudgetDisplayCell = ((String, Int), Maybe ((String, Int), Maybe (String, Int)))
|
||||
|
||||
-- | Calculate budget goals from all periodic transactions,
|
||||
-- actual balance changes from the regular transactions,
|
||||
-- and compare these to get a 'BudgetReport'.
|
||||
@ -211,8 +214,7 @@ combineBudgetAndActual ropts j
|
||||
budgetReportAsText :: ReportOpts -> BudgetReport -> String
|
||||
budgetReportAsText ropts@ReportOpts{..} budgetr =
|
||||
title ++ "\n\n" ++
|
||||
renderTable False pretty_tables_ leftCell rightCell showcell
|
||||
(maybetranspose $ budgetReportAsTable ropts budgetr)
|
||||
renderTable False pretty_tables_ leftCell rightCell (uncurry showcell) displayTableWithWidths
|
||||
where
|
||||
multiperiod = interval_ /= NoInterval
|
||||
title = printf "Budget performance in %s%s:"
|
||||
@ -227,31 +229,41 @@ budgetReportAsText ropts@ReportOpts{..} budgetr =
|
||||
Just (AtDefault _mc) -> ", current value"
|
||||
Just (AtDate d _mc) -> ", valued at "++showDate d
|
||||
Nothing -> "")
|
||||
actualwidth = maximum' $ map fst amountsAndGoals
|
||||
budgetwidth = maximum' $ map snd amountsAndGoals
|
||||
amountsAndGoals =
|
||||
map (\(a,g) -> (amountWidth a, amountWidth g)) . concatMap prrAmounts $ prRows budgetr
|
||||
|
||||
displayTableWithWidths :: Table String String ((Int, Int, Int), BudgetDisplayCell)
|
||||
displayTableWithWidths = Table rh ch $ map (zipWith (,) widths) displaycells
|
||||
Table rh ch displaycells = case budgetReportAsTable ropts budgetr of
|
||||
Table rh' ch' vals -> maybetranspose . Table rh' ch' $ map (map displayCell) vals
|
||||
|
||||
displayCell (actual, budget) = (showamt actual', budgetAndPerc <$> budget)
|
||||
where
|
||||
amountWidth = maybe 0 (length . showMixedAmountElided False)
|
||||
actual' = fromMaybe 0 actual
|
||||
budgetAndPerc b = (showamt b, showper <$> percentage actual' b)
|
||||
showamt = showMixedOneLine showAmountWithoutPrice Nothing (Just 22) color_
|
||||
showper p = let str = show (roundTo 0 p) in (str, length str)
|
||||
cellWidth ((_,wa), Nothing) = (wa, 0, 0)
|
||||
cellWidth ((_,wa), Just ((_,wb), Nothing)) = (wa, wb, 0)
|
||||
cellWidth ((_,wa), Just ((_,wb), Just (_,wp))) = (wa, wb, wp)
|
||||
|
||||
widths = zip3 actualwidths budgetwidths percentwidths
|
||||
actualwidths = map (maximum' . map (first3 . cellWidth)) cols
|
||||
budgetwidths = map (maximum' . map (second3 . cellWidth)) cols
|
||||
percentwidths = map (maximum' . map (third3 . cellWidth)) cols
|
||||
cols = transpose displaycells
|
||||
|
||||
-- XXX lay out actual, percentage and/or goal in the single table cell for now, should probably use separate cells
|
||||
showcell :: BudgetCell -> CellSpec
|
||||
showcell (mactual, mbudget) = rightCell $ actualstr ++ " " ++ budgetstr
|
||||
showcell :: (Int, Int, Int) -> BudgetDisplayCell -> CellSpec
|
||||
showcell (actualwidth, budgetwidth, percentwidth) ((actual,wa), mbudget) =
|
||||
CellSpec (replicate (actualwidth - wa) ' ' ++ actual ++ budgetstr)
|
||||
AlignRight
|
||||
(actualwidth + totalbudgetwidth)
|
||||
where
|
||||
percentwidth = 4
|
||||
actual = fromMaybe 0 mactual
|
||||
actualstr = printf ("%"++show actualwidth++"s") (showamt actual)
|
||||
totalpercentwidth = if percentwidth == 0 then 0 else percentwidth + 5
|
||||
totalbudgetwidth = if budgetwidth == 0 then 0 else budgetwidth + totalpercentwidth + 3
|
||||
budgetstr = case mbudget of
|
||||
Nothing -> replicate (percentwidth + 7 + budgetwidth) ' '
|
||||
Just budget ->
|
||||
case percentage actual budget of
|
||||
Just pct ->
|
||||
printf ("[%"++show percentwidth++"s%% of %"++show budgetwidth++"s]")
|
||||
(show $ roundTo 0 pct) (showamt' budget)
|
||||
Nothing ->
|
||||
printf ("["++replicate (percentwidth+5) ' '++"%"++show budgetwidth++"s]")
|
||||
(showamt' budget)
|
||||
showamt = showMixedAmountElided color_
|
||||
showamt' = showMixedAmountElided False -- XXX colored budget amounts disrupts layout
|
||||
Nothing -> replicate totalbudgetwidth ' '
|
||||
Just ((budget, wb), Nothing) -> " [" ++ replicate totalpercentwidth ' ' ++ replicate (budgetwidth - wb) ' ' ++ budget ++ "]"
|
||||
Just ((budget, wb), Just (pct, wp)) -> " [" ++ replicate (percentwidth - wp) ' ' ++ pct ++ "% of " ++ replicate (budgetwidth - wb) ' ' ++ budget ++ "]"
|
||||
|
||||
-- | Calculate the percentage of actual change to budget goal to show, if any.
|
||||
-- If valuing at cost, both amounts are converted to cost before comparing.
|
||||
|
@ -49,7 +49,7 @@ data CellSpec = CellSpec
|
||||
{ csString :: String
|
||||
, csAlign :: Align
|
||||
, csWidth :: Int
|
||||
}
|
||||
} deriving (Show)
|
||||
|
||||
emptyCell :: CellSpec
|
||||
emptyCell = CellSpec "" AlignRight 0
|
||||
@ -61,6 +61,7 @@ leftCell :: String -> CellSpec
|
||||
leftCell x = CellSpec x AlignLeft (strWidth x)
|
||||
|
||||
data Align = AlignLeft | AlignRight
|
||||
deriving (Show)
|
||||
|
||||
|
||||
verticalBar :: Bool -> Char
|
||||
|
@ -93,8 +93,8 @@ rsInit d reset ui@UIState{aopts=_uopts@UIOpts{cliopts_=CliOpts{reportspec_=rspec
|
||||
[s] -> s
|
||||
ss -> intercalate ", " ss
|
||||
-- _ -> "<split>" -- should do this if accounts field width < 30
|
||||
,rsItemChangeAmount = showMixedAmountElided False change
|
||||
,rsItemBalanceAmount = showMixedAmountElided False bal
|
||||
,rsItemChangeAmount = showMixedAmountElided 22 False change
|
||||
,rsItemBalanceAmount = showMixedAmountElided 22 False bal
|
||||
,rsItemTransaction = t
|
||||
}
|
||||
-- blank items are added to allow more control of scroll position; we won't allow movement over these
|
||||
|
@ -151,7 +151,7 @@ accountTransactionsReportAsText
|
||||
balwidth = maximumStrict $ 12 : map (strWidth . showamt . itembal) items
|
||||
showamt
|
||||
| no_elide_ = showMixedAmountOneLineWithoutPrice False -- color_
|
||||
| otherwise = showMixedAmountElided False
|
||||
| otherwise = showMixedAmountElided 22 False
|
||||
itemamt (_,_,_,_,a,_) = a
|
||||
itembal (_,_,_,_,_,a) = a
|
||||
-- show a title indicating which account was picked, which can be confusing otherwise
|
||||
@ -231,7 +231,7 @@ accountTransactionsReportItemAsText
|
||||
otheracctsstr
|
||||
showamt
|
||||
| no_elide_ = showMixedAmountOneLineWithoutPrice color_
|
||||
| otherwise = showMixedAmountElided color_
|
||||
| otherwise = showMixedAmountElided 22 color_
|
||||
amt = showamt change
|
||||
bal = showamt balance
|
||||
-- alternate behaviour, show null amounts as 0 instead of blank
|
||||
|
@ -38,12 +38,12 @@
|
||||
$ hledger -f- bal --budget -DTN
|
||||
Budget performance in 2016-12-01..2016-12-03:
|
||||
|
||||
|| 2016-12-01 2016-12-02 2016-12-03 Total
|
||||
==================++========================================================================================
|
||||
assets:cash || $-10 [ 40% of $-25] $-14 [ 56% of $-25] $-51 [ 204% of $-25] $-75 [ 100% of $-75]
|
||||
expenses || $10 [ 40% of $25] $14 [ 56% of $25] $51 [ 204% of $25] $75 [ 100% of $75]
|
||||
expenses:food || $10 [ 100% of $10] $9 [ 90% of $10] $11 [ 110% of $10] $30 [ 100% of $30]
|
||||
expenses:leisure || 0 [ 0% of $15] $5 [ 33% of $15] 0 [ 0% of $15] $5 [ 11% of $45]
|
||||
|| 2016-12-01 2016-12-02 2016-12-03 Total
|
||||
==================++===================================================================================
|
||||
assets:cash || $-10 [ 40% of $-25] $-14 [56% of $-25] $-51 [204% of $-25] $-75 [100% of $-75]
|
||||
expenses || $10 [ 40% of $25] $14 [56% of $25] $51 [204% of $25] $75 [100% of $75]
|
||||
expenses:food || $10 [100% of $10] $9 [90% of $10] $11 [110% of $10] $30 [100% of $30]
|
||||
expenses:leisure || 0 [ 0% of $15] $5 [33% of $15] 0 [ 0% of $15] $5 [ 11% of $45]
|
||||
|
||||
#** Default sort with account declarations
|
||||
|
||||
@ -83,12 +83,12 @@ account expenses:leisure
|
||||
$ hledger -f- bal --budget -DTN
|
||||
Budget performance in 2016-12-01..2016-12-03:
|
||||
|
||||
|| 2016-12-01 2016-12-02 2016-12-03 Total
|
||||
==================++========================================================================================
|
||||
expenses || $10 [ 40% of $25] $14 [ 56% of $25] $51 [ 204% of $25] $75 [ 100% of $75]
|
||||
expenses:leisure || 0 [ 0% of $15] $5 [ 33% of $15] 0 [ 0% of $15] $5 [ 11% of $45]
|
||||
expenses:food || $10 [ 100% of $10] $9 [ 90% of $10] $11 [ 110% of $10] $30 [ 100% of $30]
|
||||
assets:cash || $-10 [ 40% of $-25] $-14 [ 56% of $-25] $-51 [ 204% of $-25] $-75 [ 100% of $-75]
|
||||
|| 2016-12-01 2016-12-02 2016-12-03 Total
|
||||
==================++===================================================================================
|
||||
expenses || $10 [ 40% of $25] $14 [56% of $25] $51 [204% of $25] $75 [100% of $75]
|
||||
expenses:leisure || 0 [ 0% of $15] $5 [33% of $15] 0 [ 0% of $15] $5 [ 11% of $45]
|
||||
expenses:food || $10 [100% of $10] $9 [90% of $10] $11 [110% of $10] $30 [100% of $30]
|
||||
assets:cash || $-10 [ 40% of $-25] $-14 [56% of $-25] $-51 [204% of $-25] $-75 [100% of $-75]
|
||||
|
||||
# # 2. -E
|
||||
# $ hledger bal -D -b 2016-12-01 -e 2016-12-04 -f - --budget -E
|
||||
@ -156,24 +156,24 @@ Budget performance in 2016-12-01..2016-12-03:
|
||||
$ hledger -f- bal --budget -DTNS
|
||||
Budget performance in 2016-12-01..2016-12-03:
|
||||
|
||||
|| 2016-12-01 2016-12-02 2016-12-03 Total
|
||||
==================++========================================================================================
|
||||
expenses || $10 [ 40% of $25] $14 [ 56% of $25] $51 [ 204% of $25] $75 [ 100% of $75]
|
||||
expenses:food || $10 [ 100% of $10] $9 [ 90% of $10] $11 [ 110% of $10] $30 [ 100% of $30]
|
||||
expenses:leisure || 0 [ 0% of $15] $5 [ 33% of $15] 0 [ 0% of $15] $5 [ 11% of $45]
|
||||
assets:cash || $-10 [ 40% of $-25] $-14 [ 56% of $-25] $-51 [ 204% of $-25] $-75 [ 100% of $-75]
|
||||
|| 2016-12-01 2016-12-02 2016-12-03 Total
|
||||
==================++===================================================================================
|
||||
expenses || $10 [ 40% of $25] $14 [56% of $25] $51 [204% of $25] $75 [100% of $75]
|
||||
expenses:food || $10 [100% of $10] $9 [90% of $10] $11 [110% of $10] $30 [100% of $30]
|
||||
expenses:leisure || 0 [ 0% of $15] $5 [33% of $15] 0 [ 0% of $15] $5 [ 11% of $45]
|
||||
assets:cash || $-10 [ 40% of $-25] $-14 [56% of $-25] $-51 [204% of $-25] $-75 [100% of $-75]
|
||||
|
||||
#** Sort by actual amount, tree mode.
|
||||
|
||||
$ hledger -f- bal --budget -DTNS --tree
|
||||
Budget performance in 2016-12-01..2016-12-03:
|
||||
|
||||
|| 2016-12-01 2016-12-02 2016-12-03 Total
|
||||
=============++========================================================================================
|
||||
expenses || $10 [ 40% of $25] $14 [ 56% of $25] $51 [ 204% of $25] $75 [ 100% of $75]
|
||||
food || $10 [ 100% of $10] $9 [ 90% of $10] $11 [ 110% of $10] $30 [ 100% of $30]
|
||||
leisure || 0 [ 0% of $15] $5 [ 33% of $15] 0 [ 0% of $15] $5 [ 11% of $45]
|
||||
assets:cash || $-10 [ 40% of $-25] $-14 [ 56% of $-25] $-51 [ 204% of $-25] $-75 [ 100% of $-75]
|
||||
|| 2016-12-01 2016-12-02 2016-12-03 Total
|
||||
=============++===================================================================================
|
||||
expenses || $10 [ 40% of $25] $14 [56% of $25] $51 [204% of $25] $75 [100% of $75]
|
||||
food || $10 [100% of $10] $9 [90% of $10] $11 [110% of $10] $30 [100% of $30]
|
||||
leisure || 0 [ 0% of $15] $5 [33% of $15] 0 [ 0% of $15] $5 [ 11% of $45]
|
||||
assets:cash || $-10 [ 40% of $-25] $-14 [56% of $-25] $-51 [204% of $-25] $-75 [100% of $-75]
|
||||
|
||||
#** other ?
|
||||
# with -E
|
||||
|
@ -34,29 +34,29 @@
|
||||
$ hledger -f- bal -D -b 2016-12-01 -e 2016-12-04 --budget
|
||||
Budget performance in 2016-12-01..2016-12-03:
|
||||
|
||||
|| 2016-12-01 2016-12-02 2016-12-03
|
||||
==================++==================================================================
|
||||
assets:cash || $-10 [ 40% of $-25] $-14 [ 56% of $-25] $-51 [ 204% of $-25]
|
||||
expenses || $10 [ 40% of $25] $14 [ 56% of $25] $51 [ 204% of $25]
|
||||
expenses:food || $10 [ 100% of $10] $9 [ 90% of $10] $11 [ 110% of $10]
|
||||
expenses:leisure || 0 [ 0% of $15] $5 [ 33% of $15] 0 [ 0% of $15]
|
||||
------------------++------------------------------------------------------------------
|
||||
|| 0 [ 0] 0 [ 0] 0 [ 0]
|
||||
|| 2016-12-01 2016-12-02 2016-12-03
|
||||
==================++==============================================================
|
||||
assets:cash || $-10 [ 40% of $-25] $-14 [56% of $-25] $-51 [204% of $-25]
|
||||
expenses || $10 [ 40% of $25] $14 [56% of $25] $51 [204% of $25]
|
||||
expenses:food || $10 [100% of $10] $9 [90% of $10] $11 [110% of $10]
|
||||
expenses:leisure || 0 [ 0% of $15] $5 [33% of $15] 0 [ 0% of $15]
|
||||
------------------++--------------------------------------------------------------
|
||||
|| 0 [ 0] 0 [ 0] 0 [ 0]
|
||||
|
||||
# 2. -E
|
||||
$ hledger -f- bal -D -b 2016-12-01 -e 2016-12-04 --budget -E
|
||||
Budget performance in 2016-12-01..2016-12-03:
|
||||
|
||||
|| 2016-12-01 2016-12-02 2016-12-03
|
||||
==================++==================================================================
|
||||
assets:cash || $-10 [ 40% of $-25] $-14 [ 56% of $-25] $-51 [ 204% of $-25]
|
||||
expenses || $10 [ 40% of $25] $14 [ 56% of $25] $51 [ 204% of $25]
|
||||
expenses:cab || 0 0 $15
|
||||
expenses:food || $10 [ 100% of $10] $9 [ 90% of $10] $11 [ 110% of $10]
|
||||
expenses:leisure || 0 [ 0% of $15] $5 [ 33% of $15] 0 [ 0% of $15]
|
||||
expenses:movies || 0 0 $25
|
||||
------------------++------------------------------------------------------------------
|
||||
|| 0 [ 0] 0 [ 0] 0 [ 0]
|
||||
|| 2016-12-01 2016-12-02 2016-12-03
|
||||
==================++==============================================================
|
||||
assets:cash || $-10 [ 40% of $-25] $-14 [56% of $-25] $-51 [204% of $-25]
|
||||
expenses || $10 [ 40% of $25] $14 [56% of $25] $51 [204% of $25]
|
||||
expenses:cab || 0 0 $15
|
||||
expenses:food || $10 [100% of $10] $9 [90% of $10] $11 [110% of $10]
|
||||
expenses:leisure || 0 [ 0% of $15] $5 [33% of $15] 0 [ 0% of $15]
|
||||
expenses:movies || 0 0 $25
|
||||
------------------++--------------------------------------------------------------
|
||||
|| 0 [ 0] 0 [ 0] 0 [ 0]
|
||||
|
||||
# 3. Test that budget works with mix of commodities
|
||||
<
|
||||
@ -96,14 +96,14 @@ Budget performance in 2016-12-01..2016-12-03:
|
||||
$ hledger -f- bal -D -b 2016-12-01 -e 2016-12-04 --budget
|
||||
Budget performance in 2016-12-01..2016-12-03:
|
||||
|
||||
|| 2016-12-01 2016-12-02 2016-12-03
|
||||
==================++======================================================================================
|
||||
assets:cash || $-15 [ 60% of $-25] $-26 [ 104% of $-25] $-51 [ 204% of $-25]
|
||||
expenses || £10 [ $25] $5, 20 CAD [ $25] $51 [ 204% of $25]
|
||||
expenses:food || £10 [ $10] 20 CAD [ $10] $11 [ 110% of $10]
|
||||
expenses:leisure || 0 [ 0% of $15] $5 [ 33% of $15] 0 [ 0% of $15]
|
||||
------------------++--------------------------------------------------------------------------------------
|
||||
|| $-15, £10 [ 0] $-21, 20 CAD [ 0] 0 [ 0]
|
||||
|| 2016-12-01 2016-12-02 2016-12-03
|
||||
==================++===========================================================================
|
||||
assets:cash || $-15 [60% of $-25] $-26 [104% of $-25] $-51 [204% of $-25]
|
||||
expenses || £10 [ $25] $5, 20 CAD [ $25] $51 [204% of $25]
|
||||
expenses:food || £10 [ $10] 20 CAD [ $10] $11 [110% of $10]
|
||||
expenses:leisure || 0 [ 0% of $15] $5 [ 33% of $15] 0 [ 0% of $15]
|
||||
------------------++---------------------------------------------------------------------------
|
||||
|| $-15, £10 [ 0] $-21, 20 CAD [ 0] 0 [ 0]
|
||||
|
||||
# 4. --budget with no interval shows total budget for the journal period
|
||||
# (in tabular format).
|
||||
@ -132,11 +132,11 @@ Budget performance in 2018-01-01..2018-01-03:
|
||||
|
||||
|| 2018-01-01..2018-01-03
|
||||
===++========================
|
||||
a || 2 [ 7% of 30]
|
||||
b || 2 [ 2% of 100]
|
||||
c || 2 [ 0% of 1000]
|
||||
a || 2 [7% of 30]
|
||||
b || 2 [2% of 100]
|
||||
c || 2 [0% of 1000]
|
||||
---++------------------------
|
||||
|| 6 [ 1% of 1130]
|
||||
|| 6 [1% of 1130]
|
||||
|
||||
# 5. Multiple periodic transactions with different intervals are combined.
|
||||
# Budget goals with lower frequency than the report are posted in the
|
||||
@ -144,25 +144,25 @@ Budget performance in 2018-01-01..2018-01-03:
|
||||
$ hledger -f- bal --budget -D
|
||||
Budget performance in 2018-01-01..2018-01-03:
|
||||
|
||||
|| 2018-01-01 2018-01-02 2018-01-03
|
||||
===++=========================================================
|
||||
a || 1 [ 10% of 10] 0 [ 0% of 10] 1 [ 10% of 10]
|
||||
b || 1 [ 1% of 100] 0 [ 0] 1 [ 0]
|
||||
c || 1 [ 0% of 1000] 0 [ 0] 1 [ 0]
|
||||
---++---------------------------------------------------------
|
||||
|| 3 [ 0% of 1110] 0 [ 0% of 10] 3 [ 30% of 10]
|
||||
|| 2018-01-01 2018-01-02 2018-01-03
|
||||
===++==============================================
|
||||
a || 1 [10% of 10] 0 [0% of 10] 1 [10% of 10]
|
||||
b || 1 [ 1% of 100] 0 [ 0] 1 [ 0]
|
||||
c || 1 [ 0% of 1000] 0 [ 0] 1 [ 0]
|
||||
---++----------------------------------------------
|
||||
|| 3 [ 0% of 1110] 0 [0% of 10] 3 [30% of 10]
|
||||
|
||||
# 6. Budget goals with higher frequency than the report get added up appropriately.
|
||||
$ hledger -f- bal --budget -W
|
||||
Budget performance in 2018-01-01W01:
|
||||
|
||||
|| 2018-01-01W01
|
||||
===++===================
|
||||
a || 2 [ 7% of 30]
|
||||
b || 2 [ 2% of 100]
|
||||
c || 2 [ 0% of 1000]
|
||||
---++-------------------
|
||||
|| 6 [ 1% of 1130]
|
||||
|| 2018-01-01W01
|
||||
===++================
|
||||
a || 2 [7% of 30]
|
||||
b || 2 [2% of 100]
|
||||
c || 2 [0% of 1000]
|
||||
---++----------------
|
||||
|| 6 [1% of 1130]
|
||||
|
||||
# 7. A bounded two day budget. The end date is exclusive as usual.
|
||||
<
|
||||
@ -188,12 +188,12 @@ Budget performance in 2018-01-01W01:
|
||||
$ hledger -f- bal --budget -D
|
||||
Budget performance in 2018-01-01..2018-01-04:
|
||||
|
||||
|| 2018-01-01 2018-01-02 2018-01-03 2018-01-04
|
||||
==============++================================================================
|
||||
<unbudgeted> || 1 1 1 1
|
||||
a || 1 1 [ 100% of 1] 1 [ 100% of 1] 1
|
||||
--------------++----------------------------------------------------------------
|
||||
|| 2 2 [ 200% of 1] 2 [ 200% of 1] 2
|
||||
|| 2018-01-01 2018-01-02 2018-01-03 2018-01-04
|
||||
==============++======================================================
|
||||
<unbudgeted> || 1 1 1 1
|
||||
a || 1 1 [100% of 1] 1 [100% of 1] 1
|
||||
--------------++------------------------------------------------------
|
||||
|| 2 2 [200% of 1] 2 [200% of 1] 2
|
||||
|
||||
# 8. Multiple bounded budgets.
|
||||
<
|
||||
@ -218,21 +218,21 @@ Budget performance in 2018-01-01..2018-01-04:
|
||||
$ hledger -f- bal --budget -D
|
||||
Budget performance in 2018-01-01..2018-01-04:
|
||||
|
||||
|| 2018-01-01 2018-01-02 2018-01-03 2018-01-04
|
||||
===++====================================================================
|
||||
a || 1 [ 100% of 1] 1 [ 100% of 1] 1 [ 10% of 10] 1 [ 10% of 10]
|
||||
---++--------------------------------------------------------------------
|
||||
|| 1 [ 100% of 1] 1 [ 100% of 1] 1 [ 10% of 10] 1 [ 10% of 10]
|
||||
|| 2018-01-01 2018-01-02 2018-01-03 2018-01-04
|
||||
===++============================================================
|
||||
a || 1 [100% of 1] 1 [100% of 1] 1 [10% of 10] 1 [10% of 10]
|
||||
---++------------------------------------------------------------
|
||||
|| 1 [100% of 1] 1 [100% of 1] 1 [10% of 10] 1 [10% of 10]
|
||||
|
||||
# 9. A "from A to B" budget should not be included in a report beginning on B.
|
||||
$ hledger -f- bal --budget -D -b 2018/1/3
|
||||
Budget performance in 2018-01-03..2018-01-04:
|
||||
|
||||
|| 2018-01-03 2018-01-04
|
||||
===++==================================
|
||||
a || 1 [ 10% of 10] 1 [ 10% of 10]
|
||||
---++----------------------------------
|
||||
|| 1 [ 10% of 10] 1 [ 10% of 10]
|
||||
|| 2018-01-03 2018-01-04
|
||||
===++==============================
|
||||
a || 1 [10% of 10] 1 [10% of 10]
|
||||
---++------------------------------
|
||||
|| 1 [10% of 10] 1 [10% of 10]
|
||||
|
||||
<
|
||||
~ daily
|
||||
@ -250,21 +250,21 @@ Budget performance in 2018-01-03..2018-01-04:
|
||||
$ hledger -f- bal --budget -D date:2018/1/1-2018/1/3
|
||||
Budget performance in 2018-01-01..2018-01-02:
|
||||
|
||||
|| 2018-01-01 2018-01-02
|
||||
===++================================
|
||||
a || 0 [ 0% of 1] 0 [ 0% of 1]
|
||||
---++--------------------------------
|
||||
|| 0 [ 0% of 1] 0 [ 0% of 1]
|
||||
|| 2018-01-01 2018-01-02
|
||||
===++==========================
|
||||
a || 0 [0% of 1] 0 [0% of 1]
|
||||
---++--------------------------
|
||||
|| 0 [0% of 1] 0 [0% of 1]
|
||||
|
||||
# 11. With -E, zeroes are shown
|
||||
$ hledger -f- bal --budget -D date:2018/1/1-2018/1/3 -E
|
||||
Budget performance in 2018-01-01..2018-01-02:
|
||||
|
||||
|| 2018-01-01 2018-01-02
|
||||
===++================================
|
||||
a || 0 [ 0% of 1] 0 [ 0% of 1]
|
||||
---++--------------------------------
|
||||
|| 0 [ 0% of 1] 0 [ 0% of 1]
|
||||
|| 2018-01-01 2018-01-02
|
||||
===++==========================
|
||||
a || 0 [0% of 1] 0 [0% of 1]
|
||||
---++--------------------------
|
||||
|| 0 [0% of 1] 0 [0% of 1]
|
||||
|
||||
# 12. subaccounts of budgeted accounts count towards budget
|
||||
<
|
||||
@ -277,9 +277,9 @@ Budget performance in 2018-01-01..2018-01-02:
|
||||
$ hledger -f- bal --budget -N
|
||||
Budget performance in 2018-01-01:
|
||||
|
||||
|| 2018-01-01
|
||||
===++================
|
||||
a || 1 [ 100% of 1]
|
||||
|| 2018-01-01
|
||||
===++===============
|
||||
a || 1 [100% of 1]
|
||||
|
||||
# 13. budget goals on both parent and subaccounts are counted
|
||||
<
|
||||
@ -294,23 +294,23 @@ Budget performance in 2018-01-01:
|
||||
$ hledger -f- bal --budget
|
||||
Budget performance in 2018-01-01:
|
||||
|
||||
|| 2018-01-01
|
||||
=======++==================
|
||||
a || 2 [ 2% of 101]
|
||||
a:b:c || 1 [ 100% of 1]
|
||||
-------++------------------
|
||||
|| 2 [ 2% of 101]
|
||||
|| 2018-01-01
|
||||
=======++=================
|
||||
a || 2 [ 2% of 101]
|
||||
a:b:c || 1 [100% of 1]
|
||||
-------++-----------------
|
||||
|| 2 [ 2% of 101]
|
||||
|
||||
# 14. tree mode
|
||||
$ hledger -f- bal --budget --tree
|
||||
Budget performance in 2018-01-01:
|
||||
|
||||
|| 2018-01-01
|
||||
=======++==================
|
||||
a || 2 [ 2% of 101]
|
||||
b:c || 1 [ 100% of 1]
|
||||
-------++------------------
|
||||
|| 2 [ 2% of 101]
|
||||
|| 2018-01-01
|
||||
=======++=================
|
||||
a || 2 [ 2% of 101]
|
||||
b:c || 1 [100% of 1]
|
||||
-------++-----------------
|
||||
|| 2 [ 2% of 101]
|
||||
|
||||
# TODO: respect hierarchy when sorting in tree mode
|
||||
|
||||
@ -335,14 +335,14 @@ P 2018/01/26 SHARE €10
|
||||
$ hledger -f - bal -M --budget --cumulative --forecast -V
|
||||
Budget performance in 2018-05-01..2018-06-30, valued at period ends:
|
||||
|
||||
|| 2018-05-31 2018-06-30
|
||||
================++==========================================
|
||||
<unbudgeted> || €-10 €-10
|
||||
assets || €10 €10 [ 0]
|
||||
assets:bank || 0 €-1 [ 100% of €-1]
|
||||
assets:pension || €10 €11 [1100% of €1]
|
||||
----------------++------------------------------------------
|
||||
|| 0 0 [ 0]
|
||||
|| 2018-05-31 2018-06-30
|
||||
================++=================================
|
||||
<unbudgeted> || €-10 €-10
|
||||
assets || €10 €10 [ 0]
|
||||
assets:bank || 0 €-1 [ 100% of €-1]
|
||||
assets:pension || €10 €11 [1100% of €1]
|
||||
----------------++---------------------------------
|
||||
|| 0 0 [ 0]
|
||||
|
||||
# 16. With subaccounts, child accounts are properly included in the parent balance when budget is checked
|
||||
<
|
||||
@ -365,49 +365,49 @@ Budget performance in 2018-05-01..2018-06-30, valued at period ends:
|
||||
$ hledger -f- bal --budget
|
||||
Budget performance in 2019-01-01..2019-01-03:
|
||||
|
||||
|| 2019-01-01..2019-01-03
|
||||
===================++==============================
|
||||
expenses:personal || $50.00 [ 5% of $1,000.00]
|
||||
liabilities || $-50.00 [ 5% of $-1000.00]
|
||||
-------------------++------------------------------
|
||||
|| 0 [ 0]
|
||||
|| 2019-01-01..2019-01-03
|
||||
===================++===========================
|
||||
expenses:personal || $50.00 [5% of $1,000.00]
|
||||
liabilities || $-50.00 [5% of $-1000.00]
|
||||
-------------------++---------------------------
|
||||
|| 0 [ 0]
|
||||
|
||||
# 17.
|
||||
$ hledger -f- bal --budget -E
|
||||
Budget performance in 2019-01-01..2019-01-03:
|
||||
|
||||
|| 2019-01-01..2019-01-03
|
||||
========================================++==============================
|
||||
expenses:personal || $50.00 [ 5% of $1,000.00]
|
||||
expenses:personal:electronics || $20.00
|
||||
expenses:personal:electronics:upgrades || $10.00
|
||||
liabilities || $-50.00 [ 5% of $-1000.00]
|
||||
----------------------------------------++------------------------------
|
||||
|| 0 [ 0]
|
||||
|| 2019-01-01..2019-01-03
|
||||
========================================++===========================
|
||||
expenses:personal || $50.00 [5% of $1,000.00]
|
||||
expenses:personal:electronics || $20.00
|
||||
expenses:personal:electronics:upgrades || $10.00
|
||||
liabilities || $-50.00 [5% of $-1000.00]
|
||||
----------------------------------------++---------------------------
|
||||
|| 0 [ 0]
|
||||
|
||||
# 18.
|
||||
$ hledger -f- bal --budget --tree
|
||||
Budget performance in 2019-01-01..2019-01-03:
|
||||
|
||||
|| 2019-01-01..2019-01-03
|
||||
===================++==============================
|
||||
expenses:personal || $50.00 [ 5% of $1,000.00]
|
||||
liabilities || $-50.00 [ 5% of $-1000.00]
|
||||
-------------------++------------------------------
|
||||
|| 0 [ 0]
|
||||
|| 2019-01-01..2019-01-03
|
||||
===================++===========================
|
||||
expenses:personal || $50.00 [5% of $1,000.00]
|
||||
liabilities || $-50.00 [5% of $-1000.00]
|
||||
-------------------++---------------------------
|
||||
|| 0 [ 0]
|
||||
|
||||
# 19.
|
||||
$ hledger -f- bal --budget --tree -E
|
||||
Budget performance in 2019-01-01..2019-01-03:
|
||||
|
||||
|| 2019-01-01..2019-01-03
|
||||
===================++==============================
|
||||
expenses:personal || $50.00 [ 5% of $1,000.00]
|
||||
electronics || $20.00
|
||||
upgrades || $10.00
|
||||
liabilities || $-50.00 [ 5% of $-1000.00]
|
||||
-------------------++------------------------------
|
||||
|| 0 [ 0]
|
||||
|| 2019-01-01..2019-01-03
|
||||
===================++===========================
|
||||
expenses:personal || $50.00 [5% of $1,000.00]
|
||||
electronics || $20.00
|
||||
upgrades || $10.00
|
||||
liabilities || $-50.00 [5% of $-1000.00]
|
||||
-------------------++---------------------------
|
||||
|| 0 [ 0]
|
||||
|
||||
# 20. Subaccounts + nested budgets
|
||||
<
|
||||
@ -431,51 +431,51 @@ Budget performance in 2019-01-01..2019-01-03:
|
||||
$ hledger -f- bal --budget
|
||||
Budget performance in 2019-01-01..2019-01-03:
|
||||
|
||||
|| 2019-01-01..2019-01-03
|
||||
===============================++==============================
|
||||
expenses:personal || $50.00 [ 5% of $1100.00]
|
||||
expenses:personal:electronics || $20.00 [ 20% of $100.00]
|
||||
liabilities || $-50.00 [ 5% of $-1100.00]
|
||||
-------------------------------++------------------------------
|
||||
|| 0 [ 0]
|
||||
|| 2019-01-01..2019-01-03
|
||||
===============================++============================
|
||||
expenses:personal || $50.00 [ 5% of $1100.00]
|
||||
expenses:personal:electronics || $20.00 [20% of $100.00]
|
||||
liabilities || $-50.00 [ 5% of $-1100.00]
|
||||
-------------------------------++----------------------------
|
||||
|| 0 [ 0]
|
||||
|
||||
# 21.
|
||||
$ hledger -f- bal --budget -E
|
||||
Budget performance in 2019-01-01..2019-01-03:
|
||||
|
||||
|| 2019-01-01..2019-01-03
|
||||
========================================++==============================
|
||||
expenses:personal || $50.00 [ 5% of $1100.00]
|
||||
expenses:personal:electronics || $20.00 [ 20% of $100.00]
|
||||
expenses:personal:electronics:upgrades || $10.00
|
||||
liabilities || $-50.00 [ 5% of $-1100.00]
|
||||
----------------------------------------++------------------------------
|
||||
|| 0 [ 0]
|
||||
|| 2019-01-01..2019-01-03
|
||||
========================================++============================
|
||||
expenses:personal || $50.00 [ 5% of $1100.00]
|
||||
expenses:personal:electronics || $20.00 [20% of $100.00]
|
||||
expenses:personal:electronics:upgrades || $10.00
|
||||
liabilities || $-50.00 [ 5% of $-1100.00]
|
||||
----------------------------------------++----------------------------
|
||||
|| 0 [ 0]
|
||||
|
||||
# 22.
|
||||
$ hledger -f- bal --budget --tree
|
||||
Budget performance in 2019-01-01..2019-01-03:
|
||||
|
||||
|| 2019-01-01..2019-01-03
|
||||
===================++==============================
|
||||
expenses:personal || $50.00 [ 5% of $1100.00]
|
||||
electronics || $20.00 [ 20% of $100.00]
|
||||
liabilities || $-50.00 [ 5% of $-1100.00]
|
||||
-------------------++------------------------------
|
||||
|| 0 [ 0]
|
||||
|| 2019-01-01..2019-01-03
|
||||
===================++============================
|
||||
expenses:personal || $50.00 [ 5% of $1100.00]
|
||||
electronics || $20.00 [20% of $100.00]
|
||||
liabilities || $-50.00 [ 5% of $-1100.00]
|
||||
-------------------++----------------------------
|
||||
|| 0 [ 0]
|
||||
|
||||
# 23.
|
||||
$ hledger -f- bal --budget --tree -E
|
||||
Budget performance in 2019-01-01..2019-01-03:
|
||||
|
||||
|| 2019-01-01..2019-01-03
|
||||
===================++==============================
|
||||
expenses:personal || $50.00 [ 5% of $1100.00]
|
||||
electronics || $20.00 [ 20% of $100.00]
|
||||
upgrades || $10.00
|
||||
liabilities || $-50.00 [ 5% of $-1100.00]
|
||||
-------------------++------------------------------
|
||||
|| 0 [ 0]
|
||||
|| 2019-01-01..2019-01-03
|
||||
===================++============================
|
||||
expenses:personal || $50.00 [ 5% of $1100.00]
|
||||
electronics || $20.00 [20% of $100.00]
|
||||
upgrades || $10.00
|
||||
liabilities || $-50.00 [ 5% of $-1100.00]
|
||||
-------------------++----------------------------
|
||||
|| 0 [ 0]
|
||||
|
||||
## 24. Zero budget == no budget
|
||||
<
|
||||
@ -506,14 +506,14 @@ Budget performance in 2019-01-01..2019-01-02:
|
||||
|
||||
|| 2019-01-01..2019-01-02
|
||||
==================++========================
|
||||
expenses:bills || $80 [ 22% of $370]
|
||||
expenses:bills:a || $10 [ 50% of $20]
|
||||
expenses:bills:b || $40 [ 20% of $200]
|
||||
expenses:bills:c || 0 [ 0% of $50]
|
||||
expenses:bills:f || $10 [ 0]
|
||||
income:cash || $-80 [ 22% of $-370]
|
||||
expenses:bills || $80 [22% of $370]
|
||||
expenses:bills:a || $10 [50% of $20]
|
||||
expenses:bills:b || $40 [20% of $200]
|
||||
expenses:bills:c || 0 [ 0% of $50]
|
||||
expenses:bills:f || $10 [ 0]
|
||||
income:cash || $-80 [22% of $-370]
|
||||
------------------++------------------------
|
||||
|| 0 [ 0]
|
||||
|| 0 [ 0]
|
||||
|
||||
# 25. -E shows d
|
||||
$ hledger bal -f- --budget -E
|
||||
@ -521,14 +521,14 @@ Budget performance in 2019-01-01..2019-01-02:
|
||||
|
||||
|| 2019-01-01..2019-01-02
|
||||
==================++========================
|
||||
expenses:bills || $80 [ 22% of $370]
|
||||
expenses:bills:a || $10 [ 50% of $20]
|
||||
expenses:bills:b || $40 [ 20% of $200]
|
||||
expenses:bills:c || 0 [ 0% of $50]
|
||||
expenses:bills:d || $20
|
||||
expenses:bills:e || 0
|
||||
expenses:bills:f || $10 [ 0]
|
||||
income:cash || $-80 [ 22% of $-370]
|
||||
expenses:bills || $80 [22% of $370]
|
||||
expenses:bills:a || $10 [50% of $20]
|
||||
expenses:bills:b || $40 [20% of $200]
|
||||
expenses:bills:c || 0 [ 0% of $50]
|
||||
expenses:bills:d || $20
|
||||
expenses:bills:e || 0
|
||||
expenses:bills:f || $10 [ 0]
|
||||
income:cash || $-80 [22% of $-370]
|
||||
------------------++------------------------
|
||||
|| 0 [ 0]
|
||||
|| 0 [ 0]
|
||||
|
||||
|
@ -55,12 +55,12 @@ hledger bal -D -b 2016-12-01 -e 2016-12-04 -f - --budget
|
||||
>>>
|
||||
Budget performance in 2016-12-01..2016-12-03:
|
||||
|
||||
|| 2016-12-01 2016-12-02 2016-12-03
|
||||
==================++==================================================================
|
||||
assets:cash || $-10 [ 40% of $-25] $-14 [ 56% of $-25] $-51 [ 204% of $-25]
|
||||
expenses || $10 [ 40% of $25] $14 [ 56% of $25] $51 [ 204% of $25]
|
||||
expenses:food || $10 [ 100% of $10] $9 [ 90% of $10] $11 [ 110% of $10]
|
||||
expenses:leisure || 0 [ 0% of $15] $5 [ 33% of $15] 0 [ 0% of $15]
|
||||
------------------++------------------------------------------------------------------
|
||||
|| 0 [ 0] 0 [ 0] 0 [ 0]
|
||||
|| 2016-12-01 2016-12-02 2016-12-03
|
||||
==================++==============================================================
|
||||
assets:cash || $-10 [ 40% of $-25] $-14 [56% of $-25] $-51 [204% of $-25]
|
||||
expenses || $10 [ 40% of $25] $14 [56% of $25] $51 [204% of $25]
|
||||
expenses:food || $10 [100% of $10] $9 [90% of $10] $11 [110% of $10]
|
||||
expenses:leisure || 0 [ 0% of $15] $5 [33% of $15] 0 [ 0% of $15]
|
||||
------------------++--------------------------------------------------------------
|
||||
|| 0 [ 0] 0 [ 0] 0 [ 0]
|
||||
>>>=0
|
||||
|
@ -531,41 +531,41 @@ P 2000/04/01 A 4 B
|
||||
$ hledger -f- bal -M --budget
|
||||
Budget performance in 2000Q1:
|
||||
|
||||
|| Jan Feb Mar
|
||||
===++============================================================
|
||||
a || 1 A [ 50% of 2 A] 1 A [ 50% of 2 A] 1 A [ 50% of 2 A]
|
||||
---++------------------------------------------------------------
|
||||
|| 1 A [ 50% of 2 A] 1 A [ 50% of 2 A] 1 A [ 50% of 2 A]
|
||||
|| Jan Feb Mar
|
||||
===++======================================================
|
||||
a || 1 A [50% of 2 A] 1 A [50% of 2 A] 1 A [50% of 2 A]
|
||||
---++------------------------------------------------------
|
||||
|| 1 A [50% of 2 A] 1 A [50% of 2 A] 1 A [50% of 2 A]
|
||||
|
||||
# 47. budget report, valued at cost.
|
||||
$ hledger -f- bal -MTA --budget --value=c
|
||||
Budget performance in 2000Q1, valued at cost:
|
||||
|
||||
|| Jan Feb Mar Total Average
|
||||
===++=====================================================================================================
|
||||
a || 6 B [ 300% of 2 B] 7 B [ 350% of 2 B] 8 B [ 400% of 2 B] 21 B [ 350% of 6 B] 7 B [ 350% of 2 B]
|
||||
---++-----------------------------------------------------------------------------------------------------
|
||||
|| 6 B [ 300% of 2 B] 7 B [ 350% of 2 B] 8 B [ 400% of 2 B] 21 B [ 350% of 6 B] 7 B [ 350% of 2 B]
|
||||
|| Jan Feb Mar Total Average
|
||||
===++================================================================================================
|
||||
a || 6 B [300% of 2 B] 7 B [350% of 2 B] 8 B [400% of 2 B] 21 B [350% of 6 B] 7 B [350% of 2 B]
|
||||
---++------------------------------------------------------------------------------------------------
|
||||
|| 6 B [300% of 2 B] 7 B [350% of 2 B] 8 B [400% of 2 B] 21 B [350% of 6 B] 7 B [350% of 2 B]
|
||||
|
||||
# 48. budget report, valued at period ends.
|
||||
$ hledger -f- bal -MTA --budget --value=e
|
||||
Budget performance in 2000Q1, valued at period ends:
|
||||
|
||||
|| Jan Feb Mar Total Average
|
||||
===++==========================================================================================================
|
||||
a || 5 B [ 50% of 10 B] 2 B [ 50% of 4 B] 3 B [ 50% of 6 B] 10 B [ 50% of 20 B] 3 B [ 50% of 7 B]
|
||||
---++----------------------------------------------------------------------------------------------------------
|
||||
|| 5 B [ 50% of 10 B] 2 B [ 50% of 4 B] 3 B [ 50% of 6 B] 10 B [ 50% of 20 B] 3 B [ 50% of 7 B]
|
||||
|| Jan Feb Mar Total Average
|
||||
===++=============================================================================================
|
||||
a || 5 B [50% of 10 B] 2 B [50% of 4 B] 3 B [50% of 6 B] 10 B [50% of 20 B] 3 B [50% of 7 B]
|
||||
---++---------------------------------------------------------------------------------------------
|
||||
|| 5 B [50% of 10 B] 2 B [50% of 4 B] 3 B [50% of 6 B] 10 B [50% of 20 B] 3 B [50% of 7 B]
|
||||
|
||||
# 49. budget report, valued at other date.
|
||||
$ hledger -f- bal -MTA --budget --value=2000-01-15
|
||||
Budget performance in 2000Q1, valued at 2000-01-15:
|
||||
|
||||
|| Jan Feb Mar Total Average
|
||||
===++==========================================================================================================
|
||||
a || 5 B [ 50% of 10 B] 5 B [ 50% of 10 B] 5 B [ 50% of 10 B] 15 B [ 50% of 30 B] 5 B [ 50% of 10 B]
|
||||
---++----------------------------------------------------------------------------------------------------------
|
||||
|| 5 B [ 50% of 10 B] 5 B [ 50% of 10 B] 5 B [ 50% of 10 B] 15 B [ 50% of 30 B] 5 B [ 50% of 10 B]
|
||||
|| Jan Feb Mar Total Average
|
||||
===++================================================================================================
|
||||
a || 5 B [50% of 10 B] 5 B [50% of 10 B] 5 B [50% of 10 B] 15 B [50% of 30 B] 5 B [50% of 10 B]
|
||||
---++------------------------------------------------------------------------------------------------
|
||||
|| 5 B [50% of 10 B] 5 B [50% of 10 B] 5 B [50% of 10 B] 15 B [50% of 30 B] 5 B [50% of 10 B]
|
||||
|
||||
# 50. --value=then with --historical. How is the starting total valued ?
|
||||
# Currently not supported.
|
||||
|
Loading…
Reference in New Issue
Block a user