csv: don't force a second posting with amount1

A rewrite and simplification of the posting-generating code. The
"special handling for pre 1.17 rules" should now be less noticeable.
amount1/amount2 no longer force a second posting or explicit amounts
on both postings. (Only amount/amount-in/amount-out do that.)
Error messages and handling of corner cases may be more robust, also.
This commit is contained in:
Simon Michael 2020-03-12 08:52:43 -07:00
parent 8011e4e0c1
commit a1361ecc04
6 changed files with 278 additions and 335 deletions

View File

@ -457,6 +457,8 @@ journalfieldnamep = do
lift (dbgparse 2 "trying journalfieldnamep") lift (dbgparse 2 "trying journalfieldnamep")
T.unpack <$> choiceInState (map (lift . string . T.pack) journalfieldnames) T.unpack <$> choiceInState (map (lift . string . T.pack) journalfieldnames)
maxpostings = 9
-- Transaction fields and pseudo fields for CSV conversion. -- Transaction fields and pseudo fields for CSV conversion.
-- Names must precede any other name they contain, for the parser -- Names must precede any other name they contain, for the parser
-- (amount-in before amount; date2 before date). TODO: fix -- (amount-in before amount; date2 before date). TODO: fix
@ -468,7 +470,7 @@ journalfieldnames =
,"balance" ++ i ,"balance" ++ i
,"comment" ++ i ,"comment" ++ i
,"currency" ++ i ,"currency" ++ i
] | x <- [1..9], let i = show x] ] | x <- [1..maxpostings], let i = show x]
++ ++
["amount-in" ["amount-in"
,"amount-out" ,"amount-out"
@ -761,8 +763,8 @@ csvRule rules = (`getDirective` rules)
-- into account the current record and conditional rules. -- into account the current record and conditional rules.
-- Generally rules with keywords ("directives") don't have interpolated -- Generally rules with keywords ("directives") don't have interpolated
-- values, but for now it's possible. -- values, but for now it's possible.
csvRuleValue :: CsvRules -> CsvRecord -> DirectiveName -> Maybe String -- csvRuleValue :: CsvRules -> CsvRecord -> DirectiveName -> Maybe String
csvRuleValue rules record = fmap (renderTemplate rules record) . csvRule rules -- csvRuleValue rules record = fmap (renderTemplate rules record) . csvRule rules
-- | Look up the value template assigned to a hledger field by field -- | Look up the value template assigned to a hledger field by field
-- list/field assignment rules, taking into account the current record and -- list/field assignment rules, taking into account the current record and
@ -775,7 +777,7 @@ hledgerField = getEffectiveAssignment
hledgerFieldValue :: CsvRules -> CsvRecord -> HledgerFieldName -> Maybe String hledgerFieldValue :: CsvRules -> CsvRecord -> HledgerFieldName -> Maybe String
hledgerFieldValue rules record = fmap (renderTemplate rules record) . hledgerField rules record hledgerFieldValue rules record = fmap (renderTemplate rules record) . hledgerField rules record
s `withDefault` def = if null s then def else s -- s `orIfNull` def = if null s then def else s
transactionFromCsvRecord :: SourcePos -> CsvRules -> CsvRecord -> Transaction transactionFromCsvRecord :: SourcePos -> CsvRules -> CsvRecord -> Transaction
transactionFromCsvRecord sourcepos rules record = t transactionFromCsvRecord sourcepos rules record = t
@ -828,64 +830,27 @@ transactionFromCsvRecord sourcepos rules record = t
precomment = maybe "" singleline $ fieldval "precomment" precomment = maybe "" singleline $ fieldval "precomment"
---------------------------------------------------------------------- ----------------------------------------------------------------------
-- 3. Generate the postings -- 3. Generate the postings for which an account has been assigned
-- (possibly indirectly due to an amount or balance assignment)
-- Make posting 1 if possible, with special support for old syntax to p1IsVirtual = (accountNamePostingType . T.pack <$> fieldval "account1") == Just VirtualPosting
-- support pre-1.16 rules. ps = [p | n <- [1..maxpostings]
posting1 = mkPosting rules record "1" ,let comment = T.pack $ fromMaybe "" $ fieldval ("comment"++show n)
("account1" `withAlias` "account") ,let currency = fromMaybe "" (fieldval ("currency"++show n) <|> fieldval "currency")
("amount1" `withAlias` "amount") ,let mamount = getAmount rules record currency p1IsVirtual n
("amount1-in" `withAlias` "amount-in") ,let mbalance = getBalance rules record currency n
("amount1-out" `withAlias` "amount-out") ,Just (acct,isfinal) <- [getAccount rules record mamount mbalance n] -- skips Nothings
("balance1" `withAlias` "balance") ,let acct' | not isfinal && acct==unknownExpenseAccount &&
"comment1" -- comment1 does not have legacy alias fromMaybe False (mamount >>= isNegativeMixedAmount) = unknownIncomeAccount
t | otherwise = acct
where ,let p = nullposting{paccount = accountNameWithoutPostingType acct'
withAlias fld alias = ,pamount = fromMaybe missingmixedamt mamount
case (field fld, field alias) of ,ptransaction = Just t
(Just fld, Just alias) -> error' $ unlines ,pbalanceassertion = mkBalanceAssertion rules record <$> mbalance
[ "error: both \"" ++ fld ++ "\" and \"" ++ alias ++ "\" have values." ,pcomment = comment
, showRecord record ,ptype = accountNamePostingType acct
, showRules rules record }
] ]
(Nothing, Just _) -> alias
(_, Nothing) -> fld
-- Make other postings where possible, and gather all that were generated.
postings = catMaybes $ posting1 : otherpostings
where
otherpostings = [mkPostingN i | x<-[2..9], let i = show x]
where
mkPostingN n = mkPosting rules record n
("account"++n) ("amount"++n) ("amount"++n++"-in")
("amount"++n++"-out") ("balance"++n) ("comment"++n) t
-- Auto-generate a second posting or second posting amount,
-- for compatibility with pre-1.16 rules.
postings' =
case postings of
-- when rules generate just one posting, of a kind that needs to be
-- balanced, generate the second posting to balance it.
[p1@(p1',_)] ->
if ptype p1' == VirtualPosting then [p1] else [p1, p2]
where
p2 = (nullposting{paccount=unknownExpenseAccount
,pamount=costOfMixedAmount (-pamount p1')
,ptransaction=Just t}, False)
-- when rules generate exactly two postings, and only the second has
-- no amount, give it the balancing amount.
[p1@(p1',_), p2@(p2',final2)] ->
if hasAmount p1' && not (hasAmount p2')
then [p1, (p2'{pamount=costOfMixedAmount(-(pamount p1'))}, final2)]
else [p1, p2]
--
ps -> ps
-- Finally, wherever default "unknown" accounts were used, refine them
-- based on the sign of the posting amount if it's now known.
postings'' = map maybeImprove postings'
where
maybeImprove (p,final) = if final then p else improveUnknownAccountName p
---------------------------------------------------------------------- ----------------------------------------------------------------------
-- 4. Build the transaction (and name it, so the postings can reference it). -- 4. Build the transaction (and name it, so the postings can reference it).
@ -899,98 +864,99 @@ transactionFromCsvRecord sourcepos rules record = t
,tdescription = T.pack description ,tdescription = T.pack description
,tcomment = T.pack comment ,tcomment = T.pack comment
,tprecedingcomment = T.pack precomment ,tprecedingcomment = T.pack precomment
,tpostings = postings'' ,tpostings = ps
} }
-- | Given CSV rules and a CSV record, generate the corresponding transaction's -- -- | Given CSV rules and a CSV record, generate the corresponding transaction's
-- Nth posting, if sufficient fields have been assigned for it. -- -- Nth posting, if sufficient fields have been assigned for it.
-- N is provided as a string. -- -- N is provided as a string.
-- The names of the required fields are provided, allowing more flexibility. -- -- The names of the required fields are provided, allowing more flexibility.
-- The transaction which will contain this posting is also provided, -- -- The transaction which will contain this posting is also provided,
-- so we can build the usual transaction<->posting cyclic reference. -- -- so we can build the usual transaction<->posting cyclic reference.
mkPosting :: -- mkPosting :: CsvRules -> CsvRecord -> String -> Transaction -> Maybe (Posting, Bool)
CsvRules -> CsvRecord -> String -> -- mkPosting rules record n t =
HledgerFieldName -> HledgerFieldName -> HledgerFieldName ->
HledgerFieldName -> HledgerFieldName -> HledgerFieldName -> -- | Figure out the amount specified for posting N, if any.
Transaction -> -- Looks for a non-zero amount assigned to one of "amountN", "amountN-in", "amountN-out".
Maybe (Posting, Bool) -- Postings 1 or 2 also look at "amount", "amount-in", "amount-out".
mkPosting rules record number accountFld amountFld amountInFld amountOutFld balanceFld commentFld t = -- Throws an error if more than one of these has a non-zero amount assigned.
-- if we have figured out an account N, make a posting N -- A currency symbol to prepend to the amount, if any, is provided,
case maccountAndIsFinal of -- and whether posting 1 requires balancing or not.
Nothing -> Nothing getAmount :: CsvRules -> CsvRecord -> String -> Bool -> Int -> Maybe MixedAmount
Just (acct, final) -> getAmount rules record currency p1IsVirtual n =
Just (posting{paccount = accountNameWithoutPostingType acct let
,pamount = fromMaybe missingmixedamt mamount unnumberedfieldnames = ["amount","amount-in","amount-out"]
,ptransaction = Just t fieldnames = map (("amount"++show n)++) ["","-in","-out"]
,pbalanceassertion = mkBalanceAssertion rules record <$> mbalance -- For posting 1, also recognise the old amount/amount-in/amount-out names.
,pcomment = comment -- For posting 2, the same but only if posting 1 needs balancing.
,ptype = accountNamePostingType acct} ++ if n==1 || n==2 && not p1IsVirtual then unnumberedfieldnames else []
,final) nonzeroamounts = [(f,a') | f <- fieldnames
, Just v@(_:_) <- [strip . renderTemplate rules record <$> hledgerField rules record f]
, let a = parseAmount rules record currency v
, not $ isZeroMixedAmount a
-- With amount/amount-in/amount-out, in posting 2,
-- flip the sign and convert to cost, as they did before 1.17
, let a' = if f `elem` unnumberedfieldnames && n==2 then costOfMixedAmount (-a) else a
]
in case nonzeroamounts of
[] -> Nothing
[(f,a)] | "-out" `isSuffixOf` f -> Just (-a) -- for -out fields, flip the sign
[(_,a)] -> Just a
fs -> error' $
"more than one non-zero amount for this record, please ensure just one\n"
++ unlines [" " ++ padright 11 f ++ ": " ++ showMixedAmount a
++ " from rule: " ++ fromMaybe "" (hledgerField rules record f)
| (f,a) <- fs]
++ " " ++ showRecord record ++ "\n"
where where
-- the account name to use for this posting, if any, and whether it is the -- | Given a non-empty amount string to parse, along with a possibly
-- default unknown account, which may be improved later, or an explicitly -- non-empty currency symbol to prepend, parse as a hledger amount (as
-- set account, which may not. -- in journal format), or raise an error.
maccountAndIsFinal :: Maybe (AccountName, Bool) = -- The CSV rules and record are provided for the error message.
case maccount of parseAmount :: CsvRules -> CsvRecord -> String -> String -> MixedAmount
-- accountN is set to the empty string - no posting will be generated parseAmount rules record currency amountstr =
Just "" -> Nothing either mkerror (Mixed . (:[])) $
-- accountN is set (possibly to "expenses:unknown"! #1192) - mark it final
Just a -> Just (a, True)
-- accountN is unset
Nothing ->
case (mamount, mbalance) of
-- amountN is set, or implied by balanceN - set accountN to
-- the default unknown account ("expenses:unknown") and
-- allow it to be improved later
(Just _, _) -> Just (unknownExpenseAccount, False)
(_, Just _) -> Just (unknownExpenseAccount, False)
-- amountN is also unset - no posting will be generated
(Nothing, Nothing) -> Nothing
where
maccount = T.pack <$> (fieldval accountFld
-- XXX what's this needed for ? Test & document, or drop.
-- Also, this the only place we interpolate in a keyword rule, I think.
`withDefault` ruleval ("default-account" ++ number))
-- XXX what's this needed for ? Test & document, or drop.
mdefaultcurrency = rule "default-currency"
currency = fromMaybe (fromMaybe "" mdefaultcurrency) $
fieldval ("currency"++number) `withDefault` fieldval "currency"
mamount = chooseAmount rules record currency amountFld amountInFld amountOutFld
mbalance :: Maybe (Amount, GenericSourcePos) =
fieldval balanceFld >>= parsebalance currency number
where
parsebalance currency n str
| all isSpace str = Nothing
| otherwise = Just
(either (balanceerror n str) id $
runParser (evalStateT (amountp <* eof) nulljournal) "" $ runParser (evalStateT (amountp <* eof) nulljournal) "" $
T.pack $ (currency++) $ simplifySign str T.pack $ (currency++) $ simplifySign amountstr
where
mkerror e = error' $ unlines
["error: could not parse \""++amountstr++"\" as an amount"
,showRecord record
,showRules rules record
-- ,"the default-currency is: "++fromMaybe "unspecified" (getDirective "default-currency" rules)
,"the parse error is: "++customErrorBundlePretty e
,"you may need to "
++"change your amount*, balance*, or currency* rules, "
++"or add or change your skip rule"
]
-- | Figure out the expected balance (assertion or assignment) specified for posting N,
-- if any (and its parse position).
getBalance :: CsvRules -> CsvRecord -> String -> Int -> Maybe (Amount, GenericSourcePos)
getBalance rules record currency n =
(fieldval ("balance"++show n)
-- for posting 1, also recognise the old field name
<|> if n==1 then fieldval "balance" else Nothing)
>>= parsebalance currency n . strip
where
parsebalance currency n s
| null s = Nothing
| otherwise = Just
(either (mkerror n s) id $
runParser (evalStateT (amountp <* eof) nulljournal) "" $
T.pack $ (currency++) $ simplifySign s
,nullsourcepos) -- XXX parse position to show when assertion fails, ,nullsourcepos) -- XXX parse position to show when assertion fails,
-- the csv record's line number would be good -- the csv record's line number would be good
where where
balanceerror n str err = error' $ unlines mkerror n s e = error' $ unlines
["error: could not parse \""++str++"\" as balance"++n++" amount" ["error: could not parse \""++s++"\" as balance"++show n++" amount"
,showRecord record ,showRecord record
,showRules rules record ,showRules rules record
,"the default-currency is: "++fromMaybe "unspecified" mdefaultcurrency -- ,"the default-currency is: "++fromMaybe "unspecified" mdefaultcurrency
,"the parse error is: "++customErrorBundlePretty err ,"the parse error is: "++customErrorBundlePretty e
] ]
comment = T.pack $ fromMaybe "" $ fieldval commentFld -- mdefaultcurrency = rule "default-currency"
rule = csvRule rules :: DirectiveName -> Maybe FieldTemplate
ruleval = csvRuleValue rules record :: DirectiveName -> Maybe String
-- field = hledgerField rules record :: HledgerFieldName -> Maybe FieldTemplate
fieldval = hledgerFieldValue rules record :: HledgerFieldName -> Maybe String fieldval = hledgerFieldValue rules record :: HledgerFieldName -> Maybe String
-- | Default account names to use when needed.
unknownExpenseAccount = "expenses:unknown"
unknownIncomeAccount = "income:unknown"
-- | If this posting has the "expenses:unknown" account name,
-- replace that with "income:unknown" if the amount is negative.
-- The posting's amount should be explicit.
improveUnknownAccountName p@Posting{..}
| paccount == unknownExpenseAccount
&& fromMaybe False (isNegativeMixedAmount pamount) = p{paccount=unknownIncomeAccount}
| otherwise = p
-- | Make a balance assertion for the given amount, with the given parse -- | Make a balance assertion for the given amount, with the given parse
-- position (to be shown in assertion failures), with the assertion type -- position (to be shown in assertion failures), with the assertion type
@ -1013,48 +979,33 @@ mkBalanceAssertion rules record (amt, pos) = assrt{baamount=amt, baposition=pos}
, showRules rules record , showRules rules record
] ]
chooseAmount :: CsvRules -> CsvRecord -> String -> String -> String -> String -> Maybe MixedAmount -- | Figure out the account name specified for posting N, if any.
chooseAmount rules record currency amountFld amountInFld amountOutFld = -- And whether it is the default unknown account (which may be
-- improved later) or an explicitly set account (which may not).
getAccount :: CsvRules -> CsvRecord -> Maybe MixedAmount -> Maybe (Amount, GenericSourcePos) -> Int -> Maybe (AccountName, Bool)
getAccount rules record mamount mbalance n =
let let
mamount = getEffectiveAssignment rules record amountFld fieldval = hledgerFieldValue rules record :: HledgerFieldName -> Maybe String
mamountin = getEffectiveAssignment rules record amountInFld maccount = T.pack <$> fieldval ("account"++show n)
mamountout = getEffectiveAssignment rules record amountOutFld in case maccount of
parse amt = notZero =<< (parseAmount currency <$> notEmpty =<< (strip . renderTemplate rules record) <$> amt) -- accountN is set to the empty string - no posting will be generated
in Just "" -> Nothing
case (parse mamount, parse mamountin, parse mamountout) of -- accountN is set (possibly to "expenses:unknown"! #1192) - mark it final
(Nothing, Nothing, Nothing) -> Nothing Just a -> Just (a, True)
(Just a, Nothing, Nothing) -> Just a -- accountN is unset
(Nothing, Just i, Nothing) -> Just i Nothing ->
(Nothing, Nothing, Just o) -> Just $ negate o case (mamount, mbalance) of
(Nothing, Just i, Just o) -> error' $ "both "++amountInFld++" and "++amountOutFld++" have a value\n" -- amountN is set, or implied by balanceN - set accountN to
++ " "++amountInFld++": " ++ show i ++ "\n" -- the default unknown account ("expenses:unknown") and
++ " "++amountOutFld++": " ++ show o ++ "\n" -- allow it to be improved later
++ " record: " ++ showRecord record (Just _, _) -> Just (unknownExpenseAccount, False)
_ -> error' $ "found values for "++amountFld++" and for "++amountInFld++"/"++amountOutFld++"\n" (_, Just _) -> Just (unknownExpenseAccount, False)
++ "please use either "++amountFld++" or "++amountInFld++"/"++amountOutFld++"\n" -- amountN is also unset - no posting will be generated
++ " record: " ++ showRecord record (Nothing, Nothing) -> Nothing
where
notZero amt = if isZeroMixedAmount amt then Nothing else Just amt
notEmpty str = if str=="" then Nothing else Just str
parseAmount currency amountstr = -- | Default account names to use when needed.
either (amounterror amountstr) (Mixed . (:[])) unknownExpenseAccount = "expenses:unknown"
<$> runParser (evalStateT (amountp <* eof) nulljournal) "" unknownIncomeAccount = "income:unknown"
<$> T.pack
<$> (currency++)
<$> simplifySign
<$> amountstr
amounterror amountstr err = error' $ unlines
["error: could not parse \""++fromJust amountstr++"\" as an amount"
,showRecord record
,showRules rules record
,"the default-currency is: "++fromMaybe "unspecified" (getDirective "default-currency" rules)
,"the parse error is: "++customErrorBundlePretty err
,"you may need to "
++"change your amount or currency rules, "
++"or add or change your skip rule"
]
type CsvAmountString = String type CsvAmountString = String
@ -1088,7 +1039,7 @@ negateStr s = '-':s
-- | Show a (approximate) recreation of the original CSV record. -- | Show a (approximate) recreation of the original CSV record.
showRecord :: CsvRecord -> String showRecord :: CsvRecord -> String
showRecord r = "the CSV record is: "++intercalate "," (map show r) showRecord r = "record values: "++intercalate "," (map show r)
-- | Given the conversion rules, a CSV record and a hledger field name, find -- | Given the conversion rules, a CSV record and a hledger field name, find
-- the value template ultimately assigned to this field, if any, by a field -- the value template ultimately assigned to this field, if any, by a field

View File

@ -494,6 +494,9 @@ with that account name.
.PP .PP
Most often there are two postings, so you\[aq]ll want to set Most often there are two postings, so you\[aq]ll want to set
\f[C]account1\f[R] and \f[C]account2\f[R]. \f[C]account1\f[R] and \f[C]account2\f[R].
Typically \f[C]account1\f[R] is associated with the CSV file, and is set
once with a top-level assignment, while \f[C]account2\f[R] is set based
on each transaction\[aq]s description, and in conditional blocks.
.PP .PP
If a posting\[aq]s account name is left unset but its amount is set (see If a posting\[aq]s account name is left unset but its amount is set (see
below), a default account name will be chosen (like below), a default account name will be chosen (like
@ -501,38 +504,30 @@ below), a default account name will be chosen (like
.SS amount .SS amount
.PP .PP
\f[C]amountN\f[R] sets posting N\[aq]s amount. \f[C]amountN\f[R] sets posting N\[aq]s amount.
If the CSV uses separate fields for debit and credit amounts, you can
use \f[C]amountN-in\f[R] and \f[C]amountN-out\f[R] instead.
.PP .PP
Or if the CSV has debits and credits in two separate fields, use Also, for compatibility with hledger <1.17: \f[C]amount\f[R] or
\f[C]amountN-in\f[R] and \f[C]amountN-out\f[R] instead. \f[C]amount-in\f[R]/\f[C]amount-out\f[R] with no number sets the amount
.PP for postings 1 and 2.
Some aliases and special behaviour exist to support older CSV rules For posting 2 the amount is negated, and converted to cost if
(before hledger 1.17): there\[aq]s a transaction price.
.IP \[bu] 2
if \f[C]amount1\f[R] is the only posting amount assigned, then a second
posting with the balancing amount will be generated automatically.
(Unless the account name is parenthesised indicating an unbalanced
posting.)
.IP \[bu] 2
\f[C]amount\f[R] is an alias for \f[C]amount1\f[R]
.IP \[bu] 2
\f[C]amount-in\f[R]/\f[C]amount-out\f[R] are aliases for
\f[C]amount1-in\f[R]/\f[C]amount1-out\f[R]
.PP
This can occasionally get in the way.
For example, currently it\[aq]s possible to generate a transaction with
a blank amount1, but not one with a blank amount2.
.SS currency .SS currency
.PP .PP
If the CSV has the currency symbol in a separate field (ie, not part of If the CSV has the currency symbol in a separate field (ie, not part of
the amount field), you can use \f[C]currencyN\f[R] to prepend it to the amount field), you can use \f[C]currencyN\f[R] to prepend it to
posting N\[aq]s amount. posting N\[aq]s amount.
Or, \f[C]currency\f[R] affects all postings. Or, \f[C]currency\f[R] with no number affects all postings.
.SS balance .SS balance
.PP .PP
\f[C]balanceN\f[R] sets a balance assertion amount (or if the posting \f[C]balanceN\f[R] sets a balance assertion amount (or if the posting
amount is left empty, a balance assignment). amount is left empty, a balance assignment) on posting N.
You may need to adjust this with the \f[C]balance-type\f[R] rule (see .PP
below). Also, for compatibility with hledger <1.17: \f[C]balance\f[R] with no
number is equivalent to \f[C]balance1\f[R].
.PP
You can adjust the type of assertion/assignment with the
\f[C]balance-type\f[R] rule (see below).
.SS comment .SS comment
.PP .PP
Finally, \f[C]commentN\f[R] sets a comment on the Nth posting. Finally, \f[C]commentN\f[R] sets a comment on the Nth posting.

View File

@ -469,7 +469,9 @@ File: hledger_csv.info, Node: account, Next: amount, Up: Posting field names
that account name. that account name.
Most often there are two postings, so you'll want to set 'account1' Most often there are two postings, so you'll want to set 'account1'
and 'account2'. and 'account2'. Typically 'account1' is associated with the CSV file,
and is set once with a top-level assignment, while 'account2' is set
based on each transaction's description, and in conditional blocks.
If a posting's account name is left unset but its amount is set (see If a posting's account name is left unset but its amount is set (see
below), a default account name will be chosen (like "expenses:unknown" below), a default account name will be chosen (like "expenses:unknown"
@ -481,24 +483,14 @@ File: hledger_csv.info, Node: amount, Next: currency, Prev: account, Up: Pos
2.2.2.2 amount 2.2.2.2 amount
.............. ..............
'amountN' sets posting N's amount. 'amountN' sets posting N's amount. If the CSV uses separate fields for
debit and credit amounts, you can use 'amountN-in' and 'amountN-out'
instead.
Or if the CSV has debits and credits in two separate fields, use Also, for compatibility with hledger <1.17: 'amount' or
'amountN-in' and 'amountN-out' instead. 'amount-in'/'amount-out' with no number sets the amount for postings 1
and 2. For posting 2 the amount is negated, and converted to cost if
Some aliases and special behaviour exist to support older CSV rules there's a transaction price.
(before hledger 1.17):
* if 'amount1' is the only posting amount assigned, then a second
posting with the balancing amount will be generated automatically.
(Unless the account name is parenthesised indicating an unbalanced
posting.)
* 'amount' is an alias for 'amount1'
* 'amount-in'/'amount-out' are aliases for 'amount1-in'/'amount1-out'
This can occasionally get in the way. For example, currently it's
possible to generate a transaction with a blank amount1, but not one
with a blank amount2.
 
File: hledger_csv.info, Node: currency, Next: balance, Prev: amount, Up: Posting field names File: hledger_csv.info, Node: currency, Next: balance, Prev: amount, Up: Posting field names
@ -508,7 +500,7 @@ File: hledger_csv.info, Node: currency, Next: balance, Prev: amount, Up: Pos
If the CSV has the currency symbol in a separate field (ie, not part of If the CSV has the currency symbol in a separate field (ie, not part of
the amount field), you can use 'currencyN' to prepend it to posting N's the amount field), you can use 'currencyN' to prepend it to posting N's
amount. Or, 'currency' affects all postings. amount. Or, 'currency' with no number affects all postings.
 
File: hledger_csv.info, Node: balance, Next: comment, Prev: currency, Up: Posting field names File: hledger_csv.info, Node: balance, Next: comment, Prev: currency, Up: Posting field names
@ -517,7 +509,12 @@ File: hledger_csv.info, Node: balance, Next: comment, Prev: currency, Up: Po
............... ...............
'balanceN' sets a balance assertion amount (or if the posting amount is 'balanceN' sets a balance assertion amount (or if the posting amount is
left empty, a balance assignment). You may need to adjust this with the left empty, a balance assignment) on posting N.
Also, for compatibility with hledger <1.17: 'balance' with no number
is equivalent to 'balance1'.
You can adjust the type of assertion/assignment with the
'balance-type' rule (see below). 'balance-type' rule (see below).
 
@ -1044,52 +1041,52 @@ Node: Posting field names16638
Ref: #posting-field-names16790 Ref: #posting-field-names16790
Node: account16860 Node: account16860
Ref: #account16976 Ref: #account16976
Node: amount17320 Node: amount17512
Ref: #amount17451 Ref: #amount17643
Node: currency18195 Node: currency18024
Ref: #currency18330 Ref: #currency18159
Node: balance18521 Node: balance18365
Ref: #balance18655 Ref: #balance18499
Node: comment18834 Node: comment18816
Ref: #comment18951 Ref: #comment18933
Node: field assignment19114 Node: field assignment19096
Ref: #field-assignment19257 Ref: #field-assignment19239
Node: separator20075 Node: separator20057
Ref: #separator20204 Ref: #separator20186
Node: if20615 Node: if20597
Ref: #if20717 Ref: #if20699
Node: end22636 Node: end22618
Ref: #end22742 Ref: #end22724
Node: date-format22966 Node: date-format22948
Ref: #date-format23098 Ref: #date-format23080
Node: newest-first23847 Node: newest-first23829
Ref: #newest-first23985 Ref: #newest-first23967
Node: include24668 Node: include24650
Ref: #include24797 Ref: #include24779
Node: balance-type25241 Node: balance-type25223
Ref: #balance-type25361 Ref: #balance-type25343
Node: TIPS26061 Node: TIPS26043
Ref: #tips26143 Ref: #tips26125
Node: Rapid feedback26399 Node: Rapid feedback26381
Ref: #rapid-feedback26516 Ref: #rapid-feedback26498
Node: Valid CSV26976 Node: Valid CSV26958
Ref: #valid-csv27106 Ref: #valid-csv27088
Node: File Extension27298 Node: File Extension27280
Ref: #file-extension27450 Ref: #file-extension27432
Node: Reading multiple CSV files27860 Node: Reading multiple CSV files27842
Ref: #reading-multiple-csv-files28045 Ref: #reading-multiple-csv-files28027
Node: Valid transactions28286 Node: Valid transactions28268
Ref: #valid-transactions28464 Ref: #valid-transactions28446
Node: Deduplicating importing29092 Node: Deduplicating importing29074
Ref: #deduplicating-importing29271 Ref: #deduplicating-importing29253
Node: Setting amounts30304 Node: Setting amounts30286
Ref: #setting-amounts30473 Ref: #setting-amounts30455
Node: Setting currency/commodity31459 Node: Setting currency/commodity31441
Ref: #setting-currencycommodity31651 Ref: #setting-currencycommodity31633
Node: Referencing other fields32454 Node: Referencing other fields32436
Ref: #referencing-other-fields32654 Ref: #referencing-other-fields32636
Node: How CSV rules are evaluated33551 Node: How CSV rules are evaluated33533
Ref: #how-csv-rules-are-evaluated33724 Ref: #how-csv-rules-are-evaluated33706
 
End Tag Table End Tag Table

View File

@ -418,6 +418,8 @@ For more about the transaction parts they refer to, see the manual for hledger's
with that account name. with that account name.
Most often there are two postings, so you'll want to set `account1` and `account2`. Most often there are two postings, so you'll want to set `account1` and `account2`.
Typically `account1` is associated with the CSV file, and is set once with a top-level assignment,
while `account2` is set based on each transaction's description, and in conditional blocks.
If a posting's account name is left unset but its amount is set (see below), If a posting's account name is left unset but its amount is set (see below),
a default account name will be chosen (like "expenses:unknown" or "income:unknown"). a default account name will be chosen (like "expenses:unknown" or "income:unknown").
@ -425,31 +427,31 @@ a default account name will be chosen (like "expenses:unknown" or "income:unknow
#### amount #### amount
`amountN` sets posting N's amount. `amountN` sets posting N's amount.
If the CSV uses separate fields for debit and credit amounts, you can
use `amountN-in` and `amountN-out` instead.
Or if the CSV has debits and credits in two separate fields, use `amountN-in` and `amountN-out` instead. Also, for compatibility with hledger <1.17:
`amount` or `amount-in`/`amount-out` with no number sets the amount
Some aliases and special behaviour exist to support older CSV rules (before hledger 1.17): for postings 1 and 2. For posting 2 the amount is negated, and
converted to cost if there's a [transaction price](journal.html#transaction-prices).
- if `amount1` is the only posting amount assigned, then a second posting
with the balancing amount will be generated automatically.
(Unless the account name is parenthesised indicating an [unbalanced posting](journal.html#virtual-postings).)
- `amount` is an alias for `amount1`
- `amount-in`/`amount-out` are aliases for `amount1-in`/`amount1-out`
This can occasionally get in the way. For example, currently it's possible to generate
a transaction with a blank amount1, but not one with a blank amount2.
#### currency #### currency
If the CSV has the currency symbol in a separate field (ie, not part If the CSV has the currency symbol in a separate field (ie, not part
of the amount field), you can use `currencyN` to prepend it to posting of the amount field), you can use `currencyN` to prepend it to posting
N's amount. Or, `currency` affects all postings. N's amount. Or, `currency` with no number affects all postings.
#### balance #### balance
`balanceN` sets a [balance assertion](journal.html#balance-assertions) amount `balanceN` sets a [balance assertion](journal.html#balance-assertions) amount
(or if the posting amount is left empty, a [balance assignment](journal.html#balance-assignments)). (or if the posting amount is left empty, a [balance assignment](journal.html#balance-assignments))
You may need to adjust this with the [`balance-type` rule](#balance-type) (see below). on posting N.
Also, for compatibility with hledger <1.17:
`balance` with no number is equivalent to `balance1`.
You can adjust the type of assertion/assignment with the
[`balance-type` rule](#balance-type) (see below).
#### comment #### comment

View File

@ -381,42 +381,38 @@ CSV RULES
that account name. that account name.
Most often there are two postings, so you'll want to set account1 and Most often there are two postings, so you'll want to set account1 and
account2. account2. Typically account1 is associated with the CSV file, and is
set once with a top-level assignment, while account2 is set based on
each transaction's description, and in conditional blocks.
If a posting's account name is left unset but its amount is set (see If a posting's account name is left unset but its amount is set (see
below), a default account name will be chosen (like "expenses:unknown" below), a default account name will be chosen (like "expenses:unknown"
or "income:unknown"). or "income:unknown").
amount amount
amountN sets posting N's amount. amountN sets posting N's amount. If the CSV uses separate fields for
debit and credit amounts, you can use amountN-in and amountN-out in-
stead.
Or if the CSV has debits and credits in two separate fields, use Also, for compatibility with hledger <1.17: amount or amount-in/amount-
amountN-in and amountN-out instead. out with no number sets the amount for postings 1 and 2. For posting 2
the amount is negated, and converted to cost if there's a transaction
Some aliases and special behaviour exist to support older CSV rules price.
(before hledger 1.17):
o if amount1 is the only posting amount assigned, then a second posting
with the balancing amount will be generated automatically. (Unless
the account name is parenthesised indicating an unbalanced posting.)
o amount is an alias for amount1
o amount-in/amount-out are aliases for amount1-in/amount1-out
This can occasionally get in the way. For example, currently it's pos-
sible to generate a transaction with a blank amount1, but not one with
a blank amount2.
currency currency
If the CSV has the currency symbol in a separate field (ie, not part of If the CSV has the currency symbol in a separate field (ie, not part of
the amount field), you can use currencyN to prepend it to posting N's the amount field), you can use currencyN to prepend it to posting N's
amount. Or, currency affects all postings. amount. Or, currency with no number affects all postings.
balance balance
balanceN sets a balance assertion amount (or if the posting amount is balanceN sets a balance assertion amount (or if the posting amount is
left empty, a balance assignment). You may need to adjust this with left empty, a balance assignment) on posting N.
the balance-type rule (see below).
Also, for compatibility with hledger <1.17: balance with no number is
equivalent to balance1.
You can adjust the type of assertion/assignment with the balance-type
rule (see below).
comment comment
Finally, commentN sets a comment on the Nth posting. Comments can also Finally, commentN sets a comment on the Nth posting. Comments can also

View File

@ -220,7 +220,7 @@ account4 the:remainder
$ ./csvtest.sh $ ./csvtest.sh
2009-09-10 Flubber Co 2009-09-10 Flubber Co
assets:myacct $50.000 = $321.000 assets:myacct $50.000 = $321.000
expenses:unknown = $123.000 income:unknown $-50.000 = $123.000
expenses:tax $0.234 ; VAT expenses:tax $0.234 ; VAT
the:remainder the:remainder
@ -241,7 +241,7 @@ account4 the:remainder
$ ./csvtest.sh $ ./csvtest.sh
2009-09-10 Flubber Co 2009-09-10 Flubber Co
assets:myacct $50 = $321 assets:myacct $50 = $321
expenses:unknown = $123 income:unknown $-50 = $123
expenses:tax £0.234 ; VAT expenses:tax £0.234 ; VAT
the:remainder the:remainder
@ -472,7 +472,7 @@ $ ./csvtest.sh
2018-12-22 (10101010101) Someone for Joyful Systems 2018-12-22 (10101010101) Someone for Joyful Systems
sm:assets:online:paypal $7.77 = $88.66 sm:assets:online:paypal $7.77 = $88.66
sm:expenses:unknown $-7.77 sm:expenses:unknown
>=0 >=0
@ -613,15 +613,16 @@ $ ./csvtest.sh
>=0 >=0
# 31. Currently can't generate a transaction with amount on the first posting only. XXX # 31. Can generate a transaction with amount on the first posting only.
< <
2020-01-01, 1 2020-01-01, 1
RULES RULES
fields date, amount1 fields date, amount1
account2 b
$ ./csvtest.sh $ ./csvtest.sh
2020-01-01 2020-01-01
expenses:unknown 1 expenses:unknown 1
income:unknown -1 b
>=0 >=0
@ -630,23 +631,24 @@ $ ./csvtest.sh
2020-01-01, 1 2020-01-01, 1
RULES RULES
fields date, amount2 fields date, amount2
account1 asset account1 a
$ ./csvtest.sh $ ./csvtest.sh
2020-01-01 2020-01-01
asset a
expenses:unknown 1 expenses:unknown 1
>=0 >=0
# 33. If account1 is unset, the above doesn't work. Also amount2 appears to become amount1 ? XXX # 33. The old amount rules convert amount1 to cost in posting 2:
< <
2020-01-01, 1 2020-01-01, 1
RULES RULES
fields date, amount2 fields date, amt
amount %amt @@ 1 EUR
$ ./csvtest.sh $ ./csvtest.sh
2020-01-01 2020-01-01
expenses:unknown 1 expenses:unknown 1 @@ 1 EUR
income:unknown -1 income:unknown -1 EUR
>=0 >=0