megaparsec-9.1.0: Monadic parser combinators
Copyright© 2015–present Megaparsec contributors
LicenseFreeBSD
MaintainerMark Karpov <[email protected]>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Text.Megaparsec.Error.Builder

Description

A set of helpers that should make construction of ParseErrors more concise. This is primarily useful in test suites and for debugging.

Since: 6.0.0

Synopsis

Top-level helpers

err Source #

Arguments

:: Int

ParseError offset

-> ET s

Error components

-> ParseError s e

Resulting ParseError

Assemble a ParseError from the offset and the ET t value. ET t is a monoid and can be assembled by combining primitives provided by this module, see below.

errFancy Source #

Arguments

:: Int

ParseError offset

-> EF e

Error components

-> ParseError s e

Resulting ParseError

Like err, but constructs a “fancy” ParseError.

Error components

utok :: Stream s => Token s -> ET s Source #

Construct an “unexpected token” error component.

utoks :: forall s. Stream s => Tokens s -> ET s Source #

Construct an “unexpected tokens” error component. Empty chunk produces EndOfInput.

ulabel :: Stream s => String -> ET s Source #

Construct an “unexpected label” error component. Do not use with empty strings (for empty strings it's bottom).

ueof :: Stream s => ET s Source #

Construct an “unexpected end of input” error component.

etok :: Stream s => Token s -> ET s Source #

Construct an “expected token” error component.

etoks :: forall s. Stream s => Tokens s -> ET s Source #

Construct an “expected tokens” error component. Empty chunk produces EndOfInput.

elabel :: Stream s => String -> ET s Source #

Construct an “expected label” error component. Do not use with empty strings.

eeof :: Stream s => ET s Source #

Construct an “expected end of input” error component.

fancy :: ErrorFancy e -> EF e Source #

Construct a custom error component.

Data types

data ET s Source #

Auxiliary type for construction of trivial parse errors.

Instances

Instances details
Eq (Token s) => Eq (ET s) Source # 
Instance details

Defined in Text.Megaparsec.Error.Builder

Methods

(==) :: ET s -> ET s -> Bool #

(/=) :: ET s -> ET s -> Bool #

(Data s, Data (Token s), Ord (Token s)) => Data (ET s) Source # 
Instance details

Defined in Text.Megaparsec.Error.Builder

Methods

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

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

toConstr :: ET s -> Constr #

dataTypeOf :: ET s -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord (Token s) => Ord (ET s) Source # 
Instance details

Defined in Text.Megaparsec.Error.Builder

Methods

compare :: ET s -> ET s -> Ordering #

(<) :: ET s -> ET s -> Bool #

(<=) :: ET s -> ET s -> Bool #

(>) :: ET s -> ET s -> Bool #

(>=) :: ET s -> ET s -> Bool #

max :: ET s -> ET s -> ET s #

min :: ET s -> ET s -> ET s #

Generic (ET s) Source # 
Instance details

Defined in Text.Megaparsec.Error.Builder

Associated Types

type Rep (ET s) :: Type -> Type #

Methods

from :: ET s -> Rep (ET s) x #

to :: Rep (ET s) x -> ET s #

Stream s => Semigroup (ET s) Source # 
Instance details

Defined in Text.Megaparsec.Error.Builder

Methods

(<>) :: ET s -> ET s -> ET s #

sconcat :: NonEmpty (ET s) -> ET s #

stimes :: Integral b => b -> ET s -> ET s #

Stream s => Monoid (ET s) Source # 
Instance details

Defined in Text.Megaparsec.Error.Builder

Methods

mempty :: ET s #

mappend :: ET s -> ET s -> ET s #

mconcat :: [ET s] -> ET s #

type Rep (ET s) Source # 
Instance details

Defined in Text.Megaparsec.Error.Builder

type Rep (ET s) = D1 ('MetaData "ET" "Text.Megaparsec.Error.Builder" "megaparsec-9.1.0-LwCSJo9kV7SKlIV8z3kPEl" 'False) (C1 ('MetaCons "ET" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ErrorItem (Token s)))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set (ErrorItem (Token s))))))

data EF e Source #

Auxiliary type for construction of fancy parse errors.

Instances

Instances details
Eq e => Eq (EF e) Source # 
Instance details

Defined in Text.Megaparsec.Error.Builder

Methods

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

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

(Data e, Ord e) => Data (EF e) Source # 
Instance details

Defined in Text.Megaparsec.Error.Builder

Methods

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

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

toConstr :: EF e -> Constr #

dataTypeOf :: EF e -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord e => Ord (EF e) Source # 
Instance details

Defined in Text.Megaparsec.Error.Builder

Methods

compare :: EF e -> EF e -> Ordering #

(<) :: EF e -> EF e -> Bool #

(<=) :: EF e -> EF e -> Bool #

(>) :: EF e -> EF e -> Bool #

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

max :: EF e -> EF e -> EF e #

min :: EF e -> EF e -> EF e #

Generic (EF e) Source # 
Instance details

Defined in Text.Megaparsec.Error.Builder

Associated Types

type Rep (EF e) :: Type -> Type #

Methods

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

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

Ord e => Semigroup (EF e) Source # 
Instance details

Defined in Text.Megaparsec.Error.Builder

Methods

(<>) :: EF e -> EF e -> EF e #

sconcat :: NonEmpty (EF e) -> EF e #

stimes :: Integral b => b -> EF e -> EF e #

Ord e => Monoid (EF e) Source # 
Instance details

Defined in Text.Megaparsec.Error.Builder

Methods

mempty :: EF e #

mappend :: EF e -> EF e -> EF e #

mconcat :: [EF e] -> EF e #

type Rep (EF e) Source # 
Instance details

Defined in Text.Megaparsec.Error.Builder

type Rep (EF e) = D1 ('MetaData "EF" "Text.Megaparsec.Error.Builder" "megaparsec-9.1.0-LwCSJo9kV7SKlIV8z3kPEl" 'True) (C1 ('MetaCons "EF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set (ErrorFancy e)))))