imp: close: more useful defaults, retain/migrate/open modes
This commit is contained in:
parent
173f61bee0
commit
2eaab54426
@ -1,5 +1,6 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# LANGUAGE MultiWayIf #-}
|
||||
|
||||
module Hledger.Cli.Commands.Close (
|
||||
closemode
|
||||
@ -20,92 +21,75 @@ import System.Console.CmdArgs.Explicit as C
|
||||
import Hledger
|
||||
import Hledger.Cli.CliOptions
|
||||
|
||||
defclosingdesc = "closing balances"
|
||||
defopeningdesc = "opening balances"
|
||||
defclosingacct = "equity:opening/closing balances"
|
||||
defopeningacct = defclosingacct
|
||||
defretaindesc = "retain earnings"
|
||||
defclosedesc = "closing balances"
|
||||
defopendesc = "opening balances"
|
||||
defretainacct = "equity:retained earnings"
|
||||
defcloseacct = "equity:opening/closing balances"
|
||||
|
||||
closemode = hledgerCommandMode
|
||||
$(embedFileRelative "Hledger/Cli/Commands/Close.txt")
|
||||
[flagNone ["close"] (setboolopt "close") "show just closing transaction"
|
||||
,flagNone ["open"] (setboolopt "open") "show just opening transaction"
|
||||
,flagReq ["close-desc"] (\s opts -> Right $ setopt "close-desc" s opts) "DESC" ("description for closing transaction (default: "++defclosingdesc++")")
|
||||
,flagReq ["open-desc"] (\s opts -> Right $ setopt "open-desc" s opts) "DESC" ("description for opening transaction (default: "++defopeningdesc++")")
|
||||
,flagReq ["close-acct"] (\s opts -> Right $ setopt "close-acct" s opts) "ACCT" ("account to transfer closing balances to (default: "++defclosingacct++")")
|
||||
,flagReq ["open-acct"] (\s opts -> Right $ setopt "open-acct" s opts) "ACCT" ("account to transfer opening balances from (default: "++defopeningacct++")")
|
||||
[flagNone ["retain"] (setboolopt "retain") "show RX retain earnings transaction"
|
||||
,flagNone ["migrate"] (setboolopt "migrate") "show ALE closing/opening transactions"
|
||||
,flagNone ["open"] (setboolopt "open") "show ALE opening transaction"
|
||||
,flagReq ["close-desc"] (\s opts -> Right $ setopt "close-desc" s opts) "DESC" ("description for closing transaction (default: "++defclosedesc++")")
|
||||
,flagReq ["open-desc"] (\s opts -> Right $ setopt "open-desc" s opts) "DESC" ("description for opening transaction (default: "++defopendesc++")")
|
||||
,flagReq ["close-acct"] (\s opts -> Right $ setopt "close-acct" s opts) "ACCT" ("account to transfer closing balances to (default: "++defcloseacct++")")
|
||||
,flagNone ["explicit","x"] (setboolopt "explicit") "show all amounts explicitly"
|
||||
,flagNone ["interleaved"] (setboolopt "interleaved") "keep equity and non-equity postings adjacent"
|
||||
,flagNone ["interleaved"] (setboolopt "interleaved") "keep source and destination postings adjacent"
|
||||
,flagNone ["show-costs"] (setboolopt "show-costs") "keep balances with different costs separate"
|
||||
]
|
||||
[generalflagsgroup1]
|
||||
(hiddenflags ++
|
||||
-- old close flags for compatibility, hidden
|
||||
[flagNone ["closing"] (setboolopt "close") "old spelling of --close"
|
||||
,flagNone ["opening"] (setboolopt "open") "old spelling of --open"
|
||||
,flagReq ["close-to"] (\s opts -> Right $ setopt "close-acct" s opts) "ACCT" ("old spelling of --close-acct")
|
||||
,flagReq ["open-from"] (\s opts -> Right $ setopt "open-acct" s opts) "ACCT" ("old spelling of --open-acct")
|
||||
])
|
||||
(hiddenflags
|
||||
-- any old command flags for compatibility, hidden
|
||||
-- ++ []
|
||||
)
|
||||
([], Just $ argsFlag "[QUERY]")
|
||||
|
||||
-- debugger, beware: close is incredibly devious. simple rules combine to make a horrid maze.
|
||||
-- tests are in hledger/test/close.test.
|
||||
close copts@CliOpts{rawopts_=rawopts, reportspec_=rspec'} j = do
|
||||
-- Debugger, beware: close is incredibly devious; simple rules combine to make a horrid maze.
|
||||
-- Tests are in hledger/test/close.test.
|
||||
-- This code is also used by the close command.
|
||||
close copts@CliOpts{rawopts_=rawopts, reportspec_=rspec0} j = do
|
||||
let
|
||||
-- show opening entry, closing entry, or (default) both ?
|
||||
(opening, closing) =
|
||||
case (boolopt "open" rawopts, boolopt "close" rawopts) of
|
||||
(False, False) -> (True, True)
|
||||
(o, c) -> (o, c)
|
||||
(close_, open_, defclosedesc_, defopendesc_, defcloseacct_, defacctsq_) = if
|
||||
| boolopt "retain" rawopts -> (True, False, defretaindesc, undefined, defretainacct, Type [Revenue, Expense])
|
||||
| boolopt "migrate" rawopts -> (True, True, defclosedesc, defopendesc, defcloseacct, Type [Asset, Liability, Equity])
|
||||
| boolopt "open" rawopts -> (False, True, undefined, defopendesc, defcloseacct, Type [Asset, Liability, Equity])
|
||||
| otherwise -> (True, False, defclosedesc, undefined, defcloseacct, Any)
|
||||
|
||||
-- descriptions to use for the closing/opening transactions
|
||||
closingdesc = maybe (T.pack defclosingdesc) T.pack $ maybestringopt "close-desc" rawopts
|
||||
openingdesc = maybe (T.pack defopeningdesc) T.pack $ maybestringopt "open-desc" rawopts
|
||||
closedesc = T.pack $ fromMaybe defclosedesc_ $ maybestringopt "close-desc" rawopts
|
||||
opendesc = T.pack $ fromMaybe defopendesc_ $ maybestringopt "open-desc" rawopts
|
||||
closeacct = T.pack $ fromMaybe defcloseacct_ $ maybestringopt "close-acct" rawopts
|
||||
openacct = closeacct
|
||||
|
||||
-- accounts to close to and open from
|
||||
-- if only one is specified, it is used for both
|
||||
(closingacct, openingacct) =
|
||||
let (mc, mo) =
|
||||
(T.pack <$> maybestringopt "close-acct" rawopts, T.pack <$> maybestringopt "open-acct" rawopts)
|
||||
in case (mc, mo) of
|
||||
(Just c, Just o) -> (c, o)
|
||||
(Just c, Nothing) -> (c, c)
|
||||
(Nothing, Just o) -> (o, o)
|
||||
(Nothing, Nothing) -> (T.pack defclosingacct, T.pack defopeningacct)
|
||||
|
||||
ropts = (_rsReportOpts rspec'){balanceaccum_=Historical, accountlistmode_=ALFlat}
|
||||
rspec = setDefaultConversionOp NoConversionOp rspec'{_rsReportOpts=ropts}
|
||||
ropts = (_rsReportOpts rspec0){balanceaccum_=Historical, accountlistmode_=ALFlat}
|
||||
rspec1 = setDefaultConversionOp NoConversionOp rspec0{_rsReportOpts=ropts}
|
||||
|
||||
-- dates of the closing and opening transactions
|
||||
--
|
||||
-- Close.md:
|
||||
-- "The default closing date is yesterday, or the journal's end date, whichever is later.
|
||||
--
|
||||
-- Unless you are running `close` on exactly the first day of the new period,
|
||||
-- you'll want to override the closing date.
|
||||
-- This is done by specifying a [report period](#report-start--end-date),
|
||||
-- You can change this by specifying a [report end date](#report-start--end-date),
|
||||
-- where "last day of the report period" will be the closing date.
|
||||
-- The opening date is always the following day.
|
||||
-- So to close on 2020-12-31 and open on 2021-01-01, any of these work
|
||||
--
|
||||
-- - `-p 2020`
|
||||
-- - `date:2020`
|
||||
-- - `-e 2021-01-01` (remember `-e` specifies an exclusive report end date)
|
||||
-- - `-e 2021`"
|
||||
--
|
||||
q = _rsQuery rspec
|
||||
yesterday = addDays (-1) $ _rsDay rspec
|
||||
-- (Only the end date matters; a report start date will be ignored.)
|
||||
-- The opening date is always the day after the closing date."
|
||||
argsq = _rsQuery rspec1
|
||||
yesterday = addDays (-1) $ _rsDay rspec1
|
||||
yesterdayorjournalend = case journalLastDay False j of
|
||||
Just journalend -> max yesterday journalend
|
||||
Nothing -> yesterday
|
||||
mreportlastday = addDays (-1) <$> queryEndDate False q
|
||||
closingdate = fromMaybe yesterdayorjournalend mreportlastday
|
||||
openingdate = addDays 1 closingdate
|
||||
mreportlastday = addDays (-1) <$> queryEndDate False argsq
|
||||
closedate = fromMaybe yesterdayorjournalend mreportlastday
|
||||
opendate = addDays 1 closedate
|
||||
|
||||
-- should we show the amount(s) on the equity posting(s) ?
|
||||
explicit = boolopt "explicit" rawopts || copts ^. infer_costs
|
||||
|
||||
-- the balances to close
|
||||
(acctbals',_) = balanceReport rspec j
|
||||
argsacctq = filterQuery (\q -> queryIsAcct q || queryIsType q) argsq
|
||||
q2 = if queryIsNull argsacctq then And [argsq, defacctsq_] else argsq
|
||||
rspec2 = rspec1{_rsQuery=q2}
|
||||
(acctbals',_) = balanceReport rspec2 j
|
||||
acctbals = map (\(a,_,_,b) -> (a, if show_costs_ ropts then b else mixedAmountStripPrices b)) acctbals'
|
||||
totalamt = maSum $ map snd acctbals
|
||||
|
||||
@ -117,8 +101,8 @@ close copts@CliOpts{rawopts_=rawopts, reportspec_=rspec'} j = do
|
||||
interleaved = boolopt "interleaved" rawopts
|
||||
|
||||
-- the closing transaction
|
||||
closingtxn = nulltransaction{tdate=closingdate, tdescription=closingdesc, tpostings=closingps}
|
||||
closingps =
|
||||
closetxn = nulltransaction{tdate=closedate, tdescription=closedesc, tpostings=closeps}
|
||||
closeps =
|
||||
concat [
|
||||
posting{paccount = a
|
||||
,pamount = mixedAmount . precise $ negate b
|
||||
@ -131,7 +115,7 @@ close copts@CliOpts{rawopts_=rawopts, reportspec_=rspec'} j = do
|
||||
}
|
||||
|
||||
-- maybe an interleaved posting transferring this balance to equity
|
||||
: [posting{paccount=closingacct, pamount=mixedAmount $ precise b} | interleaved]
|
||||
: [posting{paccount=closeacct, pamount=mixedAmount $ precise b} | interleaved]
|
||||
|
||||
| -- get the balances for each commodity and transaction price
|
||||
(a,mb) <- acctbals
|
||||
@ -144,11 +128,11 @@ close copts@CliOpts{rawopts_=rawopts, reportspec_=rspec'} j = do
|
||||
|
||||
-- or a final multicommodity posting transferring all balances to equity
|
||||
-- (print will show this as multiple single-commodity postings)
|
||||
++ [posting{paccount=closingacct, pamount=if explicit then mixedAmountSetFullPrecision totalamt else missingmixedamt} | not interleaved]
|
||||
++ [posting{paccount=closeacct, pamount=if explicit then mixedAmountSetFullPrecision totalamt else missingmixedamt} | not interleaved]
|
||||
|
||||
-- the opening transaction
|
||||
openingtxn = nulltransaction{tdate=openingdate, tdescription=openingdesc, tpostings=openingps}
|
||||
openingps =
|
||||
opentxn = nulltransaction{tdate=opendate, tdescription=opendesc, tpostings=openps}
|
||||
openps =
|
||||
concat [
|
||||
posting{paccount = a
|
||||
,pamount = mixedAmount $ precise b
|
||||
@ -157,7 +141,7 @@ close copts@CliOpts{rawopts_=rawopts, reportspec_=rspec'} j = do
|
||||
Just s -> Just nullassertion{baamount=precise s{aprice=Nothing}}
|
||||
Nothing -> Nothing
|
||||
}
|
||||
: [posting{paccount=openingacct, pamount=mixedAmount . precise $ negate b} | interleaved]
|
||||
: [posting{paccount=openacct, pamount=mixedAmount . precise $ negate b} | interleaved]
|
||||
|
||||
| (a,mb) <- acctbals
|
||||
, let bs0 = amounts mb
|
||||
@ -167,8 +151,8 @@ close copts@CliOpts{rawopts_=rawopts, reportspec_=rspec'} j = do
|
||||
, let commoditysum = (sum bs1)]
|
||||
, (b, mcommoditysum) <- bs2
|
||||
]
|
||||
++ [posting{paccount=openingacct, pamount=if explicit then mixedAmountSetFullPrecision (maNegate totalamt) else missingmixedamt} | not interleaved]
|
||||
++ [posting{paccount=openacct, pamount=if explicit then mixedAmountSetFullPrecision (maNegate totalamt) else missingmixedamt} | not interleaved]
|
||||
|
||||
-- print them
|
||||
when closing . T.putStr $ showTransaction closingtxn
|
||||
when opening . T.putStr $ showTransaction openingtxn
|
||||
when close_ . T.putStr $ showTransaction closetxn
|
||||
when open_ . T.putStr $ showTransaction opentxn
|
||||
|
||||
@ -1,211 +1,195 @@
|
||||
## close
|
||||
|
||||
(equity)
|
||||
`close [--retain | --migrate | --open] [QUERY]`
|
||||
|
||||
Prints a sample "closing" transaction bringing specified account balances to zero,
|
||||
and an inverse "opening" transaction restoring the same account balances.
|
||||
By default:
|
||||
prints a transaction that zeroes out ("closes") all accounts,
|
||||
transferring their balances to an equity account.
|
||||
Query arguments can be added to override the accounts selection.
|
||||
Three other modes are supported:
|
||||
|
||||
If like most people you split your journal files by time, eg by year:
|
||||
at the end of the year you can use this command to "close out" your
|
||||
asset and liability (and perhaps equity) balances in the old file, and reinitialise them in the new file.
|
||||
This helps ensure that report balances remain correct whether you are including old files or not.
|
||||
(Because all closing/opening transactions except the very first will cancel out - see example below.)
|
||||
`--retain`:
|
||||
prints a transaction closing revenue and expense balances.
|
||||
This is traditionally done by businesses at the end of each accounting period;
|
||||
it is less necessary in personal and computer-based accounting,
|
||||
but it can help balance the accounting equation A=L+E.
|
||||
|
||||
Some people also use this command to close out revenue and expense balances at the end of an accounting period.
|
||||
This properly records the period's profit/loss as "retained earnings" (part of equity),
|
||||
and allows the accounting equation (A-L=E) to balance,
|
||||
which you could then check by the [bse](#balancesheetequity) report's zero total.
|
||||
`--migrate`:
|
||||
prints a transaction to close asset, liability and most equity balances,
|
||||
and another transaction to re-open them.
|
||||
This can be useful when starting a new file (for performance or data protection).
|
||||
Adding the closing transaction to the old file allows old and new files to be combined.
|
||||
|
||||
`--open`:
|
||||
as above, but prints just the opening transaction.
|
||||
This can be useful for starting a new file, leaving the old file unchanged.
|
||||
Similar to Ledger's equity command.
|
||||
|
||||
_FLAGS
|
||||
|
||||
You can print just the closing transaction by using the `--close` flag,
|
||||
or just the opening transaction with the `--open` flag.
|
||||
You can change the equity account name with `--close-acct ACCT`.
|
||||
It defaults to `equity:retained earnings` with `--retain`,
|
||||
or `equity:opening/closing balances` otherwise.
|
||||
|
||||
Their descriptions are `closing balances` and `opening balances` by default;
|
||||
you can customise these with the `--close-desc` and `--open-desc` options.
|
||||
You can change the transaction description(s)
|
||||
with `--close-desc 'DESC'` and `--open-desc 'DESC'`.
|
||||
It defaults to `retain earnings` with `--retain`,
|
||||
or `closing balances` and `opening balances` otherwise.
|
||||
|
||||
Just one balancing equity posting is used by default, with the amount left implicit.
|
||||
The default account name is `equity:opening/closing balances`.
|
||||
You can customise the account name(s) with `--close-acct` and `--open-acct`.
|
||||
(If you specify only one of these, it will be used for both.)
|
||||
Just one posting to the equity account will be used by default,
|
||||
with an implicit amount.
|
||||
|
||||
With `--x/--explicit`, the equity posting's amount will be shown explicitly,
|
||||
and if it involves multiple commodities, there will be a separate equity posting for each commodity
|
||||
(as in the print command).
|
||||
With `--x/--explicit` the amount will be shown explicitly,
|
||||
and if it involves multiple commodities, a separate posting
|
||||
will be generated for each commodity.
|
||||
|
||||
With `--interleaved`, each equity posting is shown next to the posting it balances
|
||||
(good for troubleshooting).
|
||||
With `--interleaved`, each equity posting is shown next to the
|
||||
corresponding source/destination posting.
|
||||
|
||||
The default closing date is yesterday or the journal's end date, whichever is later.
|
||||
You can change this by specifying a [report end date](#report-start--end-date);
|
||||
the last day of the report period will be the closing date.
|
||||
Eg `-e 2022` means "close on 2022-12-31".
|
||||
|
||||
The default closing date is yesterday, or the journal's end date, whichever is later.
|
||||
You can change this by specifying a [report end date](#report-start--end-date);
|
||||
(The report start date does not matter.)
|
||||
The last day of the report period will be the closing date;
|
||||
eg `-e 2022` means "close on 2022-12-31".
|
||||
The opening date is always the day after the closing date.
|
||||
|
||||
### close and costs
|
||||
|
||||
Costs are ignored (and discarded) by closing/opening transactions, by default.
|
||||
With `--show-costs`, they are preserved;
|
||||
there will be a separate equity posting for each cost in each commodity.
|
||||
This means `balance -B` reports will look the same after the transition.
|
||||
Note if you have many foreign currency or investment transactions,
|
||||
this will generate very large journal entries.
|
||||
|
||||
### close date
|
||||
|
||||
The default closing date is yesterday, or the journal's end date, whichever is later.
|
||||
|
||||
Unless you are running `close` on exactly the first day of the new period,
|
||||
you'll want to override the closing date.
|
||||
This is done by specifying a [report end date](#report-start--end-date),
|
||||
where "last day of the report period" will be the closing date.
|
||||
The opening date is always the following day.
|
||||
So to close on (end of) 2020-12-31 and open on (start of) 2021-01-01, any of these will work:
|
||||
|
||||
| end date argument | explanation
|
||||
|-------------------|----------------------------------------------------------------------
|
||||
| `-e 2021-01-01` | [end dates](#report-start--end-date) are exclusive
|
||||
| `-e 2021` | equivalent, per [smart dates](#smart-dates)
|
||||
| `-p 2020` | equivalent, the [period's](#period-expressions) begin date is ignored
|
||||
| `date:2020` | equivalent [query](#queries)
|
||||
|
||||
### Example: close asset/liability accounts for file transition
|
||||
|
||||
Carrying asset/liability balances from 2020.journal into a new file for 2021:
|
||||
|
||||
```shell
|
||||
$ hledger close -f 2020.journal -p 2020 assets liabilities
|
||||
# copy/paste the closing transaction to the end of 2020.journal
|
||||
# copy/paste the opening transaction to the start of 2021.journal
|
||||
```
|
||||
|
||||
Or:
|
||||
|
||||
```shell
|
||||
$ hledger close -f 2020.journal -p 2020 assets liabilities --open >> 2021.journal # add 2021's first transaction
|
||||
$ hledger close -f 2020.journal -p 2020 assets liabilities --close >> 2020.journal # add 2020's last transaction
|
||||
```
|
||||
|
||||
Now,
|
||||
|
||||
```shell
|
||||
$ hledger bs -f 2021.journal # just new file - balances correct
|
||||
$ hledger bs -f 2020.journal -f 2021.journal # old and new files - balances correct
|
||||
$ hledger bs -f 2020.journal # just old files - balances are zero ?
|
||||
# (exclude final closing txn, see below)
|
||||
```
|
||||
|
||||
### Hiding opening/closing transactions
|
||||
|
||||
Although the closing/opening transactions cancel out, they will be visible in reports like `print` and `register`,
|
||||
creating some visual clutter. You can exclude them all with a query, like:
|
||||
|
||||
```shell
|
||||
$ hledger print not:desc:'opening|closing' # less typing
|
||||
$ hledger print not:'equity:opening/closing balances' # more precise
|
||||
```
|
||||
|
||||
But when reporting on multiple files, this can get a bit tricky;
|
||||
you may need to keep the earliest opening balances, for a historical register report;
|
||||
or you may need to suppress a closing transaction, to see year-end balances.
|
||||
If you find yourself needing more precise [queries](#queries), here's one solution:
|
||||
add more easily-matched tags to opening/closing transactions, like this:
|
||||
|
||||
```journal
|
||||
; 2019.journal
|
||||
2019-01-01 opening balances ; earliest opening txn, no tag here
|
||||
...
|
||||
2019-12-31 closing balances ; clopen:2020
|
||||
...
|
||||
```
|
||||
```journal
|
||||
; 2020.journal
|
||||
2020-01-01 opening balances ; clopen:2020
|
||||
...
|
||||
2020-12-31 closing balances ; clopen:2021
|
||||
...
|
||||
```
|
||||
```journal
|
||||
; 2021.journal
|
||||
2021-01-01 opening balances ; clopen:2021
|
||||
...
|
||||
```
|
||||
|
||||
Now with
|
||||
```journal
|
||||
; all.journal
|
||||
include 2019.journal
|
||||
include 2020.journal
|
||||
include 2021.journal
|
||||
```
|
||||
you could do eg:
|
||||
```shell
|
||||
$ hledger -f all.journal reg -H checking not:tag:clopen
|
||||
# all years checking register, hiding non-essential opening/closing txns
|
||||
|
||||
$ hledger -f all.journal bs -p 2020 not:tag:clopen=2020
|
||||
# 2020 year end balances, suppressing 2020 closing txn
|
||||
|
||||
```
|
||||
With `--show-costs`, any amount costs are shown, with separate postings for each cost.
|
||||
(This currently the best way to view investment assets, showing lots and cost bases.)
|
||||
If you have many currency conversion or investment transactions, it can generate very large journal entries.
|
||||
|
||||
### close and balance assertions
|
||||
|
||||
The closing and opening transactions will include balance assertions,
|
||||
verifying that the accounts have first been reset to zero and then restored to their previous balance.
|
||||
These provide valuable error checking, alerting you when things get out of line,
|
||||
but you can ignore them temporarily with `-I` or just remove them if you prefer.
|
||||
Balance assertions will be generated, verifying that the accounts have been reset to zero
|
||||
(and then restored to their previous balances, if there is an opening transaction).
|
||||
|
||||
You probably shouldn't use status or realness filters (like -C or -R or `status:`) with `close`,
|
||||
or the generated balance assertions will depend on these flags.
|
||||
Likewise, if you run this command with `--auto`, the balance assertions would probably always require `--auto`.
|
||||
These provide useful error checking, but you can ignore them temporarily with `-I`,
|
||||
or remove them if you prefer.
|
||||
|
||||
Multi-day transactions (where some postings have a different date) break the balance assertions,
|
||||
because the money is temporarily "invisible" while in transit:
|
||||
You probably should avoid filtering transactions by status or realness
|
||||
(`-C`, `-R`, `status:`), or generating postings (`--auto`),
|
||||
with this command, since the balance assertions would depend on these.
|
||||
|
||||
Note custom posting dates spanning the file boundary will disrupt the balance assertions:
|
||||
|
||||
```journal
|
||||
2020/12/30 a purchase made in december, cleared in the next year
|
||||
2023-12-30 a purchase made in december, cleared in january
|
||||
expenses:food 5
|
||||
assets:bank:checking -5 ; date: 2021/1/2
|
||||
assets:bank:checking -5 ; date: 2023-01-02
|
||||
```
|
||||
|
||||
To fix the assertions, you can add a temporary account to track such in-transit money
|
||||
(splitting the multi-day transaction into two single-day transactions):
|
||||
To solve that you can transfer the money to and from a temporary account,
|
||||
in effect splitting the multi-day transaction into two single-day transactions:
|
||||
|
||||
```journal
|
||||
; in 2020.journal:
|
||||
2020/12/30 a purchase made in december, cleared in the next year
|
||||
; in 2022.journal:
|
||||
2022-12-30 a purchase made in december, cleared in january
|
||||
expenses:food 5
|
||||
liabilities:pending
|
||||
equity:pending -5
|
||||
|
||||
; in 2021.journal:
|
||||
2021/1/2 clearance of last year's pending transactions
|
||||
liabilities:pending 5 = 0
|
||||
assets:bank:checking
|
||||
; in 2023.journal:
|
||||
2023-01-02 last year's transaction cleared
|
||||
equity:pending 5 = 0
|
||||
assets:bank:checking -5
|
||||
```
|
||||
|
||||
### Example: close revenue/expense accounts to retained earnings
|
||||
### Example: retain earnings
|
||||
|
||||
For this, use `--close` to suppress the opening transaction, as it's not needed.
|
||||
Also you'll want to change the equity account name to your equivalent of
|
||||
"equity:retained earnings".
|
||||
<!-- XXX update -->
|
||||
|
||||
Closing 2021's first quarter revenues/expenses:
|
||||
Record 2022's revenues/expenses as retained earnings on 2022-12-31,
|
||||
appending the generated transaction to the journal:
|
||||
|
||||
```shell
|
||||
$ hledger close -f 2021.journal --close revenues expenses -p 2021Q1 \
|
||||
--close-acct='equity:retained earnings' >> 2021.journal
|
||||
$ hledger close --retain -f 2022.journal -p 2022 >> 2022.journal
|
||||
```
|
||||
|
||||
The same, using the default journal and current year:
|
||||
Now 2022's income statement will show only zeroes.
|
||||
To see it again, exclude the retain transaction. Eg:
|
||||
```shell
|
||||
$ hledger -f 2022.journal is not:desc:'retain earnings'
|
||||
```
|
||||
|
||||
### Example: migrate balances to a new file
|
||||
|
||||
Close assets/liabilities/equity on 2022-12-31 and re-open them on 2023-01-01:
|
||||
|
||||
```shell
|
||||
$ hledger close --close revenues expenses -p Q1 \
|
||||
--close-acct='equity:retained earnings' >> $LEDGER_FILE
|
||||
$ hledger close --migrate -f 2022.journal -p 2022
|
||||
# copy/paste the closing transaction to the end of 2022.journal
|
||||
# copy/paste the opening transaction to the start of 2023.journal
|
||||
```
|
||||
|
||||
Now, the first quarter's balance sheet should show a zero
|
||||
(unless you are using @/@@ notation without [equity postings](/investments.html#a-more-correct-entry)):
|
||||
<!--
|
||||
Or, you can automate more by generating one transaction at a time:
|
||||
|
||||
```shell
|
||||
$ hledger bse -p Q1
|
||||
$ hledger close --close -f 2022.journal -p 2022 >> 2023.journal # do this one first
|
||||
$ hledger close --open -f 2022.journal -p 2022 >> 2022.journal
|
||||
```
|
||||
-->
|
||||
|
||||
Now 2022's balance sheet will show only zeroes, indicating a balanced accounting equation.
|
||||
([Unless](/investments.html#a-more-correct-entry) you are using @/@@ notation - in that case, try adding --infer-equity.)
|
||||
To see it again, exclude the closing transaction. Eg:
|
||||
```shell
|
||||
$ hledger -f 2022.journal bs not:desc:'closing balances'
|
||||
```
|
||||
|
||||
And we must suppress the closing transaction to see the first quarter's income statement
|
||||
(using the description; `not:'retained earnings'` won't work here):
|
||||
```shell
|
||||
$ hledger is -p Q1 not:desc:'closing balances'
|
||||
### Example: excluding closing/opening transactions
|
||||
|
||||
When combining many files for multi-year reports,
|
||||
the closing/opening transactions cause some noise in reports like `print` and `register`.
|
||||
You can exclude them as shown above, but `not:desc:...` could be fragile,
|
||||
and also you will need to avoid excluding the very first opening transaction,
|
||||
which can be awkward. Here is a way to do it, using tags:
|
||||
add `clopen:` tags to all opening/closing balances transactions except the first,
|
||||
like this:
|
||||
|
||||
```journal
|
||||
; 2021.journal
|
||||
2021-06-01 first opening balances
|
||||
...
|
||||
2021-12-31 closing balances ; clopen:2022
|
||||
...
|
||||
```
|
||||
|
||||
```journal
|
||||
; 2022.journal
|
||||
2022-01-01 opening balances ; clopen:2022
|
||||
...
|
||||
2022-12-31 closing balances ; clopen:2023
|
||||
...
|
||||
```
|
||||
```journal
|
||||
; 2023.journal
|
||||
2023-01-01 opening balances ; clopen:2023
|
||||
...
|
||||
```
|
||||
|
||||
Now, assuming a combined journal like:
|
||||
|
||||
```journal
|
||||
; all.journal
|
||||
include 2021.journal
|
||||
include 2022.journal
|
||||
include 2023.journal
|
||||
```
|
||||
|
||||
The `clopen:` tag can exclude all but the first opening transaction.
|
||||
To show a clean multi-year checking register:
|
||||
```shell
|
||||
$ hledger -f all.journal areg checking not:tag:clopen
|
||||
```
|
||||
|
||||
And the year values allow more precision.
|
||||
To show 2022's year-end balance sheet:
|
||||
```shell
|
||||
$ hledger -f all.journal bs -e2023 not:tag:clopen=2023
|
||||
```
|
||||
|
||||
@ -1,5 +1,4 @@
|
||||
|
||||
# 1. Simple case
|
||||
<
|
||||
2016/1/1 open
|
||||
assets:bank $100
|
||||
@ -18,89 +17,64 @@
|
||||
liabilities $25
|
||||
assets:cash
|
||||
|
||||
$ hledger close -f- -e 2017-01-01 assets liabilities
|
||||
# 1. By default, closes all accounts, on the last day of the report period.
|
||||
$ hledger close -f- -e 2017
|
||||
2016-12-31 closing balances
|
||||
assets:bank $-80 = $0
|
||||
assets:cash $-10 = $0
|
||||
equity:opening $120 = $0
|
||||
expenses:sweets $-5 = $0
|
||||
liabilities $-25 = $0
|
||||
equity:opening/closing balances
|
||||
|
||||
>=0
|
||||
|
||||
# 2. With --retain, closes RX.
|
||||
$ hledger close -f- -e 2017 --retain
|
||||
2016-12-31 retain earnings
|
||||
expenses:sweets $-5 = $0
|
||||
equity:retained earnings
|
||||
|
||||
>=0
|
||||
|
||||
# 3. With --migrate, opens and closes ALE.
|
||||
$ hledger close -f- -p 2016 --migrate
|
||||
2016-12-31 closing balances
|
||||
assets:bank $-80 = $0
|
||||
assets:cash $-10 = $0
|
||||
equity:opening $120 = $0
|
||||
liabilities $-25 = $0
|
||||
equity:opening/closing balances
|
||||
|
||||
2017-01-01 opening balances
|
||||
assets:bank $80 = $80
|
||||
assets:cash $10 = $10
|
||||
equity:opening $-120 = $-120
|
||||
liabilities $25 = $25
|
||||
equity:opening/closing balances
|
||||
|
||||
>=0
|
||||
|
||||
# 2. A begin date should be ignored
|
||||
$ hledger close -f- -e 2017-01-01 assets liabilities -b 2016-12-01
|
||||
2016-12-31 closing balances
|
||||
assets:bank $-80 = $0
|
||||
assets:cash $-10 = $0
|
||||
liabilities $-25 = $0
|
||||
equity:opening/closing balances
|
||||
|
||||
# 4. With --open, opens ALE.
|
||||
$ hledger close -f- -p 2016 --open
|
||||
2017-01-01 opening balances
|
||||
assets:bank $80 = $80
|
||||
assets:cash $10 = $10
|
||||
equity:opening $-120 = $-120
|
||||
liabilities $25 = $25
|
||||
equity:opening/closing balances
|
||||
|
||||
>=0
|
||||
|
||||
# 3. Print just the opening transaction
|
||||
<
|
||||
2016/1/1 open
|
||||
assets:bank $100
|
||||
assets:cash $20
|
||||
equity:opening
|
||||
|
||||
2016/1/15 spend
|
||||
expenses:sweets $5
|
||||
assets:cash
|
||||
|
||||
2016/1/19 withdraw
|
||||
assets:cash $20
|
||||
assets:bank
|
||||
|
||||
2016/1/20 lend
|
||||
liabilities $25
|
||||
assets:cash
|
||||
|
||||
$ hledger close -f- -p 2016 assets liabilities --open
|
||||
2017-01-01 opening balances
|
||||
assets:bank $80 = $80
|
||||
assets:cash $10 = $10
|
||||
liabilities $25 = $25
|
||||
equity:opening/closing balances
|
||||
|
||||
>=0
|
||||
|
||||
# 4. Print just the closing transaction.
|
||||
$ hledger close -f- -p 2016 assets liabilities --close
|
||||
# 5. -x makes all amounts explicit.
|
||||
$ hledger close -f- -p 2016 -x
|
||||
2016-12-31 closing balances
|
||||
assets:bank $-80 = $0
|
||||
assets:cash $-10 = $0
|
||||
equity:opening $120 = $0
|
||||
expenses:sweets $-5 = $0
|
||||
liabilities $-25 = $0
|
||||
equity:opening/closing balances
|
||||
|
||||
>=0
|
||||
|
||||
# 5. Supplying --open --close is the same as just "close"
|
||||
# Also -x makes it show the equity amounts.
|
||||
$ hledger close -f- -p 2016 assets liabilities --open --close -x
|
||||
2016-12-31 closing balances
|
||||
assets:bank $-80 = $0
|
||||
assets:cash $-10 = $0
|
||||
liabilities $-25 = $0
|
||||
equity:opening/closing balances $115
|
||||
|
||||
2017-01-01 opening balances
|
||||
assets:bank $80 = $80
|
||||
assets:cash $10 = $10
|
||||
liabilities $25 = $25
|
||||
equity:opening/closing balances $-115
|
||||
equity:opening/closing balances 0
|
||||
|
||||
>=0
|
||||
|
||||
@ -116,10 +90,6 @@ $ hledger -f- close assets -p 2019 -x
|
||||
assets -2A = 0A
|
||||
equity:opening/closing balances 2A
|
||||
|
||||
2020-01-01 opening balances
|
||||
assets 2A = 2A
|
||||
equity:opening/closing balances -2A
|
||||
|
||||
>=0
|
||||
|
||||
# 7. With --show-costs, the transaction prices are preserved.
|
||||
@ -132,16 +102,11 @@ $ hledger -f- close assets -p 2019 --show-costs -x
|
||||
equity:opening/closing balances 1A @ 1B
|
||||
equity:opening/closing balances 1A @ 1C
|
||||
|
||||
2020-01-01 opening balances
|
||||
assets 1A @ 1B
|
||||
assets 1A @ 1C = 2A
|
||||
equity:opening/closing balances -1A @ 1B
|
||||
equity:opening/closing balances -1A @ 1C
|
||||
|
||||
>=0
|
||||
|
||||
# 8. Closing a multi-priced balance, slightly more complex
|
||||
# (different price in each transaction).
|
||||
# XXX account parentheses should be preserved here
|
||||
<
|
||||
2019/01/01
|
||||
(assets) 1A @ 1B
|
||||
@ -154,13 +119,9 @@ $ hledger -f- close assets -p 2019 -x
|
||||
assets -2A = 0A
|
||||
equity:opening/closing balances 2A
|
||||
|
||||
2020-01-01 opening balances
|
||||
assets 2A = 2A
|
||||
equity:opening/closing balances -2A
|
||||
|
||||
>=0
|
||||
|
||||
# 9. The same, with costs.
|
||||
# 9. The same with costs preserved.
|
||||
$ hledger -f- close assets -p 2019 --show-costs -x
|
||||
2019-12-31 closing balances
|
||||
assets -1A @ 1B
|
||||
@ -168,12 +129,6 @@ $ hledger -f- close assets -p 2019 --show-costs -x
|
||||
equity:opening/closing balances 1A @ 1B
|
||||
equity:opening/closing balances 1A @ 2B
|
||||
|
||||
2020-01-01 opening balances
|
||||
assets 1A @ 1B
|
||||
assets 1A @ 2B = 2A
|
||||
equity:opening/closing balances -1A @ 1B
|
||||
equity:opening/closing balances -1A @ 2B
|
||||
|
||||
>=0
|
||||
|
||||
# 10. Closing a multi-priced balance, a more complex example.
|
||||
@ -212,17 +167,6 @@ $ hledger -f- close -p 2016 assets liabilities --show-costs -x
|
||||
equity:opening/closing balances $-5,000.00 @ 0.95 EUR
|
||||
equity:opening/closing balances 5,734.00 EUR
|
||||
|
||||
2017-01-01 opening balances
|
||||
assets:bank 5,733.00 EUR = 5,733.00 EUR
|
||||
liabilities:employer $10,000.00
|
||||
liabilities:employer $-5,000.00 @ 0.93 EUR
|
||||
liabilities:employer $-5,000.00 @ 0.95 EUR = $0.00
|
||||
liabilities:employer 1.00 EUR = 1.00 EUR
|
||||
equity:opening/closing balances $-10,000.00
|
||||
equity:opening/closing balances $5,000.00 @ 0.93 EUR
|
||||
equity:opening/closing balances $5,000.00 @ 0.95 EUR
|
||||
equity:opening/closing balances -5,734.00 EUR
|
||||
|
||||
>=0
|
||||
|
||||
# 11. With --interleaved, each transfer's postings are adjacent.
|
||||
@ -241,18 +185,6 @@ $ hledger -f- close -p 2016 assets liabilities --interleaved --show-costs -x
|
||||
liabilities:employer -1.00 EUR = 0.00 EUR
|
||||
equity:opening/closing balances 1.00 EUR
|
||||
|
||||
2017-01-01 opening balances
|
||||
assets:bank 5,733.00 EUR = 5,733.00 EUR
|
||||
equity:opening/closing balances -5,733.00 EUR
|
||||
liabilities:employer $10,000.00
|
||||
equity:opening/closing balances $-10,000.00
|
||||
liabilities:employer $-5,000.00 @ 0.93 EUR
|
||||
equity:opening/closing balances $5,000.00 @ 0.93 EUR
|
||||
liabilities:employer $-5,000.00 @ 0.95 EUR = $0.00
|
||||
equity:opening/closing balances $5,000.00 @ 0.95 EUR
|
||||
liabilities:employer 1.00 EUR = 1.00 EUR
|
||||
equity:opening/closing balances -1.00 EUR
|
||||
|
||||
>=0
|
||||
|
||||
# 12. A tricky case where a closing posting was rounded and failed to balance (#1164)
|
||||
@ -278,14 +210,6 @@ $ hledger -f- close -p 2019 assets --show-costs -x
|
||||
equity:opening/closing balances $-49.390001 @ AAA 10.3528242505
|
||||
equity:opening/closing balances AAA 510.00000000
|
||||
|
||||
2020-01-01 opening balances
|
||||
assets:aaa AAA 510.00000000 = AAA 510.00000000
|
||||
assets:usd $49.50
|
||||
assets:usd $-49.390001 @ AAA 10.3528242505 = $0.109999
|
||||
equity:opening/closing balances $-49.50
|
||||
equity:opening/closing balances $49.390001 @ AAA 10.3528242505
|
||||
equity:opening/closing balances AAA -510.00000000
|
||||
|
||||
>=0
|
||||
|
||||
# 13. The same, without costs and with --interleaved.
|
||||
@ -296,12 +220,6 @@ $ hledger -f- close -p 2019 assets --interleaved -x
|
||||
assets:usd $-0.109999 = $0.00
|
||||
equity:opening/closing balances $0.109999
|
||||
|
||||
2020-01-01 opening balances
|
||||
assets:aaa AAA 510.00000000 = AAA 510.00000000
|
||||
equity:opening/closing balances AAA -510.00000000
|
||||
assets:usd $0.109999 = $0.109999
|
||||
equity:opening/closing balances $-0.109999
|
||||
|
||||
>=0
|
||||
|
||||
# 14. "The default closing date is yesterday, or the journal's end date, whichever is later."
|
||||
|
||||
Loading…
Reference in New Issue
Block a user