Simple Applicative
parser whose input is strict ByteString
.
The usage is the same as parsec.
Parsec 3 provides features which Parsec 2 does not provide:
-
Applicative
style -
ByteString
as input
But Haskell Platform includes Parsec 2, not Parsec 3. Installing Parsec 3 to Haskell Platform environment makes it mess. So, this library was implemented.
- type Parser = MkParser ByteString
- parse :: Input inp => MkParser inp a -> inp -> Maybe a
- char :: Input inp => Char -> MkParser inp Char
- anyChar :: Input inp => MkParser inp Char
- oneOf :: Input inp => String -> MkParser inp Char
- noneOf :: Input inp => String -> MkParser inp Char
- alphaNum :: Input inp => MkParser inp Char
- digit :: Input inp => MkParser inp Char
- hexDigit :: Input inp => MkParser inp Char
- space :: Input inp => MkParser inp Char
- string :: Input inp => String -> MkParser inp String
- try :: MkParser inp a -> MkParser inp a
- choice :: [MkParser inp a] -> MkParser inp a
- option :: a -> MkParser inp a -> MkParser inp a
- skipMany :: MkParser inp a -> MkParser inp ()
- skipSome :: MkParser inp a -> MkParser inp ()
- sepBy1 :: MkParser inp a -> MkParser inp b -> MkParser inp [a]
- manyTill :: MkParser inp a -> MkParser inp b -> MkParser inp [a]
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- (<$) :: Functor f => forall a b. a -> f b -> f a
- (<*>) :: Applicative f => forall a b. f (a -> b) -> f a -> f b
- (*>) :: Applicative f => forall a b. f a -> f b -> f b
- (<*) :: Applicative f => forall a b. f a -> f b -> f a
- (<**>) :: Applicative f => f a -> f (a -> b) -> f b
- (<|>) :: Alternative f => forall a. f a -> f a -> f a
- some :: Alternative f => forall a. f a -> f [a]
- many :: Alternative f => forall a. f a -> f [a]
- pure :: Applicative f => forall a. a -> f a
- data MkParser inp a = P {}
- class Eq inp => Input inp where
- satisfy :: Input inp => (Char -> Bool) -> MkParser inp Char
Documentation
Parser type
type Parser = MkParser ByteStringSource
Parser synonym for strict ByteString
.
Running parser
Char
parsers
char :: Input inp => Char -> MkParser inp CharSource
char c
parses a single character c
. Returns the parsed character.
anyChar :: Input inp => MkParser inp CharSource
This parser succeeds for any character. Returns the parsed character.
oneOf :: Input inp => String -> MkParser inp CharSource
oneOf cs
succeeds if the current character is in the supplied list of
characters cs
. Returns the parsed character.
noneOf :: Input inp => String -> MkParser inp CharSource
As the dual of oneOf
, noneOf cs
succeeds if the current
character not in the supplied list of characters cs
. Returns the
parsed character.
alphaNum :: Input inp => MkParser inp CharSource
Parses a letter or digit (a character between '0' and '9'). Returns the parsed character.
hexDigit :: Input inp => MkParser inp CharSource
Parses a hexadecimal digit (a digit or a letter between 'a' and 'f' or 'A' and 'F'). Returns the parsed character.
space :: Input inp => MkParser inp CharSource
Parses a white space character (any character which satisfies isSpace
)
Returns the parsed character.
String
parser
string :: Input inp => String -> MkParser inp StringSource
string s
parses a sequence of characters given by s
. Returns
the parsed string
Parser combinators
try :: MkParser inp a -> MkParser inp aSource
The parser try p behaves like parser p, except that it pretends that it hasn't consumed any input when an error occurs.
choice :: [MkParser inp a] -> MkParser inp aSource
choice ps
tries to apply the parsers in the list ps
in order,
until one of them succeeds. Returns the value of the succeeding
parser.
option :: a -> MkParser inp a -> MkParser inp aSource
option x p
tries to apply parser p
. If p
fails without
consuming input, it returns the value x
, otherwise the value
returned by p
.
skipMany :: MkParser inp a -> MkParser inp ()Source
skipMany p
applies the parser p
zero or more times, skipping
its result.
skipSome :: MkParser inp a -> MkParser inp ()Source
skipSome p
applies the parser p
one or more times, skipping
its result.
sepBy1 :: MkParser inp a -> MkParser inp b -> MkParser inp [a]Source
sepBy1 p sep
parses one or more occurrences of p
, separated
by sep
. Returns a list of values returned by p
.
manyTill :: MkParser inp a -> MkParser inp b -> MkParser inp [a]Source
manyTill p end
applies parser p
zero or more times until
parser end
succeeds. Returns the list of values returned by p
.
Applicative
parser combinators
(<*>) :: Applicative f => forall a b. f (a -> b) -> f a -> f b
Sequential application.
(*>) :: Applicative f => forall a b. f a -> f b -> f b
Sequence actions, discarding the value of the first argument.
(<*) :: Applicative f => forall a b. f a -> f b -> f a
Sequence actions, discarding the value of the second argument.
(<**>) :: Applicative f => f a -> f (a -> b) -> f b
A variant of <*>
with the arguments reversed.
(<|>) :: Alternative f => forall a. f a -> f a -> f a
An associative binary operation
some :: Alternative f => forall a. f a -> f [a]
One or more.
many :: Alternative f => forall a. f a -> f [a]
Zero or more.
pure :: Applicative f => forall a. a -> f a
Lift a value.
Internals
Monad (MkParser inp) | |
Functor (MkParser inp) | |
MonadPlus (MkParser inp) | |
Applicative (MkParser inp) | |
Alternative (MkParser inp) |