Merge branch 'adept-budgeting-and-forecasting' (#654)

Cleaned-up versions of a number of related PRs relating to budgeting,
periodic transactions, automated postings and period expressions, such
as: #644, #645, #646, #647, #651, #652, #653.
This commit is contained in:
Simon Michael 2017-11-26 14:57:27 -08:00
commit 8ab1911345
17 changed files with 1107 additions and 61 deletions

View File

@ -13,7 +13,6 @@ import Data.List
import Data.String.Here import Data.String.Here
import System.Console.CmdArgs import System.Console.CmdArgs
import Hledger.Cli import Hledger.Cli
import Hledger.Data.AutoTransaction
-- hledger-budget REPORT-COMMAND [--no-offset] [--no-buckets] [OPTIONS...] -- hledger-budget REPORT-COMMAND [--no-offset] [--no-buckets] [OPTIONS...]

16
examples/budget.journal Normal file
View File

@ -0,0 +1,16 @@
~ monthly from 2013/01
Expenses:Food 500 USD
Expenses:Health 200 USD
Expenses:Home 2545 USD
Expenses:Transport 120 USD
Expenses:Taxes 4300 USD ;; Taken from monthly average report
Income:US -10700 USD
Assets:US
~ every Dec 20th from 2014
Expenses:Food 500 USD ; Prize turkey, the biggest of the big
Assets:US
~ 2014/11/17
Assets:US
Expenses:Food 6000 USD ; Birthday, lots of guests

View File

@ -22,6 +22,7 @@ module Hledger.Data (
module Hledger.Data.StringFormat, module Hledger.Data.StringFormat,
module Hledger.Data.Timeclock, module Hledger.Data.Timeclock,
module Hledger.Data.Transaction, module Hledger.Data.Transaction,
module Hledger.Data.AutoTransaction,
module Hledger.Data.Types, module Hledger.Data.Types,
tests_Hledger_Data tests_Hledger_Data
) )
@ -42,6 +43,7 @@ import Hledger.Data.RawOptions
import Hledger.Data.StringFormat import Hledger.Data.StringFormat
import Hledger.Data.Timeclock import Hledger.Data.Timeclock
import Hledger.Data.Transaction import Hledger.Data.Transaction
import Hledger.Data.AutoTransaction
import Hledger.Data.Types import Hledger.Data.Types
tests_Hledger_Data :: Test tests_Hledger_Data :: Test

View File

@ -136,7 +136,8 @@ renderPostingCommentDates p = p { pcomment = comment' }
-- --
-- Note that new transactions require 'txnTieKnot' post-processing. -- Note that new transactions require 'txnTieKnot' post-processing.
-- --
-- >>> mapM_ (putStr . show) $ runPeriodicTransaction (PeriodicTransaction "monthly from 2017/1 to 2017/4" ["hi" `post` usd 1]) nulldatespan -- >>> let gen str = mapM_ (putStr . show) $ runPeriodicTransaction (PeriodicTransaction str ["hi" `post` usd 1]) nulldatespan
-- >>> gen "monthly from 2017/1 to 2017/4"
-- 2017/01/01 -- 2017/01/01
-- hi $1.00 -- hi $1.00
-- <BLANKLINE> -- <BLANKLINE>
@ -146,6 +147,86 @@ renderPostingCommentDates p = p { pcomment = comment' }
-- 2017/03/01 -- 2017/03/01
-- hi $1.00 -- hi $1.00
-- <BLANKLINE> -- <BLANKLINE>
-- >>> gen "monthly from 2017/1 to 2017/5"
-- 2017/01/01
-- hi $1.00
-- <BLANKLINE>
-- 2017/02/01
-- hi $1.00
-- <BLANKLINE>
-- 2017/03/01
-- hi $1.00
-- <BLANKLINE>
-- 2017/04/01
-- hi $1.00
-- <BLANKLINE>
-- >>> gen "every 2nd day of month from 2017/02 to 2017/04"
-- 2017/01/02
-- hi $1.00
-- <BLANKLINE>
-- 2017/02/02
-- hi $1.00
-- <BLANKLINE>
-- 2017/03/02
-- hi $1.00
-- <BLANKLINE>
-- >>> gen "monthly from 2017/1 to 2017/4"
-- 2017/01/01
-- hi $1.00
-- <BLANKLINE>
-- 2017/02/01
-- hi $1.00
-- <BLANKLINE>
-- 2017/03/01
-- hi $1.00
-- <BLANKLINE>
-- >>> gen "every 30th day of month from 2017/1 to 2017/5"
-- 2016/12/30
-- hi $1.00
-- <BLANKLINE>
-- 2017/01/30
-- hi $1.00
-- <BLANKLINE>
-- 2017/02/28
-- hi $1.00
-- <BLANKLINE>
-- 2017/03/30
-- hi $1.00
-- <BLANKLINE>
-- 2017/04/30
-- hi $1.00
-- <BLANKLINE>
-- >>> gen "every 2nd Thursday of month from 2017/1 to 2017/4"
-- 2016/12/08
-- hi $1.00
-- <BLANKLINE>
-- 2017/01/12
-- hi $1.00
-- <BLANKLINE>
-- 2017/02/09
-- hi $1.00
-- <BLANKLINE>
-- 2017/03/09
-- hi $1.00
-- <BLANKLINE>
-- >>> gen "every nov 29th from 2017 to 2019"
-- 2016/11/29
-- hi $1.00
-- <BLANKLINE>
-- 2017/11/29
-- hi $1.00
-- <BLANKLINE>
-- 2018/11/29
-- hi $1.00
-- <BLANKLINE>
-- >>> gen "weekly from 2017"
-- *** Exception: Unable to generate transactions according to "weekly from 2017" as 2017-01-01 is not a first day of the week
-- >>> gen "monthly from 2017/5/4"
-- *** Exception: Unable to generate transactions according to "monthly from 2017/5/4" as 2017-05-04 is not a first day of the month
-- >>> gen "every quarter from 2017/1/2"
-- *** Exception: Unable to generate transactions according to "every quarter from 2017/1/2" as 2017-01-02 is not a first day of the quarter
-- >>> gen "yearly from 2017/1/14"
-- *** Exception: Unable to generate transactions according to "yearly from 2017/1/14" as 2017-01-14 is not a first day of the year
runPeriodicTransaction :: PeriodicTransaction -> (DateSpan -> [Transaction]) runPeriodicTransaction :: PeriodicTransaction -> (DateSpan -> [Transaction])
runPeriodicTransaction pt = generate where runPeriodicTransaction pt = generate where
base = nulltransaction { tpostings = ptpostings pt } base = nulltransaction { tpostings = ptpostings pt }
@ -154,5 +235,18 @@ runPeriodicTransaction pt = generate where
(interval, effectspan) = (interval, effectspan) =
case parsePeriodExpr errCurrent periodExpr of case parsePeriodExpr errCurrent periodExpr of
Left e -> error' $ "Failed to parse " ++ show (T.unpack periodExpr) ++ ": " ++ showDateParseError e Left e -> error' $ "Failed to parse " ++ show (T.unpack periodExpr) ++ ": " ++ showDateParseError e
Right x -> x Right x -> checkProperStartDate x
generate jspan = [base {tdate=date} | span <- interval `splitSpan` spanIntersect effectspan jspan, let Just date = spanStart span] generate jspan = [base {tdate=date} | span <- interval `splitSpan` spanIntersect effectspan jspan, let Just date = spanStart span]
checkProperStartDate (i,s) =
case (i,spanStart s) of
(Weeks _, Just d) -> checkStart d "week"
(Months _, Just d) -> checkStart d "month"
(Quarters _, Just d) -> checkStart d "quarter"
(Years _, Just d) -> checkStart d "year"
_ -> (i,s)
where
checkStart d x =
let firstDate = fixSmartDate d ("","this",x)
in
if d == firstDate then (i,s)
else error' $ "Unable to generate transactions according to "++(show periodExpr)++" as "++(show d)++" is not a first day of the "++x

View File

@ -88,6 +88,7 @@ import Data.Time.Clock
import Data.Time.LocalTime import Data.Time.LocalTime
import Safe (headMay, lastMay, readMay) import Safe (headMay, lastMay, readMay)
import Text.Megaparsec.Compat import Text.Megaparsec.Compat
import Text.Megaparsec.Perm
import Text.Printf import Text.Printf
import Hledger.Data.Types import Hledger.Data.Types
@ -165,9 +166,15 @@ spansSpan spans = DateSpan (maybe Nothing spanStart $ headMay spans) (maybe Noth
-- >>> t (Weeks 2) "2008/01/01" "2008/01/15" -- >>> t (Weeks 2) "2008/01/01" "2008/01/15"
-- [DateSpan 2007/12/31-2008/01/13,DateSpan 2008/01/14-2008/01/27] -- [DateSpan 2007/12/31-2008/01/13,DateSpan 2008/01/14-2008/01/27]
-- >>> t (DayOfMonth 2) "2008/01/01" "2008/04/01" -- >>> t (DayOfMonth 2) "2008/01/01" "2008/04/01"
-- [DateSpan 2008/01/02-2008/02/01,DateSpan 2008/02/02-2008/03/01,DateSpan 2008/03/02-2008/04/01] -- [DateSpan 2007/12/02-2008/01/01,DateSpan 2008/01/02-2008/02/01,DateSpan 2008/02/02-2008/03/01,DateSpan 2008/03/02-2008/04/01]
-- >>> t (WeekdayOfMonth 2 4) "2011/01/01" "2011/02/15"
-- [DateSpan 2010/12/09-2011/01/12,DateSpan 2011/01/13-2011/02/09,DateSpan 2011/02/10-2011/03/09]
-- >>> t (DayOfWeek 2) "2011/01/01" "2011/01/15" -- >>> t (DayOfWeek 2) "2011/01/01" "2011/01/15"
-- [DateSpan 2011/01/04-2011/01/10,DateSpan 2011/01/11-2011/01/17] -- [DateSpan 2010/12/28-2011/01/03,DateSpan 2011/01/04-2011/01/10,DateSpan 2011/01/11-2011/01/17]
-- >>> t (DayOfYear 11 29) "2011/10/01" "2011/10/15"
-- [DateSpan 2010/11/29-2011/11/28]
-- >>> t (DayOfYear 11 29) "2011/12/01" "2012/12/15"
-- [DateSpan 2011/11/29-2012/11/28,DateSpan 2012/11/29-2013/11/28]
-- --
splitSpan :: Interval -> DateSpan -> [DateSpan] splitSpan :: Interval -> DateSpan -> [DateSpan]
splitSpan _ (DateSpan Nothing Nothing) = [DateSpan Nothing Nothing] splitSpan _ (DateSpan Nothing Nothing) = [DateSpan Nothing Nothing]
@ -177,8 +184,10 @@ splitSpan (Weeks n) s = splitspan startofweek (applyN n nextweek) s
splitSpan (Months n) s = splitspan startofmonth (applyN n nextmonth) s splitSpan (Months n) s = splitspan startofmonth (applyN n nextmonth) s
splitSpan (Quarters n) s = splitspan startofquarter (applyN n nextquarter) s splitSpan (Quarters n) s = splitspan startofquarter (applyN n nextquarter) s
splitSpan (Years n) s = splitspan startofyear (applyN n nextyear) s splitSpan (Years n) s = splitspan startofyear (applyN n nextyear) s
splitSpan (DayOfMonth n) s = splitspan (nthdayofmonthcontaining n) (applyN (n-1) nextday . nextmonth) s splitSpan (DayOfMonth n) s = splitspan (nthdayofmonthcontaining n) (nthdayofmonth n . nextmonth) s
splitSpan (WeekdayOfMonth n wd) s = splitspan (nthweekdayofmonthcontaining n wd) (advancetonthweekday n wd . nextmonth) s
splitSpan (DayOfWeek n) s = splitspan (nthdayofweekcontaining n) (applyN (n-1) nextday . nextweek) s splitSpan (DayOfWeek n) s = splitspan (nthdayofweekcontaining n) (applyN (n-1) nextday . nextweek) s
splitSpan (DayOfYear m n) s= splitspan (nthdayofyearcontaining m n) (applyN (n-1) nextday . applyN (m-1) nextmonth . nextyear) s
-- splitSpan (WeekOfYear n) s = splitspan startofweek (applyN n nextweek) s -- splitSpan (WeekOfYear n) s = splitspan startofweek (applyN n nextweek) s
-- splitSpan (MonthOfYear n) s = splitspan startofmonth (applyN n nextmonth) s -- splitSpan (MonthOfYear n) s = splitspan startofmonth (applyN n nextmonth) s
-- splitSpan (QuarterOfYear n) s = splitspan startofquarter (applyN n nextquarter) s -- splitSpan (QuarterOfYear n) s = splitspan startofquarter (applyN n nextquarter) s
@ -257,7 +266,7 @@ earliest (Just d1) (Just d2) = Just $ min d1 d2
-- | Parse a period expression to an Interval and overall DateSpan using -- | Parse a period expression to an Interval and overall DateSpan using
-- the provided reference date, or return a parse error. -- the provided reference date, or return a parse error.
parsePeriodExpr :: Day -> Text -> Either (ParseError Char MPErr) (Interval, DateSpan) parsePeriodExpr :: Day -> Text -> Either (ParseError Char MPErr) (Interval, DateSpan)
parsePeriodExpr refdate = parsewith (periodexpr refdate <* eof) parsePeriodExpr refdate s = parsewith (periodexpr refdate <* eof) (T.toLower s)
maybePeriod :: Day -> Text -> Maybe (Interval,DateSpan) maybePeriod :: Day -> Text -> Maybe (Interval,DateSpan)
maybePeriod refdate = either (const Nothing) Just . parsePeriodExpr refdate maybePeriod refdate = either (const Nothing) Just . parsePeriodExpr refdate
@ -447,6 +456,7 @@ thismonth = startofmonth
prevmonth = startofmonth . addGregorianMonthsClip (-1) prevmonth = startofmonth . addGregorianMonthsClip (-1)
nextmonth = startofmonth . addGregorianMonthsClip 1 nextmonth = startofmonth . addGregorianMonthsClip 1
startofmonth day = fromGregorian y m 1 where (y,m,_) = toGregorian day startofmonth day = fromGregorian y m 1 where (y,m,_) = toGregorian day
nthdayofmonth d day = fromGregorian y m d where (y,m,_) = toGregorian day
thisquarter = startofquarter thisquarter = startofquarter
prevquarter = startofquarter . addGregorianMonthsClip (-3) prevquarter = startofquarter . addGregorianMonthsClip (-3)
@ -461,18 +471,106 @@ prevyear = startofyear . addGregorianYearsClip (-1)
nextyear = startofyear . addGregorianYearsClip 1 nextyear = startofyear . addGregorianYearsClip 1
startofyear day = fromGregorian y 1 1 where (y,_,_) = toGregorian day startofyear day = fromGregorian y 1 1 where (y,_,_) = toGregorian day
nthdayofmonthcontaining n d | d1 >= d = d1 -- | For given date d find year-long interval that starts on given MM/DD of year
| otherwise = d2 -- and covers it.
where d1 = addDays (fromIntegral n-1) s --
d2 = addDays (fromIntegral n-1) $ nextmonth s -- Examples: lets take 2017-11-22. Year-long intervals covering it that
-- starts before Nov 22 will start in 2017. However
-- intervals that start after Nov 23rd should start in 2016:
-- >>> let wed22nd = parsedate "2017-11-22"
-- >>> nthdayofyearcontaining 11 21 wed22nd
-- 2017-11-21
-- >>> nthdayofyearcontaining 11 22 wed22nd
-- 2017-11-22
-- >>> nthdayofyearcontaining 11 23 wed22nd
-- 2016-11-23
-- >>> nthdayofyearcontaining 12 02 wed22nd
-- 2016-12-02
-- >>> nthdayofyearcontaining 12 31 wed22nd
-- 2016-12-31
-- >>> nthdayofyearcontaining 1 1 wed22nd
-- 2017-01-01
nthdayofyearcontaining m n d | mmddOfSameYear <= d = mmddOfSameYear
| otherwise = mmddOfPrevYear
where mmddOfSameYear = addDays (fromIntegral n-1) $ applyN (m-1) nextmonth s
mmddOfPrevYear = addDays (fromIntegral n-1) $ applyN (m-1) nextmonth $ prevyear s
s = startofyear d
-- | For given date d find month-long interval that starts on nth day of month
-- and covers it.
--
-- Examples: lets take 2017-11-22. Month-long intervals covering it that
-- start on 1st-22nd of month will start in Nov. However
-- intervals that start on 23rd-30th of month should start in Oct:
-- >>> let wed22nd = parsedate "2017-11-22"
-- >>> nthdayofmonthcontaining 1 wed22nd
-- 2017-11-01
-- >>> nthdayofmonthcontaining 12 wed22nd
-- 2017-11-12
-- >>> nthdayofmonthcontaining 22 wed22nd
-- 2017-11-22
-- >>> nthdayofmonthcontaining 23 wed22nd
-- 2017-10-23
-- >>> nthdayofmonthcontaining 30 wed22nd
-- 2017-10-30
nthdayofmonthcontaining n d | nthOfSameMonth <= d = nthOfSameMonth
| otherwise = nthOfPrevMonth
where nthOfSameMonth = nthdayofmonth n s
nthOfPrevMonth = nthdayofmonth n $ prevmonth s
s = startofmonth d s = startofmonth d
nthdayofweekcontaining n d | d1 >= d = d1 -- | For given date d find week-long interval that starts on nth day of week
| otherwise = d2 -- and covers it.
where d1 = addDays (fromIntegral n-1) s --
d2 = addDays (fromIntegral n-1) $ nextweek s -- Examples: 2017-11-22 is Wed. Week-long intervals that cover it and
-- start on Mon, Tue or Wed will start in the same week. However
-- intervals that start on Thu or Fri should start in prev week:
-- >>> let wed22nd = parsedate "2017-11-22"
-- >>> nthdayofweekcontaining 1 wed22nd
-- 2017-11-20
-- >>> nthdayofweekcontaining 2 wed22nd
-- 2017-11-21
-- >>> nthdayofweekcontaining 3 wed22nd
-- 2017-11-22
-- >>> nthdayofweekcontaining 4 wed22nd
-- 2017-11-16
-- >>> nthdayofweekcontaining 5 wed22nd
-- 2017-11-17
nthdayofweekcontaining n d | nthOfSameWeek <= d = nthOfSameWeek
| otherwise = nthOfPrevWeek
where nthOfSameWeek = addDays (fromIntegral n-1) s
nthOfPrevWeek = addDays (fromIntegral n-1) $ prevweek s
s = startofweek d s = startofweek d
-- | For given date d find month-long interval that starts on nth weekday of month
-- and covers it.
--
-- Examples: 2017-11-22 is 3rd Wed of Nov. Month-long intervals that cover it and
-- start on 1st-4th Wed will start in Nov. However
-- intervals that start on 4th Thu or Fri or later should start in Oct:
-- >>> let wed22nd = parsedate "2017-11-22"
-- >>> nthweekdayofmonthcontaining 1 3 wed22nd
-- 2017-11-01
-- >>> nthweekdayofmonthcontaining 3 2 wed22nd
-- 2017-11-21
-- >>> nthweekdayofmonthcontaining 4 3 wed22nd
-- 2017-11-22
-- >>> nthweekdayofmonthcontaining 4 4 wed22nd
-- 2017-10-26
-- >>> nthweekdayofmonthcontaining 4 5 wed22nd
-- 2017-10-27
nthweekdayofmonthcontaining n wd d | nthWeekdaySameMonth <= d = nthWeekdaySameMonth
| otherwise = nthWeekdayPrevMonth
where nthWeekdaySameMonth = advancetonthweekday n wd $ startofmonth d
nthWeekdayPrevMonth = advancetonthweekday n wd $ prevmonth d
-- | Advance to nth weekday wd after given start day s
advancetonthweekday n wd s = addWeeks (n-1) . firstMatch (>=s) . iterate (addWeeks 1) $ firstweekday s
where
addWeeks k = addDays (7 * fromIntegral k)
firstMatch p = head . dropWhile (not . p)
firstweekday = addDays (fromIntegral wd-1) . startofweek
---------------------------------------------------------------------- ----------------------------------------------------------------------
-- parsing -- parsing
@ -633,17 +731,11 @@ md = do
months = ["january","february","march","april","may","june", months = ["january","february","march","april","may","june",
"july","august","september","october","november","december"] "july","august","september","october","november","december"]
monthabbrevs = ["jan","feb","mar","apr","may","jun","jul","aug","sep","oct","nov","dec"] monthabbrevs = ["jan","feb","mar","apr","may","jun","jul","aug","sep","oct","nov","dec"]
-- weekdays = ["monday","tuesday","wednesday","thursday","friday","saturday","sunday"] weekdays = ["monday","tuesday","wednesday","thursday","friday","saturday","sunday"]
-- weekdayabbrevs = ["mon","tue","wed","thu","fri","sat","sun"] weekdayabbrevs = ["mon","tue","wed","thu","fri","sat","sun"]
#if MIN_VERSION_megaparsec(6,0,0) monthIndex t = maybe 0 (+1) $ t `elemIndex` months
lc = T.toLower monIndex t = maybe 0 (+1) $ t `elemIndex` monthabbrevs
#else
lc = lowercase
#endif
monthIndex t = maybe 0 (+1) $ lc t `elemIndex` months
monIndex t = maybe 0 (+1) $ lc t `elemIndex` monthabbrevs
month :: SimpleTextParser SmartDate month :: SimpleTextParser SmartDate
month = do month = do
@ -657,6 +749,12 @@ mon = do
let i = monIndex m let i = monIndex m
return ("",show i,"") return ("",show i,"")
weekday :: SimpleTextParser Int
weekday = do
wday <- choice . map string' $ weekdays ++ weekdayabbrevs
let i = head . catMaybes $ [wday `elemIndex` weekdays, wday `elemIndex` weekdayabbrevs]
return (i+1)
today,yesterday,tomorrow :: SimpleTextParser SmartDate today,yesterday,tomorrow :: SimpleTextParser SmartDate
today = string "today" >> return ("","","today") today = string "today" >> return ("","","today")
yesterday = string "yesterday" >> return ("","","yesterday") yesterday = string "yesterday" >> return ("","","yesterday")
@ -683,17 +781,43 @@ lastthisnextthing = do
return ("", T.unpack r, T.unpack p) return ("", T.unpack r, T.unpack p)
-- | -- |
-- >>> let p = parsewith (periodexpr (parsedate "2008/11/26")) :: T.Text -> Either (ParseError Char MPErr) (Interval, DateSpan) -- >>> let p s = parsewith (periodexpr (parsedate "2008/11/26") <* eof) (T.toLower s) :: Either (ParseError Char MPErr) (Interval, DateSpan)
-- >>> p "from aug to oct" -- >>> p "from Aug to Oct"
-- Right (NoInterval,DateSpan 2008/08/01-2008/09/30) -- Right (NoInterval,DateSpan 2008/08/01-2008/09/30)
-- >>> p "aug to oct" -- >>> p "aug to oct"
-- Right (NoInterval,DateSpan 2008/08/01-2008/09/30) -- Right (NoInterval,DateSpan 2008/08/01-2008/09/30)
-- >>> p "every 3 days in aug" -- >>> p "every 3 days in Aug"
-- Right (Days 3,DateSpan 2008/08) -- Right (Days 3,DateSpan 2008/08)
-- >>> p "daily from aug" -- >>> p "daily from aug"
-- Right (Days 1,DateSpan 2008/08/01-) -- Right (Days 1,DateSpan 2008/08/01-)
-- >>> p "every week to 2009" -- >>> p "every week to 2009"
-- Right (Weeks 1,DateSpan -2008/12/31) -- Right (Weeks 1,DateSpan -2008/12/31)
-- >>> p "every 2nd day of month"
-- Right (DayOfMonth 2,DateSpan -)
-- >>> p "every 2nd day"
-- Right (DayOfMonth 2,DateSpan -)
-- >>> p "every 2nd day 2009-"
-- Right (DayOfMonth 2,DateSpan 2009/01/01-)
-- >>> p "every 29th Nov"
-- Right (DayOfYear 11 29,DateSpan -)
-- >>> p "every 29th nov -2009"
-- Right (DayOfYear 11 29,DateSpan -2008/12/31)
-- >>> p "every nov 29th"
-- Right (DayOfYear 11 29,DateSpan -)
-- >>> p "every Nov 29th 2009-"
-- Right (DayOfYear 11 29,DateSpan 2009/01/01-)
-- >>> p "every 11/29 from 2009"
-- Right (DayOfYear 11 29,DateSpan 2009/01/01-)
-- >>> p "every 2nd Thursday of month to 2009"
-- Right (WeekdayOfMonth 2 4,DateSpan -2008/12/31)
-- >>> p "every 1st monday of month to 2009"
-- Right (WeekdayOfMonth 1 1,DateSpan -2008/12/31)
-- >>> p "every tue"
-- Right (DayOfWeek 2,DateSpan -)
-- >>> p "every 2nd day of week"
-- Right (DayOfWeek 2,DateSpan -)
-- >>> p "every 2nd day 2009-"
-- Right (DayOfMonth 2,DateSpan 2009/01/01-)
periodexpr :: Day -> SimpleTextParser (Interval, DateSpan) periodexpr :: Day -> SimpleTextParser (Interval, DateSpan)
periodexpr rdate = choice $ map try [ periodexpr rdate = choice $ map try [
intervalanddateperiodexpr rdate, intervalanddateperiodexpr rdate,
@ -736,31 +860,53 @@ reportinginterval = choice' [
return $ Months 2, return $ Months 2,
do string "every" do string "every"
many spacenonewline many spacenonewline
n <- fmap read $ some digitChar n <- nth
thsuffix
many spacenonewline many spacenonewline
string "day" string "day"
many spacenonewline of_ "week"
string "of"
many spacenonewline
string "week"
return $ DayOfWeek n, return $ DayOfWeek n,
do string "every" do string "every"
many spacenonewline many spacenonewline
n <- fmap read $ some digitChar n <- weekday
thsuffix return $ DayOfWeek n,
do string "every"
many spacenonewline
n <- nth
many spacenonewline many spacenonewline
string "day" string "day"
optional $ do optOf_ "month"
many spacenonewline return $ DayOfMonth n,
string "of" do string "every"
many spacenonewline many spacenonewline
string "month" let mnth = choice' [month, mon] >>= \(_,m,_) -> return (read m)
return $ DayOfMonth n d_o_y <- makePermParser $ DayOfYear <$$> (mnth <* many spacenonewline) <||> (nth <* many spacenonewline)
optOf_ "year"
return d_o_y,
do string "every"
many spacenonewline
("",m,d) <- md
optOf_ "year"
return $ DayOfYear (read m) (read d),
do string "every"
many spacenonewline
n <- nth
many spacenonewline
wd <- weekday
optOf_ "month"
return $ WeekdayOfMonth n wd
] ]
where where
of_ period = do
thsuffix = choice' $ map string ["st","nd","rd","th"] many spacenonewline
string "of"
many spacenonewline
string period
optOf_ period = optional $ try $ of_ period
nth = do n <- some digitChar
choice' $ map string ["st","nd","rd","th"]
return $ read n
-- Parse any of several variants of a basic interval, eg "daily", "every day", "every N days". -- Parse any of several variants of a basic interval, eg "daily", "every day", "every N days".
tryinterval :: String -> String -> (Int -> Interval) -> SimpleTextParser Interval tryinterval :: String -> String -> (Int -> Interval) -> SimpleTextParser Interval

View File

@ -89,7 +89,9 @@ data Interval =
| Quarters Int | Quarters Int
| Years Int | Years Int
| DayOfMonth Int | DayOfMonth Int
| WeekdayOfMonth Int Int
| DayOfWeek Int | DayOfWeek Int
| DayOfYear Int Int -- Month, Day
-- WeekOfYear Int -- WeekOfYear Int
-- MonthOfYear Int -- MonthOfYear Int
-- QuarterOfYear Int -- QuarterOfYear Int

View File

@ -104,6 +104,8 @@ data ReportOpts = ReportOpts {
-- eg in the income section of an income statement, this helps --sort-amount know -- eg in the income section of an income statement, this helps --sort-amount know
-- how to sort negative numbers. -- how to sort negative numbers.
,color_ :: Bool ,color_ :: Bool
,forecast_ :: Bool
,auto_ :: Bool
} deriving (Show, Data, Typeable) } deriving (Show, Data, Typeable)
instance Default ReportOpts where def = defreportopts instance Default ReportOpts where def = defreportopts
@ -134,6 +136,8 @@ defreportopts = ReportOpts
def def
def def
def def
def
def
rawOptsToReportOpts :: RawOpts -> IO ReportOpts rawOptsToReportOpts :: RawOpts -> IO ReportOpts
rawOptsToReportOpts rawopts = checkReportOpts <$> do rawOptsToReportOpts rawopts = checkReportOpts <$> do
@ -164,6 +168,8 @@ rawOptsToReportOpts rawopts = checkReportOpts <$> do
,sort_amount_ = boolopt "sort-amount" rawopts' ,sort_amount_ = boolopt "sort-amount" rawopts'
,pretty_tables_ = boolopt "pretty-tables" rawopts' ,pretty_tables_ = boolopt "pretty-tables" rawopts'
,color_ = color ,color_ = color
,forecast_ = boolopt "forecast" rawopts'
,auto_ = boolopt "auto" rawopts'
} }
-- | Do extra validation of raw option values, raising an error if there's a problem. -- | Do extra validation of raw option values, raising an error if there's a problem.

View File

@ -155,6 +155,8 @@ reportflags = [
,flagNone ["empty","E"] (setboolopt "empty") "show items with zero amount, normally hidden" ,flagNone ["empty","E"] (setboolopt "empty") "show items with zero amount, normally hidden"
,flagNone ["cost","B"] (setboolopt "cost") "convert amounts to their cost at transaction time (using the transaction price, if any)" ,flagNone ["cost","B"] (setboolopt "cost") "convert amounts to their cost at transaction time (using the transaction price, if any)"
,flagNone ["value","V"] (setboolopt "value") "convert amounts to their market value on the report end date (using the most recent applicable market price, if any)" ,flagNone ["value","V"] (setboolopt "value") "convert amounts to their market value on the report end date (using the most recent applicable market price, if any)"
,flagNone ["forecast"] (setboolopt "forecast") "generate forecast transactions"
,flagNone ["auto"] (setboolopt "auto") "generate automated postings"
] ]
-- | Common output-related flags: --output-file, --output-format... -- | Common output-related flags: --output-file, --output-format...

View File

@ -246,11 +246,13 @@ module Hledger.Cli.Commands.Balance (
,tests_Hledger_Cli_Commands_Balance ,tests_Hledger_Cli_Commands_Balance
) where ) where
import Data.List (intercalate) import Data.List (intercalate, nub)
import Data.Maybe import Data.Maybe
import qualified Data.Map as Map
-- import Data.Monoid -- import Data.Monoid
import qualified Data.Text as T import qualified Data.Text as T
import System.Console.CmdArgs.Explicit as C import System.Console.CmdArgs.Explicit as C
import Data.Decimal (roundTo)
import Text.CSV import Text.CSV
import Test.HUnit import Test.HUnit
import Text.Printf (printf) import Text.Printf (printf)
@ -283,6 +285,8 @@ balancemode = (defCommandMode $ ["balance"] ++ aliases) { -- also accept but don
,flagReq ["format"] (\s opts -> Right $ setopt "format" s opts) "FORMATSTR" "use this custom line format (in simple reports)" ,flagReq ["format"] (\s opts -> Right $ setopt "format" s opts) "FORMATSTR" "use this custom line format (in simple reports)"
,flagNone ["pretty-tables"] (\opts -> setboolopt "pretty-tables" opts) "use unicode when displaying tables" ,flagNone ["pretty-tables"] (\opts -> setboolopt "pretty-tables" opts) "use unicode when displaying tables"
,flagNone ["sort-amount","S"] (\opts -> setboolopt "sort-amount" opts) "sort by amount instead of account name" ,flagNone ["sort-amount","S"] (\opts -> setboolopt "sort-amount" opts) "sort by amount instead of account name"
,flagNone ["budget"] (setboolopt "budget") "compute budget from periodic transactions and compare real balances to it"
,flagNone ["show-unbudgeted"] (setboolopt "show-unbudgeted") "show full names of accounts not mentioned in budget"
] ]
++ outputflags ++ outputflags
,groupHidden = [] ,groupHidden = []
@ -293,7 +297,7 @@ balancemode = (defCommandMode $ ["balance"] ++ aliases) { -- also accept but don
-- | 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{reportopts_=ropts} j = do balance opts@CliOpts{rawopts_=rawopts,reportopts_=ropts} j = do
d <- getCurrentDay d <- getCurrentDay
case lineFormatFromOpts ropts of case lineFormatFromOpts ropts of
Left err -> error' $ unlines [err] Left err -> error' $ unlines [err]
@ -319,12 +323,58 @@ balance opts@CliOpts{reportopts_=ropts} j = do
"csv" -> \ropts r -> (++ "\n") $ printCSV $ balanceReportAsCsv ropts r "csv" -> \ropts r -> (++ "\n") $ printCSV $ balanceReportAsCsv ropts r
_ -> balanceReportAsText _ -> balanceReportAsText
writeOutput opts $ render ropts report writeOutput opts $ render ropts report
_ -> do
_ | boolopt "budget" rawopts -> do
let budget = budgetJournal opts j
j' = budgetRollUp opts budget j
report = multiBalanceReport ropts (queryFromOpts d ropts) j'
budgetReport = multiBalanceReport ropts (queryFromOpts d ropts) budget
render = case format of
-- XXX: implement csv rendering
"csv" -> (++ "\n") . printCSV . multiBalanceReportAsCsv ropts
_ -> multiBalanceReportWithBudgetAsText ropts budgetReport
writeOutput opts $ render report
| otherwise -> do
let report = multiBalanceReport ropts (queryFromOpts d ropts) j let report = multiBalanceReport ropts (queryFromOpts d ropts) j
render = case format of render = case format of
"csv" -> \ropts r -> (++ "\n") $ printCSV $ multiBalanceReportAsCsv ropts r "csv" -> (++ "\n") . printCSV . multiBalanceReportAsCsv ropts
_ -> multiBalanceReportAsText _ -> multiBalanceReportAsText ropts
writeOutput opts $ render ropts report writeOutput opts $ render report
-- | Re-map account names to closet parent with periodic transaction from budget.
-- Accounts that dont have suitable parent are either remapped to "<unbudgeted>:topAccount"
-- or left as-is if --show-unbudgeted is provided
budgetRollUp :: CliOpts -> Journal -> Journal -> Journal
budgetRollUp CliOpts{rawopts_=rawopts} budget j = j { jtxns = remapTxn <$> jtxns j }
where
budgetAccounts = nub $ concatMap (map paccount . ptpostings) $ jperiodictxns budget
remapAccount origAcctName = remapAccount' origAcctName
where
remapAccount' acctName
| acctName `elem` budgetAccounts = acctName
| otherwise =
case parentAccountName acctName of
"" | boolopt "show-unbudgeted" rawopts -> origAcctName
| otherwise -> T.append (T.pack "<unbudgeted>:") acctName
parent -> remapAccount' parent
remapPosting p = p { paccount = remapAccount $ paccount p, porigin = Just . fromMaybe p $ porigin p }
remapTxn = mapPostings (map remapPosting)
mapPostings f t = txnTieKnot $ t { tpostings = f $ tpostings t }
-- | Generate journal of all periodic transactions in the given journal for the
-- entireity of its history or reporting period, whatever is smaller
budgetJournal :: CliOpts -> Journal -> Journal
budgetJournal opts j = journalBalanceTransactions' opts j { jtxns = budget }
where
dates = spanIntersect (jdatespan j) (periodAsDateSpan $ period_ $ reportopts_ opts)
budget = [makeBudget t | pt <- jperiodictxns j, t <- runPeriodicTransaction pt dates]
makeBudget t = txnTieKnot $ t { tdescription = T.pack "Budget transaction" }
journalBalanceTransactions' opts j =
let assrt = not . ignore_assertions_ $ inputopts_ opts
in
either error' id $ journalBalanceTransactions assrt j
-- single-column balance reports -- single-column balance reports
@ -494,16 +544,73 @@ multiBalanceReportAsText opts r =
CumulativeChange -> "Ending balances (cumulative)" CumulativeChange -> "Ending balances (cumulative)"
HistoricalBalance -> "Ending balances (historical)" HistoricalBalance -> "Ending balances (historical)"
-- | Render two multi-column balance reports as plain text suitable for console output.
-- They are assumed to have same number of columns, one of them representing
-- a budget
multiBalanceReportWithBudgetAsText :: ReportOpts -> MultiBalanceReport -> MultiBalanceReport -> String
multiBalanceReportWithBudgetAsText opts budget r =
printf "%s in %s:\n\n" typeStr (showDateSpan $ multiBalanceReportSpan r)
++ renderBalanceReportTable' opts showcell tabl
where
tabl = combine (balanceReportAsTable opts r) (balanceReportAsTable opts budget)
typeStr :: String
typeStr = case balancetype_ opts of
PeriodChange -> "Balance changes"
CumulativeChange -> "Ending balances (cumulative)"
HistoricalBalance -> "Ending balances (historical)"
showcell (real, Nothing) = showamt real
showcell (real, Just budget) =
case percentage real budget of
Just pct -> printf "%s [%s%% of %s]" (showamt real) (show $ roundTo 0 pct) (showamt budget)
Nothing -> printf "%s [%s]" (showamt real) (showamt budget)
percentage real budget =
case (real, budget) of
(Mixed [a1], Mixed [a2]) | acommodity a1 == acommodity a2 && aquantity a2 /= 0 ->
Just $ 100 * aquantity a1 / aquantity a2
_ -> Nothing
showamt | color_ opts = cshowMixedAmountOneLineWithoutPrice
| otherwise = showMixedAmountOneLineWithoutPrice
-- combine reportTable budgetTable will combine them into a single table where cells
-- are tuples of (actual, Maybe budget) numbers. Main assumptions is that
-- row/column titles of budgetTable are subset of row/column titles or reportTable,
-- and there are now row/column titles in budgetTable that are not mentioned in reporTable.
-- Both of these are satisfied by construction of budget report and process of rolling up
-- account names.
combine (Table l t d) (Table l' t' d') = Table l t combinedRows
where
-- For all accounts that are present in the budget, zip real amounts with budget amounts
combinedRows = [ combineRow row budgetRow
| (acct, row) <- zip (headerContents l) d
, let budgetRow =
if acct == "" then [] -- "" is totals row
else fromMaybe [] $ Map.lookup acct budgetAccts
]
-- Budget could cover smaller interval of time than the whole journal.
-- Headers for budget row will always be a sublist of headers of row
combineRow r br =
let reportRow = zip (headerContents t) r
budgetRow = Map.fromList $ zip (headerContents t') br
findBudgetVal hdr = Map.lookup hdr budgetRow
in map (\(hdr, val) -> (val, findBudgetVal hdr)) reportRow
budgetAccts = Map.fromList $ zip (headerContents l') d'
-- | Given a table representing a multi-column balance report (for example, -- | Given a table representing a multi-column balance report (for example,
-- made using 'balanceReportAsTable'), render it in a format suitable for -- made using 'balanceReportAsTable'), render it in a format suitable for
-- console output. -- console output.
renderBalanceReportTable :: ReportOpts -> Table String String MixedAmount -> String renderBalanceReportTable :: ReportOpts -> Table String String MixedAmount -> String
renderBalanceReportTable (ReportOpts { pretty_tables_ = pretty, color_=usecolor }) = renderBalanceReportTable ropts =
renderBalanceReportTable' ropts showamt
where
showamt | color_ ropts = cshowMixedAmountOneLineWithoutPrice
| otherwise = showMixedAmountOneLineWithoutPrice
renderBalanceReportTable' :: ReportOpts -> (a -> String) -> Table String String a -> String
renderBalanceReportTable' (ReportOpts { pretty_tables_ = pretty}) showCell =
unlines unlines
. addtrailingblank . addtrailingblank
. trimborder . trimborder
. lines . lines
. render pretty id id showamt . render pretty id id showCell
. align . align
where where
addtrailingblank = (++[""]) addtrailingblank = (++[""])
@ -512,8 +619,6 @@ renderBalanceReportTable (ReportOpts { pretty_tables_ = pretty, color_=usecolor
where where
acctswidth = maximum' $ map strWidth (headerContents l) acctswidth = maximum' $ map strWidth (headerContents l)
l' = padRightWide acctswidth <$> l l' = padRightWide acctswidth <$> l
showamt | usecolor = cshowMixedAmountOneLineWithoutPrice
| otherwise = showMixedAmountOneLineWithoutPrice
-- | Build a 'Table' from a multi-column balance report. -- | Build a 'Table' from a multi-column balance report.
balanceReportAsTable :: ReportOpts -> MultiBalanceReport -> Table String String MixedAmount balanceReportAsTable :: ReportOpts -> MultiBalanceReport -> Table String String MixedAmount

View File

@ -31,7 +31,7 @@ import Data.List
import Data.Maybe import Data.Maybe
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.IO as T import qualified Data.Text.IO as T
import Data.Time (Day) import Data.Time (Day, addDays)
import Data.Word import Data.Word
import Numeric import Numeric
import Safe (readMay) import Safe (readMay)
@ -54,6 +54,7 @@ import Hledger.Data
import Hledger.Read import Hledger.Read
import Hledger.Reports import Hledger.Reports
import Hledger.Utils import Hledger.Utils
import Hledger.Query (Query(Any))
-- | Parse the user's specified journal file, maybe apply some transformations -- | Parse the user's specified journal file, maybe apply some transformations
@ -70,6 +71,8 @@ withJournalDo opts cmd = do
. anonymiseByOpts opts . anonymiseByOpts opts
. journalApplyAliases (aliasesFromOpts opts) . journalApplyAliases (aliasesFromOpts opts)
<=< journalApplyValue (reportopts_ opts) <=< journalApplyValue (reportopts_ opts)
<=< journalAddForecast opts
. generateAutomaticPostings (reportopts_ opts)
either error' f ej either error' f ej
-- | Apply the pivot transformation on a journal, if option is present. -- | Apply the pivot transformation on a journal, if option is present.
@ -117,6 +120,38 @@ journalApplyValue ropts j = do
= id = id
return $ convert j return $ convert j
-- | Run PeriodicTransactions from journal from today or journal end to requested end day.
-- Add generated transactions to the journal
journalAddForecast :: CliOpts -> Journal -> IO Journal
journalAddForecast opts j = do
today <- getCurrentDay
-- Create forecast starting from end of journal + 1 day, and until the end of requested reporting period
-- If end is not provided, do 180 days of forecast.
-- Note that jdatespan already returns last day + 1
let startDate = fromMaybe today $ spanEnd (jdatespan j)
endDate = fromMaybe (addDays 180 today) $ periodEnd (period_ ropts)
dates = DateSpan (Just startDate) (Just endDate)
withForecast = [makeForecast t | pt <- jperiodictxns j, t <- runPeriodicTransaction pt dates, spanContainsDate dates (tdate t) ] ++ (jtxns j)
makeForecast t = txnTieKnot $ t { tdescription = T.pack "Forecast transaction" }
ropts = reportopts_ opts
if forecast_ ropts
then return $ journalBalanceTransactions' opts j { jtxns = withForecast }
else return j
where
journalBalanceTransactions' opts j =
let assrt = not . ignore_assertions_ $ inputopts_ opts
in
either error' id $ journalBalanceTransactions assrt j
-- | Generate Automatic postings and add them to the current journal.
generateAutomaticPostings :: ReportOpts -> Journal -> Journal
generateAutomaticPostings ropts j =
if auto_ ropts then j { jtxns = map modifier $ jtxns j } else j
where
modifier = foldr (flip (.) . runModifierTransaction') id mtxns
runModifierTransaction' = fmap txnTieKnot . runModifierTransaction Any
mtxns = jmodifiertxns j
-- | Write some output to stdout or to a file selected by --output-file. -- | Write some output to stdout or to a file selected by --output-file.
-- If the file exists it will be overwritten. -- If the file exists it will be overwritten.
writeOutput :: CliOpts -> String -> IO () writeOutput :: CliOpts -> String -> IO ()

View File

@ -239,21 +239,59 @@ Examples:
`-p "quarterly"` `-p "quarterly"`
------------------------------------------ ------------------------------------------
Note that `weekly`, `monthly`, `quarterly` and `yearly` intervals will
always start on the first day on week, month, quarter or year
accordingly, and will end on the last day of same period, even if
associated period expression specifies different explicit start and end date.
For example:
------------------------------------------
`-p "weekly from 2009/1/1 to 2009/4/1"` -- starts on 2008/12/29, closest preceeding Monday
`-p "monthly in 2008/11/25"` -- starts on 2018/11/01
`-p "quarterly from 2009-05-05 to 2009-06-01"` - starts on 2009/04/01, ends on 2009/06/30, which are first and last days of Q2 2009
`-p "yearly from 2009-12-29"` - starts on 2009/01/01, first day of 2009
------------------------------------------
The following more complex report intervals are also supported: The following more complex report intervals are also supported:
`biweekly`, `biweekly`,
`bimonthly`, `bimonthly`,
`every N days|weeks|months|quarters|years`, `every day|week|month|quarter|year`,
`every Nth day [of month]`, `every N days|weeks|months|quarters|years`.
`every Nth day of week`.
All of these will start on the first day of the requested period and end on the last one, as described above.
Examples: Examples:
------------------------------------------ ------------------------------------------
`-p "bimonthly from 2008"` `-p "bimonthly from 2008"` -- periods will have boundaries on 2008/01/01, 2008/03/01, ...
`-p "every 2 weeks"` `-p "every 2 weeks"` -- starts on closest preceeding Monday
`-p "every 5 days from 1/3"` `-p "every 5 month from 2009/03"` -- periods will have boundaries on 2009/03/01, 2009/08/01, ...
------------------------------------------ ------------------------------------------
If you want intervals that start on arbitrary day of your choosing and span a week, month or year, you need to use any of the following:
`every Nth day of week`,
`every <weekday>`,
`every Nth day [of month]`,
`every Nth weekday [of month]`,
`every MM/DD [of year]`,
`every Nth MMM [of year]`,
`every MMM Nth [of year]`.
Examples:
------------------------------------------
`-p "every 2nd day of week"` -- periods will go from Tue to Tue
`-p "every Tue"` -- same
`-p "every 15th day"` -- period boundaries will be on 15th of each month
`-p "every 2nd Monday"` -- period boundaries will be on second Monday of each month
`-p "every 11/05"` -- yearly periods with boundaries on 5th of Nov
`-p "every 5th Nov"` -- same
`-p "every Nov 5th"` -- same
------------------------------------------
Show historical balances at end of 15th each month (N is exclusive end date): Show historical balances at end of 15th each month (N is exclusive end date):
`hledger balance -H -p "every 16th day"` `hledger balance -H -p "every 16th day"`

View File

@ -113,6 +113,7 @@ library
, text >=0.11 , text >=0.11
, utf8-string >=0.3.5 && <1.1 , utf8-string >=0.3.5 && <1.1
, wizards ==1.0.* , wizards ==1.0.*
, Decimal
if (!(os(windows))) && (flag(terminfo)) if (!(os(windows))) && (flag(terminfo))
build-depends: build-depends:
terminfo terminfo
@ -192,6 +193,7 @@ executable hledger
, text >=0.11 , text >=0.11
, utf8-string >=0.3.5 && <1.1 , utf8-string >=0.3.5 && <1.1
, wizards ==1.0.* , wizards ==1.0.*
, Decimal
if (!(os(windows))) && (flag(terminfo)) if (!(os(windows))) && (flag(terminfo))
build-depends: build-depends:
terminfo terminfo
@ -241,6 +243,7 @@ test-suite test
, text >=0.11 , text >=0.11
, utf8-string >=0.3.5 && <1.1 , utf8-string >=0.3.5 && <1.1
, wizards ==1.0.* , wizards ==1.0.*
, Decimal
, test-framework , test-framework
, test-framework-hunit , test-framework-hunit
if (!(os(windows))) && (flag(terminfo)) if (!(os(windows))) && (flag(terminfo))

View File

@ -149,6 +149,7 @@ library:
- text >=0.11 - text >=0.11
- utf8-string >=0.3.5 && <1.1 - utf8-string >=0.3.5 && <1.1
- wizards ==1.0.* - wizards ==1.0.*
- Decimal
executables: executables:
hledger: hledger:
@ -178,6 +179,7 @@ executables:
- text >=0.11 - text >=0.11
- utf8-string >=0.3.5 && <1.1 - utf8-string >=0.3.5 && <1.1
- wizards ==1.0.* - wizards ==1.0.*
- Decimal
tests: tests:
test: test:
@ -204,6 +206,7 @@ tests:
- text >=0.11 - text >=0.11
- utf8-string >=0.3.5 && <1.1 - utf8-string >=0.3.5 && <1.1
- wizards ==1.0.* - wizards ==1.0.*
- Decimal
- test-framework - test-framework
- test-framework-hunit - test-framework-hunit

View File

@ -0,0 +1,323 @@
# Budgeting and forecasting
Budgeting and forecasting allows you to keep better track of your expenses and future financial situation.
If you write down your expectations of what your income/expenses/investment yields/etc should be, you can use them to:
- check how far off are your expectations from reality (budgeting)
- project your future account activity or balances (forecasting)
(This section uses examples/bcexample.hledger from hledger source repository).
## Periodic budget
To start budgeting, you need to know what your average yearly or weekly expenditures are. Hledger could help you with that.
Usually the interval for which you compute budget figures will be the same as the interval between
your paychecks -- monthly or weekly.
Lets create monthly (-M) report for years 2013-2014 (-b 2013) of all
top-level expense categories (--depth 2 Expenses), looking for average
figures (-A) in the cost at the time of transaction (-B), limiting
ourselves to USD transactions only, to save screen space:
```shell
$ hledger balance -f bcexample.hledger -MBA -b 2013 --depth 2 Expenses cur:USD
Balance changes in 2013/01/01-2014/10/31:
|| 2013/01 2013/02 2013/03 ... 2014/07 2014/08 2014/09 2014/10 Average
====================++========================================...==================================================================
Expenses:Financial || 4.00 USD 12.95 USD 39.80 USD ... 30.85 USD 21.90 USD 12.95 USD 4.00 USD 17.83 USD
Expenses:Food || 396.46 USD 481.48 USD 603.32 USD ... 871.20 USD 768.23 USD 466.72 USD 83.00 USD 562.10 USD
Expenses:Health || 290.70 USD 193.80 USD 193.80 USD ... 290.70 USD 193.80 USD 193.80 USD 96.90 USD 207.01 USD
Expenses:Home || 2544.98 USD 2545.02 USD 2544.97 USD ... 2545.12 USD 2545.01 USD 2545.10 USD 0 2429.33 USD
Expenses:Taxes || 5976.60 USD 3984.40 USD 4901.83 USD ... 5976.60 USD 3984.40 USD 3984.40 USD 1992.20 USD 4322.27 USD
Expenses:Transport || 120.00 USD 120.00 USD 120.00 USD ... 0 120.00 USD 120.00 USD 120.00 USD 109.09 USD
--------------------++----------------------------------------...------------------------------------------------------------------
|| 9332.74 USD 7337.65 USD 8403.72 USD ... 9714.47 USD 7633.34 USD 7322.97 USD 2296.10 USD 7647.64 USD
```
This report is rather wide and portion of it had been cut out for
brevity. Most interesting column is the last one, it shows average
monthly expenses for each category. Expenses in Food, Health, Home and
Transport categories seem to roughly similar month to month, so lets
create a budget for them.
Budgets are described with periodic transactions. Periodic transaction
has `~` instead of date and period expression instead of description. In this case
we want to create a monthly budget that will come into effect starting from January 2013,
which will include income of 10000 USD that is partically spent on Food, Health, Home and Transport
and the rest becomes our Assets:
```journal
~ monthly from 2013/01
Expenses:Food 500 USD
Expenses:Health 200 USD
Expenses:Home 2545 USD
Expenses:Transport 120 USD
Income:US -10700 USD ;; Taken as monthy average of Income account group
Assets:US
```
This transaction could be put into separate file (budget.journal) or
could be kept in the main journal. Normally hledger will ignore it and
will not include it in any computations or reports.
To put it into action, you need to add `--budget` switch to your balance invocation. If you do that,
you would be able to see how your past expenses aligned with the budget that you just created. This
time, lets not limit accounts in any way:
```shell
$ hledger balance -f bcexample.hledger -f budget.journal -MB -b 2013 --budget cur:USD
Balance changes in 2013/01/01-2014/10/31:
|| 2013/01 2013/02 2013/03
==========================++===========================================================================================================
<unbudgeted>:Expenses || 5980.60 USD 3997.35 USD 4941.63 USD
<unbudgeted>:Liabilities || 293.09 USD -147.51 USD -66.01 USD
Assets:US || 1893.32 USD [26% of 7335 USD] 2929.77 USD [40% of 7335 USD] -3898.89 USD [-53% of 7335 USD]
Expenses:Food || 396.46 USD [79% of 500 USD] 481.48 USD [96% of 500 USD] 603.32 USD [121% of 500 USD]
Expenses:Health || 290.70 USD [145% of 200 USD] 193.80 USD [97% of 200 USD] 193.80 USD [97% of 200 USD]
Expenses:Home || 2544.98 USD [100% of 2545 USD] 2545.02 USD [100% of 2545 USD] 2544.97 USD [100% of 2545 USD]
Expenses:Transport || 120.00 USD [100% of 120 USD] 120.00 USD [100% of 120 USD] 120.00 USD [100% of 120 USD]
Income:US || -15119.10 USD [141% of -10700 USD] -10331.21 USD [97% of -10700 USD] -11079.40 USD [104% of -10700 USD]
--------------------------++-----------------------------------------------------------------------------------------------------------
|| -3599.95 USD -211.30 USD -6640.58 USD
```
Numbers in square brackets give you your budget estimate and percentage of it used by your real expenses. Numbers below 100% mean
that you have some of your budget left, numbers over 100% mean that you went over your budget.
You can notice that actual numbers for Assets:US seem to be well below computed budget of 7335 USD. Why? Answer to this is in the first
row of the report: we have quite a lot of unbudgeted Expenses!
Notice that even though we have not limited accounts in any way, report includes just those mentioned in the budget. This is on purpose,
assumption is that when you are checking your budgets you probably do not want unbudgeted accounts getting in your way. Another thing to
note is that budget numbers have been allocated to top-level expense subcategories (like Expenses:Food). Journal has subaccounts under
Food, but to compute budget report they have all been rolled up into a nearest parent with budget number associated with it. Accounts that
do not have such parent went into `<unbudgeted>` row.
Allright, it seems that for Jan 2013 we have ~3000 USD of budgeted expenses and almost twice as much unbudgeted. Lets figure out what they are.
We can see more details if we add `--show-unbudgeted` switch:
```shell
$ hledger balance -f bcexample.hledger -f budget.journal -M -b 2013-01 -e 2013-02 --budget cur:USD --show-unbudgeted
Balance changes in 2013/01:
|| 2013/01
==================================++====================================
Assets:US || 1893.32 USD [26% of 7335 USD]
Expenses:Financial:Fees || 4.00 USD
Expenses:Food || 396.46 USD [79% of 500 USD]
Expenses:Health || 290.70 USD [145% of 200 USD]
Expenses:Home || 2544.98 USD [100% of 2545 USD]
Expenses:Taxes:Y2013:US:CityNYC || 524.76 USD
Expenses:Taxes:Y2013:US:Federal || 3188.76 USD
Expenses:Taxes:Y2013:US:Medicare || 319.86 USD
Expenses:Taxes:Y2013:US:SDI || 3.36 USD
Expenses:Taxes:Y2013:US:SocSec || 844.62 USD
Expenses:Taxes:Y2013:US:State || 1095.24 USD
Expenses:Transport || 120.00 USD [100% of 120 USD]
Income:US || -15119.10 USD [141% of -10700 USD]
Liabilities:US:Chase:Slate || 293.09 USD
----------------------------------++------------------------------------
|| -3599.95 USD
```
All the accounts that were rolled up into `<unbudgeted>` category are now shown with their original name, but budgeted accounts are still rolled up. It
is easy to see now that we forgot taxes. Lets add them to our budget:
```journal
~ monthly from 2013/01
Expenses:Food 500 USD
Expenses:Health 200 USD
Expenses:Home 2545 USD
Expenses:Transport 120 USD
Expenses:Taxes 4300 USD ;; Taken from monthly average report
Income:US -10700 USD
Assets:US
```
Lets try again for a couple of month with this updated budget:
```shell
$ hledger balance -f bcexample.hledger -f budget.journal -M -b 2013-01 -e 2013-04 --budget cur:USD
Balance changes in 2013q1:
|| 2013/01 2013/02 2013/03
==========================++===========================================================================================================
<unbudgeted>:Expenses || 4.00 USD 12.95 USD 39.80 USD
<unbudgeted>:Liabilities || 293.09 USD -147.51 USD -66.01 USD
Assets:US || 1893.32 USD [62% of 3035 USD] 2929.77 USD [97% of 3035 USD] -3898.89 USD [-128% of 3035 USD]
Expenses:Food || 396.46 USD [79% of 500 USD] 481.48 USD [96% of 500 USD] 603.32 USD [121% of 500 USD]
Expenses:Health || 290.70 USD [145% of 200 USD] 193.80 USD [97% of 200 USD] 193.80 USD [97% of 200 USD]
Expenses:Home || 2544.98 USD [100% of 2545 USD] 2545.02 USD [100% of 2545 USD] 2544.97 USD [100% of 2545 USD]
Expenses:Taxes || 5976.60 USD [139% of 4300 USD] 3984.40 USD [93% of 4300 USD] 4901.83 USD [114% of 4300 USD]
Expenses:Transport || 120.00 USD [100% of 120 USD] 120.00 USD [100% of 120 USD] 120.00 USD [100% of 120 USD]
Income:US || -15119.10 USD [141% of -10700 USD] -10331.21 USD [97% of -10700 USD] -11079.40 USD [104% of -10700 USD]
--------------------------++-----------------------------------------------------------------------------------------------------------
|| -3599.95 USD -211.30 USD -6640.58 USD
```
Now unbudgeted amounts are much smaller and some of them could be dismissed as noise, and we can see that budget created is actually
close enough to the real numbers, meaning that they are usually close to average that we put in our budget.
## Envelope budget
Budget report that we have used so far assumes that any unused budget amount for a given (monthly) period will not contribute to the
budget of the next period. Alternative popular "envelope budget" strategy assumes that you put a certain amount of money into an envelope
each month, and any unused amount stays there for future expenses. This is easy to simulate by adding --cumulative switch. Lets redo
the last report with it:
```shell
$ hledger balance -f bcexample.hledger -f budget.journal -M -b 2013-01 -e 2013-04 --cumulative --budget cur:USD
Ending balances (cumulative) in 2013q1:
|| 2013/01/31 2013/02/28 2013/03/31
==========================++============================================================================================================
<unbudgeted>:Expenses || 4.00 USD 16.95 USD 56.75 USD
<unbudgeted>:Liabilities || 293.09 USD 145.58 USD 79.57 USD
Assets:US || 1893.32 USD [62% of 3035 USD] 4823.09 USD [79% of 6070 USD] 924.20 USD [10% of 9105 USD]
Expenses:Food || 396.46 USD [79% of 500 USD] 877.94 USD [88% of 1000 USD] 1481.26 USD [99% of 1500 USD]
Expenses:Health || 290.70 USD [145% of 200 USD] 484.50 USD [121% of 400 USD] 678.30 USD [113% of 600 USD]
Expenses:Home || 2544.98 USD [100% of 2545 USD] 5090.00 USD [100% of 5090 USD] 7634.97 USD [100% of 7635 USD]
Expenses:Taxes || 5976.60 USD [139% of 4300 USD] 9961.00 USD [116% of 8600 USD] 14862.83 USD [115% of 12900 USD]
Expenses:Transport || 120.00 USD [100% of 120 USD] 240.00 USD [100% of 240 USD] 360.00 USD [100% of 360 USD]
Income:US || -15119.10 USD [141% of -10700 USD] -25450.31 USD [119% of -21400 USD] -36529.71 USD [114% of -32100 USD]
--------------------------++------------------------------------------------------------------------------------------------------------
|| -3599.95 USD -3811.25 USD -10451.83 USD
```
If you look at Expenses:Food category, you will see that every month budget is increased by 500 USD, and by March total amount budgeted
is 1500 USD, of which 1481.26 USD is spent. If you look back at the previous non-cumulative monthly budget report, you will see that in March food expenses
were 121% of the budgeted amount, but cumulative report shows that taking into account budget carry-over from Jan and Feb we are well withing planned numbers.
# Forecasting
Budget transaction that was created could be used to predict what would be our financial situation in the future. If you add `--forecast` switch, you will
see how budgeted income and expense affects you past the last transaction in the journal. Since journal ends in Oct 2014, lets see next two month:
```shell
$ hledger balance -f bcexample.hledger -f budget.journal -M -b 2014-10 -e 2015 --forecast cur:USD
Balance changes in 2014q4:
|| 2014/10 2014/11 2014/12
====================================++======================================
Assets:US || 0 3035 USD 3035 USD
Assets:US:BofA:Checking || -2453.40 USD 0 0
Assets:US:ETrade:Cash || 5000.00 USD 0 0
Expenses:Financial:Fees || 4.00 USD 0 0
Expenses:Food || 0 500 USD 500 USD
Expenses:Food:Restaurant || 83.00 USD 0 0
Expenses:Health || 0 200 USD 200 USD
Expenses:Health:Dental:Insurance || 2.90 USD 0 0
Expenses:Health:Life:GroupTermLife || 24.32 USD 0 0
Expenses:Health:Medical:Insurance || 27.38 USD 0 0
Expenses:Health:Vision:Insurance || 42.30 USD 0 0
Expenses:Home || 0 2545 USD 2545 USD
Expenses:Taxes || 0 4300 USD 4300 USD
Expenses:Taxes:Y2014:US:CityNYC || 174.92 USD 0 0
Expenses:Taxes:Y2014:US:Federal || 1062.92 USD 0 0
Expenses:Taxes:Y2014:US:Medicare || 106.62 USD 0 0
Expenses:Taxes:Y2014:US:SDI || 1.12 USD 0 0
Expenses:Taxes:Y2014:US:SocSec || 281.54 USD 0 0
Expenses:Taxes:Y2014:US:State || 365.08 USD 0 0
Expenses:Transport || 0 120 USD 120 USD
Expenses:Transport:Tram || 120.00 USD 0 0
Income:US || 0 -10700 USD -10700 USD
Income:US:Hoogle:GroupTermLife || -24.32 USD 0 0
Income:US:Hoogle:Salary || -4615.38 USD 0 0
Liabilities:US:Chase:Slate || -203.00 USD 0 0
------------------------------------++--------------------------------------
|| 0 0 0
```
Note that this time there is no roll-up of accounts. Unlike `--budget`, which could be used with `balance` command only, `--forecast`
could be used with any report. Forecast transactions would be added to your real journal and would appear in the report you requested as
if you have entered them on the scheduled dates.
Since quite a lot of accounts do not have any budgeted transactions, lets limit the depth of the report to avoid seeing lots of zeroes:
```shell
$ hledger balance -f bcexample.hledger -f budget.journal -M -b 2014-10 -e 2015 --forecast cur:USD --depth 2
Balance changes in 2014q4:
|| 2014/10 2014/11 2014/12
====================++======================================
Assets:US || 2546.60 USD 3035 USD 3035 USD
Expenses:Financial || 4.00 USD 0 0
Expenses:Food || 83.00 USD 500 USD 500 USD
Expenses:Health || 96.90 USD 200 USD 200 USD
Expenses:Home || 0 2545 USD 2545 USD
Expenses:Taxes || 1992.20 USD 4300 USD 4300 USD
Expenses:Transport || 120.00 USD 120 USD 120 USD
Income:US || -4639.70 USD -10700 USD -10700 USD
Liabilities:US || -203.00 USD 0 0
--------------------++--------------------------------------
|| 0 0 0
```
As you can see, we should expect 3035 USD to be added into Assets:US each month. It is quite easy to see how overal amount of Assets will change with time if you use
`--cumulative` switch:
```shell
$ hledger balance -f bcexample.hledger -f budget.journal -M -b 2014-10 -e 2015 --forecast cur:USD --depth 2 --cumulative
Ending balances (cumulative) in 2014q4:
|| 2014/10/31 2014/11/30 2014/12/31
====================++============================================
Assets:US || 2546.60 USD 5581.60 USD 8616.60 USD
Expenses:Financial || 4.00 USD 4.00 USD 4.00 USD
Expenses:Food || 83.00 USD 583.00 USD 1083.00 USD
Expenses:Health || 96.90 USD 296.90 USD 496.90 USD
Expenses:Home || 0 2545 USD 5090 USD
Expenses:Taxes || 1992.20 USD 6292.20 USD 10592.20 USD
Expenses:Transport || 120.00 USD 240.00 USD 360.00 USD
Income:US || -4639.70 USD -15339.70 USD -26039.70 USD
Liabilities:US || -203.00 USD -203.00 USD -203.00 USD
--------------------++--------------------------------------------
|| 0 0 0
```
According to forecast, assets are expected to grow to 8600+ USD by the end of 2014. However, our forecast does not include a couple
of big one-off year end expenses. First, we plan to buy prize turkey for the Christmas table every year from 2014, spending up to 500 USD on it.
And on 17th Nov 2014 we would celebrate birthday of significant other, spending up to 6000 USD in a fancy restaurant:
```journal
~ every 20th Dec from 2014
Expenses:Food 500 USD ; Prize turkey, the biggest of the big
Assets:US
~ 2014/11/17
Assets:US
Expenses:Food 6000 USD ; Birthday, lots of guests
```
Note that turkey transaction is not entered as "yearly from 2014/12/20", since yearly/quarterly/monthy/weekly periodic expressions always generate
entries at the first day of the calendar year/quarter/month/week. Thus "monthly from 2014/12" will occur on 2014/12/01, 2015/01/01, ..., whereas
"every 20th of month from 2014/12" will happen on 2014/12/20, 2015/12/20, etc.
With latest additions forecast now looks like this:
```shell
hledger balance -f bcexample.hledger -f budget.journal -M -b 2014-10 -e 2015 --forecast cur:USD --depth 2 --cumulative
Ending balances (cumulative) in 2014q4:
|| 2014/10/31 2014/11/30 2014/12/31
====================++============================================
Assets:US || 2546.60 USD -418.40 USD 2116.60 USD
Expenses:Financial || 4.00 USD 4.00 USD 4.00 USD
Expenses:Food || 83.00 USD 6583.00 USD 7583.00 USD
Expenses:Health || 96.90 USD 296.90 USD 496.90 USD
Expenses:Home || 0 2545 USD 5090 USD
Expenses:Taxes || 1992.20 USD 6292.20 USD 10592.20 USD
Expenses:Transport || 120.00 USD 240.00 USD 360.00 USD
Income:US || -4639.70 USD -15339.70 USD -26039.70 USD
Liabilities:US || -203.00 USD -203.00 USD -203.00 USD
--------------------++--------------------------------------------
|| 0 0 0
```
It is easy to see that in Nov 2014 we will run out of Assets. Using `register` we can figure out when or why it would happen:
```shell
$ hledger register -f bcexample.hledger -f budget.journal -b 2014-10 -e 2014-12 --forecast cur:USD Assets
2014/10/04 "BANK FEES" | "Monthly bank fee" Assets:US:BofA:Checking -4.00 USD -4.00 USD
2014/10/09 "Hoogle" | "Payroll" Assets:US:BofA:Checking 2550.60 USD 2546.60 USD
2014/10/10 "Transfering accumulated savings to o.. Assets:US:BofA:Checking -5000.00 USD -2453.40 USD
Assets:US:ETrade:Cash 5000.00 USD 2546.60 USD
2014/11/01 Forecast transaction Assets:US 3035 USD 5581.60 USD
2014/11/17 Forecast transaction Assets:US -6000 USD -418.40 USD
```
It is 6000 USD planned for birthday! Something will have to be done about the birthday plans.

78
tests/budget/auto.test Normal file
View File

@ -0,0 +1,78 @@
# Add proportional income tax (from documentation)
hledger print -f- --auto
<<<
2016/1/1 paycheck
income:remuneration $-100
income:donations $-15
assets:bank
2016/1/1 withdraw
assets:cash $20
assets:bank
= ^income
(liabilities:tax) *.33 ; income tax
>>>
2016/01/01 paycheck
income:remuneration $-100
income:donations $-15
assets:bank
(liabilities:tax) $-33 ; income tax
(liabilities:tax) $-5 ; income tax
2016/01/01 withdraw
assets:cash $20
assets:bank
>>>2
>>>=0
hledger register -f- --auto
<<<
2016/1/1 paycheck
income:remuneration $-100
income:donations $-15
assets:bank
2016/1/1 withdraw
assets:cash $20
assets:bank
= ^income
(liabilities:tax) *.33 ; income tax
>>>
2016/01/01 paycheck income:remuneration $-100 $-100
income:donations $-15 $-115
assets:bank $115 0
(liabilities:tax) $-33 $-33
(liabilities:tax) $-5 $-38
2016/01/01 withdraw assets:cash $20 $-18
assets:bank $-20 $-38
>>>2
>>>=0
hledger balance -f- --auto
<<<
2016/1/1 paycheck
income:remuneration $-100
income:donations $-15
assets:bank
2016/1/1 withdraw
assets:cash $20
assets:bank
= ^income
(liabilities:tax) *.33 ; income tax
>>>
$115 assets
$95 bank
$20 cash
$-115 income
$-15 donations
$-100 remuneration
$-38 liabilities:tax
--------------------
$-38
>>>2
>>>=0

92
tests/budget/budget.test Normal file
View File

@ -0,0 +1,92 @@
# Test --budget switch
hledger bal -D -b 2016-12-01 -e 2016-12-04 -f - --budget
<<<
2016/12/01
expenses:food $10
assets:cash
2016/12/02
expenses:food $9
assets:cash
2016/12/03
expenses:food $11
assets:cash
2016/12/02
expenses:leisure $5
assets:cash
2016/12/03
expenses:movies $25
assets:cash
2016/12/03
expenses:cab $15
assets:cash
~ daily from 2016/1/1
expenses:food $10
expenses:leisure $15
assets:cash
>>>
Balance changes in 2016/12/01-2016/12/03:
|| 2016/12/01 2016/12/02 2016/12/03
=======================++=============================================================
<unbudgeted>:expenses || 0 0 $40
assets:cash || $-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 [$15] $5 [33% of $15] 0 [$15]
-----------------------++-------------------------------------------------------------
|| 0 0 0
>>>2
>>>=0
# --show-unbudgeted
hledger bal -D -b 2016-12-01 -e 2016-12-04 -f - --budget --show-unbudgeted
<<<
2016/12/01
expenses:food $10
assets:cash
2016/12/02
expenses:food $9
assets:cash
2016/12/03
expenses:food $11
assets:cash
2016/12/02
expenses:leisure $5
assets:cash
2016/12/03
expenses:movies $25
assets:cash
2016/12/03
expenses:cab $15
assets:cash
~ daily from 2016/1/1
expenses:food $10
expenses:leisure $15
assets:cash
>>>
Balance changes 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:cab || 0 0 $15
expenses:food || $10 [100% of $10] $9 [90% of $10] $11 [110% of $10]
expenses:leisure || 0 [$15] $5 [33% of $15] 0 [$15]
expenses:movies || 0 0 $25
------------------++-------------------------------------------------------------
|| 0 0 0
>>>2
>>>=0

102
tests/budget/forecast.test Normal file
View File

@ -0,0 +1,102 @@
# Test --forecast switch
hledger bal -M -b 2016-11 -e 2017-02 -f - --forecast
<<<
2016/12/31
expenses:housing $600
assets:cash
~ monthly from 2016/1
income $-1000
expenses:food $20
expenses:leisure $15
expenses:grocery $30
assets:cash
>>>
Balance changes in 2016/12/01-2017/01/31:
|| 2016/12 2017/01
==================++==================
assets:cash || $-600 $935
expenses:food || 0 $20
expenses:grocery || 0 $30
expenses:housing || $600 0
expenses:leisure || 0 $15
income || 0 $-1000
------------------++------------------
|| 0 0
>>>2
>>>=0
hledger print -b 2016-11 -e 2017-02 -f - --forecast
<<<
2016/12/31
expenses:housing $600
assets:cash
~ monthly from 2016/1
income $-1000
expenses:food $20
expenses:leisure $15
expenses:grocery $30
assets:cash
>>>
2016/12/31
expenses:housing $600
assets:cash
2017/01/01 Forecast transaction
income $-1000
expenses:food $20
expenses:leisure $15
expenses:grocery $30
assets:cash
>>>2
>>>=0
hledger register -b 2016-11 -e 2017-02 -f - --forecast
<<<
2016/12/31
expenses:housing $600
assets:cash
~ monthly from 2016/1
income $-1000
expenses:food $20
expenses:leisure $15
expenses:grocery $30
assets:cash
>>>
2016/12/31 expenses:housing $600 $600
assets:cash $-600 0
2017/01/01 Forecast transact.. income $-1000 $-1000
expenses:food $20 $-980
expenses:leisure $15 $-965
expenses:grocery $30 $-935
assets:cash $935 0
>>>2
>>>=0
# Check that --forecast generates transactions only after last transaction in journal
hledger register -b 2015-12 -e 2017-02 -f - assets:cash --forecast
<<<
2016/01/01
expenses:fun $10 ; more fireworks
assets:cash
2016/12/02
expenses:housing $600
assets:cash
~ yearly from 2016
income $-10000 ; bonus
assets:cash
>>>
2016/01/01 assets:cash $-10 $-10
2016/12/02 assets:cash $-600 $-610
2017/01/01 Forecast transact.. assets:cash $10000 $9390
>>>2
>>>=0