Skip to content

Commit 13cc38a

Browse files
committed
New String function: parseErrorHuman
1 parent 413fb9e commit 13cc38a

File tree

3 files changed

+64
-4
lines changed

3 files changed

+64
-4
lines changed

src/Parsing.purs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -50,9 +50,11 @@ import Data.Tuple (Tuple(..), fst)
5050
-- | the position in the input stream at which the error occurred.
5151
data ParseError = ParseError String Position
5252

53+
-- | Get the `Message` from a `ParseError`
5354
parseErrorMessage :: ParseError -> String
5455
parseErrorMessage (ParseError msg _) = msg
5556

57+
-- | Get the `Position` from a `ParseError`.
5658
parseErrorPosition :: ParseError -> Position
5759
parseErrorPosition (ParseError _ pos) = pos
5860

src/Parsing/String.purs

Lines changed: 50 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
1-
-- | Primitive parsers for working with an input stream of type `String`.
1+
-- | Primitive parsers and functions for working with an input stream of
2+
-- | type `String`.
23
-- |
34
-- | All of these primitive parsers will consume when they succeed.
45
-- |
@@ -47,15 +48,18 @@ module Parsing.String
4748
, regex
4849
, anyTill
4950
, consumeWith
51+
, parseErrorHuman
5052
) where
5153

5254
import Prelude hiding (between)
5355

5456
import Control.Monad.Rec.Class (Step(..), tailRecM)
57+
import Data.Array (replicate)
5558
import Data.Array.NonEmpty as NonEmptyArray
5659
import Data.Either (Either(..))
5760
import Data.Enum (fromEnum, toEnum)
5861
import Data.Function.Uncurried (mkFn5, runFn2)
62+
import Data.Int (odd)
5963
import Data.Maybe (Maybe(..), fromJust)
6064
import Data.String (CodePoint, Pattern(..), codePointAt, length, null, splitAt, stripPrefix, uncons)
6165
import Data.String as String
@@ -339,4 +343,48 @@ anyTill p = do
339343
( do
340344
_ <- anyCodePoint
341345
pure $ Loop unit
342-
)
346+
)
347+
348+
-- | Returns three `String`s which, when printed line-by-line, will show
349+
-- | a nice human-readable parsing error message.
350+
-- |
351+
-- | The first argument is the input `String` given to the parser which
352+
-- | errored.
353+
-- |
354+
-- | The second argument is a positive `Int` which indicates how many
355+
-- | characters of input `String` context are wanted around the parsing error.
356+
-- |
357+
-- | The third argument is the `ParseError` for the input `String`.
358+
-- |
359+
-- | #### Example
360+
-- |
361+
-- | ```
362+
-- | let input = "12345six789"
363+
-- | case runParser input (replicateA 9 String.Basic.digit) of
364+
-- | Left err -> log $ String.joinWith "\n" $ parseErrorHuman input 20 err
365+
-- | ```
366+
-- | ---
367+
-- | ```
368+
-- | Expected more phrases at position index:5 (line:1, column:6)
369+
-- | ▼
370+
-- | 12345six789
371+
-- | ```
372+
parseErrorHuman :: String -> Int -> ParseError -> Array String
373+
parseErrorHuman input contextSize (ParseError msg (Position { line, column, index })) =
374+
-- inspired by
375+
-- https://github.com/elm/parser/blob/master/README.md#tracking-context
376+
--
377+
-- TODO
378+
-- * constrain the context window to enclosing newlines
379+
-- * grow the context window to contextSize if the error is at beginning or end of input
380+
[ msg <> " at position index:" <> show index <> " (line:" <> show line <> ", column:" <> show column <> ")"
381+
, (String.joinWith "" (replicate (index - minPosBefore) " ")) <> ""
382+
, inputContext
383+
]
384+
where
385+
inputLength = String.length input
386+
-- position minus half of context until the prior newline
387+
minPosBefore = max 0 (index - (contextSize / 2) - if odd contextSize then 1 else 0)
388+
-- position plus half of context until the following newline
389+
maxPosAfter = min inputLength (index + (contextSize / 2))
390+
inputContext = String.take (maxPosAfter - minPosBefore) (String.drop minPosBefore input)

test/Main.purs

Lines changed: 12 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ import Data.NonEmpty ((:|))
2323
import Data.Number (infinity, nan)
2424
import Data.Number as Data.Number
2525
import Data.String (toUpper)
26+
import Data.String as String
2627
import Data.String.CodePoints as SCP
2728
import Data.String.CodeUnits (fromCharArray, singleton)
2829
import Data.String.CodeUnits as SCU
@@ -34,12 +35,13 @@ import Effect.Console (log, logShow)
3435
import Effect.Unsafe (unsafePerformEffect)
3536
import Node.Process (lookupEnv)
3637
import Parsing (ParseError(..), ParseState(..), Parser, ParserT, Position(..), consume, fail, getParserT, initialPos, parseErrorMessage, parseErrorPosition, position, region, runParser)
37-
import Parsing.Combinators (advance, between, chainl, chainl1, chainr, chainr1, choice, empty, endBy, endBy1, lookAhead, many, many1, many1Till, many1Till_, manyIndex, manyTill, manyTill_, notFollowedBy, optionMaybe, sepBy, sepBy1, sepEndBy, sepEndBy1, skipMany, skipMany1, try, (<?>), (<??>), (<~?>))
38+
import Parsing.Combinators (advance, between, chainl, chainl1, chainr, chainr1, choice, empty, endBy, endBy1, lookAhead, many, many1, many1Till, many1Till_, manyIndex, manyTill, manyTill_, notFollowedBy, optionMaybe, replicateA, sepBy, sepBy1, sepEndBy, sepEndBy1, skipMany, skipMany1, try, (<?>), (<??>), (<~?>))
3839
import Parsing.Combinators.Array as Combinators.Array
3940
import Parsing.Expr (Assoc(..), Operator(..), buildExprParser)
4041
import Parsing.Language (haskellDef, haskellStyle, javaStyle)
41-
import Parsing.String (anyChar, anyCodePoint, anyTill, char, eof, match, regex, rest, satisfy, string, takeN)
42+
import Parsing.String (anyChar, anyCodePoint, anyTill, char, eof, match, parseErrorHuman, regex, rest, satisfy, string, takeN)
4243
import Parsing.String.Basic (intDecimal, letter, noneOfCodePoints, number, oneOfCodePoints, skipSpaces, whiteSpace)
44+
import Parsing.String.Basic as String.Basic
4345
import Parsing.String.Replace (breakCap, replace, replaceT, splitCap, splitCapT)
4446
import Parsing.Token (TokenParser, makeTokenParser, token, when)
4547
import Parsing.Token as Token
@@ -1070,3 +1072,11 @@ main = do
10701072
{ actual: lmap parseErrorPosition $ runParser "aa" $ advance consume
10711073
, expected: Left (Position { index: 0, line: 1, column: 1 })
10721074
}
1075+
1076+
log "\nTESTS error messages\n"
1077+
do
1078+
let input = "12345six789"
1079+
-- case runParser input (manyIndex 9 9 \_ -> String.Basic.digit) of
1080+
case runParser input (replicateA 9 String.Basic.digit) of
1081+
Right (_ :: Array Char) -> pure unit
1082+
Left err -> log $ String.joinWith "\n" $ parseErrorHuman input 20 err

0 commit comments

Comments
 (0)