mirror of
https://github.com/simonmichael/hledger.git
synced 2024-12-26 20:02:27 +03:00
imp: errors: more error prettification
This commit is contained in:
parent
84f951e020
commit
1c67d0860e
@ -115,11 +115,11 @@ transactionCheckBalanced BalancingOpts{commodity_styles_} t = errs
|
||||
where
|
||||
rmsg
|
||||
| rsumok = ""
|
||||
| not rsignsok = "The real postings all have the same sign."
|
||||
| not rsignsok = "The real postings all have the same sign. Consider negating some of them."
|
||||
| otherwise = "The real postings' sum should be 0 but is: " ++ showMixedAmountOneLine rsumcost
|
||||
bvmsg
|
||||
| bvsumok = ""
|
||||
| not bvsignsok = "The balanced virtual postings all have the same sign."
|
||||
| not bvsignsok = "The balanced virtual postings all have the same sign. Consider negating some of them."
|
||||
| otherwise = "The balanced virtual postings' sum should be 0 but is: " ++ showMixedAmountOneLine bvsumcost
|
||||
|
||||
-- | Legacy form of transactionCheckBalanced.
|
||||
@ -159,22 +159,34 @@ balanceTransactionHelper bopts t = do
|
||||
[] -> Right (txnTieKnot t', inferredamtsandaccts)
|
||||
errs -> Left $ transactionBalanceError t' errs'
|
||||
where
|
||||
errs' = errs ++
|
||||
[ "Inference of conversion costs has been disallowed."
|
||||
ismulticommodity = (length $ transactionCommodities t') > 1
|
||||
errs' =
|
||||
[ "Automatic commodity conversion is not enabled."
|
||||
| ismulticommodity && not (infer_transaction_prices_ bopts)
|
||||
] ++
|
||||
errs ++
|
||||
if ismulticommodity
|
||||
then
|
||||
[ "Consider adjusting this entry's amounts, adding missing postings,"
|
||||
, "or recording conversion price(s) with @, @@ or equity postings."
|
||||
]
|
||||
where
|
||||
ismulticommodity = (length $ mconcat $ map (maCommodities . pamount) $ tpostings t') > 1
|
||||
else
|
||||
[ "Consider adjusting this entry's amounts, or adding missing postings."
|
||||
]
|
||||
|
||||
transactionCommodities :: Transaction -> S.Set CommoditySymbol
|
||||
transactionCommodities t = mconcat $ map (maCommodities . pamount) $ tpostings t
|
||||
|
||||
-- | Generate a transaction balancing error message, given the transaction
|
||||
-- and one or more suberror messages.
|
||||
transactionBalanceError :: Transaction -> [String] -> String
|
||||
transactionBalanceError t errs = printf "%s:\n%s\n\n%s\n%s"
|
||||
transactionBalanceError t errs = printf "%s:\n%s\n\nThis %stransaction is unbalanced.\n%s"
|
||||
(sourcePosPairPretty $ tsourcepos t)
|
||||
(textChomp ex)
|
||||
("This transaction is unbalanced."::String)
|
||||
(if ismulticommodity then "multi-commodity " else "" :: String)
|
||||
(chomp $ unlines errs)
|
||||
where
|
||||
ismulticommodity = (length $ transactionCommodities t) > 1
|
||||
(_f,_l,_mcols,ex) = makeTransactionErrorExcerpt t finderrcols
|
||||
where
|
||||
finderrcols _ = Nothing
|
||||
@ -591,12 +603,16 @@ checkBalanceAssertionOneCommodityB p@Posting{paccount=assertedacct} assertedamt
|
||||
-- "display precision: %d",
|
||||
"this balance was asserted: %s", -- (at display precision: %s)",
|
||||
"but the actual balance is: %s", -- (at display precision: %s)",
|
||||
"a difference of: %s"
|
||||
"a difference of: %s",
|
||||
"",
|
||||
"Consider viewing this account's register to troubleshoot. Eg:",
|
||||
"",
|
||||
"hledger reg -I '%s'%s"
|
||||
])
|
||||
(sourcePosPretty pos)
|
||||
(textChomp ex)
|
||||
-- (showDate $ postingDate p)
|
||||
(T.unpack $ paccount p) -- XXX pack
|
||||
acct
|
||||
(if isinclusive then " (including subaccounts)" else "" :: String)
|
||||
assertedcomm
|
||||
(if istotal then " (no other commodity balance allowed)" else "" :: String)
|
||||
@ -606,7 +622,10 @@ checkBalanceAssertionOneCommodityB p@Posting{paccount=assertedacct} assertedamt
|
||||
(show $ aquantity actualbalincomm)
|
||||
-- (showAmount actualbalincommodity)
|
||||
(show $ aquantity assertedamt - aquantity actualbalincomm)
|
||||
(acct ++ if isinclusive then "" else "$")
|
||||
(if istotal then "" else (" cur:'"++T.unpack assertedcomm++"'"))
|
||||
where
|
||||
acct = T.unpack $ paccount p
|
||||
ass = fromJust $ pbalanceassertion p -- PARTIAL: fromJust won't fail, there is a balance assertion
|
||||
pos = baposition ass
|
||||
(_,_,_,ex) = makePostingErrorExcerpt p finderrcols
|
||||
@ -648,7 +667,7 @@ checkBalanceAssignmentPostingDateB :: Posting -> Balancing s ()
|
||||
checkBalanceAssignmentPostingDateB p =
|
||||
when (hasBalanceAssignment p && isJust (pdate p)) $
|
||||
throwError $ chomp $ unlines [
|
||||
"can't use balance assignment with custom posting date"
|
||||
"Balance assignments and custom posting dates may not be combined."
|
||||
,""
|
||||
,chomp1 $ T.unpack $ maybe (T.unlines $ showPostingLines p) showTransaction $ ptransaction p
|
||||
,"Balance assignments may not be used on postings with a custom posting date"
|
||||
@ -664,7 +683,7 @@ checkBalanceAssignmentUnassignableAccountB p = do
|
||||
unassignable <- R.asks bsUnassignable
|
||||
when (hasBalanceAssignment p && paccount p `S.member` unassignable) $
|
||||
throwError $ chomp $ unlines [
|
||||
"can't use balance assignment with auto postings"
|
||||
"Balance assignments and auto postings may not be combined."
|
||||
,""
|
||||
,chomp1 $ T.unpack $ maybe (T.unlines $ showPostingLines p) (showTransaction) $ ptransaction p
|
||||
,"Balance assignments may not be used on accounts affected by auto posting rules"
|
||||
|
@ -40,8 +40,16 @@ journalCheckAccounts j = mapM_ checkacct (journalPostings j)
|
||||
where
|
||||
checkacct p@Posting{paccount=a}
|
||||
| a `elem` journalAccountNamesDeclared j = Right ()
|
||||
| otherwise = Left $
|
||||
printf "%s:%d:\n%sundeclared account \"%s\"\n" f l ex a
|
||||
| otherwise = Left $ printf (unlines [
|
||||
"%s:%d:"
|
||||
,"%s"
|
||||
,"Strict account checking is enabled, and"
|
||||
,"account %s has not been declared."
|
||||
,"Consider adding an account directive. Examples:"
|
||||
,""
|
||||
,"account %s"
|
||||
,"account %s ; type:A ; (L,E,R,X,C,V)"
|
||||
]) f l ex (show a) a a
|
||||
where
|
||||
(f,l,_mcols,ex) = makePostingErrorExcerpt p finderrcols
|
||||
-- Calculate columns suitable for highlighting the excerpt.
|
||||
@ -61,7 +69,16 @@ journalCheckCommodities j = mapM_ checkcommodities (journalPostings j)
|
||||
case findundeclaredcomm p of
|
||||
Nothing -> Right ()
|
||||
Just (comm, _) ->
|
||||
Left $ printf "%s:%d:\n%sundeclared commodity \"%s\"\n" f l ex comm
|
||||
Left $ printf (unlines [
|
||||
"%s:%d:"
|
||||
,"%s"
|
||||
,"Strict commodity checking is enabled, and"
|
||||
,"commodity %s has not been declared."
|
||||
,"Consider adding a commodity directive. Examples:"
|
||||
,""
|
||||
,"commodity %s1000.00"
|
||||
,"commodity 1.000,00 %s"
|
||||
]) f l ex (show comm) comm comm
|
||||
where
|
||||
(f,l,_mcols,ex) = makePostingErrorExcerpt p finderrcols
|
||||
where
|
||||
@ -122,7 +139,15 @@ journalCheckPayees j = mapM_ checkpayee (jtxns j)
|
||||
checkpayee t
|
||||
| payee `elem` journalPayeesDeclared j = Right ()
|
||||
| otherwise = Left $
|
||||
printf "%s:%d:\n%sundeclared payee \"%s\"\n" f l ex payee
|
||||
printf (unlines [
|
||||
"%s:%d:"
|
||||
,"%s"
|
||||
,"Strict payee checking is enabled, and"
|
||||
,"payee %s has not been declared."
|
||||
,"Consider adding a payee directive. Examples:"
|
||||
,""
|
||||
,"payee %s"
|
||||
]) f l ex (show payee) payee
|
||||
where
|
||||
payee = transactionPayee t
|
||||
(f,l,_mcols,ex) = makeTransactionErrorExcerpt t finderrcols
|
||||
|
@ -6,10 +6,12 @@ where
|
||||
import Control.Monad (forM)
|
||||
import Data.List (groupBy)
|
||||
import Text.Printf (printf)
|
||||
import qualified Data.Text as T (pack, unlines)
|
||||
|
||||
import Hledger.Data.Errors (makeTransactionErrorExcerpt)
|
||||
import Hledger.Data.Transaction (transactionFile, transactionDateOrDate2)
|
||||
import Hledger.Data.Types
|
||||
import Hledger.Utils (textChomp)
|
||||
|
||||
journalCheckOrdereddates :: WhichDate -> Journal -> Either String ()
|
||||
journalCheckOrdereddates whichdate j = do
|
||||
@ -25,13 +27,17 @@ journalCheckOrdereddates whichdate j = do
|
||||
FoldAcc{fa_previous=Nothing} -> Right ()
|
||||
FoldAcc{fa_error=Nothing} -> Right ()
|
||||
FoldAcc{fa_error=Just t, fa_previous=Just tprev} -> Left $ printf
|
||||
"%s:%d:\n%stransaction date%s is out of order with previous transaction date %s"
|
||||
f l ex datenum tprevdate
|
||||
("%s:%d:\n%s\nOrdered dates checking is enabled, and this transaction's\n"
|
||||
++ "date%s (%s) is out of order with the previous transaction.\n"
|
||||
++ "Consider moving this entry into date order, or adjusting its date.")
|
||||
f l ex datenum (show $ getdate t)
|
||||
where
|
||||
(f,l,_mcols,ex) = makeTransactionErrorExcerpt t finderrcols
|
||||
(_,_,_,ex1) = makeTransactionErrorExcerpt tprev (const Nothing)
|
||||
(f,l,_,ex2) = makeTransactionErrorExcerpt t finderrcols
|
||||
-- separate the two excerpts by a space-beginning line to help flycheck-hledger parse them
|
||||
ex = T.unlines [textChomp ex1, T.pack " ", textChomp ex2]
|
||||
finderrcols _t = Just (1, Just 10)
|
||||
datenum = if whichdate==SecondaryDate then "2" else ""
|
||||
tprevdate = show $ getdate tprev
|
||||
|
||||
data FoldAcc a b = FoldAcc
|
||||
{ fa_error :: Maybe a
|
||||
|
@ -17,6 +17,7 @@ import Hledger.Data.Errors (makePostingErrorExcerpt)
|
||||
import Hledger.Data.Journal (journalPostings, journalAccountNamesUsed)
|
||||
import Hledger.Data.Posting (isVirtual)
|
||||
import Hledger.Data.Types
|
||||
import Hledger.Utils (chomp)
|
||||
|
||||
-- | Check that all the journal's postings are to accounts with a unique leaf name.
|
||||
-- Otherwise, return an error message for the first offending posting.
|
||||
@ -46,9 +47,13 @@ checkposting :: [(Text,[AccountName])] -> Posting -> Either String ()
|
||||
checkposting leafandfullnames p@Posting{paccount=a} =
|
||||
case [lf | lf@(_,fs) <- leafandfullnames, a `elem` fs] of
|
||||
[] -> Right ()
|
||||
(leaf,fulls):_ -> Left $ printf
|
||||
"%s:%d:\n%saccount leaf name \"%s\" is not unique\nit is used in account names: %s"
|
||||
f l ex leaf accts
|
||||
(leaf,fulls):_ -> Left $ chomp $ printf
|
||||
("%s:%d:\n%s\nChecking for unique account leaf names is enabled, and\n"
|
||||
++"account leaf name %s is not unique.\n"
|
||||
++"It appears in these account names:\n%s"
|
||||
++"\nConsider changing these account names so their last parts are different."
|
||||
)
|
||||
f l ex (show leaf) accts
|
||||
where
|
||||
-- t = fromMaybe nulltransaction ptransaction -- XXX sloppy
|
||||
(f,l,_mcols,ex) = makePostingErrorExcerpt p finderrcols
|
||||
@ -59,4 +64,4 @@ checkposting leafandfullnames p@Posting{paccount=a} =
|
||||
llen = T.length $ accountLeafName a
|
||||
col = 5 + (if isVirtual p then 1 else 0) + alen - llen
|
||||
col2 = col + llen - 1
|
||||
accts = T.intercalate ", " $ map (("\""<>).(<>"\"")) fulls
|
||||
accts = T.unlines fulls -- $ map (("\""<>).(<>"\"")) fulls
|
||||
|
@ -498,11 +498,12 @@ datep' mYear = do
|
||||
let dateStr = show year ++ [sep1] ++ show month ++ [sep2] ++ show day
|
||||
|
||||
when (sep1 /= sep2) $ customFailure $ parseErrorAtRegion startOffset endOffset $
|
||||
"invalid date: separators are different, should be the same"
|
||||
"This date is malformed because the separators are different.\n"
|
||||
++"Please use consistent separators."
|
||||
|
||||
case fromGregorianValid year month day of
|
||||
Nothing -> customFailure $ parseErrorAtRegion startOffset endOffset $
|
||||
"well-formed but invalid date: " ++ dateStr
|
||||
"This date is invalid, please correct it: " ++ dateStr
|
||||
Just date -> pure $! date
|
||||
|
||||
partialDate :: Int -> Maybe Year -> Month -> Char -> MonthDay -> TextParser m Day
|
||||
@ -512,12 +513,13 @@ datep' mYear = do
|
||||
Just year ->
|
||||
case fromGregorianValid year month day of
|
||||
Nothing -> customFailure $ parseErrorAtRegion startOffset endOffset $
|
||||
"well-formed but invalid date: " ++ dateStr
|
||||
"This date is invalid, please correct it: " ++ dateStr
|
||||
Just date -> pure $! date
|
||||
where dateStr = show year ++ [sep] ++ show month ++ [sep] ++ show day
|
||||
|
||||
Nothing -> customFailure $ parseErrorAtRegion startOffset endOffset $
|
||||
"partial date "++dateStr++" found, but the current year is unknown"
|
||||
"The partial date "++dateStr++" can not be parsed because the current year is unknown.\n"
|
||||
++"Consider making it a full date, or add a default year directive.\n"
|
||||
where dateStr = show month ++ [sep] ++ show day
|
||||
|
||||
{-# INLINABLE datep' #-}
|
||||
|
@ -134,7 +134,7 @@ toRegexCI = memo $ \s -> mkRegexErr s (RegexpCI s <$> makeRegexOptsM defaultComp
|
||||
-- | Make a nice error message for a regexp error.
|
||||
mkRegexErr :: Text -> Maybe a -> Either RegexError a
|
||||
mkRegexErr s = maybe (Left errmsg) Right
|
||||
where errmsg = T.unpack $ "this regular expression could not be compiled: " <> s
|
||||
where errmsg = T.unpack $ "This regular expression is malformed, please correct it:\n" <> s
|
||||
|
||||
-- Convert a Regexp string to a compiled Regex, throw an error
|
||||
toRegex' :: Text -> Regexp
|
||||
|
@ -120,8 +120,10 @@ parseErrorAtRegion
|
||||
-> HledgerParseErrorData
|
||||
parseErrorAtRegion startOffset endOffset msg =
|
||||
if startOffset < endOffset
|
||||
then ErrorFailAt startOffset endOffset msg
|
||||
else ErrorFailAt startOffset (startOffset+1) msg
|
||||
then ErrorFailAt startOffset endOffset msg'
|
||||
else ErrorFailAt startOffset (startOffset+1) msg'
|
||||
where
|
||||
msg' = "\n" ++ msg
|
||||
|
||||
|
||||
--- * Re-parsing
|
||||
|
@ -10,7 +10,7 @@ $ hledger -f- check accounts
|
||||
2020-01-01
|
||||
(a) 1
|
||||
$ hledger -f- check accounts
|
||||
>2 /undeclared account "a"/
|
||||
>2 /account "a" has not been declared/
|
||||
>=1
|
||||
|
||||
# 3. also fails for forecast accounts
|
||||
@ -20,12 +20,12 @@ account a
|
||||
a $1
|
||||
b
|
||||
$ hledger -f- --today 2022-01-01 --forecast check accounts
|
||||
>2 /undeclared account "b"/
|
||||
>2 /account "b" has not been declared/
|
||||
>=1
|
||||
|
||||
# 4. also fails in --strict mode
|
||||
$ hledger -f- --today 2022-01-01 --forecast --strict bal
|
||||
>2 /undeclared account "b"/
|
||||
>2 /account "b" has not been declared/
|
||||
>=1
|
||||
|
||||
# 5. also fails for auto accounts
|
||||
@ -40,10 +40,10 @@ account a
|
||||
|
||||
2022-02-01
|
||||
$ hledger -f- --auto check accounts
|
||||
>2 /undeclared account "b"/
|
||||
>2 /account "b" has not been declared/
|
||||
>=1
|
||||
|
||||
# 6. also fails in --strict mode
|
||||
$ hledger -f- --auto --strict bal
|
||||
>2 /undeclared account "b"/
|
||||
>2 /account "b" has not been declared/
|
||||
>=1
|
||||
|
@ -10,7 +10,7 @@ $ hledger -f- check commodities
|
||||
2020-01-01
|
||||
(a) $1
|
||||
$ hledger -f- check commodities
|
||||
>2 /undeclared commodity "\$"/
|
||||
>2 /commodity "\$" has not been declared/
|
||||
>=1
|
||||
|
||||
# 3. But commodityless zero amounts will not fail
|
||||
@ -27,5 +27,5 @@ $ hledger -f- check commodities
|
||||
(a) $0
|
||||
|
||||
$ hledger -f- check commodities
|
||||
>2 /undeclared commodity "\$"/
|
||||
>2 /commodity "\$" has not been declared/
|
||||
>=1
|
||||
|
@ -12,7 +12,7 @@ $ hledger -f- check ordereddates
|
||||
2020-01-01
|
||||
(a) 1
|
||||
$ hledger -f- check ordereddates
|
||||
>2 /transaction date is out of order/
|
||||
>2 /date .*is out of order/
|
||||
>=1
|
||||
|
||||
# With --date2, it checks secondary dates instead
|
||||
@ -26,7 +26,7 @@ $ hledger -f- check ordereddates --date2
|
||||
2020-01-01=2020-01-03
|
||||
2020-01-02
|
||||
$ hledger -f- check ordereddates --date2
|
||||
>2 /transaction date2 is out of order/
|
||||
>2 /date2 .*is out of order/
|
||||
>=1
|
||||
|
||||
# XXX not supported: With a query, only matched transactions' dates are checked.
|
||||
|
@ -9,7 +9,7 @@ $ hledger -f - check payees
|
||||
<
|
||||
2020-01-01 foo
|
||||
$ hledger -f - check payees
|
||||
>2 /undeclared payee "foo"/
|
||||
>2 /payee "foo" has not been declared/
|
||||
>=1
|
||||
|
||||
# or:
|
||||
@ -17,5 +17,5 @@ $ hledger -f - check payees
|
||||
payee foo
|
||||
2020-01-01 the payee | foo
|
||||
$ hledger -f - check payees
|
||||
>2 /undeclared payee "the payee"/
|
||||
>2 /payee "the payee" has not been declared/
|
||||
>=1
|
||||
|
@ -160,7 +160,7 @@ $ hledger -f- print --auto -x
|
||||
|
||||
# 9.
|
||||
$ hledger print -f- --auto
|
||||
>2 /can't use balance assignment with auto postings/
|
||||
>2 /Balance assignments and auto postings may not be combined/
|
||||
>=1
|
||||
|
||||
|
||||
|
@ -225,7 +225,7 @@ $ hledger -f - stats
|
||||
b =$-1 ; date:2012/1/1
|
||||
|
||||
$ hledger -f - stats
|
||||
>2 /can't use balance assignment with custom posting date/
|
||||
>2 /Balance assignments and custom posting dates may not be combined/
|
||||
>=1
|
||||
|
||||
# 13. Posting Date
|
||||
|
@ -5,7 +5,7 @@ hledger -f- print
|
||||
2010/31/12 x
|
||||
a 1
|
||||
b
|
||||
>>>2 /invalid date/
|
||||
>>>2 /date is invalid/
|
||||
>>>= 1
|
||||
# 2. too-large day
|
||||
hledger -f- print
|
||||
@ -13,7 +13,7 @@ hledger -f- print
|
||||
2010/12/32 x
|
||||
a 1
|
||||
b
|
||||
>>>2 /invalid date/
|
||||
>>>2 /date is invalid/
|
||||
>>>= 1
|
||||
# 3. 29th feb on leap year should be ok
|
||||
hledger -f- print
|
||||
@ -33,7 +33,7 @@ hledger -f- print
|
||||
2001/2/29 x
|
||||
a 1
|
||||
b
|
||||
>>>2 /invalid date/
|
||||
>>>2 /date is invalid/
|
||||
>>>= 1
|
||||
# 5. dates must be followed by whitespace or newline
|
||||
hledger -f- print
|
||||
|
@ -128,8 +128,10 @@ hledger: Error: -:1-3:
|
||||
| a 1A
|
||||
| b 1B
|
||||
|
||||
This transaction is unbalanced.
|
||||
The real postings all have the same sign.
|
||||
This multi-commodity transaction is unbalanced.
|
||||
The real postings all have the same sign. Consider negating some of them.
|
||||
Consider adjusting this entry's amounts, adding missing postings,
|
||||
or recording conversion price(s) with @, @@ or equity postings.
|
||||
>=1
|
||||
|
||||
# 12. Typical "hledger equity --close" transaction does not trigger sign error.
|
||||
|
Loading…
Reference in New Issue
Block a user