megaparsec-5.0.1: 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

Instances

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-5.0.1-8N1BMUMVDcXHJNhpuo08Wu" 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)))

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

Minimal complete definition

representFail, representIndentation

Methods

representFail :: String -> e Source #

Represent message passed to fail in parser monad.

Since: 5.0.0

representIndentation :: Ordering -> Pos -> Pos -> e Source #

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: desired ordering between reference level and actual level, reference indentation level, actual indentation level

Instances

Eq Dec Source # 

Methods

(==) :: Dec -> Dec -> Bool #

(/=) :: Dec -> Dec -> Bool #

Data Dec Source # 

Methods

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

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

toConstr :: Dec -> Constr #

dataTypeOf :: Dec -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Dec Source # 

Methods

compare :: Dec -> Dec -> Ordering #

(<) :: Dec -> Dec -> Bool #

(<=) :: Dec -> Dec -> Bool #

(>) :: Dec -> Dec -> Bool #

(>=) :: Dec -> Dec -> Bool #

max :: Dec -> Dec -> Dec #

min :: Dec -> Dec -> Dec #

Read Dec Source # 
Show Dec Source # 

Methods

showsPrec :: Int -> Dec -> ShowS #

show :: Dec -> String #

showList :: [Dec] -> ShowS #

NFData Dec Source # 

Methods

rnf :: Dec -> () #

ShowErrorComponent Dec Source # 
ErrorComponent Dec Source # 

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

Instances

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

Methods

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

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

(Data t, Data e, Ord t, Ord e) => 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 t, Ord e, Read t, Read e) => Read (ParseError t e) Source # 
(Show t, Show e) => 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, Typeable * t, Show 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 # 
type Rep (ParseError t e) = D1 (MetaData "ParseError" "Text.Megaparsec.Error" "megaparsec-5.0.1-8N1BMUMVDcXHJNhpuo08Wu" False) (C1 (MetaCons "ParseError" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "errorPos") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty SourcePos))) (S1 (MetaSel (Just Symbol "errorUnexpected") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set (ErrorItem t))))) ((:*:) (S1 (MetaSel (Just Symbol "errorExpected") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set (ErrorItem t)))) (S1 (MetaSel (Just Symbol "errorCustom") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set e))))))

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.

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

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

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