appar-0.1.2: A simple applicative parser

Text.Appar.ByteString

Contents

Description

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:

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

Documentation

Parser type

type Parser = MkParser ByteStringSource

Parser synonym for strict ByteString.

Running parser

parse :: MkParser ByteString a -> ByteString -> Maybe aSource

Run a 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.

digit :: Input inp => MkParser inp CharSource

Parses a digit. 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

(<$>) :: Functor f => (a -> b) -> f a -> f b

An infix synonym for fmap.

(<$) :: Functor f => forall a b. a -> f b -> f a

Replace all locations in the input with the same value. The default definition is fmap . const, but this may be overridden with a more efficient version.

(<*>) :: 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

data MkParser inp a Source

Constructors

P 

Fields

runParser :: inp -> (Maybe a, inp)

Getting the internal parser.

class Eq inp => Input inp whereSource

The class for parser input.

Methods

car :: inp -> CharSource

The head function for input

cdr :: inp -> inpSource

The tail function for input

nil :: inpSource

The end of input

isNil :: inp -> BoolSource

The function to check the end of input

satisfy :: Input inp => (Char -> Bool) -> MkParser inp CharSource

The parser satisfy f succeeds for any character for which the supplied function f returns True. Returns the character that is actually parsed.