Copyright | © 2015–2018 Megaparsec contributors |
---|---|
License | FreeBSD |
Maintainer | Mark Karpov <markkarpov92@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
A set of helpers that should make construction of ParseError
s more
concise. This is primarily useful in test suites and for debugging, you
most certainly don't need it for normal usage.
Since: megaparsec-6.0.0
Synopsis
- err :: NonEmpty SourcePos -> ET t -> ParseError t e
- errFancy :: NonEmpty SourcePos -> EF e -> ParseError t e
- posI :: NonEmpty SourcePos
- posN :: forall s. Stream s => Int -> s -> NonEmpty SourcePos
- utok :: Ord t => t -> ET t
- utoks :: Ord t => [t] -> ET t
- ulabel :: Ord t => String -> ET t
- ueof :: Ord t => ET t
- etok :: Ord t => t -> ET t
- etoks :: Ord t => [t] -> ET t
- elabel :: Ord t => String -> ET t
- eeof :: Ord t => ET t
- fancy :: ErrorFancy e -> EF e
- data ET t
- data EF e
Top-level helpers
:: NonEmpty SourcePos |
|
-> ET t | Error components |
-> ParseError t e | Resulting |
Assemble a ParseError
from source position and
value. To
create source position, two helpers are available: ET
tposI
and posN
.
is a monoid and can be assembled by combining primitives
provided by this module, see below.ET
t
:: NonEmpty SourcePos |
|
-> EF e | Error components |
-> ParseError t e | Resulting |
Like err
, but constructs a “fancy” ParseError
.
Error position
Error components
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).
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.
fancy :: ErrorFancy e -> EF e Source #
Construct a custom error component.
Data types
Auxiliary type for construction of trivial parse errors.
Instances
Eq t => Eq (ET t) Source # | |
(Data t, Ord t) => Data (ET t) Source # | |
Defined in Text.Megaparsec.Error.Builder 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) # dataTypeOf :: ET t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (ET t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 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 # | |
Generic (ET t) Source # | |
Ord t => Semigroup (ET t) Source # | |
Ord t => Monoid (ET t) Source # | |
type Rep (ET t) Source # | |
Defined in Text.Megaparsec.Error.Builder type Rep (ET t) = D1 (MetaData "ET" "Text.Megaparsec.Error.Builder" "megaparsec-6.5.0-4VKBtSFJhna3iLscGKIZAP" False) (C1 (MetaCons "ET" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ErrorItem t))) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set (ErrorItem t))))) |
Auxiliary type for construction of fancy parse errors.
Instances
Eq e => Eq (EF e) Source # | |
(Data e, Ord e) => Data (EF e) Source # | |
Defined in Text.Megaparsec.Error.Builder 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) # 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 :: (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 # | |
Generic (EF e) Source # | |
Ord e => Semigroup (EF e) Source # | |
Ord e => Monoid (EF e) Source # | |
type Rep (EF e) Source # | |
Defined in Text.Megaparsec.Error.Builder type Rep (EF e) = D1 (MetaData "EF" "Text.Megaparsec.Error.Builder" "megaparsec-6.5.0-4VKBtSFJhna3iLscGKIZAP" False) (C1 (MetaCons "EF" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set (ErrorFancy e))))) |