Copyright | © 2015–2018 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.
You probably do not want to import this module directly because Text.Megaparsec re-exports it anyway.
Synopsis
- data ErrorItem t
- data ErrorFancy e
- data ParseError t e
- = TrivialError (NonEmpty SourcePos) (Maybe (ErrorItem t)) (Set (ErrorItem t))
- | FancyError (NonEmpty SourcePos) (Set (ErrorFancy e))
- errorPos :: ParseError t e -> NonEmpty SourcePos
- class ShowToken a where
- class LineToken a where
- class Ord a => ShowErrorComponent a where
- parseErrorPretty :: (Ord t, ShowToken t, ShowErrorComponent e) => ParseError t e -> String
- parseErrorPretty' :: (ShowToken (Token s), LineToken (Token s), ShowErrorComponent e, Stream s) => s -> ParseError (Token s) e -> String
- parseErrorPretty_ :: forall s e. (ShowToken (Token s), LineToken (Token s), ShowErrorComponent e, Stream s) => Pos -> s -> ParseError (Token s) e -> String
- sourcePosStackPretty :: NonEmpty SourcePos -> String
- parseErrorTextPretty :: (Ord t, ShowToken t, ShowErrorComponent e) => ParseError t e -> String
Parse error type
Data type that is used to represent “unexpected/expected” items in
ParseError
. The data type is parametrized over the token type t
.
Since: megaparsec-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) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ErrorItem t) # toConstr :: ErrorItem t -> Constr # dataTypeOf :: ErrorItem t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (ErrorItem t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (ErrorItem t)) # gmapT :: (forall b. Data b => b -> b) -> ErrorItem t -> ErrorItem t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ErrorItem t -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ErrorItem t -> r # gmapQ :: (forall d. Data d => d -> u) -> ErrorItem t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ErrorItem t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ErrorItem t -> m (ErrorItem t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ErrorItem t -> m (ErrorItem t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ErrorItem t -> m (ErrorItem t) # | |
Ord t => Ord (ErrorItem t) Source # | |
Defined in Text.Megaparsec.Error | |
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 | |
(Ord t, ShowToken t) => ShowErrorComponent (ErrorItem t) Source # | |
Defined in Text.Megaparsec.Error showErrorComponent :: ErrorItem t -> String Source # | |
type Rep (ErrorItem t) Source # | |
Defined in Text.Megaparsec.Error type Rep (ErrorItem t) = D1 (MetaData "ErrorItem" "Text.Megaparsec.Error" "megaparsec-6.5.0-4VKBtSFJhna3iLscGKIZAP" 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 :: * -> *))) |
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: megaparsec-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, can be conveniently disabled by indexing
|
Instances
data ParseError t e Source #
represents a parse error parametrized over the token
type ParseError
t et
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
instances of the data type allow 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: megaparsec-6.0.0
TrivialError (NonEmpty SourcePos) (Maybe (ErrorItem t)) (Set (ErrorItem t)) | Trivial errors, generated by Megaparsec's machinery. The data constructor includes the stack of source positions, unexpected token (if any), and expected tokens. |
FancyError (NonEmpty SourcePos) (Set (ErrorFancy e)) | Fancy, custom errors. |
Instances
errorPos :: ParseError t e -> NonEmpty SourcePos Source #
Get position of given ParseError
.
Since: megaparsec-6.0.0
Pretty-printing
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.
Since: megaparsec-5.0.0
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).
class LineToken a where Source #
Type class for tokens that support operations necessary for selecting and displaying relevant line of input.
Since: megaparsec-6.0.0
tokenAsChar :: a -> Char Source #
Convert a token to a Char
. This is used to print relevant line from
input stream by turning a list of tokens into a String
.
tokenIsNewline :: a -> Bool Source #
Check if given token is a newline or contains newline.
Instances
LineToken Char Source # | |
Defined in Text.Megaparsec.Error tokenAsChar :: Char -> Char Source # tokenIsNewline :: Char -> Bool Source # | |
LineToken Word8 Source # | |
Defined in Text.Megaparsec.Error tokenAsChar :: Word8 -> Char Source # tokenIsNewline :: Word8 -> Bool Source # |
class Ord a => ShowErrorComponent a where Source #
The type class defines how to print custom data component of
ParseError
.
Since: megaparsec-5.0.0
showErrorComponent :: a -> String Source #
Pretty-print custom data component of ParseError
.
Instances
ShowErrorComponent Void Source # | |
Defined in Text.Megaparsec.Error showErrorComponent :: Void -> String Source # | |
ShowErrorComponent e => ShowErrorComponent (ErrorFancy e) Source # | |
Defined in Text.Megaparsec.Error showErrorComponent :: ErrorFancy e -> String Source # | |
(Ord t, ShowToken t) => ShowErrorComponent (ErrorItem t) Source # | |
Defined in Text.Megaparsec.Error showErrorComponent :: ErrorItem t -> String 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.
Since: megaparsec-5.0.0
:: (ShowToken (Token s), LineToken (Token s), ShowErrorComponent e, Stream s) | |
=> s | Original input stream |
-> ParseError (Token s) e | Parse error to render |
-> String | Result of rendering |
Pretty-print a ParseError
and display the line on which the parse
error occurred. The rendered String
always ends with a newline.
Note that if you work with include files and have a stack of
SourcePos
es in ParseError
, it's up to you to provide correct input
stream corresponding to the file in which parse error actually happened.
parseErrorPretty'
is defined in terms of the more general
parseErrorPretty_
function which allows to specify tab width as well:
parseErrorPretty' = parseErrorPretty_ defaultTabWidth
Since: megaparsec-6.0.0
:: (ShowToken (Token s), LineToken (Token s), ShowErrorComponent e, Stream s) | |
=> Pos | Tab width |
-> s | Original input stream |
-> ParseError (Token s) e | Parse error to render |
-> String | Result of rendering |
Just like parseErrorPretty'
, but allows to specify tab width.
Since: megaparsec-6.1.0
sourcePosStackPretty :: NonEmpty SourcePos -> String Source #
Pretty-print a stack of source positions.
Since: megaparsec-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: megaparsec-5.1.0