Safe Haskell | None |
---|---|
Language | Haskell2010 |
Parsers that can consume and return a prefix of their input.
Synopsis
- class LookAheadParsing m => InputParsing m where
- type ParserInput m
- type ParserPosition m
- getInput :: m (ParserInput m)
- getSourcePos :: m (ParserPosition m)
- anyToken :: m (ParserInput m)
- take :: Int -> m (ParserInput m)
- satisfy :: (ParserInput m -> Bool) -> m (ParserInput m)
- notSatisfy :: (ParserInput m -> Bool) -> m ()
- scan :: state -> (state -> ParserInput m -> Maybe state) -> m (ParserInput m)
- string :: ParserInput m -> m (ParserInput m)
- takeWhile :: (ParserInput m -> Bool) -> m (ParserInput m)
- takeWhile1 :: (ParserInput m -> Bool) -> m (ParserInput m)
- class (CharParsing m, InputParsing m) => InputCharParsing m where
- satisfyCharInput :: (Char -> Bool) -> m (ParserInput m)
- notSatisfyChar :: (Char -> Bool) -> m ()
- scanChars :: state -> (state -> Char -> Maybe state) -> m (ParserInput m)
- takeCharsWhile :: (Char -> Bool) -> m (ParserInput m)
- takeCharsWhile1 :: (Char -> Bool) -> m (ParserInput m)
- class InputParsing m => ConsumedInputParsing m where
- match :: m a -> m (ParserInput m, a)
- newtype Lazy f a = Lazy {
- getLazy :: f a
- newtype Strict f a = Strict {
- getStrict :: f a
Documentation
class LookAheadParsing m => InputParsing m where Source #
Methods for parsing monoidal inputs
type ParserInput m Source #
The type of the input stream that the parser m
expects to parse.
type ParserPosition m Source #
type ParserPosition m = Dual Int
getInput :: m (ParserInput m) Source #
Always sucessful parser that returns the entire remaining input without consuming it.
getSourcePos :: m (ParserPosition m) Source #
Retrieve the Position
reached by the parser in the input source.
default getSourcePos :: (FactorialMonoid (ParserInput m), Functor m, ParserPosition m ~ Dual Int) => m (ParserPosition m) Source #
anyToken :: m (ParserInput m) Source #
A parser that accepts any single atomic prefix of the input stream.
anyToken == satisfy (const True) anyToken == take 1
take :: Int -> m (ParserInput m) Source #
A parser that accepts exactly the given number of input atoms.
take n == count n anyToken
satisfy :: (ParserInput m -> Bool) -> m (ParserInput m) Source #
A parser that accepts an input atom only if it satisfies the given predicate.
default satisfy :: Monad m => (ParserInput m -> Bool) -> m (ParserInput m) Source #
notSatisfy :: (ParserInput m -> Bool) -> m () Source #
A parser that succeeds exactly when satisfy doesn't, equivalent to
notFollowedBy
.
satisfy
scan :: state -> (state -> ParserInput m -> Maybe state) -> m (ParserInput m) Source #
A stateful scanner. The predicate modifies a state argument, and each transformed state is passed to successive
invocations of the predicate on each token of the input until one returns Nothing
or the input ends.
This parser does not fail. It will return an empty string if the predicate returns Nothing
on the first
character.
Note: Because this parser does not fail, do not use it with combinators such as many
,
because such parsers loop until a failure occurs. Careless use will thus result in an infinite loop.
default scan :: (Monad m, FactorialMonoid (ParserInput m)) => state -> (state -> ParserInput m -> Maybe state) -> m (ParserInput m) Source #
string :: ParserInput m -> m (ParserInput m) Source #
A parser that consumes and returns the given prefix of the input.
default string :: (Monad m, LeftReductive (ParserInput m), FactorialMonoid (ParserInput m), Show (ParserInput m)) => ParserInput m -> m (ParserInput m) Source #
takeWhile :: (ParserInput m -> Bool) -> m (ParserInput m) Source #
A parser accepting the longest sequence of input atoms that match the given predicate; an optimized version of
concat
.
many
.
satisfy
.
Note: Because this parser does not fail, do not use it with combinators such as many
,
because such parsers loop until a failure occurs. Careless use will thus result in an infinite loop.
default takeWhile :: (Monad m, FactorialMonoid (ParserInput m)) => (ParserInput m -> Bool) -> m (ParserInput m) Source #
takeWhile1 :: (ParserInput m -> Bool) -> m (ParserInput m) Source #
A parser accepting the longest non-empty sequence of input atoms that match the given predicate; an optimized
version of concat
.
some
.
satisfy
.
default takeWhile1 :: (Monad m, FactorialMonoid (ParserInput m)) => (ParserInput m -> Bool) -> m (ParserInput m) Source #
Instances
class (CharParsing m, InputParsing m) => InputCharParsing m where Source #
Methods for parsing textual monoid inputs
satisfyCharInput :: (Char -> Bool) -> m (ParserInput m) Source #
Specialization of satisfy
on textual inputs, accepting an input character only if it satisfies the given
predicate, and returning the input atom that represents the character. Equivalent to fmap singleton
. Char.satisfy
notSatisfyChar :: (Char -> Bool) -> m () Source #
A parser that succeeds exactly when satisfy doesn't, equivalent to notFollowedBy . Char.satisfy
scanChars :: state -> (state -> Char -> Maybe state) -> m (ParserInput m) Source #
Stateful scanner like scan
, but specialized for TextualMonoid
inputs.
default scanChars :: (Monad m, TextualMonoid (ParserInput m)) => state -> (state -> Char -> Maybe state) -> m (ParserInput m) Source #
takeCharsWhile :: (Char -> Bool) -> m (ParserInput m) Source #
Specialization of takeWhile
on TextualMonoid
inputs, accepting the longest sequence of input characters that
match the given predicate; an optimized version of fmap fromString . many . Char.satisfy
.
Note: Because this parser does not fail, do not use it with combinators such as many
,
because such parsers loop until a failure occurs. Careless use will thus result in an infinite loop.
default takeCharsWhile :: (Monad m, TextualMonoid (ParserInput m)) => (Char -> Bool) -> m (ParserInput m) Source #
takeCharsWhile1 :: (Char -> Bool) -> m (ParserInput m) Source #
Specialization of takeWhile1
on TextualMonoid
inputs, accepting the longest sequence of input characters
that match the given predicate; an optimized version of fmap fromString . some . Char.satisfy
.
default takeCharsWhile1 :: (Monad m, TextualMonoid (ParserInput m)) => (Char -> Bool) -> m (ParserInput m) Source #
Instances
class InputParsing m => ConsumedInputParsing m where Source #
Parsers that keep track of the consumed input.
match :: m a -> m (ParserInput m, a) Source #
Return both the result of a parse and the portion of the input that the argument parser consumed.
Instances
Wrapper that signifies lazy ByteString
inputs
Instances
Wrapper that signifies strict ByteString
inputs