hectoparsec-0.1.0.0: Flexible and powerful parser combinators
Copyright(c) comp 2020
LicenseMIT
Maintaineronecomputer00@gmail.com
Stabilitystable
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hectoparsec.Class

Description

Typeclass for a monad that implements the basic combinators for parsing.

Combinators that are derived from the basic combinators are also defined here.

Synopsis

MonadParser typeclass

class (Stream s, MonadPlus m) => MonadParser s e l m | m -> s e l where Source #

Monad m that implements the primitive parsers for a stream s, using custom errors e and custom labels l. These parsers should have a notion of whether the input was consumed or not. They should also track the parser state, errors, and labels.

The MonadPlus instance should be equal to the Alternative instance, and it should implement the operations for branching parsers. In particular, p <|> q must commit to the first branch that consumes input.

The ParserT instance is the canonical instance for this class.

Methods

matchToken Source #

Arguments

:: (Maybe (Token s) -> Either (ErrorItem s e l) a)

A function to match on tokens. It can return either an error item or the resulting value.

-> m a 

Match on a token, returning either the value or an error. If this succeeds, input is consumed.

For matching by equality, use the derived char combinator.

matchTokens Source #

Arguments

:: Int

Length n of the chunk to take. If n <= 0, no tokens are taken.

-> (Chunk s -> Either (ErrorItem s e l) a)

A function to match on the chunk. If the chunk is empty, then n <= 0 or we are at the end.

-> m a 

Match on a chunk of at most n length, returning either the value or an error. If it fails, the parser will backtrack the stream. If this succeeds and chunk is non-empty, input is consumed.

For matching by equality, use the derived string combinator.

matchTokenWhile Source #

Arguments

:: (Token s -> Bool)

The predicate to check a token.

-> (Chunk s -> Either (ErrorItem s e l) a)

A function to match on the chunk.

-> m a 

Take tokens that satisfy a predicate, and match on them, returning either the value or an error. If it fails, the parser will backtrack the stream. If this succeeds and the chunk is non-empty, input is consumed.

For matching just by a predicate, use the derived tokenWhile and tokenWhile1 combinators.

endOfInput :: m () Source #

A parser that only succeeds at the end of the stream.

withLabel :: Maybe l -> m a -> m a Source #

Adds or removes a label for a parser. See label and hidden for more information.

By default, no parsers defined in this library are labelled. It is entirely up to you to label parsers.

try :: m a -> m a Source #

Backtracks a parser if it failed. That is, if a parser p fails, then try p will be considered to not have consumed input. This can be used for arbitrary look ahead.

In the example below, alt1 will not act as expected, since red will consume the 'r', meaning rad will not be tried. Adding try in alt2 will allow it to work as expected.

red = char 'r' >> char 'e' >> char 'd'
rad = char 'r' >> char 'a' >> char 'd'
alt1 = red <|> rad
alt2 = try red <|> rad

lookAhead :: m a -> m a Source #

Backtracks a parser if it succeeds. That is, if a parser p succeeds, then lookAhead p will be considered to not have consumed input.

This does not affect the parser if it fails, i.e. failed parsers can still consume input. Use try along with this function if you need to backtrack on failure too.

notFollowedBy :: m a -> m () Source #

Creates a parser that only succeeds if the original fails.

This parser never consumes input nor modifies parser state.

recover :: (ParseError s e l -> m a) -> m a -> m a Source #

Creates a parser that can recover from parse failures.

If the recovery parser fails, it will act as if only the original parser failed.

observing :: m a -> m (Either (ParseError s e l) a) Source #

Observes the result of a parser, allowing parsing to continue on failure.

Note that this does not backtrack the parser whether it succeeds or fails.

parseError :: ParseError s e l -> m a Source #

Fails parsing with a parse error.

getState :: m (State s) Source #

Gets the parser state.

putState :: State s -> m () Source #

Replaces the parser state.

Instances

Instances details
MonadParser s e l m => MonadParser s e l (MaybeT m) Source # 
Instance details

Defined in Hectoparsec.Class

Methods

matchToken :: (Maybe (Token s) -> Either (ErrorItem s e l) a) -> MaybeT m a Source #

matchTokens :: Int -> (Chunk s -> Either (ErrorItem s e l) a) -> MaybeT m a Source #

matchTokenWhile :: (Token s -> Bool) -> (Chunk s -> Either (ErrorItem s e l) a) -> MaybeT m a Source #

endOfInput :: MaybeT m () Source #

withLabel :: Maybe l -> MaybeT m a -> MaybeT m a Source #

try :: MaybeT m a -> MaybeT m a Source #

lookAhead :: MaybeT m a -> MaybeT m a Source #

notFollowedBy :: MaybeT m a -> MaybeT m () Source #

recover :: (ParseError s e l -> MaybeT m a) -> MaybeT m a -> MaybeT m a Source #

observing :: MaybeT m a -> MaybeT m (Either (ParseError s e l) a) Source #

parseError :: ParseError s e l -> MaybeT m a Source #

getState :: MaybeT m (State s) Source #

putState :: State s -> MaybeT m () Source #

(Monoid w, MonadParser s e l m) => MonadParser s e l (AccumT w m) Source # 
Instance details

Defined in Hectoparsec.Class

Methods

matchToken :: (Maybe (Token s) -> Either (ErrorItem s e l) a) -> AccumT w m a Source #

matchTokens :: Int -> (Chunk s -> Either (ErrorItem s e l) a) -> AccumT w m a Source #

matchTokenWhile :: (Token s -> Bool) -> (Chunk s -> Either (ErrorItem s e l) a) -> AccumT w m a Source #

endOfInput :: AccumT w m () Source #

withLabel :: Maybe l -> AccumT w m a -> AccumT w m a Source #

try :: AccumT w m a -> AccumT w m a Source #

lookAhead :: AccumT w m a -> AccumT w m a Source #

notFollowedBy :: AccumT w m a -> AccumT w m () Source #

recover :: (ParseError s e l -> AccumT w m a) -> AccumT w m a -> AccumT w m a Source #

observing :: AccumT w m a -> AccumT w m (Either (ParseError s e l) a) Source #

parseError :: ParseError s e l -> AccumT w m a Source #

getState :: AccumT w m (State s) Source #

putState :: State s -> AccumT w m () Source #

(Monoid err, MonadParser s e l m) => MonadParser s e l (ExceptT err m) Source # 
Instance details

Defined in Hectoparsec.Class

Methods

matchToken :: (Maybe (Token s) -> Either (ErrorItem s e l) a) -> ExceptT err m a Source #

matchTokens :: Int -> (Chunk s -> Either (ErrorItem s e l) a) -> ExceptT err m a Source #

matchTokenWhile :: (Token s -> Bool) -> (Chunk s -> Either (ErrorItem s e l) a) -> ExceptT err m a Source #

endOfInput :: ExceptT err m () Source #

withLabel :: Maybe l -> ExceptT err m a -> ExceptT err m a Source #

try :: ExceptT err m a -> ExceptT err m a Source #

lookAhead :: ExceptT err m a -> ExceptT err m a Source #

notFollowedBy :: ExceptT err m a -> ExceptT err m () Source #

recover :: (ParseError s e l -> ExceptT err m a) -> ExceptT err m a -> ExceptT err m a Source #

observing :: ExceptT err m a -> ExceptT err m (Either (ParseError s e l) a) Source #

parseError :: ParseError s e l -> ExceptT err m a Source #

getState :: ExceptT err m (State s) Source #

putState :: State s -> ExceptT err m () Source #

MonadParser s e l m => MonadParser s e l (IdentityT m) Source # 
Instance details

Defined in Hectoparsec.Class

MonadParser s e l m => MonadParser s e l (ReaderT r m) Source # 
Instance details

Defined in Hectoparsec.Class

Methods

matchToken :: (Maybe (Token s) -> Either (ErrorItem s e l) a) -> ReaderT r m a Source #

matchTokens :: Int -> (Chunk s -> Either (ErrorItem s e l) a) -> ReaderT r m a Source #

matchTokenWhile :: (Token s -> Bool) -> (Chunk s -> Either (ErrorItem s e l) a) -> ReaderT r m a Source #

endOfInput :: ReaderT r m () Source #

withLabel :: Maybe l -> ReaderT r m a -> ReaderT r m a Source #

try :: ReaderT r m a -> ReaderT r m a Source #

lookAhead :: ReaderT r m a -> ReaderT r m a Source #

notFollowedBy :: ReaderT r m a -> ReaderT r m () Source #

recover :: (ParseError s e l -> ReaderT r m a) -> ReaderT r m a -> ReaderT r m a Source #

observing :: ReaderT r m a -> ReaderT r m (Either (ParseError s e l) a) Source #

parseError :: ParseError s e l -> ReaderT r m a Source #

getState :: ReaderT r m (State s) Source #

putState :: State s -> ReaderT r m () Source #

MonadParser s e l m => MonadParser s e l (StateT st m) Source # 
Instance details

Defined in Hectoparsec.Class

Methods

matchToken :: (Maybe (Token s) -> Either (ErrorItem s e l) a) -> StateT st m a Source #

matchTokens :: Int -> (Chunk s -> Either (ErrorItem s e l) a) -> StateT st m a Source #

matchTokenWhile :: (Token s -> Bool) -> (Chunk s -> Either (ErrorItem s e l) a) -> StateT st m a Source #

endOfInput :: StateT st m () Source #

withLabel :: Maybe l -> StateT st m a -> StateT st m a Source #

try :: StateT st m a -> StateT st m a Source #

lookAhead :: StateT st m a -> StateT st m a Source #

notFollowedBy :: StateT st m a -> StateT st m () Source #

recover :: (ParseError s e l -> StateT st m a) -> StateT st m a -> StateT st m a Source #

observing :: StateT st m a -> StateT st m (Either (ParseError s e l) a) Source #

parseError :: ParseError s e l -> StateT st m a Source #

getState :: StateT st m (State s) Source #

putState :: State s -> StateT st m () Source #

MonadParser s e l m => MonadParser s e l (StateT st m) Source # 
Instance details

Defined in Hectoparsec.Class

Methods

matchToken :: (Maybe (Token s) -> Either (ErrorItem s e l) a) -> StateT st m a Source #

matchTokens :: Int -> (Chunk s -> Either (ErrorItem s e l) a) -> StateT st m a Source #

matchTokenWhile :: (Token s -> Bool) -> (Chunk s -> Either (ErrorItem s e l) a) -> StateT st m a Source #

endOfInput :: StateT st m () Source #

withLabel :: Maybe l -> StateT st m a -> StateT st m a Source #

try :: StateT st m a -> StateT st m a Source #

lookAhead :: StateT st m a -> StateT st m a Source #

notFollowedBy :: StateT st m a -> StateT st m () Source #

recover :: (ParseError s e l -> StateT st m a) -> StateT st m a -> StateT st m a Source #

observing :: StateT st m a -> StateT st m (Either (ParseError s e l) a) Source #

parseError :: ParseError s e l -> StateT st m a Source #

getState :: StateT st m (State s) Source #

putState :: State s -> StateT st m () Source #

(Monoid w, MonadParser s e l m) => MonadParser s e l (WriterT w m) Source # 
Instance details

Defined in Hectoparsec.Class

Methods

matchToken :: (Maybe (Token s) -> Either (ErrorItem s e l) a) -> WriterT w m a Source #

matchTokens :: Int -> (Chunk s -> Either (ErrorItem s e l) a) -> WriterT w m a Source #

matchTokenWhile :: (Token s -> Bool) -> (Chunk s -> Either (ErrorItem s e l) a) -> WriterT w m a Source #

endOfInput :: WriterT w m () Source #

withLabel :: Maybe l -> WriterT w m a -> WriterT w m a Source #

try :: WriterT w m a -> WriterT w m a Source #

lookAhead :: WriterT w m a -> WriterT w m a Source #

notFollowedBy :: WriterT w m a -> WriterT w m () Source #

recover :: (ParseError s e l -> WriterT w m a) -> WriterT w m a -> WriterT w m a Source #

observing :: WriterT w m a -> WriterT w m (Either (ParseError s e l) a) Source #

parseError :: ParseError s e l -> WriterT w m a Source #

getState :: WriterT w m (State s) Source #

putState :: State s -> WriterT w m () Source #

(Monoid w, MonadParser s e l m) => MonadParser s e l (WriterT w m) Source # 
Instance details

Defined in Hectoparsec.Class

Methods

matchToken :: (Maybe (Token s) -> Either (ErrorItem s e l) a) -> WriterT w m a Source #

matchTokens :: Int -> (Chunk s -> Either (ErrorItem s e l) a) -> WriterT w m a Source #

matchTokenWhile :: (Token s -> Bool) -> (Chunk s -> Either (ErrorItem s e l) a) -> WriterT w m a Source #

endOfInput :: WriterT w m () Source #

withLabel :: Maybe l -> WriterT w m a -> WriterT w m a Source #

try :: WriterT w m a -> WriterT w m a Source #

lookAhead :: WriterT w m a -> WriterT w m a Source #

notFollowedBy :: WriterT w m a -> WriterT w m () Source #

recover :: (ParseError s e l -> WriterT w m a) -> WriterT w m a -> WriterT w m a Source #

observing :: WriterT w m a -> WriterT w m (Either (ParseError s e l) a) Source #

parseError :: ParseError s e l -> WriterT w m a Source #

getState :: WriterT w m (State s) Source #

putState :: State s -> WriterT w m () Source #

(Monoid w, MonadParser s e l m) => MonadParser s e l (WriterT w m) Source # 
Instance details

Defined in Hectoparsec.Class

Methods

matchToken :: (Maybe (Token s) -> Either (ErrorItem s e l) a) -> WriterT w m a Source #

matchTokens :: Int -> (Chunk s -> Either (ErrorItem s e l) a) -> WriterT w m a Source #

matchTokenWhile :: (Token s -> Bool) -> (Chunk s -> Either (ErrorItem s e l) a) -> WriterT w m a Source #

endOfInput :: WriterT w m () Source #

withLabel :: Maybe l -> WriterT w m a -> WriterT w m a Source #

try :: WriterT w m a -> WriterT w m a Source #

lookAhead :: WriterT w m a -> WriterT w m a Source #

notFollowedBy :: WriterT w m a -> WriterT w m () Source #

recover :: (ParseError s e l -> WriterT w m a) -> WriterT w m a -> WriterT w m a Source #

observing :: WriterT w m a -> WriterT w m (Either (ParseError s e l) a) Source #

parseError :: ParseError s e l -> WriterT w m a Source #

getState :: WriterT w m (State s) Source #

putState :: State s -> WriterT w m () Source #

Stream s => MonadParser s e l (ParserT s e l m) Source # 
Instance details

Defined in Hectoparsec.Primitive

Methods

matchToken :: (Maybe (Token s) -> Either (ErrorItem s e l) a) -> ParserT s e l m a Source #

matchTokens :: Int -> (Chunk s -> Either (ErrorItem s e l) a) -> ParserT s e l m a Source #

matchTokenWhile :: (Token s -> Bool) -> (Chunk s -> Either (ErrorItem s e l) a) -> ParserT s e l m a Source #

endOfInput :: ParserT s e l m () Source #

withLabel :: Maybe l -> ParserT s e l m a -> ParserT s e l m a Source #

try :: ParserT s e l m a -> ParserT s e l m a Source #

lookAhead :: ParserT s e l m a -> ParserT s e l m a Source #

notFollowedBy :: ParserT s e l m a -> ParserT s e l m () Source #

recover :: (ParseError s e l -> ParserT s e l m a) -> ParserT s e l m a -> ParserT s e l m a Source #

observing :: ParserT s e l m a -> ParserT s e l m (Either (ParseError s e l) a) Source #

parseError :: ParseError s e l -> ParserT s e l m a Source #

getState :: ParserT s e l m (State s) Source #

putState :: State s -> ParserT s e l m () Source #

(Monoid w, MonadParser s e l m) => MonadParser s e l (RWST r w st m) Source # 
Instance details

Defined in Hectoparsec.Class

Methods

matchToken :: (Maybe (Token s) -> Either (ErrorItem s e l) a) -> RWST r w st m a Source #

matchTokens :: Int -> (Chunk s -> Either (ErrorItem s e l) a) -> RWST r w st m a Source #

matchTokenWhile :: (Token s -> Bool) -> (Chunk s -> Either (ErrorItem s e l) a) -> RWST r w st m a Source #

endOfInput :: RWST r w st m () Source #

withLabel :: Maybe l -> RWST r w st m a -> RWST r w st m a Source #

try :: RWST r w st m a -> RWST r w st m a Source #

lookAhead :: RWST r w st m a -> RWST r w st m a Source #

notFollowedBy :: RWST r w st m a -> RWST r w st m () Source #

recover :: (ParseError s e l -> RWST r w st m a) -> RWST r w st m a -> RWST r w st m a Source #

observing :: RWST r w st m a -> RWST r w st m (Either (ParseError s e l) a) Source #

parseError :: ParseError s e l -> RWST r w st m a Source #

getState :: RWST r w st m (State s) Source #

putState :: State s -> RWST r w st m () Source #

(Monoid w, MonadParser s e l m) => MonadParser s e l (RWST r w st m) Source # 
Instance details

Defined in Hectoparsec.Class

Methods

matchToken :: (Maybe (Token s) -> Either (ErrorItem s e l) a) -> RWST r w st m a Source #

matchTokens :: Int -> (Chunk s -> Either (ErrorItem s e l) a) -> RWST r w st m a Source #

matchTokenWhile :: (Token s -> Bool) -> (Chunk s -> Either (ErrorItem s e l) a) -> RWST r w st m a Source #

endOfInput :: RWST r w st m () Source #

withLabel :: Maybe l -> RWST r w st m a -> RWST r w st m a Source #

try :: RWST r w st m a -> RWST r w st m a Source #

lookAhead :: RWST r w st m a -> RWST r w st m a Source #

notFollowedBy :: RWST r w st m a -> RWST r w st m () Source #

recover :: (ParseError s e l -> RWST r w st m a) -> RWST r w st m a -> RWST r w st m a Source #

observing :: RWST r w st m a -> RWST r w st m (Either (ParseError s e l) a) Source #

parseError :: ParseError s e l -> RWST r w st m a Source #

getState :: RWST r w st m (State s) Source #

putState :: State s -> RWST r w st m () Source #

(Monoid w, MonadParser s e l m) => MonadParser s e l (RWST r w st m) Source # 
Instance details

Defined in Hectoparsec.Class

Methods

matchToken :: (Maybe (Token s) -> Either (ErrorItem s e l) a) -> RWST r w st m a Source #

matchTokens :: Int -> (Chunk s -> Either (ErrorItem s e l) a) -> RWST r w st m a Source #

matchTokenWhile :: (Token s -> Bool) -> (Chunk s -> Either (ErrorItem s e l) a) -> RWST r w st m a Source #

endOfInput :: RWST r w st m () Source #

withLabel :: Maybe l -> RWST r w st m a -> RWST r w st m a Source #

try :: RWST r w st m a -> RWST r w st m a Source #

lookAhead :: RWST r w st m a -> RWST r w st m a Source #

notFollowedBy :: RWST r w st m a -> RWST r w st m () Source #

recover :: (ParseError s e l -> RWST r w st m a) -> RWST r w st m a -> RWST r w st m a Source #

observing :: RWST r w st m a -> RWST r w st m (Either (ParseError s e l) a) Source #

parseError :: ParseError s e l -> RWST r w st m a Source #

getState :: RWST r w st m (State s) Source #

putState :: State s -> RWST r w st m () Source #

Derived combinators

Input consumption

anyToken :: MonadParser s e l m => m (Token s) Source #

Parses any token.

char :: (MonadParser s e l m, Eq (Token s)) => Token s -> m (Token s) Source #

Parses a specific token. Note that this parser is not labelled by default.

semicolon = char ';'

string :: forall s e l m. (MonadParser s e l m, Eq (Chunk s)) => Chunk s -> m (Chunk s) Source #

Parses a specific sequence of tokens. This fully backtracks, since it uses matchTokens. Note that this parser is not labelled by default.

color = string "red" <|> string "green" <|> string "blue"

satisfy :: MonadParser s e l m => (Token s -> Bool) -> m (Token s) Source #

Parses a token that satisfies a predicate.

digit = satisfy isDigit

peek :: MonadParser s e l m => m (Maybe (Token s)) Source #

Peeks at the next token, without advancing the stream in any way.

peekNext :: MonadParser s e l m => m (Token s) Source #

Peeks at the next token, without advancing the stream in any way. If the stream is empty (i.e. there is no next token), an unexpected end of input error is reported.

countTokens :: forall s e l m. MonadParser s e l m => Int -> m (Chunk s) Source #

Parses a chunk of length exactly n, not more, not less. This fully backtracks, since it uses matchTokens.

tokenWhile :: MonadParser s e l m => (Token s -> Bool) -> m (Chunk s) Source #

Takes zero or more tokens that match a predicate. The resulting parser cannot fail. This fully backtracks, since it uses matchTokenWhile. This should be more performant than using many and satisfy.

digits = tokenWhile isDigit

tokenWhile1 :: forall s e l m. MonadParser s e l m => (Token s -> Bool) -> m (Chunk s) Source #

Takes one or more tokens that match a predicate. This fully backtracks, since it uses matchTokenWhile. This should be more performant than using some and satisfy.

digits1 = tokenWhile1 isDigit

matchRest :: MonadParser s e l m => m (Chunk s) Source #

Consumes the rest of the input. This parser cannot fail, though the chunk may be empty.

atEnd :: MonadParser s e l m => m Bool Source #

A parser that checks whether we are at the end of the stream.

Label combinators

label :: MonadParser s e l m => l -> m a -> m a Source #

Adds a label to a parser. This is used for labelling parsers that do not have one for better error messages, or for labelling a complex combination of parsers where you want to give it a more general label instead of merging the labels of each constituent parser.

label lbl p = withLabel (Just lbl) p

(<?>) :: MonadParser s e l m => m a -> l -> m a infix 0 Source #

Adds a label to a parser. Simply a synonym for flip label.

hidden :: MonadParser s e l m => m a -> m a Source #

Removes the label from a parser. This can be used to hide labels from errors.

hidden p = withLabel Nothing p

Error combinators

restore :: MonadParser s e l m => (ParseError s e l -> Bool) -> m a -> m a Source #

Restores the state to before using the parser if the error passes a predicate.

The result parser still fails if the given parser fails.

unexpected :: MonadParser s e l m => Unexpected s -> [l] -> m a Source #

Fails parsing with an unexpected item and a list of expected items.

failure :: MonadParser s e l m => String -> m a Source #

Fails parsing with a failure message. These errors are generally for broken invariants.

customError :: MonadParser s e l m => e -> m a Source #

Fails parsing with a custom error.

State combinators

getsState :: MonadParser s e l m => (State s -> a) -> m a Source #

Gets the parser state applied to a function.

getsState f = f <$> getState

modifyState :: MonadParser s e l m => (State s -> State s) -> m () Source #

Modifies the parser state by a function.

modifyState f = getState >>= putState . f

getInput :: MonadParser s e l m => m s Source #

Gets the input.

getsInput :: MonadParser s e l m => (s -> a) -> m a Source #

Gets the input applied to a function.

getsInput f = f <$> getInput

putInput :: MonadParser s e l m => s -> m () Source #

Replaces the input.

modifyInput :: MonadParser s e l m => (s -> s) -> m () Source #

Modifies the input by a function.

modifyInput f = getInput >>= putInput . f

getPos :: MonadParser s e l m => m Pos Source #

Gets the position in the source text.

getOffset :: MonadParser s e l m => m Int Source #

Gets the offset in the input stream.