appar-0.1.6: A simple applicative parser

Safe HaskellSafe
LanguageHaskell98

Text.Appar.LazyByteString

Contents

Description

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:

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 ByteString Source #

Parser synonym for strict ByteString.

Running parser

parse :: Input inp => MkParser inp a -> inp -> Maybe a Source #

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

digit :: Input inp => MkParser inp Char Source #

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

Expand

Convert from a Maybe Int to a Maybe String using show:

>>> show <$> Nothing
Nothing
>>> show <$> Just 3
Just "3"

Convert from an Either Int Int to an 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)

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

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 => 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

data MkParser inp a Source #

Constructors

P 

Fields

Instances
Monad (MkParser inp) Source # 
Instance details

Defined in Text.Appar.Parser

Methods

(>>=) :: MkParser inp a -> (a -> MkParser inp b) -> MkParser inp b #

(>>) :: MkParser inp a -> MkParser inp b -> MkParser inp b #

return :: a -> MkParser inp a #

fail :: String -> MkParser inp a #

Functor (MkParser inp) Source # 
Instance details

Defined in Text.Appar.Parser

Methods

fmap :: (a -> b) -> MkParser inp a -> MkParser inp b #

(<$) :: a -> MkParser inp b -> MkParser inp a #

MonadFail (MkParser inp) Source # 
Instance details

Defined in Text.Appar.Parser

Methods

fail :: String -> MkParser inp a #

Applicative (MkParser inp) Source # 
Instance details

Defined in Text.Appar.Parser

Methods

pure :: a -> MkParser inp a #

(<*>) :: MkParser inp (a -> b) -> MkParser inp a -> MkParser inp b #

liftA2 :: (a -> b -> c) -> MkParser inp a -> MkParser inp b -> MkParser inp c #

(*>) :: MkParser inp a -> MkParser inp b -> MkParser inp b #

(<*) :: MkParser inp a -> MkParser inp b -> MkParser inp a #

Alternative (MkParser inp) Source # 
Instance details

Defined in Text.Appar.Parser

Methods

empty :: MkParser inp a #

(<|>) :: MkParser inp a -> MkParser inp a -> MkParser inp a #

some :: MkParser inp a -> MkParser inp [a] #

many :: MkParser inp a -> MkParser inp [a] #

MonadPlus (MkParser inp) Source # 
Instance details

Defined in Text.Appar.Parser

Methods

mzero :: MkParser inp a #

mplus :: MkParser inp a -> MkParser inp a -> MkParser inp a #

class Eq inp => Input inp where Source #

The class for parser input.

Methods

car :: inp -> Char Source #

The head function for input

cdr :: inp -> inp Source #

The tail function for input

nil :: inp Source #

The end of input

isNil :: inp -> Bool Source #

The function to check the end of input

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

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