| Copyright | © 2015–present Megaparsec contributors |
|---|---|
| License | FreeBSD |
| Maintainer | Mark Karpov <markkarpov92@gmail.com> |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Text.Megaparsec.Error
Contents
Description
Parse errors. The current version of Megaparsec supports 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
- data ErrorItem t
- data ErrorFancy e
- = ErrorFail String
- | ErrorIndentation Ordering Pos Pos
- | ErrorCustom e
- data ParseError s e
- = TrivialError Int (Maybe (ErrorItem (Token s))) (Set (ErrorItem (Token s)))
- | FancyError Int (Set (ErrorFancy e))
- mapParseError :: Ord e' => (e -> e') -> ParseError s e -> ParseError s e'
- errorOffset :: ParseError s e -> Int
- setErrorOffset :: Int -> ParseError s e -> ParseError s e
- data ParseErrorBundle s e = ParseErrorBundle {
- bundleErrors :: NonEmpty (ParseError s e)
- bundlePosState :: PosState s
- attachSourcePos :: (Traversable t, TraversableStream s) => (a -> Int) -> t a -> PosState s -> (t (a, SourcePos), PosState s)
- class Ord a => ShowErrorComponent a where
- showErrorComponent :: a -> String
- errorComponentLen :: a -> Int
- errorBundlePretty :: forall s e. (VisualStream s, TraversableStream s, ShowErrorComponent e) => ParseErrorBundle s e -> String
- errorBundlePrettyForGhcPreProcessors :: forall s e. (VisualStream s, TraversableStream s, ShowErrorComponent e) => ParseErrorBundle s e -> String
- errorBundlePrettyWith :: forall s e. (VisualStream s, TraversableStream s) => (Maybe String -> SourcePos -> ParseError s e -> String) -> ParseErrorBundle s e -> String
- parseErrorPretty :: (VisualStream s, ShowErrorComponent e) => ParseError s e -> String
- parseErrorTextPretty :: forall s e. (VisualStream s, ShowErrorComponent e) => ParseError s e -> String
- showErrorItem :: VisualStream s => Proxy s -> ErrorItem (Token s) -> String
Parse error type
A data type that is used to represent “unexpected/expected” items in
ParseError . It is parametrized over the token type t.
Since: 5.0.0
Constructors
End of input
Instances
Instances details
Instance details
Defined in Text.Megaparsec.Error
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 t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (ErrorItem t)) #
dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 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 :: forall r r'. (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) #
Instance details
Defined in Text.Megaparsec.Error
Instance details
Defined in Text.Megaparsec.Error
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
Incorrect indentation error: desired ordering between reference level and actual level, reference indentation level, actual indentation level
Custom error data
Instances
Instances details
Instance details
Defined in Text.Megaparsec.Error
Methods
fmap :: (a -> b) -> ErrorFancy a -> ErrorFancy b #
(<$) :: a -> ErrorFancy b -> ErrorFancy a #
Instance details
Defined in Text.Megaparsec.Error
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 e0. (Data d, Data e0) => c (t d e0)) -> 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 :: forall r r'. (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) #
Instance details
Defined in Text.Megaparsec.Error
Associated Types
type Rep (ErrorFancy e) :: Type -> Type #
Instance details
Defined in Text.Megaparsec.Error
Methods
readsPrec :: Int -> ReadS (ErrorFancy e) #
readList :: ReadS [ErrorFancy e] #
readPrec :: ReadPrec (ErrorFancy e) #
readListPrec :: ReadPrec [ErrorFancy e] #
Instance details
Defined in Text.Megaparsec.Error
Methods
showsPrec :: Int -> ErrorFancy e -> ShowS #
show :: ErrorFancy e -> String #
showList :: [ErrorFancy e] -> ShowS #
Instance details
Defined in Text.Megaparsec.Error
Methods
(==) :: ErrorFancy e -> ErrorFancy e -> Bool #
(/=) :: ErrorFancy e -> ErrorFancy e -> Bool #
Instance details
Defined in Text.Megaparsec.Error
Methods
compare :: ErrorFancy e -> ErrorFancy e -> Ordering #
(<) :: ErrorFancy e -> ErrorFancy e -> Bool #
(<=) :: ErrorFancy e -> ErrorFancy e -> Bool #
(>) :: ErrorFancy e -> ErrorFancy e -> Bool #
(>=) :: ErrorFancy e -> ErrorFancy e -> Bool #
max :: ErrorFancy e -> ErrorFancy e -> ErrorFancy e #
min :: ErrorFancy e -> ErrorFancy e -> ErrorFancy e #
Instance details
Defined in Text.Megaparsec.Error
data ParseError s e Source #
represents a parse error parametrized over the
stream type ParseError s es and the custom data e.
Semigroup and Monoid instances of the data type allow us to merge
parse errors from different branches of parsing. When merging two
ParseError s, 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: 7.0.0
Constructors
Trivial errors, generated by the Megaparsec's machinery. The data constructor includes the offset of error, unexpected token (if any), and expected tokens.
Type of the first argument was changed in the version 7.0.0.
Fancy, custom errors.
Type of the first argument was changed in the version 7.0.0.
Instances
Instances details
Instance details
Defined in Text.Megaparsec.Error
Methods
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParseError s e -> c (ParseError s e) #
gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParseError s e) #
toConstr :: ParseError s e -> Constr #
dataTypeOf :: ParseError s e -> DataType #
dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParseError s e)) #
dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (ParseError s e)) #
gmapT :: (forall b. Data b => b -> b) -> ParseError s e -> ParseError s e #
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParseError s e -> r #
gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParseError s e -> r #
gmapQ :: (forall d. Data d => d -> u) -> ParseError s e -> [u] #
gmapQi :: Int -> (forall d. Data d => d -> u) -> ParseError s e -> u #
gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParseError s e -> m (ParseError s e) #
gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseError s e -> m (ParseError s e) #
gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseError s e -> m (ParseError s e) #
Instance details
Defined in Text.Megaparsec.Error
Methods
mempty :: ParseError s e #
mappend :: ParseError s e -> ParseError s e -> ParseError s e #
mconcat :: [ParseError s e] -> ParseError s e #
Instance details
Defined in Text.Megaparsec.Error
Methods
(<>) :: ParseError s e -> ParseError s e -> ParseError s e #
sconcat :: NonEmpty (ParseError s e) -> ParseError s e #
stimes :: Integral b => b -> ParseError s e -> ParseError s e #
Instance details
Defined in Text.Megaparsec.Error
Methods
toException :: ParseError s e -> SomeException #
fromException :: SomeException -> Maybe (ParseError s e) #
displayException :: ParseError s e -> String #
Instance details
Defined in Text.Megaparsec.Error
Associated Types
type Rep (ParseError s e) :: Type -> Type #
Methods
from :: ParseError s e -> Rep (ParseError s e) x #
to :: Rep (ParseError s e) x -> ParseError s e #
Instance details
Defined in Text.Megaparsec.Error
Methods
showsPrec :: Int -> ParseError s e -> ShowS #
show :: ParseError s e -> String #
showList :: [ParseError s e] -> ShowS #
Instance details
Defined in Text.Megaparsec.Error
Methods
(==) :: ParseError s e -> ParseError s e -> Bool #
(/=) :: ParseError s e -> ParseError s e -> Bool #
Instance details
Defined in Text.Megaparsec.Error
mapParseError :: Ord e' => (e -> e') -> ParseError s e -> ParseError s e' Source #
errorOffset :: ParseError s e -> Int Source #
Get the offset of a ParseError .
Since: 7.0.0
setErrorOffset :: Int -> ParseError s e -> ParseError s e Source #
Set the offset of a ParseError .
Since: 8.0.0
data ParseErrorBundle s e Source #
A non-empty collection of ParseError s equipped with PosState that
allows us to pretty-print the errors efficiently and correctly.
Since: 7.0.0
Constructors
Fields
- bundleErrors :: NonEmpty (ParseError s e)
A collection of
ParseErrors that is sorted by parse error offsets - bundlePosState :: PosState s
The state that is used for line/column calculation
Instances
Instances details
Instance details
Defined in Text.Megaparsec.Error
Methods
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParseErrorBundle s e -> c (ParseErrorBundle s e) #
gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParseErrorBundle s e) #
toConstr :: ParseErrorBundle s e -> Constr #
dataTypeOf :: ParseErrorBundle s e -> DataType #
dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParseErrorBundle s e)) #
dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (ParseErrorBundle s e)) #
gmapT :: (forall b. Data b => b -> b) -> ParseErrorBundle s e -> ParseErrorBundle s e #
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParseErrorBundle s e -> r #
gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParseErrorBundle s e -> r #
gmapQ :: (forall d. Data d => d -> u) -> ParseErrorBundle s e -> [u] #
gmapQi :: Int -> (forall d. Data d => d -> u) -> ParseErrorBundle s e -> u #
gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParseErrorBundle s e -> m (ParseErrorBundle s e) #
gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseErrorBundle s e -> m (ParseErrorBundle s e) #
gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseErrorBundle s e -> m (ParseErrorBundle s e) #
Instance details
Defined in Text.Megaparsec.Error
Methods
toException :: ParseErrorBundle s e -> SomeException #
fromException :: SomeException -> Maybe (ParseErrorBundle s e) #
displayException :: ParseErrorBundle s e -> String #
Instance details
Defined in Text.Megaparsec.Error
Associated Types
type Rep (ParseErrorBundle s e) :: Type -> Type #
Methods
from :: ParseErrorBundle s e -> Rep (ParseErrorBundle s e) x #
to :: Rep (ParseErrorBundle s e) x -> ParseErrorBundle s e #
Instance details
Defined in Text.Megaparsec.Error
Methods
showsPrec :: Int -> ParseErrorBundle s e -> ShowS #
show :: ParseErrorBundle s e -> String #
showList :: [ParseErrorBundle s e] -> ShowS #
Instance details
Defined in Text.Megaparsec.Error
Methods
(==) :: ParseErrorBundle s e -> ParseErrorBundle s e -> Bool #
(/=) :: ParseErrorBundle s e -> ParseErrorBundle s e -> Bool #
Instance details
Defined in Text.Megaparsec.Error
Arguments
How to project offset from an item (e.g. errorOffset )
The collection of items
Attach SourcePos es to items in a Traversable container given that
there is a projection allowing us to get an offset per item.
Items must be in ascending order with respect to their offsets.
Since: 7.0.0
Pretty-printing
class Ord a => ShowErrorComponent a where Source #
The type class defines how to print a custom component of ParseError .
Since: 5.0.0
Minimal complete definition
Methods
showErrorComponent :: a -> String Source #
Pretty-print a component of ParseError .
errorComponentLen :: a -> Int Source #
Length of the error component in characters, used for highlighting of parse errors in input string.
Since: 7.0.0
Instances
Instances details
Instance details
Defined in Text.Megaparsec.Error
Arguments
Parse error bundle to display
Textual rendition of the bundle
Pretty-print a ParseErrorBundle . All ParseError s in the bundle will
be pretty-printed in order together with the corresponding offending
lines by doing a single pass over the input stream. The rendered String
always ends with a newline.
Since: 7.0.0
errorBundlePrettyForGhcPreProcessors Source #
Arguments
Parse error bundle to display
Textual rendition of the bundle
Pretty-print a ParseErrorBundle . All ParseError s in the bundle will
be pretty-printed in order by doing a single pass over the input stream.
The rendered format is suitable for custom GHC pre-processors (as can be specified with -F -pgmF).
Since: 9.7.0
errorBundlePrettyWith Source #
Arguments
Parse error bundle to display
Textual rendition of the bundle
Pretty-print a ParseErrorBundle . All ParseError s in the bundle will
be pretty-printed in order, by applying a provided format function, with
a single pass over the input stream.
Since: 9.7.0
Arguments
Parse error to render
Result of rendering
Pretty-print a ParseError . The rendered String always ends with a
newline.
Since: 5.0.0
Pretty-print a textual part of a ParseError , that is, everything
except for its position. The rendered String always ends with a
newline.
Since: 5.1.0
showErrorItem :: VisualStream s => Proxy s -> ErrorItem (Token s) -> String Source #
Pretty-print an ErrorItem .
Since: 9.4.0