megaparsec-6.1.1: Monadic parser combinators

Copyright© 2015–2017 Megaparsec contributors
LicenseFreeBSD
MaintainerMark Karpov <markkarpov92@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.Megaparsec.Error

Contents

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.

You probably do not want to import this module directly because Text.Megaparsec re-exports it anyway.

Synopsis

Parse error type

data ErrorItem t Source #

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

Constructors

Tokens (NonEmpty t)

Non-empty stream of tokens

Label (NonEmpty Char)

Label (cannot be empty)

EndOfInput

End of input

Instances

Functor ErrorItem Source # 

Methods

fmap :: (a -> b) -> ErrorItem a -> ErrorItem b #

(<$) :: a -> ErrorItem b -> ErrorItem a #

Eq t => Eq (ErrorItem t) Source # 

Methods

(==) :: ErrorItem t -> ErrorItem t -> Bool #

(/=) :: ErrorItem t -> ErrorItem t -> Bool #

Data t => Data (ErrorItem t) Source # 

Methods

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 (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (ErrorItem t)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t 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 # 
Read t => Read (ErrorItem t) Source # 
Show t => Show (ErrorItem t) Source # 
Generic (ErrorItem t) Source # 

Associated Types

type Rep (ErrorItem t) :: * -> * #

Methods

from :: ErrorItem t -> Rep (ErrorItem t) x #

to :: Rep (ErrorItem t) x -> ErrorItem t #

NFData t => NFData (ErrorItem t) Source # 

Methods

rnf :: ErrorItem t -> () #

(Ord t, ShowToken t) => ShowErrorComponent (ErrorItem t) Source # 
type Rep (ErrorItem t) Source # 
type Rep (ErrorItem t) = D1 (MetaData "ErrorItem" "Text.Megaparsec.Error" "megaparsec-6.1.1-CMqSyVo2ujBIkjeh07Majh" False) ((:+:) (C1 (MetaCons "Tokens" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty t)))) ((:+:) (C1 (MetaCons "Label" PrefixI False) (S1 (MetaSel (Nothing 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: 6.0.0

Constructors

ErrorFail String

fail has been used in parser monad

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 ErrorFancy by Void

Instances

Functor ErrorFancy Source # 

Methods

fmap :: (a -> b) -> ErrorFancy a -> ErrorFancy b #

(<$) :: a -> ErrorFancy b -> ErrorFancy a #

Eq e => Eq (ErrorFancy e) Source # 

Methods

(==) :: ErrorFancy e -> ErrorFancy e -> Bool #

(/=) :: ErrorFancy e -> ErrorFancy e -> Bool #

Data e => Data (ErrorFancy e) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ErrorFancy e -> c (ErrorFancy e) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ErrorFancy e) #

toConstr :: ErrorFancy e -> Constr #

dataTypeOf :: ErrorFancy e -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (ErrorFancy e)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d a. (Data d, Data a) => c (t d a)) -> Maybe (c (ErrorFancy e)) #

gmapT :: (forall b. Data b => b -> b) -> ErrorFancy e -> ErrorFancy e #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ErrorFancy e -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ErrorFancy e -> r #

gmapQ :: (forall d. Data d => d -> u) -> ErrorFancy e -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ErrorFancy e -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ErrorFancy e -> m (ErrorFancy e) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ErrorFancy e -> m (ErrorFancy e) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ErrorFancy e -> m (ErrorFancy e) #

Ord e => Ord (ErrorFancy e) Source # 
Read e => Read (ErrorFancy e) Source # 
Show e => Show (ErrorFancy e) Source # 
Generic (ErrorFancy e) Source # 

Associated Types

type Rep (ErrorFancy e) :: * -> * #

Methods

from :: ErrorFancy e -> Rep (ErrorFancy e) x #

to :: Rep (ErrorFancy e) x -> ErrorFancy e #

NFData a => NFData (ErrorFancy a) Source # 

Methods

rnf :: ErrorFancy a -> () #

ShowErrorComponent e => ShowErrorComponent (ErrorFancy e) Source # 
type Rep (ErrorFancy e) Source # 

data ParseError t e Source #

ParseError t e represents a parse error 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 instances of the data type allow to merge parse errors from different branches of parsing. When merging two ParseErrors, 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: 6.0.0

Constructors

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

(Eq e, Eq t) => Eq (ParseError t e) Source # 

Methods

(==) :: ParseError t e -> ParseError t e -> Bool #

(/=) :: ParseError t e -> ParseError t e -> Bool #

(Ord e, Ord t, Data e, Data t) => Data (ParseError t e) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParseError t e -> c (ParseError t e) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParseError t e) #

toConstr :: ParseError t e -> Constr #

dataTypeOf :: ParseError t e -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (ParseError t e)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d a. (Data d, Data a) => c (t d a)) -> Maybe (c (ParseError t e)) #

gmapT :: (forall b. Data b => b -> b) -> ParseError t e -> ParseError t e #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParseError t e -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParseError t e -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParseError t e -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParseError t e -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParseError t e -> m (ParseError t e) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseError t e -> m (ParseError t e) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseError t e -> m (ParseError t e) #

(Ord e, Ord t, Read e, Read t) => Read (ParseError t e) Source # 
(Show e, Show t) => Show (ParseError t e) Source # 

Methods

showsPrec :: Int -> ParseError t e -> ShowS #

show :: ParseError t e -> String #

showList :: [ParseError t e] -> ShowS #

Generic (ParseError t e) Source # 

Associated Types

type Rep (ParseError t e) :: * -> * #

Methods

from :: ParseError t e -> Rep (ParseError t e) x #

to :: Rep (ParseError t e) x -> ParseError t e #

(Ord t, Ord e) => Semigroup (ParseError t e) Source # 

Methods

(<>) :: ParseError t e -> ParseError t e -> ParseError t e #

sconcat :: NonEmpty (ParseError t e) -> ParseError t e #

stimes :: Integral b => b -> ParseError t e -> ParseError t e #

(Ord t, Ord e) => Monoid (ParseError t e) Source # 

Methods

mempty :: ParseError t e #

mappend :: ParseError t e -> ParseError t e -> ParseError t e #

mconcat :: [ParseError t e] -> ParseError t e #

(Show t, Ord t, ShowToken t, Typeable * t, Show e, ShowErrorComponent e, Typeable * e) => Exception (ParseError t e) Source # 
(NFData t, NFData e) => NFData (ParseError t e) Source # 

Methods

rnf :: ParseError t e -> () #

type Rep (ParseError t e) Source # 

errorPos :: ParseError t e -> NonEmpty SourcePos Source #

Get position of given ParseError.

Since: 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: 5.0.0

Minimal complete definition

showTokens

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).

class LineToken a where Source #

Type class for tokens that support operations necessary for selecting and displaying relevant line of input.

Since: 6.0.0

Minimal complete definition

tokenAsChar, tokenIsNewline

Methods

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.

class Ord a => ShowErrorComponent a where Source #

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

Since: 5.0.0

Minimal complete definition

showErrorComponent

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 a ParseError. The rendered String always ends with a newline.

Since: 5.0.0

parseErrorPretty' Source #

Arguments

:: (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 SourcePoses 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: 6.0.0

parseErrorPretty_ Source #

Arguments

:: (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: 6.1.0

sourcePosStackPretty :: NonEmpty SourcePos -> String Source #

Pretty-print a stack of source positions.

Since: 5.0.0

parseErrorTextPretty Source #

Arguments

:: (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