Merge pull request #1885 from simonmichael/errors
Catalog, test and improve error messages
This commit is contained in:
		
						commit
						7ecfe23a91
					
				| @ -115,12 +115,12 @@ transactionCheckBalanced BalancingOpts{commodity_styles_} t = errs | ||||
|       where | ||||
|         rmsg | ||||
|           | rsumok        = "" | ||||
|           | not rsignsok  = "real postings all have the same sign" | ||||
|           | otherwise     = "real postings' sum should be 0 but is: " ++ showMixedAmount rsumcost | ||||
|           | 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 = "balanced virtual postings all have the same sign" | ||||
|           | otherwise     = "balanced virtual postings' sum should be 0 but is: " ++ showMixedAmount bvsumcost | ||||
|           | 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. | ||||
| isTransactionBalanced :: BalancingOpts -> Transaction -> Bool | ||||
| @ -157,20 +157,36 @@ balanceTransactionHelper bopts t = do | ||||
|     if infer_transaction_prices_ bopts then inferBalancingPrices t else t | ||||
|   case transactionCheckBalanced bopts t' of | ||||
|     []   -> Right (txnTieKnot t', inferredamtsandaccts) | ||||
|     errs -> Left $ transactionBalanceError t' errs | ||||
|     errs -> Left $ transactionBalanceError t' errs' | ||||
|       where | ||||
|         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."  | ||||
|           ] | ||||
|           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 (unlines | ||||
|   [ "unbalanced transaction: %s:", | ||||
|     "%s", | ||||
|     "\n%s" | ||||
|   ]) | ||||
| transactionBalanceError t errs = printf "%s:\n%s\n\nThis %stransaction is unbalanced.\n%s" | ||||
|   (sourcePosPairPretty $ tsourcepos t) | ||||
|   (textChomp ex) | ||||
|   (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 | ||||
| @ -193,12 +209,12 @@ inferBalancingAmount :: | ||||
| inferBalancingAmount styles t@Transaction{tpostings=ps} | ||||
|   | length amountlessrealps > 1 | ||||
|       = Left $ transactionBalanceError t | ||||
|         ["can't have more than one real posting with no amount" | ||||
|         ,"(remember to put two or more spaces between account and amount)"] | ||||
|         ["There can't be more than one real posting with no amount." | ||||
|         ,"(Remember to put two or more spaces between account and amount.)"] | ||||
|   | length amountlessbvps > 1 | ||||
|       = Left $ transactionBalanceError t | ||||
|         ["can't have more than one balanced virtual posting with no amount" | ||||
|         ,"(remember to put two or more spaces between account and amount)"] | ||||
|         ["There can't be more than one balanced virtual posting with no amount." | ||||
|         ,"(Remember to put two or more spaces between account and amount.)"] | ||||
|   | otherwise | ||||
|       = let psandinferredamts = map inferamount ps | ||||
|             inferredacctsandamts = [(paccount p, amt) | (p, Just amt) <- psandinferredamts] | ||||
| @ -577,42 +593,45 @@ checkBalanceAssertionOneCommodityB p@Posting{paccount=assertedacct} assertedamt | ||||
|       aquantity | ||||
|         -- traceWith (("actual:"++).showAmountDebug) | ||||
|         actualbalincomm | ||||
|     errmsg = printf (unlines | ||||
|       [ "balance assertion: %s:", | ||||
|     errmsg = chomp $ printf (unlines | ||||
|       [ "%s:", | ||||
|         "%s\n", | ||||
|         "This balance assertion failed.", | ||||
|         -- "date:       %s", | ||||
|         "account:    %-30s%s", | ||||
|         "commodity:  %-30s%s", | ||||
|         "In account:    %s", | ||||
|         "and commodity: %s", | ||||
|         -- "display precision:  %d", | ||||
|         "asserted:   %s", -- (at display precision: %s)", | ||||
|         "actual:     %s", -- (at display precision: %s)", | ||||
|         "difference: %s" | ||||
|         "this balance was asserted: %s", -- (at display precision: %s)", | ||||
|         "but the actual balance is: %s", -- (at display precision: %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 | ||||
|       (if isinclusive then " (including subaccounts)" else "" :: String) | ||||
|       assertedcomm | ||||
|       (if istotal then " (no other commodity balance allowed)" else "" :: String) | ||||
|       (if isinclusive then printf "%-30s  (including subaccounts)" acct else acct) | ||||
|       (if istotal     then printf "%-30s  (no other commodities allowed)" (T.unpack assertedcomm) else (T.unpack assertedcomm)) | ||||
|       -- (asprecision $ astyle actualbalincommodity)  -- should be the standard display precision I think | ||||
|       (show $ aquantity actualbalincomm) | ||||
|       -- (showAmount actualbalincommodity) | ||||
|       (show $ aquantity assertedamt) | ||||
|       -- (showAmount 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 | ||||
|           where | ||||
|             finderrcols p t trendered = Just (col, Just col2) | ||||
|               where | ||||
|                 -- col  = unPos $ sourceColumn pos | ||||
|                 -- col2 = col + (length $ wbUnpack $ showBalanceAssertion ass) | ||||
|                 -- The saved parse position may not correspond to the rendering in the error message. | ||||
|                 -- Instead, we analyse the rendering to find the columns: | ||||
|                 tlines = length $ T.lines $ tcomment t  -- transaction comment can generate extra lines | ||||
|                 -- Analyse the rendering to find the columns to highlight. | ||||
|                 tlines = dbg5 "tlines" $ max 1 $ length $ T.lines $ tcomment t  -- transaction comment can generate extra lines | ||||
|                 (col, col2) = | ||||
|                   let def = (5, maximum (map T.length $ T.lines trendered))  -- fallback: underline whole posting. Shouldn't happen. | ||||
|                   in | ||||
| @ -621,8 +640,8 @@ checkBalanceAssertionOneCommodityB p@Posting{paccount=assertedacct} assertedamt | ||||
|                       Just idx -> fromMaybe def $ do | ||||
|                         let | ||||
|                           beforeps = take (idx-1) $ tpostings t | ||||
|                           beforepslines = sum $ map (length . T.lines . pcomment) beforeps   -- posting comment can generate extra lines (assume only one commodity shown) | ||||
|                         assertionline <- headMay $ drop (tlines + beforepslines) $ T.lines trendered | ||||
|                           beforepslines = dbg5 "beforepslines" $ sum $ map (max 1 . length . T.lines . pcomment) beforeps   -- posting comment can generate extra lines (assume only one commodity shown) | ||||
|                         assertionline <- dbg5 "assertionline" $ headMay $ drop (tlines + beforepslines) $ T.lines trendered | ||||
|                         let | ||||
|                           col2 = T.length assertionline | ||||
|                           l = dropWhile (/= '=') $ reverse $ T.unpack assertionline | ||||
| @ -646,7 +665,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" | ||||
| @ -662,7 +681,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" | ||||
|  | ||||
| @ -26,6 +26,7 @@ import Hledger.Utils | ||||
| -- on the transaction line, and a column(s) marker. | ||||
| -- Returns the file path, line number, column(s) if known, | ||||
| -- and the rendered excerpt, or as much of these as is possible. | ||||
| -- A limitation: columns will be accurate for the rendered error message but not for the original journal data. | ||||
| makeTransactionErrorExcerpt :: Transaction -> (Transaction -> Maybe (Int, Maybe Int)) -> (FilePath, Int, Maybe (Int, Maybe Int), Text) | ||||
| makeTransactionErrorExcerpt t findtxnerrorcolumns = (f, tl, merrcols, ex) | ||||
|   -- XXX findtxnerrorcolumns is awkward, I don't think this is the final form | ||||
| @ -58,6 +59,7 @@ decorateTransactionErrorExcerpt l mcols txt = | ||||
| -- on the problem posting's line, and a column indicator. | ||||
| -- Returns the file path, line number, column(s) if known, | ||||
| -- and the rendered excerpt, or as much of these as is possible. | ||||
| -- A limitation: columns will be accurate for the rendered error message but not for the original journal data. | ||||
| makePostingErrorExcerpt :: Posting -> (Posting -> Transaction -> Text -> Maybe (Int, Maybe Int)) -> (FilePath, Int, Maybe (Int, Maybe Int), Text) | ||||
| makePostingErrorExcerpt p findpostingerrorcolumns = | ||||
|   case ptransaction p of | ||||
|  | ||||
| @ -40,12 +40,21 @@ journalCheckAccounts j = mapM_ checkacct (journalPostings j) | ||||
|   where | ||||
|     checkacct p@Posting{paccount=a} | ||||
|       | a `elem` journalAccountNamesDeclared j = Right () | ||||
|       | otherwise = Left $  | ||||
|         printf "%s:%d:%d-%d:\n%sundeclared account \"%s\"\n" f l col col2 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 | ||||
|           col  = maybe 0 fst mcols | ||||
|           col2 = maybe 0 (fromMaybe 0 . snd) mcols | ||||
|           (f,l,_mcols,ex) = makePostingErrorExcerpt p finderrcols | ||||
|           -- Calculate columns suitable for highlighting the excerpt. | ||||
|           -- We won't show these in the main error line as they aren't | ||||
|           -- accurate for the actual data. | ||||
|           finderrcols p _ _ = Just (col, Just col2) | ||||
|             where | ||||
|               col = 5 + if isVirtual p then 1 else 0 | ||||
| @ -60,11 +69,18 @@ journalCheckCommodities j = mapM_ checkcommodities (journalPostings j) | ||||
|       case findundeclaredcomm p of | ||||
|         Nothing -> Right () | ||||
|         Just (comm, _) -> | ||||
|           Left $ printf "%s:%d:%d-%d:\n%sundeclared commodity \"%s\"\n" f l col col2 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 | ||||
|             col  = maybe 0 fst mcols | ||||
|             col2 = maybe 0 (fromMaybe 0 . snd) mcols | ||||
|             (f,l,_mcols,ex) = makePostingErrorExcerpt p finderrcols | ||||
|       where | ||||
|         -- Find the first undeclared commodity symbol in this posting's amount | ||||
|         -- or balance assertion amount, if any. The boolean will be true if | ||||
| @ -83,6 +99,10 @@ journalCheckCommodities j = mapM_ checkcommodities (journalPostings j) | ||||
|             assertioncomms = [acommodity a | Just a <- [baamount <$> pbalanceassertion]] | ||||
|             findundeclared = find (`M.notMember` jcommodities j) | ||||
| 
 | ||||
|         -- Calculate columns suitable for highlighting the excerpt. | ||||
|         -- We won't show these in the main error line as they aren't | ||||
|         -- accurate for the actual data. | ||||
| 
 | ||||
|         -- Find the best position for an error column marker when this posting | ||||
|         -- is rendered by showTransaction. | ||||
|         -- Reliably locating a problem commodity symbol in showTransaction output | ||||
| @ -119,12 +139,21 @@ journalCheckPayees j = mapM_ checkpayee (jtxns j) | ||||
|     checkpayee t | ||||
|       | payee `elem` journalPayeesDeclared j = Right () | ||||
|       | otherwise = Left $ | ||||
|         printf "%s:%d:%d-%d:\n%sundeclared payee \"%s\"\n" f l col col2 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 | ||||
|         col  = maybe 0 fst mcols | ||||
|         col2 = maybe 0 (fromMaybe 0 . snd) mcols | ||||
|         (f,l,_mcols,ex) = makeTransactionErrorExcerpt t finderrcols | ||||
|         -- Calculate columns suitable for highlighting the excerpt. | ||||
|         -- We won't show these in the main error line as they aren't | ||||
|         -- accurate for the actual data. | ||||
|         finderrcols t = Just (col, Just col2) | ||||
|           where | ||||
|             col  = T.length (showTransactionLineFirstPart t) + 2 | ||||
|  | ||||
| @ -6,11 +6,12 @@ where | ||||
| import Control.Monad (forM) | ||||
| import Data.List (groupBy) | ||||
| import Text.Printf (printf) | ||||
| import Data.Maybe (fromMaybe) | ||||
| 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 | ||||
| @ -26,15 +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:%d-%d:\n%stransaction date%s is out of order with previous transaction date %s"  | ||||
|         f l col col2 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 | ||||
|           col  = maybe 0 fst mcols | ||||
|           col2 = maybe 0 (fromMaybe 0 . snd) mcols | ||||
|           (_,_,_,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 | ||||
|  | ||||
| @ -11,13 +11,13 @@ import Data.List (groupBy, sortBy) | ||||
| import Data.Text (Text) | ||||
| import qualified Data.Text as T | ||||
| import Text.Printf (printf) | ||||
| import Data.Maybe (fromMaybe) | ||||
| 
 | ||||
| import Hledger.Data.AccountName (accountLeafName) | ||||
| import Hledger.Data.Errors (makePostingErrorExcerpt) | ||||
| import Hledger.Data.Journal (journalPostings, journalAccountNamesUsed) | ||||
| import Hledger.Data.Posting (isVirtual) | ||||
| import Hledger.Data.Types | ||||
| import Hledger.Utils (chomp, textChomp) | ||||
| 
 | ||||
| -- | 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. | ||||
| @ -26,9 +26,33 @@ journalCheckUniqueleafnames j = do | ||||
|   -- find all duplicate leafnames, and the full account names they appear in | ||||
|   case finddupes $ journalLeafAndFullAccountNames j of | ||||
|     [] -> Right () | ||||
|     dupes -> | ||||
|       -- report the first posting that references one of them (and its position), for now | ||||
|       mapM_ (checkposting dupes) $ journalPostings j | ||||
|     -- pick the first duplicated leafname and show the transactions of | ||||
|     -- the first two postings using it, highlighting the second as the error. | ||||
|     (leaf,fulls):_ -> | ||||
|       case filter ((`elem` fulls).paccount) $ journalPostings j of | ||||
|         ps@(p:p2:_) -> 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, which are used in %d places:\n%s" | ||||
|           ++"\nConsider changing these account names so their last parts are different." | ||||
|           ) | ||||
|           f l ex (show leaf) (length ps) accts | ||||
|           where | ||||
|             -- t = fromMaybe nulltransaction ptransaction  -- XXX sloppy | ||||
|             (_,_,_,ex1) = makePostingErrorExcerpt p (\_ _ _ -> Nothing) | ||||
|             (f,l,_,ex2) = makePostingErrorExcerpt p2 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 p _ _ = Just (col, Just col2) | ||||
|               where | ||||
|                 a = paccount p | ||||
|                 alen = T.length a | ||||
|                 llen = T.length $ accountLeafName a | ||||
|                 col = 5 + (if isVirtual p then 1 else 0) + alen - llen | ||||
|                 col2 = col + llen - 1 | ||||
|             accts = T.unlines fulls | ||||
| 
 | ||||
|         _ -> Right ()  -- shouldn't happen | ||||
| 
 | ||||
| finddupes :: (Ord leaf, Eq full) => [(leaf, full)] -> [(leaf, [full])] | ||||
| finddupes leafandfullnames = zip dupLeafs dupAccountNames | ||||
| @ -42,24 +66,3 @@ finddupes leafandfullnames = zip dupLeafs dupAccountNames | ||||
| journalLeafAndFullAccountNames :: Journal -> [(Text, AccountName)] | ||||
| journalLeafAndFullAccountNames = map leafAndAccountName . journalAccountNamesUsed | ||||
|   where leafAndAccountName a = (accountLeafName a, a) | ||||
| 
 | ||||
| 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:%d-%d:\n%saccount leaf name \"%s\" is not unique\nit is used in account names: %s"  | ||||
|       f l col col2 ex leaf accts | ||||
|       where | ||||
|         -- t = fromMaybe nulltransaction ptransaction  -- XXX sloppy | ||||
|         col  = maybe 0 fst mcols | ||||
|         col2 = maybe 0 (fromMaybe 0 . snd) mcols | ||||
|         (f,l,mcols,ex) = makePostingErrorExcerpt p finderrcols | ||||
|           where | ||||
|             finderrcols p _ _ = Just (col, Just col2) | ||||
|               where | ||||
|                 alen = T.length $ paccount p | ||||
|                 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 | ||||
|  | ||||
| @ -28,7 +28,6 @@ import Hledger.Data.Types | ||||
| import Hledger.Data.Dates | ||||
| import Hledger.Data.Amount | ||||
| import Hledger.Data.Posting | ||||
| import Hledger.Data.Transaction | ||||
| 
 | ||||
| instance Show TimeclockEntry where | ||||
|     show t = printf "%s %s %s  %s" (show $ tlcode t) (show $ tldatetime t) (tlaccount t) (tldescription t) | ||||
| @ -76,10 +75,19 @@ timeclockEntriesToTransactions now (i:o:rest) | ||||
|       i' = i{tldatetime=itime{localDay=addDays 1 idate, localTimeOfDay=midnight}} | ||||
| {- HLINT ignore timeclockEntriesToTransactions -} | ||||
| 
 | ||||
| errorExpectedCodeButGot expected actual = errorWithSourceLine line $ "expected timeclock code " ++ (show expected) ++ " but got " ++ show (tlcode actual) | ||||
|     where line = unPos . sourceLine $ tlsourcepos actual | ||||
| 
 | ||||
| errorWithSourceLine line msg = error $ "line " ++ show line ++ ": " ++ msg | ||||
| errorExpectedCodeButGot :: TimeclockCode -> TimeclockEntry -> a | ||||
| errorExpectedCodeButGot expected actual = error' $ printf | ||||
|   ("%s:\n%s\n%s\n\nExpected timeclock %s entry but got %s.\n" | ||||
|   ++"Only one session may be clocked in at a time.\n" | ||||
|   ++"Please alternate i and o, beginning with i.") | ||||
|   (sourcePosPretty $ tlsourcepos actual) | ||||
|   (l ++ " | " ++ show actual) | ||||
|   (replicate (length l) ' ' ++ " |" ++ replicate c ' ' ++ "^") | ||||
|   (show expected) | ||||
|   (show $ tlcode actual) | ||||
|   where | ||||
|     l = show $ unPos $ sourceLine $ tlsourcepos actual | ||||
|     c = unPos $ sourceColumn $ tlsourcepos actual | ||||
| 
 | ||||
| -- | Convert a timeclock clockin and clockout entry to an equivalent journal | ||||
| -- transaction, representing the time expenditure. Note this entry is  not balanced, | ||||
| @ -87,9 +95,23 @@ errorWithSourceLine line msg = error $ "line " ++ show line ++ ": " ++ msg | ||||
| entryFromTimeclockInOut :: TimeclockEntry -> TimeclockEntry -> Transaction | ||||
| entryFromTimeclockInOut i o | ||||
|     | otime >= itime = t | ||||
|     | otherwise = error' . T.unpack $ | ||||
|         "clock-out time less than clock-in time in:\n" <> showTransaction t  -- PARTIAL: | ||||
|     | otherwise = | ||||
|       -- Clockout time earlier than clockin is an error. | ||||
|       -- (Clockin earlier than preceding clockin/clockout is allowed.) | ||||
|       error' $ printf | ||||
|         ("%s:\n%s\nThis clockout time (%s) is earlier than the previous clockin.\n" | ||||
|         ++"Please adjust it to be later than %s.") | ||||
|         (sourcePosPretty $ tlsourcepos o) | ||||
|         (unlines [ | ||||
|           replicate (length l) ' '++ " | " ++ show i, | ||||
|           l ++ " | " ++ show o, | ||||
|           (replicate (length l) ' ' ++ " |" ++ replicate c ' ' ++ replicate 19 '^') | ||||
|           ]) | ||||
|         (show $ tldatetime o) | ||||
|         (show $ tldatetime i) | ||||
|     where | ||||
|       l = show $ unPos $ sourceLine $ tlsourcepos o | ||||
|       c = (unPos $ sourceColumn $ tlsourcepos o) + 2 | ||||
|       t = Transaction { | ||||
|             tindex       = 0, | ||||
|             tsourcepos   = (tlsourcepos i, tlsourcepos i), | ||||
|  | ||||
| @ -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' #-} | ||||
| @ -1389,10 +1391,10 @@ commenttagsanddatesp mYear = do | ||||
| -- Left ...not a bracketed date... | ||||
| -- | ||||
| -- >>> either (Left . customErrorBundlePretty) Right $ rtp (bracketeddatetagsp Nothing) "[2016/1/32]" | ||||
| -- Left ...1:2:...well-formed but invalid date: 2016/1/32... | ||||
| -- Left ...1:2:...This date is invalid... | ||||
| -- | ||||
| -- >>> either (Left . customErrorBundlePretty) Right $ rtp (bracketeddatetagsp Nothing) "[1/31]" | ||||
| -- Left ...1:2:...partial date 1/31 found, but the current year is unknown... | ||||
| -- Left ...1:2:...The partial date 1/31 can not be parsed... | ||||
| -- | ||||
| -- >>> either (Left . customErrorBundlePretty) Right $ rtp (bracketeddatetagsp Nothing) "[0123456789/-.=/-.=]" | ||||
| -- Left ...1:13:...expecting month or day... | ||||
|  | ||||
| @ -797,7 +797,7 @@ makeHledgerClassyLenses ''ReportSpec | ||||
| -- >>> _rsQuery <$> setEither querystring ["assets"] defreportspec | ||||
| -- Right (Acct (RegexpCI "assets")) | ||||
| -- >>> _rsQuery <$> setEither querystring ["(assets"] defreportspec | ||||
| -- Left "this regular expression could not be compiled: (assets" | ||||
| -- Left "This regular expression is malformed... | ||||
| -- >>> _rsQuery $ set querystring ["assets"] defreportspec | ||||
| -- Acct (RegexpCI "assets") | ||||
| -- >>> _rsQuery $ set querystring ["(assets"] defreportspec | ||||
|  | ||||
| @ -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 | ||||
|  | ||||
| @ -4,5 +4,5 @@ | ||||
|   a  -10£ | ||||
|   b  16$ | ||||
| $ hledger -f - check balancednoautoconversion | ||||
| >2 /real postings' sum should be 0 but is:  16\$/ | ||||
| >2 /real postings' sum should be 0 but is: 16\$, -10£/ | ||||
| >=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 | ||||
|  | ||||
| @ -1039,7 +1039,7 @@ account1 assets:bank:checking | ||||
| fields date, description, account2, amount | ||||
| 
 | ||||
| $  ./csvtest.sh | ||||
| >2 /unbalanced transaction/ | ||||
| >2 /transaction is unbalanced/ | ||||
| >=1 | ||||
| 
 | ||||
| ## .  | ||||
|  | ||||
| @ -1,44 +1,40 @@ | ||||
| # Check error messages of hledger in $PATH against current error tests.
 | ||||
| test: | ||||
| 	@printf "Running error message tests with hledger $$(hledger --version | awk '{print $$2}'):\n" | ||||
| 	shelltest *.test | ||||
| HLEDGER ?= hledger | ||||
| 
 | ||||
| TESTJOURNALS=*.j | ||||
| # Executable .j, .csv, .timeclock, and .timedot files are error example scripts.
 | ||||
| # Some shenanigans here to order them nicely.
 | ||||
| ERRORSCRIPTS := \
 | ||||
| 	$$(find -s . -name '*.j'         -perm +rwx -exec basename {} \; | grep -v csv) \
 | ||||
| 	$$(find -s . -name '*.timeclock' -perm +rwx -exec basename {} \; ) \
 | ||||
| 	$$(find -s . -name '*.timedot'   -perm +rwx -exec basename {} \; ) \
 | ||||
| 	$$(find -s . -name 'csv*'        -perm +rwx -exec basename {} \; ) \
 | ||||
| 	$$(find -s . -name '*.sh'        -perm +rwx -exec basename {} \; ) \
 | ||||
| 
 | ||||
| list: | ||||
| 	@echo "Error example scripts detected:" | ||||
| 	@for s in $(ERRORSCRIPTS); do echo $$s; done | ||||
| 
 | ||||
| # Check error messages of $HLEDGER against current error tests.
 | ||||
| # A few tests (csvstdinrules.sh) may use "hledger" in $PATH instead of $HLEDGER.
 | ||||
| test: | ||||
| 	@printf "Running error message tests with hledger $$($(HLEDGER) --version | awk '{print $$2}'):\n" | ||||
| 	shelltest -w $(HLEDGER) *.test | ||||
| 
 | ||||
| # Update error message tests and readme based on the latest test journals
 | ||||
| # and error output of hledger in $PATH.
 | ||||
| update: tests readme | ||||
| 
 | ||||
| tests: | ||||
| 	@printf "Updating *.test with the error messages of hledger $$(hledger --version | awk '{print $$2}')\n" | ||||
| 	@printf "(Re)generating *.test with the error messages of hledger $$($(HLEDGER) --version | awk '{print $$2}')\n" | ||||
| 	@read -p "ok ? Press enter: " | ||||
| 	for f in $(TESTJOURNALS); do make -s $$(basename $$f .j).test; done | ||||
| 	make -s test | ||||
| 	@for f in $(ERRORSCRIPTS); do echo "HLEDGER=$(HLEDGER) ./hledger2shelltest $$f"; HLEDGER=$(HLEDGER) ./hledger2shelltest $$f; done | ||||
| 
 | ||||
| # Generate a shelltest. Run the test script/journal to generate the error message.
 | ||||
| # Since the error will contain an absolute file path, we must:
 | ||||
| # 1. remove most of the file path
 | ||||
| # 2. test with a (multiline) regex rather than literal text
 | ||||
| # 3. backslash-quote most forward slashes in error messages
 | ||||
| # 4. neutralise any remaining problematic error text (eg in parseable-regexps.test)
 | ||||
| %.test: %.j | ||||
| 	head -1 $< | sed -E 's%#!/usr/bin/env -S (.*)%$$$$$$ \1 $<%' >$@ | ||||
| 	printf ">>>2 /" >>$@ | ||||
| 	-./$< 2>&1 | sed -E \
 | ||||
| 		-e 's%(hledger: Error: ).*/\./(.*)%\1.*\2%' \
 | ||||
| 		-e 's%/%\\/%g' \
 | ||||
| 		-e 's%alias \\/\(\\/%alias \\/\\(\\/%' \
 | ||||
| 		-e 's%compiled: \(%compiled: \\(%' \
 | ||||
| 		>>$@ | ||||
| 	printf "/\n>>>= 1" >>$@ | ||||
| 
 | ||||
| readme: $(TESTJOURNALS) | ||||
| 	@printf "Updating README.md with the error messages of hledger $$(hledger --version | awk '{print $$2}')\n" | ||||
| readme: | ||||
| 	@printf "Updating README.md with the error messages of hledger $$($(HLEDGER) --version)\n" | ||||
| 	@read -p "ok ? Press enter: " | ||||
| 	sed '/<!-- GENERATED: -->/q' <README.md >README.md.tmp | ||||
| 	echo "$$(hledger --version | cut -d, -f1) error messages:" >>README.md.tmp | ||||
| 	for f in $(TESTJOURNALS); do \
 | ||||
| 		printf '\n### %s\n```\n%s\n```\n\n' "$$(basename "$$f" .j)" "$$(./"$$f" 2>&1)"; \
 | ||||
| 	echo "$$($(HLEDGER) --version | cut -d, -f1) error messages:" >>README.md.tmp | ||||
| 	for f in $(ERRORSCRIPTS); do \
 | ||||
| 		printf '\n### %s\n```\n%s\n```\n\n' "$$(echo "$$f" | sed -E 's/\.[^.]+$$//')" "$$(./"$$f" 2>&1)"; \
 | ||||
| 	done >>README.md.tmp | ||||
| 	mv README.md.tmp README.md | ||||
| 
 | ||||
|  | ||||
										
											
												File diff suppressed because one or more lines are too long
											
										
									
								
							| @ -1,9 +1,15 @@ | ||||
| $$$ hledger check accounts -f accounts.j | ||||
| >>>2 /hledger: Error: .*accounts.j:4:6-6: | ||||
|   | 2022-01-01 | ||||
| 4 |     (a)               1 | ||||
|   |      ^ | ||||
| undeclared account "a" | ||||
| >>>2 /hledger: Error: .*accounts.j:4: | ||||
|   \| 2022-01-01 | ||||
| 4 \|     \(a\)               1 | ||||
|   \|      \^ | ||||
| 
 | ||||
| Strict account checking is enabled, and | ||||
| account "a" has not been declared. | ||||
| Consider adding an account directive. Examples: | ||||
| 
 | ||||
| account a | ||||
| account a    ; type:A  ; \(L,E,R,X,C,V\) | ||||
| 
 | ||||
| / | ||||
| >>>= 1 | ||||
| @ -1,14 +1,15 @@ | ||||
| $ hledger check -f assertions.j | ||||
| >2 /hledger: Error: balance assertion: .*assertions.j:4:8: | ||||
|   | 2022-01-01 | ||||
| 4 |     a               0 = 1 | ||||
|   | ^^^^^^^^^^ | ||||
| $$$ hledger check -f assertions.j | ||||
| >>>2 /hledger: Error: .*assertions.j:4:8: | ||||
|   \| 2022-01-01 | ||||
| 4 \|     a               0 = 1 | ||||
|   \|                       \^\^\^ | ||||
| 
 | ||||
| account:    a                              | ||||
| commodity:                                 | ||||
| asserted:   0 | ||||
| actual:     1 | ||||
| difference: 1 | ||||
| This balance assertion failed. | ||||
| In account:    a | ||||
| and commodity:  | ||||
| this balance was asserted: 1 | ||||
| but the actual balance is: 0 | ||||
| a difference of:           1 | ||||
| 
 | ||||
| / | ||||
| >=1 | ||||
| Consider viewing this account'/ | ||||
| >>>= 1 | ||||
|  | ||||
| @ -1,9 +1,10 @@ | ||||
| $ hledger check -f balanced.j | ||||
| >2 /hledger: Error: unbalanced transaction: .*balanced.j:3-4: | ||||
| 3 | 2022-01-01 | ||||
|   |     a               1 | ||||
| 
 | ||||
| real postings' sum should be 0 but is: 1 | ||||
| $$$ hledger check -f balanced.j | ||||
| >>>2 /hledger: Error: .*balanced.j:3-4: | ||||
| 3 \| 2022-01-01 | ||||
|   \|     a               1 | ||||
| 
 | ||||
| This transaction is unbalanced. | ||||
| The real postings' sum should be 0 but is: 1 | ||||
| Consider adjusting this entry's amounts, or adding missing postings. | ||||
| / | ||||
| >= 1 | ||||
| >>>= 1 | ||||
|  | ||||
| @ -1,11 +1,11 @@ | ||||
| $ hledger check balancednoautoconversion -f balancednoautoconversion.j | ||||
| >2 /hledger: Error: unbalanced transaction: .*balancednoautoconversion.j:6-8: | ||||
| 6 | 2022-01-01 | ||||
|   |     a             1 A | ||||
|   |     b            -1 B | ||||
| $$$ hledger check balancednoautoconversion -f balancednoautoconversion.j | ||||
| >>>2 /hledger: Error: .*balancednoautoconversion.j:6-8: | ||||
| 6 \| 2022-01-01 | ||||
|   \|     a             1 A | ||||
|   \|     b            -1 B | ||||
| 
 | ||||
| real postings' sum should be 0 but is:  1 A | ||||
| -1 B | ||||
| 
 | ||||
| / | ||||
| >= 1 | ||||
| This multi-commodity transaction is unbalanced. | ||||
| Automatic commodity conversion is not enabled. | ||||
| The real postings' sum should be 0 but is: 1 A, -1 B | ||||
| Consider adjusting this entry's/ | ||||
| >>>= 1 | ||||
|  | ||||
| @ -1,9 +1,15 @@ | ||||
| $$$ hledger check commodities -f commodities.j | ||||
| >>>2 /hledger: Error: .*commodities.j:6:21-23: | ||||
|   | 2022-01-01 | ||||
| 6 |     (a)             A 1 | ||||
|   |                     ^^^ | ||||
| undeclared commodity "A" | ||||
| >>>2 /hledger: Error: .*commodities.j:6: | ||||
|   \| 2022-01-01 | ||||
| 6 \|     \(a\)             A 1 | ||||
|   \|                     \^\^\^ | ||||
| 
 | ||||
| Strict commodity checking is enabled, and | ||||
| commodity "A" has not been declared. | ||||
| Consider adding a commodity directive. Examples: | ||||
| 
 | ||||
| commodity A1000.00 | ||||
| commodity 1.000,00 A | ||||
| 
 | ||||
| / | ||||
| >>>= 1 | ||||
							
								
								
									
										5
									
								
								hledger/test/errors/csvamountonenonzero.csv
									
									
									
									
									
										Executable file
									
								
							
							
						
						
									
										5
									
								
								hledger/test/errors/csvamountonenonzero.csv
									
									
									
									
									
										Executable file
									
								
							| @ -0,0 +1,5 @@ | ||||
| #!/usr/bin/env -S hledger print -f  | ||||
| # Non-zero for both amount-in and amount-out. | ||||
| 2022-01-01,1, | ||||
| 2022-01-02,1,0 | ||||
| 2022-01-03,1,2 | ||||
| 
 | 
							
								
								
									
										4
									
								
								hledger/test/errors/csvamountonenonzero.csv.rules
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										4
									
								
								hledger/test/errors/csvamountonenonzero.csv.rules
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,4 @@ | ||||
| skip 2 | ||||
| date %1 | ||||
| amount-in %2 | ||||
| amount-out %3 | ||||
							
								
								
									
										10
									
								
								hledger/test/errors/csvamountonenonzero.test
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										10
									
								
								hledger/test/errors/csvamountonenonzero.test
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,10 @@ | ||||
| $$$ hledger print -f  csvamountonenonzero.csv | ||||
| >>>2 /hledger: Error: multiple non-zero amounts assigned, | ||||
| please ensure just one. \(https:\/\/hledger.org\/csv.html#amount\) | ||||
|   record values: "2022-01-03","1","2" | ||||
|   for posting: 1 | ||||
|   assignment: amount-in %2	=> value: 1 | ||||
|   assignment: amount-out %3	=> value: 2 | ||||
| 
 | ||||
| / | ||||
| >>>= 1 | ||||
							
								
								
									
										5
									
								
								hledger/test/errors/csvamountparse.csv
									
									
									
									
									
										Executable file
									
								
							
							
						
						
									
										5
									
								
								hledger/test/errors/csvamountparse.csv
									
									
									
									
									
										Executable file
									
								
							| @ -0,0 +1,5 @@ | ||||
| #!/usr/bin/env -S hledger print -f  | ||||
| # Unparseable amount. | ||||
| 2022-01-01,1 | ||||
| 2022-01-02,$1 | ||||
| 2022-01-03,badamount | ||||
| 
 | 
							
								
								
									
										3
									
								
								hledger/test/errors/csvamountparse.csv.rules
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										3
									
								
								hledger/test/errors/csvamountparse.csv.rules
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,3 @@ | ||||
| skip 2 | ||||
| date %1 | ||||
| amount %2 | ||||
							
								
								
									
										15
									
								
								hledger/test/errors/csvamountparse.test
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										15
									
								
								hledger/test/errors/csvamountparse.test
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,15 @@ | ||||
| $$$ hledger print -f  csvamountparse.csv | ||||
| >>>2 /hledger: Error: error: could not parse "badamount" as an amount | ||||
| record values: "2022-01-03","badamount" | ||||
| the amount rule is: %2 | ||||
| the date rule is: %1 | ||||
| 
 | ||||
| the parse error is:      1:10: | ||||
|   \| | ||||
| 1 \| badamount | ||||
|   \|          \^ | ||||
| unexpected end of input | ||||
| expecting '\+', '-', or number | ||||
| 
 | ||||
| you may need to change your/ | ||||
| >>>= 1 | ||||
							
								
								
									
										3
									
								
								hledger/test/errors/csvbalanceparse.csv
									
									
									
									
									
										Executable file
									
								
							
							
						
						
									
										3
									
								
								hledger/test/errors/csvbalanceparse.csv
									
									
									
									
									
										Executable file
									
								
							| @ -0,0 +1,3 @@ | ||||
| #!/usr/bin/env -S hledger print -f  | ||||
| # Unparseable balance amount. | ||||
| 2022-01-03,badbalance | ||||
| 
 | 
							
								
								
									
										3
									
								
								hledger/test/errors/csvbalanceparse.csv.rules
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										3
									
								
								hledger/test/errors/csvbalanceparse.csv.rules
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,3 @@ | ||||
| skip 2 | ||||
| date %1 | ||||
| balance %2 | ||||
							
								
								
									
										16
									
								
								hledger/test/errors/csvbalanceparse.test
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										16
									
								
								hledger/test/errors/csvbalanceparse.test
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,16 @@ | ||||
| $$$ hledger print -f  csvbalanceparse.csv | ||||
| >>>2 /hledger: Error: error: could not parse "badbalance" as balance1 amount | ||||
| record values: "2022-01-03","badbalance" | ||||
| the balance rule is: %2 | ||||
| the date rule is: %1 | ||||
| 
 | ||||
| the parse error is:      1:11: | ||||
|   \| | ||||
| 1 \| badbalance | ||||
|   \|           \^ | ||||
| unexpected end of input | ||||
| expecting '\+', '-', or number | ||||
| 
 | ||||
| 
 | ||||
| / | ||||
| >>>= 1 | ||||
							
								
								
									
										4
									
								
								hledger/test/errors/csvbalancetypeparse.csv
									
									
									
									
									
										Executable file
									
								
							
							
						
						
									
										4
									
								
								hledger/test/errors/csvbalancetypeparse.csv
									
									
									
									
									
										Executable file
									
								
							| @ -0,0 +1,4 @@ | ||||
| #!/usr/bin/env -S hledger check -f  | ||||
| # See rules. | ||||
| 2022-01-01,1 | ||||
| 
 | ||||
| 
 | 
							
								
								
									
										4
									
								
								hledger/test/errors/csvbalancetypeparse.csv.rules
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										4
									
								
								hledger/test/errors/csvbalancetypeparse.csv.rules
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,4 @@ | ||||
| skip 2 | ||||
| date %1 | ||||
| balance %2 | ||||
| balance-type badtype | ||||
							
								
								
									
										9
									
								
								hledger/test/errors/csvbalancetypeparse.test
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										9
									
								
								hledger/test/errors/csvbalancetypeparse.test
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,9 @@ | ||||
| $$$ hledger check -f  csvbalancetypeparse.csv | ||||
| >>>2 /hledger: Error: balance-type "badtype" is invalid. Use =, ==, =\* or ==\*. | ||||
| record values: "2022-01-01","1" | ||||
| the balance rule is: %2 | ||||
| the date rule is: %1 | ||||
| 
 | ||||
| 
 | ||||
| / | ||||
| >>>= 1 | ||||
							
								
								
									
										4
									
								
								hledger/test/errors/csvdateformat.csv
									
									
									
									
									
										Executable file
									
								
							
							
						
						
									
										4
									
								
								hledger/test/errors/csvdateformat.csv
									
									
									
									
									
										Executable file
									
								
							| @ -0,0 +1,4 @@ | ||||
| #!/usr/bin/env -S hledger print -f  | ||||
| # See rules (missing/bad date-format rule). | ||||
| # Note check doesn't show this error; print was needed. | ||||
| a,b | ||||
| 
 | 
							
								
								
									
										2
									
								
								hledger/test/errors/csvdateformat.csv.rules
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										2
									
								
								hledger/test/errors/csvdateformat.csv.rules
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,2 @@ | ||||
| skip 3 | ||||
| date %1 | ||||
							
								
								
									
										8
									
								
								hledger/test/errors/csvdateformat.test
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										8
									
								
								hledger/test/errors/csvdateformat.test
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,8 @@ | ||||
| $$$ hledger print -f  csvdateformat.csv | ||||
| >>>2 /hledger: Error: error: could not parse "a" as a date using date format "YYYY\/M\/D", "YYYY-M-D" or "YYYY.M.D" | ||||
| record values: "a","b" | ||||
| the date rule is:   %1 | ||||
| the date-format is: unspecified | ||||
| you may need to change your date rule, add a date-format rule, or change your skip rule | ||||
| for m\/d\/y or d\/m\/y d/ | ||||
| >>>= 1 | ||||
							
								
								
									
										4
									
								
								hledger/test/errors/csvdateparse.csv
									
									
									
									
									
										Executable file
									
								
							
							
						
						
									
										4
									
								
								hledger/test/errors/csvdateparse.csv
									
									
									
									
									
										Executable file
									
								
							| @ -0,0 +1,4 @@ | ||||
| #!/usr/bin/env -S hledger check -f  | ||||
| # Date value not parseable by date-format rule. | ||||
| 2022-01-01,b | ||||
| baddate,b | ||||
| 
 | 
							
								
								
									
										3
									
								
								hledger/test/errors/csvdateparse.csv.rules
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										3
									
								
								hledger/test/errors/csvdateparse.csv.rules
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,3 @@ | ||||
| skip 2 | ||||
| date %1 | ||||
| date-format %Y-%m-%d | ||||
							
								
								
									
										8
									
								
								hledger/test/errors/csvdateparse.test
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										8
									
								
								hledger/test/errors/csvdateparse.test
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,8 @@ | ||||
| $$$ hledger check -f  csvdateparse.csv | ||||
| >>>2 /hledger: Error: error: could not parse "baddate" as a date using date format "%Y-%m-%d" | ||||
| record values: "baddate","b" | ||||
| the date rule is:   %1 | ||||
| the date-format is: %Y-%m-%d | ||||
| you may need to change your date rule, change your date-format rule, or change your skip rule | ||||
| for m\/d\/y or d\/m\/y dates, use dat/ | ||||
| >>>= 1 | ||||
							
								
								
									
										3
									
								
								hledger/test/errors/csvdaterule.csv
									
									
									
									
									
										Executable file
									
								
							
							
						
						
									
										3
									
								
								hledger/test/errors/csvdaterule.csv
									
									
									
									
									
										Executable file
									
								
							| @ -0,0 +1,3 @@ | ||||
| #!/usr/bin/env -S hledger check -f  | ||||
| # Rules have no date rule. | ||||
| a,b | ||||
| 
 | 
							
								
								
									
										1
									
								
								hledger/test/errors/csvdaterule.csv.rules
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										1
									
								
								hledger/test/errors/csvdaterule.csv.rules
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1 @@ | ||||
| skip 2 | ||||
							
								
								
									
										6
									
								
								hledger/test/errors/csvdaterule.test
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										6
									
								
								hledger/test/errors/csvdaterule.test
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,6 @@ | ||||
| $$$ hledger check -f  csvdaterule.csv | ||||
| >>>2 /hledger: Error: offset=0: | ||||
| Please specify \(at top level\) the date field. Eg: date %1 | ||||
| 
 | ||||
| / | ||||
| >>>= 1 | ||||
							
								
								
									
										4
									
								
								hledger/test/errors/csvdecimalmarkparse.csv
									
									
									
									
									
										Executable file
									
								
							
							
						
						
									
										4
									
								
								hledger/test/errors/csvdecimalmarkparse.csv
									
									
									
									
									
										Executable file
									
								
							| @ -0,0 +1,4 @@ | ||||
| #!/usr/bin/env -S hledger check -f  | ||||
| # See rules. | ||||
| 2022-01-01,1.0 | ||||
| 
 | ||||
| 
 | 
							
								
								
									
										4
									
								
								hledger/test/errors/csvdecimalmarkparse.csv.rules
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										4
									
								
								hledger/test/errors/csvdecimalmarkparse.csv.rules
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,4 @@ | ||||
| skip 2 | ||||
| date %1 | ||||
| amount %2 | ||||
| decimal-mark badmark | ||||
							
								
								
									
										4
									
								
								hledger/test/errors/csvdecimalmarkparse.test
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										4
									
								
								hledger/test/errors/csvdecimalmarkparse.test
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,4 @@ | ||||
| $$$ hledger check -f  csvdecimalmarkparse.csv | ||||
| >>>2 /hledger: Error: decimal-mark's argument should be "." or "," \(not "badmark"\) | ||||
| / | ||||
| >>>= 1 | ||||
							
								
								
									
										3
									
								
								hledger/test/errors/csvifblocknonempty.csv
									
									
									
									
									
										Executable file
									
								
							
							
						
						
									
										3
									
								
								hledger/test/errors/csvifblocknonempty.csv
									
									
									
									
									
										Executable file
									
								
							| @ -0,0 +1,3 @@ | ||||
| #!/usr/bin/env -S hledger check -f  | ||||
| # Rules have an empty conditional block. | ||||
| a,b | ||||
| 
 | 
							
								
								
									
										2
									
								
								hledger/test/errors/csvifblocknonempty.csv.rules
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										2
									
								
								hledger/test/errors/csvifblocknonempty.csv.rules
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,2 @@ | ||||
| # no (indented) rules following if | ||||
| if foo | ||||
							
								
								
									
										10
									
								
								hledger/test/errors/csvifblocknonempty.test
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										10
									
								
								hledger/test/errors/csvifblocknonempty.test
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,10 @@ | ||||
| $$$ hledger check -f  csvifblocknonempty.csv | ||||
| >>>2 /hledger: Error: .*csvifblocknonempty.csv.rules:2:1: | ||||
|   \| | ||||
| 2 \| if foo | ||||
|   \| \^ | ||||
| start of conditional block found, but no assignment rules afterward | ||||
| \(assignment rules in a conditional block should be indented\) | ||||
| 
 | ||||
| / | ||||
| >>>= 1 | ||||
							
								
								
									
										3
									
								
								hledger/test/errors/csviftablefieldnames.csv
									
									
									
									
									
										Executable file
									
								
							
							
						
						
									
										3
									
								
								hledger/test/errors/csviftablefieldnames.csv
									
									
									
									
									
										Executable file
									
								
							| @ -0,0 +1,3 @@ | ||||
| #!/usr/bin/env -S hledger check -f  | ||||
| # See rules. | ||||
| 
 | ||||
| 
 | 
							
								
								
									
										2
									
								
								hledger/test/errors/csviftablefieldnames.csv.rules
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										2
									
								
								hledger/test/errors/csviftablefieldnames.csv.rules
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,2 @@ | ||||
| # if table not using valid CSV field names. | ||||
| if,date,nosuchfield,description | ||||
							
								
								
									
										8
									
								
								hledger/test/errors/csviftablefieldnames.test
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										8
									
								
								hledger/test/errors/csviftablefieldnames.test
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,8 @@ | ||||
| $$$ hledger check -f  csviftablefieldnames.csv | ||||
| >>>2 /hledger: Error: .*csviftablefieldnames.csv.rules:2:9: | ||||
|   \| | ||||
| 2 \| if,date,nosuchfield,description | ||||
|   \|         \^\^\^\^\^\^\^\^\^\^\^\^ | ||||
| unexpected "nosuchfield," | ||||
| expecting "account1", "account10", "account11", "account12", "account13", "account14", "account15", "account16", "account17", "account18", "/ | ||||
| >>>= 1 | ||||
							
								
								
									
										3
									
								
								hledger/test/errors/csviftablenonempty.csv
									
									
									
									
									
										Executable file
									
								
							
							
						
						
									
										3
									
								
								hledger/test/errors/csviftablenonempty.csv
									
									
									
									
									
										Executable file
									
								
							| @ -0,0 +1,3 @@ | ||||
| #!/usr/bin/env -S hledger check -f  | ||||
| # See rules. | ||||
| 
 | ||||
| 
 | 
							
								
								
									
										2
									
								
								hledger/test/errors/csviftablenonempty.csv.rules
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										2
									
								
								hledger/test/errors/csviftablenonempty.csv.rules
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,2 @@ | ||||
| # no (indented) rules following if table | ||||
| if,date,description,comment | ||||
							
								
								
									
										9
									
								
								hledger/test/errors/csviftablenonempty.test
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										9
									
								
								hledger/test/errors/csviftablenonempty.test
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,9 @@ | ||||
| $$$ hledger check -f  csviftablenonempty.csv | ||||
| >>>2 /hledger: Error: .*csviftablenonempty.csv.rules:2:1: | ||||
|   \| | ||||
| 2 \| if,date,description,comment | ||||
|   \| \^ | ||||
| start of conditional table found, but no assignment rules afterward | ||||
| 
 | ||||
| / | ||||
| >>>= 1 | ||||
							
								
								
									
										3
									
								
								hledger/test/errors/csviftablevaluecount.csv
									
									
									
									
									
										Executable file
									
								
							
							
						
						
									
										3
									
								
								hledger/test/errors/csviftablevaluecount.csv
									
									
									
									
									
										Executable file
									
								
							| @ -0,0 +1,3 @@ | ||||
| #!/usr/bin/env -S hledger check -f  | ||||
| # See rules. | ||||
| 
 | ||||
| 
 | 
							
								
								
									
										4
									
								
								hledger/test/errors/csviftablevaluecount.csv.rules
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										4
									
								
								hledger/test/errors/csviftablevaluecount.csv.rules
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,4 @@ | ||||
| # if table where some records have wrong number of values. | ||||
| if,date,description | ||||
| two,val1,val2 | ||||
| one,val1 | ||||
							
								
								
									
										9
									
								
								hledger/test/errors/csviftablevaluecount.test
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										9
									
								
								hledger/test/errors/csviftablevaluecount.test
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,9 @@ | ||||
| $$$ hledger check -f  csviftablevaluecount.csv | ||||
| >>>2 /hledger: Error: .*csviftablevaluecount.csv.rules:4:1: | ||||
|   \| | ||||
| 4 \| one,val1 | ||||
|   \| \^ | ||||
| line of conditional table should have 2 values, but this one has only 1 | ||||
| 
 | ||||
| / | ||||
| >>>= 1 | ||||
							
								
								
									
										0
									
								
								hledger/test/errors/csvnoinclude.csv
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										0
									
								
								hledger/test/errors/csvnoinclude.csv
									
									
									
									
									
										Normal file
									
								
							|  | 
							
								
								
									
										6
									
								
								hledger/test/errors/csvnoinclude.j
									
									
									
									
									
										Executable file
									
								
							
							
						
						
									
										6
									
								
								hledger/test/errors/csvnoinclude.j
									
									
									
									
									
										Executable file
									
								
							| @ -0,0 +1,6 @@ | ||||
| #!/usr/bin/env -S hledger check -f  | ||||
| # Trying to include a CSV file. | ||||
| 
 | ||||
| include csvinclude.csv | ||||
| 
 | ||||
| 
 | ||||
							
								
								
									
										9
									
								
								hledger/test/errors/csvnoinclude.test
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										9
									
								
								hledger/test/errors/csvnoinclude.test
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,9 @@ | ||||
| $$$ hledger check -f  csvnoinclude.j | ||||
| >>>2 /hledger: Error: .*csvnoinclude.j:4:23: | ||||
|   \| | ||||
| 4 \| include csvinclude.csv | ||||
|   \|                       \^ | ||||
| No existing files match pattern: csvinclude.csv | ||||
| 
 | ||||
| / | ||||
| >>>= 1 | ||||
							
								
								
									
										2
									
								
								hledger/test/errors/csvskipvalue.csv
									
									
									
									
									
										Executable file
									
								
							
							
						
						
									
										2
									
								
								hledger/test/errors/csvskipvalue.csv
									
									
									
									
									
										Executable file
									
								
							| @ -0,0 +1,2 @@ | ||||
| #!/usr/bin/env -S hledger check -f  | ||||
| # See rules. | ||||
| 
 | 
							
								
								
									
										2
									
								
								hledger/test/errors/csvskipvalue.csv.rules
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										2
									
								
								hledger/test/errors/csvskipvalue.csv.rules
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,2 @@ | ||||
| date %1 | ||||
| skip badval | ||||
							
								
								
									
										4
									
								
								hledger/test/errors/csvskipvalue.test
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										4
									
								
								hledger/test/errors/csvskipvalue.test
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,4 @@ | ||||
| $$$ hledger check -f  csvskipvalue.csv | ||||
| >>>2 /hledger: Error: could not parse skip value: "badval" | ||||
| / | ||||
| >>>= 1 | ||||
							
								
								
									
										6
									
								
								hledger/test/errors/csvstatusparse.csv
									
									
									
									
									
										Executable file
									
								
							
							
						
						
									
										6
									
								
								hledger/test/errors/csvstatusparse.csv
									
									
									
									
									
										Executable file
									
								
							| @ -0,0 +1,6 @@ | ||||
| #!/usr/bin/env -S hledger print -f  | ||||
| # Status value not parseable. | ||||
| 2022-01-01,* | ||||
| 2022-01-02,! | ||||
| 2022-01-03, | ||||
| 2022-01-04,badstatus | ||||
| 
 | 
							
								
								
									
										3
									
								
								hledger/test/errors/csvstatusparse.csv.rules
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										3
									
								
								hledger/test/errors/csvstatusparse.csv.rules
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,3 @@ | ||||
| skip 2 | ||||
| date %1 | ||||
| status %2 | ||||
							
								
								
									
										12
									
								
								hledger/test/errors/csvstatusparse.test
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										12
									
								
								hledger/test/errors/csvstatusparse.test
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,12 @@ | ||||
| $$$ hledger print -f  csvstatusparse.csv | ||||
| >>>2 /hledger: Error: error: could not parse "badstatus" as a cleared status \(should be \*, ! or empty\) | ||||
| the parse error is:      1:1: | ||||
|   \| | ||||
| 1 \| badstatus | ||||
|   \| \^ | ||||
| unexpected 'b' | ||||
| expecting '!', '\*', or end of input | ||||
| 
 | ||||
| 
 | ||||
| / | ||||
| >>>= 1 | ||||
							
								
								
									
										4
									
								
								hledger/test/errors/csvstdinrules.sh
									
									
									
									
									
										Executable file
									
								
							
							
						
						
									
										4
									
								
								hledger/test/errors/csvstdinrules.sh
									
									
									
									
									
										Executable file
									
								
							| @ -0,0 +1,4 @@ | ||||
| #!/usr/bin/env -S  sh | ||||
| # Second space above is significant, prevents shelltest's "-w hledger" substitution. | ||||
| # Try to read CSV from stdin without specifying a rules file. | ||||
| echo | hledger -fcsv:- check | ||||
							
								
								
									
										4
									
								
								hledger/test/errors/csvstdinrules.test
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										4
									
								
								hledger/test/errors/csvstdinrules.test
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,4 @@ | ||||
| $$$  sh csvstdinrules.sh | ||||
| >>>2 /hledger: Error: please use --rules-file when reading CSV from stdin | ||||
| / | ||||
| >>>= 1 | ||||
							
								
								
									
										5
									
								
								hledger/test/errors/csvtwofields.csv
									
									
									
									
									
										Executable file
									
								
							
							
						
						
									
										5
									
								
								hledger/test/errors/csvtwofields.csv
									
									
									
									
									
										Executable file
									
								
							| @ -0,0 +1,5 @@ | ||||
| #!/usr/bin/env -S hledger check -f  | ||||
| # Record(s) have less than two fields. | ||||
| a,a | ||||
| b | ||||
| c,c | ||||
| 
 | 
							
								
								
									
										2
									
								
								hledger/test/errors/csvtwofields.csv.rules
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										2
									
								
								hledger/test/errors/csvtwofields.csv.rules
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,2 @@ | ||||
| skip 2 | ||||
| date %1 | ||||
							
								
								
									
										4
									
								
								hledger/test/errors/csvtwofields.test
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										4
									
								
								hledger/test/errors/csvtwofields.test
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,4 @@ | ||||
| $$$ hledger check -f  csvtwofields.csv | ||||
| >>>2 /hledger: Error: CSV record \["b"\] has less than two fields | ||||
| / | ||||
| >>>= 1 | ||||
							
								
								
									
										46
									
								
								hledger/test/errors/hledger2shelltest
									
									
									
									
									
										Executable file
									
								
							
							
						
						
									
										46
									
								
								hledger/test/errors/hledger2shelltest
									
									
									
									
									
										Executable file
									
								
							| @ -0,0 +1,46 @@ | ||||
| #!/usr/bin/env bash | ||||
| # hledger2shelltest SCRIPT | ||||
| # | ||||
| # Speaking generally: given an executable hashbang script (beginning with #!/usr/bin/env), | ||||
| # this generates a similarly-named shelltestrunner test that will repeatably | ||||
| # run the same command as the script and test its (stderr) output. | ||||
| # (Ideally, this would be built in to shelltestrunner.) | ||||
| # More precisely, this generates a test expecting no stdout, the given stderr, | ||||
| # and an error exit code, for scripts reproducing various hledger errors. | ||||
| # | ||||
| # The script is run once to capture its output, which is then adjusted | ||||
| # for use in a shelltest regex matcher: | ||||
| # - common regex metacharacters are escaped | ||||
| # - file paths are simplified | ||||
| # - any remaining problematic text is sanitised | ||||
| # - the regex is trimmed to <= 300 chars, to avoid a shelltestrunner limitation. | ||||
| 
 | ||||
| SCRIPT="$1" | ||||
| TEST=$(echo "$SCRIPT" | sed -E 's/\.[^.]+$//').test | ||||
| 
 | ||||
| { | ||||
| head -1 "$SCRIPT" | sed -E "s%#!/usr/bin/env -S (.*)%\$\$\$ \1 $SCRIPT%" | ||||
| printf ">>>2 /" | ||||
| ./"$SCRIPT" 2>&1 | sed -E \ | ||||
|   -e 's/\^/\\^/g' \ | ||||
|   -e 's/\$/\\$/g' \ | ||||
|   -e 's/\+/\\+/g' \ | ||||
|   -e 's/\*/\\*/g' \ | ||||
|   -e 's/\[/\\[/g' \ | ||||
|   -e 's/\]/\\]/g' \ | ||||
|   -e 's/\(/\\(/g' \ | ||||
|   -e 's/\)/\\)/g' \ | ||||
|   -e 's/\|/\\|/g' \ | ||||
|   -e 's%(hledger: Error: ).*/\./(.*)%\1.*\2%' \ | ||||
|   -e 's%/%\\/%g' \ | ||||
|   | head -c 300 | ||||
| printf "/\n>>>= 1\n" | ||||
| } >"$TEST" | ||||
| 
 | ||||
| 
 | ||||
| #  -e 's%alias \\/\(\\/%alias \\/\\(\\/%' \ | ||||
| #  -e 's%compiled: \(%compiled: \\(%' \ | ||||
| 
 | ||||
| # gnused() {  # GNU sed, called gsed on mac | ||||
| #     if hash gsed 2>/dev/null; then gsed "$@"; else sed "$@"; fi | ||||
| # } | ||||
| @ -1,8 +1,13 @@ | ||||
| $$$ hledger check ordereddates -f ordereddates.j | ||||
| >>>2 /hledger: Error: .*ordereddates.j:10:1-10: | ||||
| 10 | 2022-01-01 p | ||||
|    | ^^^^^^^^^^ | ||||
|    |     (a)               1 | ||||
| transaction date is out of order with previous transaction date 2022-01-02 | ||||
| / | ||||
| >>>2 /hledger: Error: .*ordereddates.j:10: | ||||
| 7 \| 2022-01-02 p | ||||
|   \|     \(a\)               1 | ||||
|   | ||||
| 10 \| 2022-01-01 p | ||||
|    \| \^\^\^\^\^\^\^\^\^\^ | ||||
|    \|     \(a\)               1 | ||||
| 
 | ||||
| Ordered dates checking is enabled, and this transaction's | ||||
| date \(2022-01-01\) is out of order with the previous transaction. | ||||
| Consider/ | ||||
| >>>= 1 | ||||
| @ -1,9 +1,10 @@ | ||||
| $$$ hledger check -f parseable-dates.j | ||||
| >>>2 /hledger: Error: .*parseable-dates.j:3:1: | ||||
|   | | ||||
| 3 | 2022\/1\/32 | ||||
|   | ^^^^^^^^^ | ||||
| well-formed but invalid date: 2022\/1\/32 | ||||
|   \| | ||||
| 3 \| 2022\/1\/32 | ||||
|   \| \^\^\^\^\^\^\^\^\^ | ||||
| 
 | ||||
| This date is invalid, please correct it: 2022\/1\/32 | ||||
| 
 | ||||
| / | ||||
| >>>= 1 | ||||
| @ -1,9 +1,11 @@ | ||||
| $$$ hledger check -f parseable-regexps.j | ||||
| >>>2 /hledger: Error: .*parseable-regexps.j:3:8: | ||||
|   | | ||||
| 3 | alias \/\(\/ = a | ||||
|   |        ^ | ||||
| this regular expression could not be compiled: \( | ||||
|   \| | ||||
| 3 \| alias \/\(\/ = a | ||||
|   \|        \^ | ||||
| 
 | ||||
| This regular expression is malformed, please correct it: | ||||
| \( | ||||
| 
 | ||||
| / | ||||
| >>>= 1 | ||||
| @ -1,8 +1,8 @@ | ||||
| $$$ hledger check -f parseable.j | ||||
| >>>2 /hledger: Error: .*parseable.j:3:2: | ||||
|   | | ||||
| 3 | 1 | ||||
|   |  ^ | ||||
|   \| | ||||
| 3 \| 1 | ||||
|   \|  \^ | ||||
| unexpected newline | ||||
| expecting date separator or digit | ||||
| 
 | ||||
|  | ||||
| @ -1,9 +1,14 @@ | ||||
| $$$ hledger check payees -f payees.j | ||||
| >>>2 /hledger: Error: .*payees.j:6:12-12: | ||||
| 6 | 2022-01-01 p | ||||
|   |            ^ | ||||
|   |     (a)             A 1 | ||||
| undeclared payee "p" | ||||
| >>>2 /hledger: Error: .*payees.j:6: | ||||
| 6 \| 2022-01-01 p | ||||
|   \|            \^ | ||||
|   \|     \(a\)             A 1 | ||||
| 
 | ||||
| Strict payee checking is enabled, and | ||||
| payee "p" has not been declared. | ||||
| Consider adding a payee directive. Examples: | ||||
| 
 | ||||
| payee p | ||||
| 
 | ||||
| / | ||||
| >>>= 1 | ||||
							
								
								
									
										10
									
								
								hledger/test/errors/tcclockouttime.test
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										10
									
								
								hledger/test/errors/tcclockouttime.test
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,10 @@ | ||||
| $$$ hledger check -f tcclockouttime.timeclock | ||||
| >>>2 /hledger: Error: .*tcclockouttime.timeclock:5:1: | ||||
|   \| i 2022-01-01 00:01:00    | ||||
| 5 \| o 2022-01-01 00:00:00    | ||||
|   \|   \^\^\^\^\^\^\^\^\^\^\^\^\^\^\^\^\^\^\^ | ||||
| 
 | ||||
| This clockout time \(2022-01-01 00:00:00\) is earlier than the previous clockin. | ||||
| Please adjust it to be later than 2022-01-01 00:01:00. | ||||
| / | ||||
| >>>= 1 | ||||
							
								
								
									
										5
									
								
								hledger/test/errors/tcclockouttime.timeclock
									
									
									
									
									
										Executable file
									
								
							
							
						
						
									
										5
									
								
								hledger/test/errors/tcclockouttime.timeclock
									
									
									
									
									
										Executable file
									
								
							| @ -0,0 +1,5 @@ | ||||
| #!/usr/bin/env -S hledger check -f | ||||
| # Clockout time before previous clockin. | ||||
| 
 | ||||
| i 2022/01/01 00:01:00 | ||||
| o 2022/01/01 00:00:00 | ||||
							
								
								
									
										10
									
								
								hledger/test/errors/tcorderedactions.test
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										10
									
								
								hledger/test/errors/tcorderedactions.test
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,10 @@ | ||||
| $$$ hledger check -f  tcorderedactions.timeclock | ||||
| >>>2 /hledger: Error: .*tcorderedactions.timeclock:8:1: | ||||
| 8 \| i 2022-01-01 00:01:00    | ||||
|   \| \^ | ||||
| 
 | ||||
| Expected timeclock o entry but got i. | ||||
| Only one session may be clocked in at a time. | ||||
| Please alternate i and o, beginning with i. | ||||
| / | ||||
| >>>= 1 | ||||
							
								
								
									
										8
									
								
								hledger/test/errors/tcorderedactions.timeclock
									
									
									
									
									
										Executable file
									
								
							
							
						
						
									
										8
									
								
								hledger/test/errors/tcorderedactions.timeclock
									
									
									
									
									
										Executable file
									
								
							| @ -0,0 +1,8 @@ | ||||
| #!/usr/bin/env -S hledger check -f  | ||||
| # Clockin/clockout out of order: | ||||
| # two clockins without intervening clockout, | ||||
| # two clockouts without intervening clockin, | ||||
| # or an initial clockout with no preceding clockin. | ||||
| 
 | ||||
| i 2022/01/01 00:00:00 | ||||
| i 2022/01/01 00:01:00 | ||||
| @ -1,9 +1,13 @@ | ||||
| $$$ hledger check uniqueleafnames -f uniqueleafnames.j | ||||
| >>>2 /hledger: Error: .*uniqueleafnames.j:9:8-8: | ||||
|   | 2022-01-01 p | ||||
| 9 |     (a:c)               1 | ||||
|   |        ^ | ||||
| account leaf name "c" is not unique | ||||
| it is used in account names: "a:c", "b:c" | ||||
| / | ||||
| >>>2 /hledger: Error: .*uniqueleafnames.j:12: | ||||
|   \| 2022-01-01 p | ||||
| 9 \|     \(a:c\)               1 | ||||
|  ... | ||||
|    \| 2022-01-01 p | ||||
| 12 \|     \(b:c\)               1 | ||||
|    \|        \^ | ||||
| 
 | ||||
| Checking for unique account leaf names is enabled, and | ||||
| account leaf name "c" is not unique. | ||||
| It appears in these account names, which a/ | ||||
| >>>= 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 | ||||
| 
 | ||||
| 
 | ||||
|  | ||||
| @ -56,7 +56,7 @@ $ hledger -f - stats | ||||
|   b   $-1  = $-3 | ||||
| 
 | ||||
| $ hledger -f - stats | ||||
| >2 /balance assertion.*11:12/ | ||||
| >2 /Error: -:11:12/ | ||||
| >=1 | ||||
| 
 | ||||
| # 4. should also work without commodity symbols | ||||
| @ -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 | ||||
| @ -314,7 +314,7 @@ $ hledger -f - stats | ||||
|     a       0 == $1 | ||||
| 
 | ||||
| $ hledger -f - stats | ||||
| >2 /balance assertion.*10:15/ | ||||
| >2 /Error: -:10:15:/ | ||||
| >=1 | ||||
| 
 | ||||
| # 18. Mix different commodities and total assignments | ||||
| @ -385,7 +385,7 @@ commodity $1000.00 | ||||
|     (a)             $1.00  = $1.01 | ||||
| 
 | ||||
| $ hledger -f- print | ||||
| >2 /difference: 0\.004/ | ||||
| >2 /a difference of.*0\.004/ | ||||
| >=1 | ||||
| 
 | ||||
| # 23. This fails | ||||
| @ -399,7 +399,7 @@ commodity $1000.00 | ||||
|     (a)             $1.00  = $1.0061 | ||||
| 
 | ||||
| $ hledger -f- print | ||||
| >2 /difference: 0\.0001/ | ||||
| >2 /a difference of.*0\.0001/ | ||||
| >=1 | ||||
| 
 | ||||
| # 24. Inclusive assertions include balances from subaccounts. | ||||
|  | ||||
| @ -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 | ||||
|  | ||||
| @ -56,7 +56,7 @@ $ hledger -f - print -x | ||||
|   c | ||||
| 
 | ||||
| $ hledger -f journal:- print | ||||
| >2 /can't have more than one real posting with no amount/ | ||||
| >2 /can't be more than one real posting with no amount/ | ||||
| >=1 | ||||
| 
 | ||||
| # 6. Two (or more) virtual postings with implicit amount cannot be balanced. | ||||
| @ -123,13 +123,15 @@ $ hledger -f- print | ||||
|   b  1B | ||||
| $ hledger -f- print | ||||
| >2 | ||||
| hledger: Error: unbalanced transaction: -:1-3: | ||||
| hledger: Error: -:1-3: | ||||
| 1 | 2020-01-01 | ||||
|   |     a              1A | ||||
|   |     b              1B | ||||
| 
 | ||||
| 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. | ||||
|  | ||||
| @ -22,7 +22,7 @@ $ hledger -f timeclock:- print | ||||
| >2 | ||||
| >= 0 | ||||
| 
 | ||||
| # Command-line account aliases are applied. | ||||
| # 2. Command-line account aliases are applied. | ||||
| $ hledger -ftimeclock:- print --alias '/account/=FOO' | ||||
| 2009-01-01 * 08:00-09:00 | ||||
|     ()           1.00h | ||||
| @ -35,37 +35,29 @@ $ hledger -ftimeclock:- print --alias '/account/=FOO' | ||||
| 
 | ||||
| >= 0 | ||||
| 
 | ||||
| # For a missing clock-out, now is implied | ||||
| # 3. For a missing clock-out, now is implied | ||||
| < | ||||
| i 2020/1/1 08:00 | ||||
| $ hledger -f timeclock:- balance | ||||
| > /./ | ||||
| >= 0 | ||||
| 
 | ||||
| # For a log not starting with clock-out, print error | ||||
| # 4. For a log not starting with clock-out, print error | ||||
| < | ||||
| o 2020/1/1 08:00 | ||||
| $ hledger -f timeclock:- balance | ||||
| >2 /line 1: expected timeclock code i/ | ||||
| >2 /Expected timeclock i entry/ | ||||
| >= !0 | ||||
| 
 | ||||
| # For a different log starting not with clock-out, print error | ||||
| < | ||||
| o 2020/1/1 08:00 | ||||
| o 2020/1/1 09:00 | ||||
| $ hledger -f timeclock:- balance | ||||
| >2 /line 1: expected timeclock code i/ | ||||
| >= !0 | ||||
| 
 | ||||
| # For two consecutive clock-in, print error | ||||
| # 5. For two consecutive clock-ins, print error | ||||
| < | ||||
| i 2020/1/1 08:00 | ||||
| i 2020/1/1 09:00 | ||||
| $ hledger -f timeclock:- balance | ||||
| >2 /line 2: expected timeclock code o/ | ||||
| >2 /Expected timeclock o entry/ | ||||
| >= !0 | ||||
| 
 | ||||
| # Timeclock amounts are always rounded to two decimal places,  | ||||
| # 6. Timeclock amounts are always rounded to two decimal places,  | ||||
| # even when displayed by print (#1527). | ||||
| < | ||||
| i 2020-01-30 08:38:35 a | ||||
|  | ||||
		Loading…
	
		Reference in New Issue
	
	Block a user