Copyright | © 2015–present Megaparsec contributors |
---|---|
License | FreeBSD |
Maintainer | Mark Karpov <markkarpov92@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Parse errors. The current version of Megaparsec supports typed errors
instead of
String
-based ones. This gives a lot of flexibility in
describing what exactly went wrong as well as a way to return arbitrary
data in case of failure.
You probably do not want to import this module directly because Text.Megaparsec re-exports it anyway.
Synopsis
- data ErrorItem t
-
data
ErrorFancy
e
- = ErrorFail String
- | ErrorIndentation Ordering Pos Pos
- | ErrorCustom e
-
data
ParseError
s e
- = TrivialError Int ( Maybe ( ErrorItem ( Token s))) ( Set ( ErrorItem ( Token s)))
- | FancyError Int ( Set ( ErrorFancy e))
- mapParseError :: Ord e' => (e -> e') -> ParseError s e -> ParseError s e'
- errorOffset :: ParseError s e -> Int
- setErrorOffset :: Int -> ParseError s e -> ParseError s e
-
data
ParseErrorBundle
s e =
ParseErrorBundle
{
- bundleErrors :: NonEmpty ( ParseError s e)
- bundlePosState :: PosState s
- attachSourcePos :: ( Traversable t, TraversableStream s) => (a -> Int ) -> t a -> PosState s -> (t (a, SourcePos ), PosState s)
-
class
Ord
a =>
ShowErrorComponent
a
where
- showErrorComponent :: a -> String
- errorComponentLen :: a -> Int
- errorBundlePretty :: forall s e. ( VisualStream s, TraversableStream s, ShowErrorComponent e) => ParseErrorBundle s e -> String
- parseErrorPretty :: ( VisualStream s, ShowErrorComponent e) => ParseError s e -> String
- parseErrorTextPretty :: forall s e. ( VisualStream s, ShowErrorComponent e) => ParseError s e -> String
Parse error type
A data type that is used to represent “unexpected/expected” items in
ParseError
. It is parametrized over the token type
t
.
Since: 5.0.0
Tokens ( NonEmpty t) |
Non-empty stream of tokens |
Label ( NonEmpty Char ) |
Label (cannot be empty) |
EndOfInput |
End of input |
Instances
Functor ErrorItem Source # | |
Eq t => Eq ( ErrorItem t) Source # | |
Data t => Data ( ErrorItem t) Source # | |
Defined in Text.Megaparsec.Error gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> ErrorItem t -> c ( ErrorItem t) Source # gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( ErrorItem t) Source # toConstr :: ErrorItem t -> Constr Source # dataTypeOf :: ErrorItem t -> DataType Source # dataCast1 :: Typeable t0 => ( forall d. Data d => c (t0 d)) -> Maybe (c ( ErrorItem t)) Source # dataCast2 :: Typeable t0 => ( forall d e. ( Data d, Data e) => c (t0 d e)) -> Maybe (c ( ErrorItem t)) Source # gmapT :: ( forall b. Data b => b -> b) -> ErrorItem t -> ErrorItem t Source # gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> ErrorItem t -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> ErrorItem t -> r Source # gmapQ :: ( forall d. Data d => d -> u) -> ErrorItem t -> [u] Source # gmapQi :: Int -> ( forall d. Data d => d -> u) -> ErrorItem t -> u Source # gmapM :: Monad m => ( forall d. Data d => d -> m d) -> ErrorItem t -> m ( ErrorItem t) Source # gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> ErrorItem t -> m ( ErrorItem t) Source # gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> ErrorItem t -> m ( ErrorItem t) Source # |
|
Ord t => Ord ( ErrorItem t) Source # | |
Defined in Text.Megaparsec.Error compare :: ErrorItem t -> ErrorItem t -> Ordering Source # (<) :: ErrorItem t -> ErrorItem t -> Bool Source # (<=) :: ErrorItem t -> ErrorItem t -> Bool Source # (>) :: ErrorItem t -> ErrorItem t -> Bool Source # (>=) :: ErrorItem t -> ErrorItem t -> Bool Source # |
|
Read t => Read ( ErrorItem t) Source # | |
Show t => Show ( ErrorItem t) Source # | |
Generic ( ErrorItem t) Source # | |
NFData t => NFData ( ErrorItem t) Source # | |
Defined in Text.Megaparsec.Error |
|
type Rep ( ErrorItem t) Source # | |
Defined in Text.Megaparsec.Error
type
Rep
(
ErrorItem
t) =
D1
('
MetaData
"ErrorItem" "Text.Megaparsec.Error" "megaparsec-9.2.1-EI4cRL0SAfYAOxBOfPeCV9" '
False
) (
C1
('
MetaCons
"Tokens" '
PrefixI
'
False
) (
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
(
NonEmpty
t)))
:+:
(
C1
('
MetaCons
"Label" '
PrefixI
'
False
) (
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
(
NonEmpty
Char
)))
:+:
C1
('
MetaCons
"EndOfInput" '
PrefixI
'
False
) (
U1
::
Type
->
Type
)))
|
data ErrorFancy e Source #
Additional error data, extendable by user. When no custom data is
necessary, the type is typically indexed by
Void
to “cancel” the
ErrorCustom
constructor.
Since: 6.0.0
ErrorFail String |
|
ErrorIndentation Ordering Pos Pos |
Incorrect indentation error: desired ordering between reference level and actual level, reference indentation level, actual indentation level |
ErrorCustom e |
Custom error data |
Instances
data ParseError s e Source #
represents a parse error parametrized over the
stream type
ParseError
s e
s
and the custom data
e
.
Semigroup
and
Monoid
instances of the data type allow us to merge
parse errors from different branches of parsing. When merging two
ParseError
s, the longest match is preferred; if positions are the same,
custom data sets and collections of message items are combined. Note that
fancy errors take precedence over trivial errors in merging.
Since: 7.0.0
TrivialError Int ( Maybe ( ErrorItem ( Token s))) ( Set ( ErrorItem ( Token s))) |
Trivial errors, generated by the Megaparsec's machinery. The data constructor includes the offset of error, unexpected token (if any), and expected tokens. Type of the first argument was changed in the version 7.0.0 . |
FancyError Int ( Set ( ErrorFancy e)) |
Fancy, custom errors. Type of the first argument was changed in the version 7.0.0 . |
Instances
mapParseError :: Ord e' => (e -> e') -> ParseError s e -> ParseError s e' Source #
errorOffset :: ParseError s e -> Int Source #
Get the offset of a
ParseError
.
Since: 7.0.0
setErrorOffset :: Int -> ParseError s e -> ParseError s e Source #
Set the offset of a
ParseError
.
Since: 8.0.0
data ParseErrorBundle s e Source #
A non-empty collection of
ParseError
s equipped with
PosState
that
allows us to pretty-print the errors efficiently and correctly.
Since: 7.0.0
ParseErrorBundle | |
|
Instances
:: ( Traversable t, TraversableStream s) | |
=> (a -> Int ) |
How to project offset from an item (e.g.
|
-> t a |
The collection of items |
-> PosState s |
Initial
|
-> (t (a, SourcePos ), PosState s) |
The collection with
|
Attach
SourcePos
es to items in a
Traversable
container given that
there is a projection allowing us to get an offset per item.
Items must be in ascending order with respect to their offsets.
Since: 7.0.0
Pretty-printing
class Ord a => ShowErrorComponent a where Source #
The type class defines how to print a custom component of
ParseError
.
Since: 5.0.0
showErrorComponent :: a -> String Source #
Pretty-print a component of
ParseError
.
errorComponentLen :: a -> Int Source #
Length of the error component in characters, used for highlighting of parse errors in input string.
Since: 7.0.0
Instances
ShowErrorComponent Void Source # | |
Defined in Text.Megaparsec.Error showErrorComponent :: Void -> String Source # errorComponentLen :: Void -> Int Source # |
:: forall s e. ( VisualStream s, TraversableStream s, ShowErrorComponent e) | |
=> ParseErrorBundle s e |
Parse error bundle to display |
-> String |
Textual rendition of the bundle |
Pretty-print a
ParseErrorBundle
. All
ParseError
s in the bundle will
be pretty-printed in order together with the corresponding offending
lines by doing a single pass over the input stream. The rendered
String
always ends with a newline.
Since: 7.0.0
:: ( VisualStream s, ShowErrorComponent e) | |
=> ParseError s e |
Parse error to render |
-> String |
Result of rendering |
Pretty-print a
ParseError
. The rendered
String
always ends with a
newline.
Since: 5.0.0
:: forall s e. ( VisualStream s, ShowErrorComponent e) | |
=> ParseError s e |
Parse error to render |
-> String |
Result of rendering |
Pretty-print a textual part of a
ParseError
, that is, everything
except for its position. The rendered
String
always ends with a
newline.
Since: 5.1.0