megaparsec-6.4.0: Monadic parser combinators

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

Text.Megaparsec.Error.Builder

Contents

Description

A set of helpers that should make construction of ParseErrors more concise. This is primarily useful in test suites and for debugging, you most certainly don't need it for normal usage.

Since: 6.0.0

Synopsis

Top-level helpers

err Source #

Arguments

:: NonEmpty SourcePos

ParseError position

-> ET t

Error components

-> ParseError t e

Resulting ParseError

Assemble a ParseError from source position and ET t value. To create source position, two helpers are available: posI and posN. ET t is a monoid and can be assembled by combining primitives provided by this module, see below.

errFancy Source #

Arguments

:: NonEmpty SourcePos

ParseError position

-> EF e

Error components

-> ParseError t e

Resulting ParseError

Like err, but constructs a “fancy” ParseError.

Error position

posI :: NonEmpty SourcePos Source #

Initial source position with empty file name.

posN :: forall s. Stream s => Int -> s -> NonEmpty SourcePos Source #

posN n s returns source position achieved by applying advanceN method corresponding to the type of stream s.

Error components

utok :: Ord t => t -> ET t Source #

Construct an “unexpected token” error component.

utoks :: Ord t => [t] -> ET t Source #

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

ulabel :: Ord t => String -> ET t Source #

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

ueof :: Ord t => ET t Source #

Construct an “unexpected end of input” error component.

etok :: Ord t => t -> ET t Source #

Construct an “expected token” error component.

etoks :: Ord t => [t] -> ET t Source #

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

elabel :: Ord t => String -> ET t Source #

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

eeof :: Ord t => ET t Source #

Construct an “expected end of input” error component.

fancy :: ErrorFancy e -> EF e Source #

Construct a custom error component.

Data types

data ET t Source #

Auxiliary type for construction of trivial parse errors.

Instances

Eq t => Eq (ET t) Source # 

Methods

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

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

(Ord t, Data t) => Data (ET t) Source # 

Methods

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

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

toConstr :: ET t -> Constr #

dataTypeOf :: ET t -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord t => Ord (ET t) Source # 

Methods

compare :: ET t -> ET t -> Ordering #

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

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

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

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

max :: ET t -> ET t -> ET t #

min :: ET t -> ET t -> ET t #

Generic (ET t) Source # 

Associated Types

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

Methods

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

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

Ord t => Semigroup (ET t) Source # 

Methods

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

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

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

Ord t => Monoid (ET t) Source # 

Methods

mempty :: ET t #

mappend :: ET t -> ET t -> ET t #

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

type Rep (ET t) Source # 
type Rep (ET t) = D1 * (MetaData "ET" "Text.Megaparsec.Error.Builder" "megaparsec-6.4.0-xl4HlJBghw88uZEZB1lRf" False) (C1 * (MetaCons "ET" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (ErrorItem t)))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Set (ErrorItem t))))))

data EF e Source #

Auxiliary type for construction of fancy parse errors.

Instances

Eq e => Eq (EF e) Source # 

Methods

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

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

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

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 a. (Data d, Data a) => c (t d a)) -> 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 :: (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 # 

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 # 

Associated Types

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

Methods

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

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

Ord e => Semigroup (EF e) Source # 

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 # 

Methods

mempty :: EF e #

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

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

type Rep (EF e) Source # 
type Rep (EF e) = D1 * (MetaData "EF" "Text.Megaparsec.Error.Builder" "megaparsec-6.4.0-xl4HlJBghw88uZEZB1lRf" False) (C1 * (MetaCons "EF" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Set (ErrorFancy e)))))