Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Simple Applicative
parser whose input is lazy ByteString
.
The usage is the same as parsec.
Parsec 3 provides features which Parsec 2 does not provide:
Applicative
styleByteString
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.
Synopsis
- 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 => a -> f b -> f a
- (<*>) :: Applicative f => f (a -> b) -> f a -> f b
- (*>) :: Applicative f => f a -> f b -> f b
- (<*) :: Applicative f => f a -> f b -> f a
- (<**>) :: Applicative f => f a -> f (a -> b) -> f b
- (<|>) :: Alternative f => f a -> f a -> f a
- some :: Alternative f => f a -> f [a]
- many :: Alternative f => f a -> f [a]
- pure :: Applicative f => 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 ByteString Source #
Parser synonym for strict ByteString
.
Running parser
Char
parsers
char :: Input inp => Char -> MkParser inp Char Source #
char c
parses a single character c
. Returns the parsed character.
anyChar :: Input inp => MkParser inp Char Source #
This parser succeeds for any character. Returns the parsed character.
oneOf :: Input inp => String -> MkParser inp Char Source #
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 Char Source #
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 Char Source #
Parses a letter or digit (a character between '0' and '9'). Returns the parsed character.
hexDigit :: Input inp => MkParser inp Char Source #
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 Char Source #
Parses a white space character (any character which satisfies isSpace
)
Returns the parsed character.
String
parser
string :: Input inp => String -> MkParser inp String Source #
string s
parses a sequence of characters given by s
. Returns
the parsed string
Parser combinators
try :: MkParser inp a -> MkParser inp a Source #
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 a Source #
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 a Source #
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
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 #
An infix synonym for fmap
.
The name of this operator is an allusion to $
.
Note the similarities between their types:
($) :: (a -> b) -> a -> b (<$>) :: Functor f => (a -> b) -> f a -> f b
Whereas $
is function application, <$>
is function
application lifted over a Functor
.
Examples
Convert from a
to a Maybe
Int
using Maybe
String
show
:
>>>
show <$> Nothing
Nothing>>>
show <$> Just 3
Just "3"
Convert from an
to an Either
Int
Int
Either
Int
String
using show
:
>>>
show <$> Left 17
Left 17>>>
show <$> Right 17
Right "17"
Double each element of a list:
>>>
(*2) <$> [1,2,3]
[2,4,6]
Apply even
to the second element of a pair:
>>>
even <$> (2,2)
(2,True)
(<*>) :: Applicative f => f (a -> b) -> f a -> f b infixl 4 #
Sequential application.
A few functors support an implementation of <*>
that is more
efficient than the default one.
(*>) :: Applicative f => f a -> f b -> f b infixl 4 #
Sequence actions, discarding the value of the first argument.
(<*) :: Applicative f => f a -> f b -> f a infixl 4 #
Sequence actions, discarding the value of the second argument.
(<**>) :: Applicative f => f a -> f (a -> b) -> f b infixl 4 #
A variant of <*>
with the arguments reversed.
(<|>) :: Alternative f => f a -> f a -> f a infixl 3 #
An associative binary operation
some :: Alternative f => f a -> f [a] #
One or more.
many :: Alternative f => f a -> f [a] #
Zero or more.
pure :: Applicative f => a -> f a #
Lift a value.
Internals
class Eq inp => Input inp where Source #
The class for parser input.
The head function for input
The tail function for input
The end of input
The function to check the end of input
Instances
Input String Source # | |
Input ByteString Source # | |
Defined in Text.Appar.Input car :: ByteString -> Char Source # cdr :: ByteString -> ByteString Source # nil :: ByteString Source # isNil :: ByteString -> Bool Source # | |
Input ByteString Source # | |
Defined in Text.Appar.Input car :: ByteString -> Char Source # cdr :: ByteString -> ByteString Source # nil :: ByteString Source # isNil :: ByteString -> Bool Source # |