Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data RawError chunk token
- = RawErrorMatchEnd !token
- | RawErrorAnyToken
- | RawErrorAnyChunk
- | RawErrorSatisfyToken !(Maybe token)
- | RawErrorMatchToken !token !(Maybe token)
- | RawErrorMatchChunk !chunk !(Maybe chunk)
- | RawErrorTakeTokensWhile1 !(Maybe token)
- | RawErrorDropTokensWhile1 !(Maybe token)
- newtype StreamError s = StreamError {
- unStreamError :: RawError (Chunk s) (Token s)
- coerceStreamError :: (Chunk s ~ Chunk t, Token s ~ Token t) => StreamError s -> StreamError t
- data CompoundError s e
- data Mark l s = Mark {}
- data ParseError l s e = ParseError {
- peMarkStack :: !(MarkStack l s)
- peEndState :: !s
- peError :: !(CompoundError s e)
- parseErrorResume :: ParseError l s e -> s
- parseErrorLabels :: ParseError l s e -> Seq l
- markParseError :: Mark l s -> ParseError l s e -> ParseError l s e
- unmarkParseError :: ParseError l s e -> ParseError l s e
- parseErrorEnclosingLabels :: ParseError l s e -> Seq l
- parseErrorNarrowestSpan :: PosStream s => ParseError l s e -> (Maybe l, Span (Pos s))
- newtype ParseErrorBundle l s e = ParseErrorBundle {
- unParseErrorBundle :: NESeq (ParseError l s e)
- listParseErrors :: ParseErrorBundle l s e -> [ParseError l s e]
- matchSoleParseError :: ParseErrorBundle l s e -> Maybe (ParseError l s e)
- data ParseSuccess s a = ParseSuccess {
- psEndState :: !s
- psValue :: !a
- data ParseResult l s e a
- = ParseResultError !(ParseErrorBundle l s e)
- | ParseResultSuccess !(ParseSuccess s a)
Documentation
data RawError chunk token Source #
RawErrorMatchEnd !token | |
RawErrorAnyToken | |
RawErrorAnyChunk | |
RawErrorSatisfyToken !(Maybe token) | |
RawErrorMatchToken !token !(Maybe token) | |
RawErrorMatchChunk !chunk !(Maybe chunk) | |
RawErrorTakeTokensWhile1 !(Maybe token) | |
RawErrorDropTokensWhile1 !(Maybe token) |
newtype StreamError s Source #
RawStreamError
specialized to Stream
types - newtyped to allow GHC
to derive eq/show in the absense of type families.
StreamError | |
|
Instances
(Eq (Token s), Eq (Chunk s)) => Eq (StreamError s) Source # | |
Defined in SimpleParser.Result (==) :: StreamError s -> StreamError s -> Bool # (/=) :: StreamError s -> StreamError s -> Bool # | |
(Show (Token s), Show (Chunk s)) => Show (StreamError s) Source # | |
Defined in SimpleParser.Result showsPrec :: Int -> StreamError s -> ShowS # show :: StreamError s -> String # showList :: [StreamError s] -> ShowS # | |
(Token s ~ Char, TextualChunked (Chunk s)) => ExplainError (StreamError s) Source # | |
Defined in SimpleParser.Explain explainError :: StreamError s -> ErrorExplanation Source # |
coerceStreamError :: (Chunk s ~ Chunk t, Token s ~ Token t) => StreamError s -> StreamError t Source #
data CompoundError s e Source #
Instances
data ParseError l s e Source #
ParseError | |
|
Instances
(Eq l, Eq s, Eq (Token s), Eq (Chunk s), Eq e) => Eq (ParseError l s e) Source # | |
Defined in SimpleParser.Result (==) :: ParseError l s e -> ParseError l s e -> Bool # (/=) :: ParseError l s e -> ParseError l s e -> Bool # | |
(Show l, Show s, Show (Token s), Show (Chunk s), Show e) => Show (ParseError l s e) Source # | |
Defined in SimpleParser.Result showsPrec :: Int -> ParseError l s e -> ShowS # show :: ParseError l s e -> String # showList :: [ParseError l s e] -> ShowS # | |
(Typeable l, Typeable s, Typeable (Token s), Typeable (Chunk s), Typeable e, Show l, Show s, Show (Token s), Show (Chunk s), Show e) => Exception (ParseError l s e) Source # | |
Defined in SimpleParser.Result toException :: ParseError l s e -> SomeException # fromException :: SomeException -> Maybe (ParseError l s e) # displayException :: ParseError l s e -> String # |
parseErrorResume :: ParseError l s e -> s Source #
Returns the resumption point of the ParseError
.
If it has been marked, we use that, otherwise we assume it starts at the exact error point.
parseErrorLabels :: ParseError l s e -> Seq l Source #
Returns the sequence of ALL labels from coarsest to finest.
markParseError :: Mark l s -> ParseError l s e -> ParseError l s e Source #
Updates a ParseError
with a resumption point.
unmarkParseError :: ParseError l s e -> ParseError l s e Source #
Clears marks from a ParseError
.
parseErrorEnclosingLabels :: ParseError l s e -> Seq l Source #
Returns labels enclosing the narrowest span, from coarsest to finest Does NOT include the label for the narrowest span (if any).
parseErrorNarrowestSpan :: PosStream s => ParseError l s e -> (Maybe l, Span (Pos s)) Source #
Returns the narrowest span
newtype ParseErrorBundle l s e Source #
ParseErrorBundle | |
|
Instances
(Eq l, Eq s, Eq (Token s), Eq (Chunk s), Eq e) => Eq (ParseErrorBundle l s e) Source # | |
Defined in SimpleParser.Result (==) :: ParseErrorBundle l s e -> ParseErrorBundle l s e -> Bool # (/=) :: ParseErrorBundle l s e -> ParseErrorBundle l s e -> Bool # | |
(Show l, Show s, Show (Token s), Show (Chunk s), Show e) => Show (ParseErrorBundle l s e) Source # | |
Defined in SimpleParser.Result showsPrec :: Int -> ParseErrorBundle l s e -> ShowS # show :: ParseErrorBundle l s e -> String # showList :: [ParseErrorBundle l s e] -> ShowS # | |
(Typeable l, Typeable s, Typeable (Token s), Typeable (Chunk s), Typeable e, Show l, Show s, Show (Token s), Show (Chunk s), Show e) => Exception (ParseErrorBundle l s e) Source # | |
Defined in SimpleParser.Result toException :: ParseErrorBundle l s e -> SomeException # fromException :: SomeException -> Maybe (ParseErrorBundle l s e) # displayException :: ParseErrorBundle l s e -> String # |
listParseErrors :: ParseErrorBundle l s e -> [ParseError l s e] Source #
Lists all errors in the bundle.
matchSoleParseError :: ParseErrorBundle l s e -> Maybe (ParseError l s e) Source #
If there is only one parse error in the bundle, return it, otherwise return nothing.
Errors can accumulate if you use unrestricted branching (with orParser
or Alternative
<|>
) or manual Parser
constructor application.
However, if you always branch with lookAheadMatch
then you will have singleton parse errors, and this will always return Just
.
data ParseSuccess s a Source #
ParseSuccess | |
|
Instances
data ParseResult l s e a Source #
ParseResultError !(ParseErrorBundle l s e) | |
ParseResultSuccess !(ParseSuccess s a) |
Instances
Functor (ParseResult l s e) Source # | |
Defined in SimpleParser.Result fmap :: (a -> b) -> ParseResult l s e a -> ParseResult l s e b # (<$) :: a -> ParseResult l s e b -> ParseResult l s e a # | |
Foldable (ParseResult l s e) Source # | |
Defined in SimpleParser.Result fold :: Monoid m => ParseResult l s e m -> m # foldMap :: Monoid m => (a -> m) -> ParseResult l s e a -> m # foldMap' :: Monoid m => (a -> m) -> ParseResult l s e a -> m # foldr :: (a -> b -> b) -> b -> ParseResult l s e a -> b # foldr' :: (a -> b -> b) -> b -> ParseResult l s e a -> b # foldl :: (b -> a -> b) -> b -> ParseResult l s e a -> b # foldl' :: (b -> a -> b) -> b -> ParseResult l s e a -> b # foldr1 :: (a -> a -> a) -> ParseResult l s e a -> a # foldl1 :: (a -> a -> a) -> ParseResult l s e a -> a # toList :: ParseResult l s e a -> [a] # null :: ParseResult l s e a -> Bool # length :: ParseResult l s e a -> Int # elem :: Eq a => a -> ParseResult l s e a -> Bool # maximum :: Ord a => ParseResult l s e a -> a # minimum :: Ord a => ParseResult l s e a -> a # sum :: Num a => ParseResult l s e a -> a # product :: Num a => ParseResult l s e a -> a # | |
Traversable (ParseResult l s e) Source # | |
Defined in SimpleParser.Result traverse :: Applicative f => (a -> f b) -> ParseResult l s e a -> f (ParseResult l s e b) # sequenceA :: Applicative f => ParseResult l s e (f a) -> f (ParseResult l s e a) # mapM :: Monad m => (a -> m b) -> ParseResult l s e a -> m (ParseResult l s e b) # sequence :: Monad m => ParseResult l s e (m a) -> m (ParseResult l s e a) # | |
(Eq l, Eq s, Eq (Token s), Eq (Chunk s), Eq e, Eq a) => Eq (ParseResult l s e a) Source # | |
Defined in SimpleParser.Result (==) :: ParseResult l s e a -> ParseResult l s e a -> Bool # (/=) :: ParseResult l s e a -> ParseResult l s e a -> Bool # | |
(Show l, Show s, Show (Token s), Show (Chunk s), Show e, Show a) => Show (ParseResult l s e a) Source # | |
Defined in SimpleParser.Result showsPrec :: Int -> ParseResult l s e a -> ShowS # show :: ParseResult l s e a -> String # showList :: [ParseResult l s e a] -> ShowS # |