imp:print: clean up special tags; show them more often with --verbose-tags
- These special hidden tags, used internally, have been renamed: - `_modified` -> `_modified-transaction` - `_cost-matched` -> `_cost-posting` - `_conversion-matched` -> `_conversion-posting` - All special hidden tags now have a similarly-named visible tag, and `--verbose-tags` now shows those more often, which is useful when troubleshooting `--infer-equity`, `--infer-costs`, or the matching of redundant costs and conversion postings. - The `generated-posting:` tag added by `--infer-equity` is now valueless. - The `modified-transaction:` tag added by `--auto` now appears on its own line.
This commit is contained in:
parent
9bf28b1b0e
commit
1ad9fbb4a8
@ -999,10 +999,10 @@ journalToCost cost j@Journal{jtxns=ts} = j{jtxns=map (transactionToCost cost) ts
|
||||
-- This is always called before transaction balancing to tag the redundant-cost postings so they can be ignored.
|
||||
-- With --infer-costs, it is called again after transaction balancing (when it has more information to work with) to infer costs from equity postings.
|
||||
-- See transactionTagCostsAndEquityAndMaybeInferCosts for more details, and hledger manual > Cost reporting for more background.
|
||||
journalTagCostsAndEquityAndMaybeInferCosts :: Bool -> Journal -> Either String Journal
|
||||
journalTagCostsAndEquityAndMaybeInferCosts addcosts j = do
|
||||
journalTagCostsAndEquityAndMaybeInferCosts :: Bool -> Bool -> Journal -> Either String Journal
|
||||
journalTagCostsAndEquityAndMaybeInferCosts verbosetags addcosts j = do
|
||||
let conversionaccts = journalConversionAccounts j
|
||||
ts <- mapM (transactionTagCostsAndEquityAndMaybeInferCosts addcosts conversionaccts) $ jtxns j
|
||||
ts <- mapM (transactionTagCostsAndEquityAndMaybeInferCosts verbosetags addcosts conversionaccts) $ jtxns j
|
||||
return j{jtxns=ts}
|
||||
|
||||
-- | Add equity postings inferred from costs, where needed and possible.
|
||||
|
||||
@ -33,7 +33,7 @@ import Hledger.Data.Errors
|
||||
import Hledger.Data.Journal
|
||||
import Hledger.Data.JournalChecks.Ordereddates
|
||||
import Hledger.Data.JournalChecks.Uniqueleafnames
|
||||
import Hledger.Data.Posting (isVirtual, postingDate, transactionAllTags, conversionPostingTagName, costPostingTagName, postingAsLines)
|
||||
import Hledger.Data.Posting (isVirtual, postingDate, transactionAllTags, conversionPostingTagName, costPostingTagName, postingAsLines, generatedPostingTagName, generatedTransactionTagName, modifiedTransactionTagName)
|
||||
import Hledger.Data.Types
|
||||
import Hledger.Data.Amount (amountIsZero, amountsRaw, missingamt, oneLineFmt, showMixedAmountWith)
|
||||
import Hledger.Data.Transaction (transactionPayee, showTransactionLineFirstPart, partitionAndCheckConversionPostings)
|
||||
@ -233,15 +233,16 @@ builtinTags = [
|
||||
,"assert" -- appears on txns generated by close --assert
|
||||
,"retain" -- appears on txns generated by close --retain
|
||||
,"start" -- appears on txns generated by close --migrate/--close/--open/--assign
|
||||
,"generated-transaction" -- with --verbose-tags, appears on generated periodic txns
|
||||
,"generated-posting" -- with --verbose-tags, appears on generated auto postings
|
||||
,"modified" -- with --verbose-tags, appears on txns which have had auto postings added
|
||||
-- hidden tags used internally (and also queryable):
|
||||
,"_generated-transaction" -- always exists on generated periodic txns
|
||||
,"_generated-posting" -- always exists on generated auto postings
|
||||
,"_modified" -- always exists on txns which have had auto postings added
|
||||
,conversionPostingTagName -- marks costful postings which have been matched with a nearby pair of equity conversion postings
|
||||
]
|
||||
-- these tags are used in both hidden and visible form
|
||||
<> ts <> map toVisibleTagName ts
|
||||
where
|
||||
ts = [
|
||||
generatedTransactionTagName -- marks txns generated by periodic rule
|
||||
,modifiedTransactionTagName -- marks txns which have had auto postings added
|
||||
,generatedPostingTagName -- marks postings which have been generated
|
||||
,costPostingTagName -- marks equity conversion postings which have been matched with a nearby costful posting
|
||||
,conversionPostingTagName -- marks costful postings which have been matched with a nearby pair of equity conversion postings
|
||||
]
|
||||
|
||||
-- | In each tranaction, check that any conversion postings occur in adjacent pairs.
|
||||
|
||||
@ -20,7 +20,7 @@ import Text.Printf
|
||||
import Hledger.Data.Types
|
||||
import Hledger.Data.Dates
|
||||
import Hledger.Data.Amount
|
||||
import Hledger.Data.Posting (post, commentAddTagNextLine)
|
||||
import Hledger.Data.Posting (post, generatedTransactionTagName)
|
||||
import Hledger.Data.Transaction
|
||||
|
||||
-- $setup
|
||||
@ -205,13 +205,11 @@ runPeriodicTransaction verbosetags PeriodicTransaction{..} requestedspan =
|
||||
,tstatus = ptstatus
|
||||
,tcode = ptcode
|
||||
,tdescription = ptdescription
|
||||
,tcomment = ptcomment &
|
||||
(if verbosetags then (`commentAddTagNextLine` ("generated-transaction",period)) else id)
|
||||
,ttags = pttags &
|
||||
(("_generated-transaction",period) :) &
|
||||
(if verbosetags then (("generated-transaction" ,period) :) else id)
|
||||
,tcomment = ptcomment
|
||||
,ttags = pttags
|
||||
,tpostings = ptpostings
|
||||
}
|
||||
& transactionAddHiddenAndMaybeVisibleTag verbosetags (generatedTransactionTagName, period)
|
||||
period = "~ " <> ptperiodexpr
|
||||
-- All the date spans described by this periodic transaction rule.
|
||||
alltxnspans = splitSpan adjust ptinterval span'
|
||||
|
||||
@ -41,6 +41,7 @@ module Hledger.Data.Posting (
|
||||
postingApplyCommodityStyles,
|
||||
postingStyleAmounts,
|
||||
postingAddTags,
|
||||
postingAddHiddenAndMaybeVisibleTag,
|
||||
-- * date operations
|
||||
postingDate,
|
||||
postingDate2,
|
||||
@ -54,8 +55,11 @@ module Hledger.Data.Posting (
|
||||
commentAddTag,
|
||||
commentAddTagUnspaced,
|
||||
commentAddTagNextLine,
|
||||
conversionPostingTagName,
|
||||
generatedTransactionTagName,
|
||||
modifiedTransactionTagName,
|
||||
generatedPostingTagName,
|
||||
costPostingTagName,
|
||||
conversionPostingTagName,
|
||||
|
||||
-- * arithmetic
|
||||
sumPostings,
|
||||
@ -96,7 +100,6 @@ import qualified Data.Text.Lazy.Builder as TB
|
||||
import Data.Time.Calendar (Day)
|
||||
import Safe (maximumBound)
|
||||
import Text.DocLayout (realLength)
|
||||
|
||||
import Text.Tabular.AsciiWide hiding (render)
|
||||
|
||||
import Hledger.Utils
|
||||
@ -107,22 +110,16 @@ import Hledger.Data.Dates (nulldate, spanContainsDate)
|
||||
import Hledger.Data.Valuation
|
||||
|
||||
|
||||
-- | These are hidden tags used internally to mark:
|
||||
-- (1) "matched conversion postings", which are to an account of Conversion type and have a nearby equivalent costful or potentially costful posting, and
|
||||
-- (2) "matched cost postings", which have or could have a cost that's equivalent to nearby conversion postings.
|
||||
--
|
||||
-- One or both of these tags are added during journal finalising:
|
||||
-- (1) before transaction balancing, to allow ignoring redundant costs
|
||||
-- (2) when inferring costs from equity conversion postings, and
|
||||
-- (3) when inferring equity conversion postings from costs.
|
||||
--
|
||||
-- These are hidden tags, mainly for internal use, and not visible in output. (XXX visibility would be useful for troubleshooting)
|
||||
-- But they are mentioned in docs and can be matched by user queries, which can be useful occasionally;
|
||||
-- so consider user impact before changing these names.
|
||||
--
|
||||
conversionPostingTagName, costPostingTagName :: TagName
|
||||
conversionPostingTagName = "_conversion-matched"
|
||||
costPostingTagName = "_cost-matched"
|
||||
-- | Special tags hledger sometimes adds to mark various things.
|
||||
-- These should be hidden tag names, beginning with _.
|
||||
-- With --verbose-tags, the equivalent visible tags will also be added.
|
||||
-- These tag names are mentioned in docs and can be matched by user queries, so consider the impact before changing them.
|
||||
generatedTransactionTagName, modifiedTransactionTagName, costPostingTagName, conversionPostingTagName, generatedPostingTagName :: TagName
|
||||
generatedTransactionTagName = "_generated-transaction" -- ^ transactions generated by a periodic txn rule
|
||||
modifiedTransactionTagName = "_modified-transaction" -- ^ transactions modified by an auto posting rule
|
||||
generatedPostingTagName = "_generated-posting" -- ^ postings generated by hledger for one reason or another
|
||||
costPostingTagName = "_cost-posting" -- ^ postings which have or could have a cost that's equivalent to nearby conversion postings
|
||||
conversionPostingTagName = "_conversion-posting" -- ^ postings to an equity account of Conversion type which have an amount that's equivalent to a nearby costful or potentially costful posting
|
||||
|
||||
instance HasAmounts BalanceAssertion where
|
||||
styleAmounts styles ba@BalanceAssertion{baamount} = ba{baamount=styleAmounts styles baamount}
|
||||
@ -463,9 +460,21 @@ postingApplyAliases aliases p@Posting{paccount} =
|
||||
++ "\n to account name: "++T.unpack paccount++"\n "++e
|
||||
|
||||
-- | Add tags to a posting, discarding any for which the posting already has a value.
|
||||
-- Note this does not add tags to the posting's comment.
|
||||
postingAddTags :: Posting -> [Tag] -> Posting
|
||||
postingAddTags p@Posting{ptags} tags = p{ptags=ptags `union` tags}
|
||||
|
||||
-- | Add the given hidden tag to a posting; and with a true argument,
|
||||
-- also add the equivalent visible tag to the posting's tags and comment fields.
|
||||
-- If the posting already has these tags (with any value), do nothing.
|
||||
postingAddHiddenAndMaybeVisibleTag :: Bool -> HiddenTag -> Posting -> Posting
|
||||
postingAddHiddenAndMaybeVisibleTag verbosetags ht p@Posting{pcomment=c, ptags} =
|
||||
(p `postingAddTags` ([ht] <> [vt|verbosetags]))
|
||||
{pcomment=if verbosetags && not hadtag then c `commentAddTag` vt else c}
|
||||
where
|
||||
vt@(vname,_) = toVisibleTag ht
|
||||
hadtag = any ((== (T.toLower vname)) . T.toLower . fst) ptags -- XXX should regex-quote vname
|
||||
|
||||
-- | Apply a specified valuation to this posting's amount, using the
|
||||
-- provided price oracle, commodity styles, and reference dates.
|
||||
-- See amountApplyValuation.
|
||||
@ -492,15 +501,17 @@ postingAddInferredEquityPostings verbosetags equityAcct p
|
||||
-- this posting is already tagged as having associated conversion postings
|
||||
| costPostingTagName `elem` map fst (ptags p) = [p]
|
||||
-- tag the posting, and for each of its costs, add an equivalent pair of conversion postings after it
|
||||
| otherwise = p `postingAddTags` [(costPostingTagName,"")] : concatMap makeConversionPostings costs
|
||||
| otherwise =
|
||||
postingAddHiddenAndMaybeVisibleTag verbosetags (costPostingTagName,"") p :
|
||||
concatMap makeConversionPostings costs
|
||||
where
|
||||
costs = filter (isJust . acost) . amountsRaw $ pamount p
|
||||
makeConversionPostings amt = case acost amt of
|
||||
Nothing -> []
|
||||
Just _ -> [ cp{ paccount = accountPrefix <> amtCommodity
|
||||
Just _ -> [ convp{ paccount = accountPrefix <> amtCommodity
|
||||
, pamount = mixedAmount . negate $ amountStripCost amt
|
||||
}
|
||||
, cp{ paccount = accountPrefix <> costCommodity
|
||||
, convp{ paccount = accountPrefix <> costCommodity
|
||||
, pamount = mixedAmount cost
|
||||
}
|
||||
]
|
||||
@ -508,14 +519,9 @@ postingAddInferredEquityPostings verbosetags equityAcct p
|
||||
cost = amountCost amt
|
||||
amtCommodity = commodity amt
|
||||
costCommodity = commodity cost
|
||||
cp = p{ pcomment = pcomment p & (if verbosetags then (`commentAddTag` ("generated-posting","conversion")) else id)
|
||||
, ptags =
|
||||
(conversionPostingTagName,"") :
|
||||
("_generated-posting","conversion") :
|
||||
(if verbosetags then [("generated-posting", "conversion")] else [])
|
||||
, pbalanceassertion = Nothing
|
||||
, poriginal = Nothing
|
||||
}
|
||||
convp = p{pbalanceassertion=Nothing, poriginal=Nothing}
|
||||
& postingAddHiddenAndMaybeVisibleTag verbosetags (conversionPostingTagName,"")
|
||||
& postingAddHiddenAndMaybeVisibleTag verbosetags (generatedPostingTagName, "")
|
||||
accountPrefix = mconcat [ equityAcct, ":", T.intercalate "-" $ sort [amtCommodity, costCommodity], ":"]
|
||||
-- Take the commodity of an amount and collapse consecutive spaces to a single space
|
||||
commodity = T.unwords . filter (not . T.null) . T.words . acommodity
|
||||
|
||||
@ -34,6 +34,8 @@ module Hledger.Data.Transaction
|
||||
, transactionMapPostingAmounts
|
||||
, transactionAmounts
|
||||
, partitionAndCheckConversionPostings
|
||||
, transactionAddTags
|
||||
, transactionAddHiddenAndMaybeVisibleTag
|
||||
-- * helpers
|
||||
, payeeAndNoteFromDescription
|
||||
, payeeAndNoteFromDescription'
|
||||
@ -76,6 +78,8 @@ import Hledger.Data.Amount
|
||||
import Hledger.Data.Valuation
|
||||
import Data.Decimal (normalizeDecimal, decimalPlaces)
|
||||
import Data.Functor ((<&>))
|
||||
import Data.Function ((&))
|
||||
import Data.List (union)
|
||||
|
||||
|
||||
instance HasAmounts Transaction where
|
||||
@ -249,6 +253,22 @@ type IdxPosting = (Int, Posting)
|
||||
|
||||
label s = ((s <> ": ")++)
|
||||
|
||||
-- | Add tags to a transaction, discarding any for which it already has a value.
|
||||
-- Note this does not add tags to the transaction's comment.
|
||||
transactionAddTags :: Transaction -> [Tag] -> Transaction
|
||||
transactionAddTags t@Transaction{ttags} tags = t{ttags=ttags `union` tags}
|
||||
|
||||
-- | Add the given hidden tag to a transaction; and with a true argument,
|
||||
-- also add the equivalent visible tag to the transaction's tags and comment fields.
|
||||
-- If the transaction already has these tags (with any value), do nothing.
|
||||
transactionAddHiddenAndMaybeVisibleTag :: Bool -> HiddenTag -> Transaction -> Transaction
|
||||
transactionAddHiddenAndMaybeVisibleTag verbosetags ht t@Transaction{tcomment=c, ttags} =
|
||||
(t `transactionAddTags` ([ht] <> [vt|verbosetags]))
|
||||
{tcomment=if verbosetags && not hadtag then c `commentAddTagNextLine` vt else c}
|
||||
where
|
||||
vt@(vname,_) = toVisibleTag ht
|
||||
hadtag = any ((== (T.toLower vname)) . T.toLower . fst) ttags -- XXX should regex-quote vname
|
||||
|
||||
-- | Find, associate, and tag the corresponding equity conversion postings and costful or potentially costful postings in this transaction.
|
||||
-- With a true addcosts argument, also generate and add any equivalent costs that are missing.
|
||||
-- The (previously detected) names of all equity conversion accounts should be provided.
|
||||
@ -260,8 +280,8 @@ label s = ((s <> ": ")++)
|
||||
--
|
||||
-- The name reflects the complexity of this and its helpers; clarification is ongoing.
|
||||
--
|
||||
transactionTagCostsAndEquityAndMaybeInferCosts :: Bool -> [AccountName] -> Transaction -> Either String Transaction
|
||||
transactionTagCostsAndEquityAndMaybeInferCosts addcosts conversionaccts t = first (annotateErrorWithTransaction t . T.unpack) $ do
|
||||
transactionTagCostsAndEquityAndMaybeInferCosts :: Bool -> Bool -> [AccountName] -> Transaction -> Either String Transaction
|
||||
transactionTagCostsAndEquityAndMaybeInferCosts verbosetags1 addcosts conversionaccts t = first (annotateErrorWithTransaction t . T.unpack) $ do
|
||||
-- number the postings
|
||||
let npostings = zip [0..] $ tpostings t
|
||||
|
||||
@ -273,7 +293,7 @@ transactionTagCostsAndEquityAndMaybeInferCosts addcosts conversionaccts t = firs
|
||||
-- 1. each pair of conversion postings, and the corresponding postings which balance them, are tagged for easy identification
|
||||
-- 2. each pair of balancing postings which did't have an explicit cost, have had a cost calculated and added to one of them
|
||||
-- 3. if any ambiguous situation was detected, an informative error is raised
|
||||
processposting <- transformIndexedPostingsF (tagAndMaybeAddCostsForEquityPostings addcosts) conversionPairs otherps
|
||||
processposting <- transformIndexedPostingsF (tagAndMaybeAddCostsForEquityPostings verbosetags1 addcosts) conversionPairs otherps
|
||||
|
||||
-- And if there was no error, use it to modify the transaction's postings.
|
||||
return t{tpostings = map (snd . processposting) npostings}
|
||||
@ -306,8 +326,8 @@ transactionTagCostsAndEquityAndMaybeInferCosts addcosts conversionaccts t = firs
|
||||
-- 3. if in add costs mode, and the potential equivalent-cost posting does not have that explicit cost, add it
|
||||
-- 4. or if there is a problem, raise an informative error or do nothing, as appropriate.
|
||||
-- Or if there are no costful postings at all, do nothing.
|
||||
tagAndMaybeAddCostsForEquityPostings :: Bool -> (IdxPosting, IdxPosting) -> StateT ([IdxPosting], [IdxPosting]) (Either Text) (IdxPosting -> IdxPosting)
|
||||
tagAndMaybeAddCostsForEquityPostings addcosts' ((n1, cp1), (n2, cp2)) = StateT $ \(costps, otherps) -> do
|
||||
tagAndMaybeAddCostsForEquityPostings :: Bool -> Bool -> (IdxPosting, IdxPosting) -> StateT ([IdxPosting], [IdxPosting]) (Either Text) (IdxPosting -> IdxPosting)
|
||||
tagAndMaybeAddCostsForEquityPostings verbosetags addcosts' ((n1, cp1), (n2, cp2)) = StateT $ \(costps, otherps) -> do
|
||||
-- Get the two conversion posting amounts, if possible
|
||||
ca1 <- conversionPostingAmountNoCost cp1
|
||||
ca2 <- conversionPostingAmountNoCost cp2
|
||||
@ -328,8 +348,8 @@ transactionTagCostsAndEquityAndMaybeInferCosts addcosts conversionaccts t = firs
|
||||
|
||||
-- A function that adds a cost and/or tag to a numbered posting if appropriate.
|
||||
postingAddCostAndOrTag np costp (n,p) =
|
||||
(n, if | n == np -> costp `postingAddTags` [(costPostingTagName,"")] -- add this tag to the posting with a cost
|
||||
| n == n1 || n == n2 -> p `postingAddTags` [(conversionPostingTagName,"")] -- add this tag to the two equity conversion postings
|
||||
(n, if | n == np -> costp & postingAddHiddenAndMaybeVisibleTag verbosetags (costPostingTagName,"") -- if it's the specified posting number, replace it with the costful posting, and tag it
|
||||
| n == n1 || n == n2 -> p & postingAddHiddenAndMaybeVisibleTag verbosetags (conversionPostingTagName,"") -- if it's one of the equity conversion postings, tag it
|
||||
| otherwise -> p)
|
||||
|
||||
-- Annotate any errors with the conversion posting pair
|
||||
|
||||
@ -23,10 +23,10 @@ import Safe (headDef)
|
||||
import Hledger.Data.Types
|
||||
import Hledger.Data.Amount
|
||||
import Hledger.Data.Dates
|
||||
import Hledger.Data.Transaction (txnTieKnot)
|
||||
import Hledger.Data.Transaction (txnTieKnot, transactionAddHiddenAndMaybeVisibleTag)
|
||||
import Hledger.Query (Query, filterQuery, matchesAmount, matchesPostingExtra,
|
||||
parseQuery, queryIsAmt, queryIsSym, simplifyQuery)
|
||||
import Hledger.Data.Posting (commentJoin, commentAddTag, postingAddTags)
|
||||
import Hledger.Data.Posting (commentJoin, commentAddTag, postingAddTags, modifiedTransactionTagName)
|
||||
import Hledger.Utils (dbg6, wrap)
|
||||
|
||||
-- $setup
|
||||
@ -47,14 +47,10 @@ modifyTransactions :: (AccountName -> Maybe AccountType)
|
||||
modifyTransactions atypes atags styles d verbosetags tmods ts = do
|
||||
fs <- mapM (transactionModifierToFunction atypes atags styles d verbosetags) tmods -- convert modifiers to functions, or return a parse error
|
||||
let
|
||||
modifytxn t = t''
|
||||
modifytxn t =
|
||||
t' & if t'/=t then transactionAddHiddenAndMaybeVisibleTag verbosetags (modifiedTransactionTagName,"") else id
|
||||
where
|
||||
t' = foldr (flip (.)) id fs t -- apply each function in turn
|
||||
t'' = if t' == t
|
||||
then t'
|
||||
else t'{tcomment=tcomment t' & (if verbosetags then (`commentAddTag` ("modified","")) else id)
|
||||
,ttags=ttags t' & (("_modified","") :) & (if verbosetags then (("modified","") :) else id)
|
||||
}
|
||||
|
||||
Right $ map modifytxn ts
|
||||
|
||||
|
||||
@ -33,6 +33,7 @@ module Hledger.Data.Types (
|
||||
where
|
||||
|
||||
import GHC.Generics (Generic)
|
||||
import Data.Bifunctor (first)
|
||||
import Data.Decimal (Decimal, DecimalRaw(..))
|
||||
import Data.Default (Default(..))
|
||||
import Data.Functor (($>))
|
||||
@ -44,6 +45,7 @@ import Data.List (intercalate)
|
||||
import qualified Data.Map as M
|
||||
import Data.Ord (comparing)
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import Data.Time.Calendar (Day)
|
||||
import Data.Time.Clock.POSIX (POSIXTime)
|
||||
import Data.Time.LocalTime (LocalTime)
|
||||
@ -390,8 +392,25 @@ data PostingType = RegularPosting | VirtualPosting | BalancedVirtualPosting
|
||||
type TagName = Text
|
||||
type TagValue = Text
|
||||
type Tag = (TagName, TagValue) -- ^ A tag name and (possibly empty) value.
|
||||
type HiddenTag = Tag -- ^ A tag whose name begins with _.
|
||||
type DateTag = (TagName, Day)
|
||||
|
||||
-- | Add the _ prefix to a normal visible tag's name, making it a hidden tag.
|
||||
toHiddenTag :: Tag -> HiddenTag
|
||||
toHiddenTag = first toHiddenTagName
|
||||
|
||||
-- | Drop the _ prefix from a hidden tag's name, making it a normal visible tag.
|
||||
toVisibleTag :: HiddenTag -> Tag
|
||||
toVisibleTag = first toVisibleTagName
|
||||
|
||||
-- | Add the _ prefix to a normal visible tag's name, making it a hidden tag.
|
||||
toHiddenTagName :: TagName -> TagName
|
||||
toHiddenTagName = T.cons '_'
|
||||
|
||||
-- | Drop the _ prefix from a hidden tag's name, making it a normal visible tag.
|
||||
toVisibleTagName :: TagName -> TagName
|
||||
toVisibleTagName = T.drop 1
|
||||
|
||||
-- | The status of a transaction or posting, recorded with a status mark
|
||||
-- (nothing, !, or *). What these mean is ultimately user defined.
|
||||
data Status = Unmarked | Pending | Cleared
|
||||
|
||||
@ -350,7 +350,7 @@ journalFinalise iopts@InputOpts{auto_,balancingopts_,infer_costs_,infer_equity_,
|
||||
& journalStyleAmounts -- Infer and apply commodity styles (but don't round) - should be done early
|
||||
<&> journalAddForecast verbose_tags_ (forecastPeriod iopts pj) -- Add forecast transactions if enabled
|
||||
<&> journalPostingsAddAccountTags -- Add account tags to postings, so they can be matched by auto postings.
|
||||
>>= journalTagCostsAndEquityAndMaybeInferCosts False -- Tag equity conversion postings and redundant costs, to help journalBalanceTransactions ignore them.
|
||||
>>= journalTagCostsAndEquityAndMaybeInferCosts verbose_tags_ False -- Tag equity conversion postings and redundant costs, to help journalBalanceTransactions ignore them.
|
||||
>>= (if auto_ && not (null $ jtxnmodifiers pj)
|
||||
then journalAddAutoPostings verbose_tags_ _ioDay balancingopts_ -- Add auto postings if enabled, and account tags if needed. Does preliminary transaction balancing.
|
||||
else pure)
|
||||
@ -364,7 +364,7 @@ journalFinalise iopts@InputOpts{auto_,balancingopts_,infer_costs_,infer_equity_,
|
||||
-- <&> dbg9With (("journalFinalise amounts after styling, forecasting, auto postings, transaction balancing"<>).showJournalAmountsDebug)
|
||||
>>= journalInferCommodityStyles -- infer commodity styles once more now that all posting amounts are present
|
||||
-- >>= Right . dbg0With (pshow.journalCommodityStyles)
|
||||
>>= (if infer_costs_ then journalTagCostsAndEquityAndMaybeInferCosts True else pure) -- With --infer-costs, infer costs from equity postings where possible
|
||||
>>= (if infer_costs_ then journalTagCostsAndEquityAndMaybeInferCosts verbose_tags_ True else pure) -- With --infer-costs, infer costs from equity postings where possible
|
||||
<&> (if infer_equity_ then journalInferEquityFromCosts verbose_tags_ else id) -- With --infer-equity, infer equity postings from costs where possible
|
||||
<&> dbg9With (lbl "amounts after equity-inferring".showJournalAmountsDebug)
|
||||
<&> journalInferMarketPricesFromTransactions -- infer market prices from commodity-exchanging transactions
|
||||
|
||||
@ -1883,37 +1883,24 @@ Tags you can set to influence hledger's behaviour:
|
||||
type -- declares an account's type
|
||||
```
|
||||
|
||||
Tags hledger adds to indicate generated data:
|
||||
Tags hledger adds to indicate generated data (either always, or when `--verbose-tags` is used):
|
||||
```
|
||||
t -- appears on postings generated by timedot letters
|
||||
assert -- appears on txns generated by close --assert
|
||||
retain -- appears on txns generated by close --retain
|
||||
start -- appears on txns generated by close --migrate/--close/--open/--assign
|
||||
generated-transaction -- appears on generated periodic txns (with --verbose-tags)
|
||||
generated-posting -- appears on generated auto postings (with --verbose-tags)
|
||||
modified -- appears on txns which have had auto postings added (with --verbose-tags)
|
||||
```
|
||||
|
||||
These similar tags are also provided; they are not displayed, but can be relied on for querying:
|
||||
```
|
||||
_generated-transaction -- exists on generated periodic txns (always)
|
||||
_generated-posting -- exists on generated auto postings (always)
|
||||
_modified -- exists on txns which have had auto postings added (always)
|
||||
```
|
||||
|
||||
The following non-displayed tags are used internally by hledger,
|
||||
(1) to ignore redundant costs when balancing transactions,
|
||||
(2) when using --infer-costs, and
|
||||
(3) when using --infer-equity.
|
||||
Essentially they mark postings with costs which have corresponding equity conversion postings, and vice-versa.
|
||||
They are queryable, but you should not rely on them for your reports:
|
||||
```
|
||||
_conversion-matched -- marks "matched conversion postings", which are to a V/Conversion account
|
||||
and have a nearby equivalent costful or potentially costful posting
|
||||
_cost-matched -- marks "matched cost postings", which have or could have a cost
|
||||
generated-transaction -- appears on txns generated by a periodic rule
|
||||
modified-transaction -- appears on txns which have had auto postings added
|
||||
generated-posting -- appears on generated postings
|
||||
cost-posting -- marks postings which have a cost, or could have a cost,
|
||||
that's equivalent to nearby conversion postings
|
||||
conversion-posting -- marks postings which are to a V/Conversion account
|
||||
and whose amount is equivalent to a nearby cost posting
|
||||
```
|
||||
|
||||
The `*-transaction` and `*-posting` tags above are also added as hidden tags (with a `_` prefix).
|
||||
Hidden tags are not displayed, but can be relied on for querying.
|
||||
|
||||
### Tag values
|
||||
|
||||
Tags can have a value, which is any text after the colon up until a comma or end of line, with surrounding whitespace removed.
|
||||
|
||||
@ -52,13 +52,15 @@ $ hledger -f - check tags
|
||||
; retain:
|
||||
; start:
|
||||
; generated-transaction:
|
||||
; modified-transaction:
|
||||
; generated-posting:
|
||||
; modified:
|
||||
; cost-posting:
|
||||
; conversion-posting:
|
||||
; _generated-transaction:
|
||||
; _modified-transaction:
|
||||
; _generated-posting:
|
||||
; _modified:
|
||||
; _conversion-matched:
|
||||
; _cost-matched:
|
||||
; _cost-posting:
|
||||
; _conversion-posting:
|
||||
$ hledger -f - check tags
|
||||
|
||||
# ** 7. Declaring the built-in special tags is harmless.
|
||||
@ -72,11 +74,13 @@ tag assert ; appears on txns generated by close --assert
|
||||
tag retain ; appears on txns generated by close --retain
|
||||
tag start ; appears on txns generated by close --migrate/--close/--open/--assign
|
||||
tag generated-transaction ; with --verbose-tags, appears on generated periodic txns
|
||||
tag modified-transaction ; with --verbose-tags, appears on txns which have had auto postings added
|
||||
tag generated-posting ; with --verbose-tags, appears on generated auto postings
|
||||
tag modified ; with --verbose-tags, appears on txns which have had auto postings added
|
||||
tag cost-posting ; with --verbose-tags, appears on cost postings
|
||||
tag conversion-posting ; with --verbose-tags, appears on conversion postings
|
||||
tag _generated-transaction ; always exists on generated periodic txns
|
||||
tag _modified-transaction ; always exists on txns which have had auto postings added
|
||||
tag _generated-posting ; always exists on generated auto postings
|
||||
tag _modified ; always exists on txns which have had auto postings added
|
||||
tag _conversion-matched ; exists on postings which have been matched with a nearby @/@@ cost notation
|
||||
tag _cost-matched ; exists on postings which have been matched with a nearby @/@@ cost notation
|
||||
tag _cost-posting ; exists on postings which have been matched with a nearby @/@@ cost notation
|
||||
tag _conversion-posting ; exists on postings which have been matched with a nearby @/@@ cost notation
|
||||
$ hledger -f - check tags
|
||||
|
||||
@ -16,7 +16,8 @@
|
||||
# ** 1. print. Auto-generated postings are inserted below the matched one.
|
||||
# With --verbose-tags, informative tags will also be added.
|
||||
$ hledger print -f- --auto --verbose-tags
|
||||
2016-01-01 paycheck ; modified:
|
||||
2016-01-01 paycheck
|
||||
; modified-transaction:
|
||||
income:remuneration $-100
|
||||
(liabilities:tax) $-33 ; income tax, generated-posting: = ^income
|
||||
income:donations $-15
|
||||
@ -181,7 +182,8 @@ $ hledger print -f- --auto
|
||||
|
||||
# ** 10.
|
||||
$ hledger -f- print --auto --verbose-tags
|
||||
2018-01-01 ; modified:
|
||||
2018-01-01
|
||||
; modified-transaction:
|
||||
Expenses:Joint:Widgets $100.00 @ £0.50
|
||||
Expenses:Joint $-100.00 @ £0.50 ; generated-posting: = ^Expenses:Joint
|
||||
Liabilities:Joint:Bob $50.00 @ £0.50 ; generated-posting: = ^Expenses:Joint
|
||||
|
||||
@ -29,9 +29,9 @@ $ hledger -f- print --explicit --cost
|
||||
# and with --verbose-tags, they will be visibly tagged.
|
||||
$ hledger -f- print --infer-equity --verbose-tags
|
||||
2011-01-01
|
||||
expenses:foreign currency €100 @ $1.35
|
||||
equity:conversion:$-€:€ €-100 ; generated-posting: conversion
|
||||
equity:conversion:$-€:$ $135.00 ; generated-posting: conversion
|
||||
expenses:foreign currency €100 @ $1.35 ; cost-posting:
|
||||
equity:conversion:$-€:€ €-100 ; conversion-posting:, generated-posting:
|
||||
equity:conversion:$-€:$ $135.00 ; conversion-posting:, generated-posting:
|
||||
assets $-135.00
|
||||
|
||||
>=0
|
||||
|
||||
@ -12,7 +12,8 @@
|
||||
assets:cash $20
|
||||
assets:bank
|
||||
$ hledger rewrite -f- ^income --add-posting '(liabilities:tax) *.33 ; income tax' --verbose-tags
|
||||
2016-01-01 paycheck ; modified:
|
||||
2016-01-01 paycheck
|
||||
; modified-transaction:
|
||||
income:remuneration $-100
|
||||
(liabilities:tax) $-33 ; income tax, generated-posting: = ^income
|
||||
income:donations $-15
|
||||
@ -181,12 +182,14 @@ $ hledger rewrite -f- assets:bank and 'amt:<0' --add-posting 'expenses:fee $5'
|
||||
(budget:misc) *-1
|
||||
|
||||
$ hledger rewrite -f- date:2017/1 --add-posting 'Here comes Santa $0' --verbose-tags
|
||||
2016-12-31 ; modified:
|
||||
2016-12-31
|
||||
; modified-transaction:
|
||||
expenses:housing $600
|
||||
(budget:housing) $-600 ; generated-posting: = ^expenses:housing
|
||||
assets:cash
|
||||
|
||||
2017-01-01 ; modified:
|
||||
2017-01-01
|
||||
; modified-transaction:
|
||||
expenses:food $20
|
||||
(budget:food) $-20 ; generated-posting: = ^expenses:grocery ^expenses:food
|
||||
Here comes Santa $0 ; generated-posting: = date:2017/1
|
||||
@ -199,7 +202,8 @@ $ hledger rewrite -f- date:2017/1 --add-posting 'Here comes Santa $0' --verbos
|
||||
assets:cash
|
||||
Here comes Santa $0 ; generated-posting: = date:2017/1
|
||||
|
||||
2017-01-02 ; modified:
|
||||
2017-01-02
|
||||
; modified-transaction:
|
||||
assets:cash $200.00
|
||||
Here comes Santa $0 ; generated-posting: = date:2017/1
|
||||
assets:bank
|
||||
|
||||
Loading…
Reference in New Issue
Block a user