Copyright | © 2015–2017 Megaparsec contributors |
---|---|
License | FreeBSD |
Maintainer | Mark Karpov <markkarpov92@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Parse errors. Current version of Megaparsec supports well-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.
- data ErrorItem t
- class Ord e => ErrorComponent e where
- data Dec
- data ParseError t e = ParseError {
- errorPos :: NonEmpty SourcePos
- errorUnexpected :: Set (ErrorItem t)
- errorExpected :: Set (ErrorItem t)
- errorCustom :: Set e
- class ShowToken a where
- class Ord a => ShowErrorComponent a where
- parseErrorPretty :: (Ord t, ShowToken t, ShowErrorComponent e) => ParseError t e -> String
- sourcePosStackPretty :: NonEmpty SourcePos -> String
- parseErrorTextPretty :: (Ord t, ShowToken t, ShowErrorComponent e) => ParseError t e -> String
Documentation
Data type that is used to represent “unexpected/expected” items in
ParseError
. The data type 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 |
Eq t => Eq (ErrorItem t) Source # | |
Data t => Data (ErrorItem t) Source # | |
Ord t => Ord (ErrorItem t) Source # | |
Read t => Read (ErrorItem t) Source # | |
Show t => Show (ErrorItem t) Source # | |
Generic (ErrorItem t) Source # | |
Arbitrary t => Arbitrary (ErrorItem t) Source # | |
NFData t => NFData (ErrorItem t) Source # | |
(Ord t, ShowToken t) => ShowErrorComponent (ErrorItem t) Source # | |
type Rep (ErrorItem t) Source # | |
class Ord e => ErrorComponent e where Source #
The type class defines how to represent information about various
exceptional situations. Data types that are used as custom data component
in ParseError
must be instances of this type class.
Since: 5.0.0
“Default error component”. This is our instance of ErrorComponent
provided out-of-box.
Since: 5.0.0
data ParseError t e Source #
ParseError
represents… parse errors. It provides the stack of source
positions, a set of expected and unexpected tokens as well as a set of
custom associated data. The data type is parametrized over the token type
t
and the custom data e
.
Note that the stack of source positions contains current position as its head, and the rest of positions allows to track full sequence of include files with topmost source file at the end of the list.
Semigroup
(and Monoid
) instance of the data type allows 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.
ParseError | |
|
(Eq e, Eq t) => Eq (ParseError t e) Source # | |
(Ord e, Ord t, Data e, Data t) => Data (ParseError t e) Source # | |
(Ord e, Ord t, Read e, Read t) => Read (ParseError t e) Source # | |
(Show e, Show t) => Show (ParseError t e) Source # | |
Generic (ParseError t e) Source # | |
(Ord t, Ord e) => Semigroup (ParseError t e) Source # | |
(Ord t, Ord e) => Monoid (ParseError t e) Source # | |
(Arbitrary t, Ord t, Arbitrary e, Ord e) => Arbitrary (ParseError t e) Source # | |
(Show t, Typeable * t, Ord t, ShowToken t, Show e, Typeable * e, ShowErrorComponent e) => Exception (ParseError t e) Source # | |
(NFData t, NFData e) => NFData (ParseError t e) Source # | |
type Rep (ParseError t e) Source # | |
class ShowToken a where Source #
Type class ShowToken
includes methods that allow to pretty-print
single token as well as stream of tokens. This is used for rendering of
error messages.
showTokens :: NonEmpty a -> String Source #
Pretty-print non-empty stream of tokens. This function is also used to print single tokens (represented as singleton lists).
Since: 5.0.0
class Ord a => ShowErrorComponent a where Source #
The type class defines how to print custom data component of
ParseError
.
Since: 5.0.0
showErrorComponent :: a -> String Source #
Pretty-print custom data component of ParseError
.
ShowErrorComponent Dec Source # | |
(Ord t, ShowToken t) => ShowErrorComponent (ErrorItem t) Source # | |
:: (Ord t, ShowToken t, ShowErrorComponent e) | |
=> ParseError t e | Parse error to render |
-> String | Result of rendering |
Pretty-print a ParseError
. The rendered String
always ends with a
newline.
The function is defined as:
parseErrorPretty e = sourcePosStackPretty (errorPos e) ++ ":\n" ++ parseErrorTextPretty e
Since: 5.0.0
sourcePosStackPretty :: NonEmpty SourcePos -> String Source #
Pretty-print a stack of source positions.
Since: 5.0.0
:: (Ord t, ShowToken t, ShowErrorComponent e) | |
=> ParseError t e | Parse error to render |
-> String | Result of rendering |
Pretty-print a textual part of a ParseError
, that is, everything
except stack of source positions. The rendered staring always ends with a
new line.
Since: 5.1.0