megaparsec-5.0.0: Monadic parser combinators

Copyright© 2015–2016 Megaparsec contributors
LicenseFreeBSD
MaintainerMark Karpov <markkarpov@opmbx.org>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.Megaparsec.Error

Description

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.

Synopsis

Documentation

data ErrorItem t Source

Data type that is used to represent “unexpected/expected” items in parse error. The data type is parametrized over token type t.

Since: 5.0.0

Constructors

Tokens (NonEmpty t)

Non-empty stream of tokens

Label (NonEmpty Char)

Label (cannot be empty)

EndOfInput

End of input

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

Methods

representFail :: String -> e Source

Represent message passed to fail in parser monad.

Since: 5.0.0

representIndentation Source

Arguments

:: Ordering

Desired ordering between reference level and actual level

-> Pos

Reference indentation level

-> Pos

Actual indentation level

-> e 

Represent information about incorrect indentation.

Since: 5.0.0

data Dec Source

“Default error component”. This in our instance of ErrorComponent provided out-of-box.

Since: 5.0.0

Constructors

DecFail String

fail has been used in parser monad

DecIndentation Ordering Pos Pos

Incorrect indentation error

data ParseError t e Source

The data type ParseError represents parse errors. It provides the stack of source positions, set of expected and unexpected tokens as well as set of custom associated data. The data type is parametrized over token type t and custom data e.

Note that 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 (or Monoid) instance of the data type allows to merge parse errors from different branches of parsing. When merging two ParseErrors, longest match is preferred; if positions are the same, custom data sets and collections of message items are combined.

Constructors

ParseError 

Fields

errorPos :: NonEmpty SourcePos

Stack of source positions

errorUnexpected :: Set (ErrorItem t)

Unexpected items

errorExpected :: Set (ErrorItem t)

Expected items

errorCustom :: Set e

Associated data, if any

Instances

(Eq t, Eq e) => Eq (ParseError t e) Source 
(Ord t, Ord e, Read t, Read e) => Read (ParseError t e) Source 
(Show t, Show e) => Show (ParseError t e) Source 
(Show t, Typeable * t, Show e, Typeable * e) => Exception (ParseError t e) Source 
(Ord t, Ord e) => Monoid (ParseError t e) Source 
(Ord t, Ord e) => Semigroup (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.

Methods

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

Instances

class Ord a => ShowErrorComponent a where Source

The type class defines how to print custom data component of ParseError.

Since: 5.0.0

Methods

showErrorComponent :: a -> String Source

Pretty-print custom data component of ParseError.

parseErrorPretty Source

Arguments

:: (Ord t, ShowToken t, ShowErrorComponent e) 
=> ParseError t e

Parse error to render

-> String

Result of rendering

Pretty-print ParseError. Note that rendered String always ends with a newline.

Since: 5.0.0

sourcePosStackPretty :: NonEmpty SourcePos -> String Source

Pretty-print stack of source positions.

Since: 5.0.0