foundation-0.0.21: Alternative prelude with batteries and no dependencies

LicenseBSD-style
MaintainerHaskell Foundation
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Foundation.Parser

Contents

Description

The current implementation is mainly, if not copy/pasted, inspired from memory's Parser.

Foundation Parser makes use of the Foundation's Collection and Sequential classes to allow you to define generic parsers over any Sequential of inpu.

This way you can easily implements parsers over LString, String.

flip parseOnly "my.email@address.com" $ do
   EmailAddress
     <$> (takeWhile ((/=) '@' <*  element '@')
     <*> takeAll
Synopsis

Documentation

data Parser input result Source #

Foundation's Parser monad.

Its implementation is based on the parser in memory.

Instances
ParserSource input => Monad (Parser input) Source # 
Instance details

Defined in Foundation.Parser

Methods

(>>=) :: Parser input a -> (a -> Parser input b) -> Parser input b #

(>>) :: Parser input a -> Parser input b -> Parser input b #

return :: a -> Parser input a #

fail :: String -> Parser input a #

Functor (Parser input) Source # 
Instance details

Defined in Foundation.Parser

Methods

fmap :: (a -> b) -> Parser input a -> Parser input b #

(<$) :: a -> Parser input b -> Parser input a #

ParserSource input => Applicative (Parser input) Source # 
Instance details

Defined in Foundation.Parser

Methods

pure :: a -> Parser input a #

(<*>) :: Parser input (a -> b) -> Parser input a -> Parser input b #

liftA2 :: (a -> b -> c) -> Parser input a -> Parser input b -> Parser input c #

(*>) :: Parser input a -> Parser input b -> Parser input b #

(<*) :: Parser input a -> Parser input b -> Parser input a #

ParserSource input => Alternative (Parser input) Source # 
Instance details

Defined in Foundation.Parser

Methods

empty :: Parser input a #

(<|>) :: Parser input a -> Parser input a -> Parser input a #

some :: Parser input a -> Parser input [a] #

many :: Parser input a -> Parser input [a] #

ParserSource input => MonadPlus (Parser input) Source # 
Instance details

Defined in Foundation.Parser

Methods

mzero :: Parser input a #

mplus :: Parser input a -> Parser input a -> Parser input a #

parse :: ParserSource input => Parser input a -> input -> Result input a Source #

Run a Parser on a ByteString and return a Result

parseFeed :: (ParserSource input, Monad m) => m (Chunk input) -> Parser input a -> input -> m (Result input a) Source #

Run a parser on an @initial input.

If the Parser need more data than available, the @feeder function is automatically called and fed to the More continuation.

parseOnly :: (ParserSource input, Monoid (Chunk input)) => Parser input a -> input -> Either (ParseError input) a Source #

parse only the given input

The left-over `Element input` will be ignored, if the parser call for more data it will be continuously fed with Nothing (up to 256 iterations).

Result

data Result input result Source #

result of executing the parser over the given input

Constructors

ParseFailed (ParseError input)

the parser failed with the given ParserError

ParseOk (Chunk input) result

the parser complete successfuly with the remaining Chunk

ParseMore (Chunk input -> Result input result)

the parser needs more input, pass an empty Chunk or mempty to tell the parser you don't have anymore inputs.

Instances
Functor (Result input) Source # 
Instance details

Defined in Foundation.Parser

Methods

fmap :: (a -> b) -> Result input a -> Result input b #

(<$) :: a -> Result input b -> Result input a #

(Show k, Show input) => Show (Result input k) Source # 
Instance details

Defined in Foundation.Parser

Methods

showsPrec :: Int -> Result input k -> ShowS #

show :: Result input k -> String #

showList :: [Result input k] -> ShowS #

data ParseError input Source #

common parser error definition

Constructors

NotEnough (CountOf (Element input))

meaning the parser was short of CountOf Element of input.

NotEnoughParseOnly

The parser needed more data, only when using parseOnly

ExpectedElement (Element input) (Element input)

when using element

Expected (Chunk input) (Chunk input)

when using elements or string

Satisfy (Maybe String)

the satisfy or satisfy_ function failed,

Instances
Show input => Show (ParseError input) Source # 
Instance details

Defined in Foundation.Parser

Methods

showsPrec :: Int -> ParseError input -> ShowS #

show :: ParseError input -> String #

showList :: [ParseError input] -> ShowS #

Show (ParseError String) Source # 
Instance details

Defined in Foundation.Parser

(Typeable input, Show input) => Exception (ParseError input) Source # 
Instance details

Defined in Foundation.Parser

reportError :: ParseError input -> Parser input a Source #

helper function to report error when writing parsers

This way we can provide more detailed error when building custom parsers and still avoid to use the naughty _fail_.

myParser :: Parser input Int
myParser = reportError $ Satisfy (Just "this function is not implemented...")

Parser source

class (Sequential input, IndexedCollection input) => ParserSource input where Source #

Minimal complete definition

nullChunk, appendChunk, subChunk, spanChunk

Associated Types

type Chunk input Source #

Methods

nullChunk :: input -> Chunk input -> Bool Source #

appendChunk :: input -> Chunk input -> input Source #

subChunk :: input -> Offset (Element input) -> CountOf (Element input) -> Chunk input Source #

spanChunk :: input -> Offset (Element input) -> (Element input -> Bool) -> (Chunk input, Offset (Element input)) Source #

Instances
ParserSource String Source # 
Instance details

Defined in Foundation.Parser

Associated Types

type Chunk String :: * Source #

ParserSource [a] Source # 
Instance details

Defined in Foundation.Parser

Associated Types

type Chunk [a] :: * Source #

Methods

nullChunk :: [a] -> Chunk [a] -> Bool Source #

appendChunk :: [a] -> Chunk [a] -> [a] Source #

subChunk :: [a] -> Offset (Element [a]) -> CountOf (Element [a]) -> Chunk [a] Source #

spanChunk :: [a] -> Offset (Element [a]) -> (Element [a] -> Bool) -> (Chunk [a], Offset (Element [a])) Source #

combinator

peek :: ParserSource input => Parser input (Maybe (Element input)) Source #

peek the first element from the input source without consuming it

Returns Nothing if there is no more input to parse.

element :: (ParserSource input, Eq (Element input), Element input ~ Element (Chunk input)) => Element input -> Parser input () Source #

anyElement :: ParserSource input => Parser input (Element input) Source #

Get the next `Element input` from the parser

elements :: (ParserSource input, Sequential (Chunk input), Element (Chunk input) ~ Element input, Eq (Chunk input)) => Chunk input -> Parser input () Source #

satisfy :: ParserSource input => Maybe String -> (Element input -> Bool) -> Parser input (Element input) Source #

take one element if satisfy the given predicate

satisfy_ :: ParserSource input => (Element input -> Bool) -> Parser input (Element input) Source #

take one element if satisfy the given predicate

take :: (ParserSource input, Sequential (Chunk input), Element input ~ Element (Chunk input)) => CountOf (Element (Chunk input)) -> Parser input (Chunk input) Source #

takeWhile :: (ParserSource input, Sequential (Chunk input)) => (Element input -> Bool) -> Parser input (Chunk input) Source #

takeAll :: (ParserSource input, Sequential (Chunk input)) => Parser input (Chunk input) Source #

Take the remaining elements from the current position in the stream

skip :: ParserSource input => CountOf (Element input) -> Parser input () Source #

skipWhile :: (ParserSource input, Sequential (Chunk input)) => (Element input -> Bool) -> Parser input () Source #

skipAll :: (ParserSource input, Collection (Chunk input)) => Parser input () Source #

consume every chunk of the stream

(<|>) :: Alternative f => f a -> f a -> f a infixl 3 #

An associative binary operation

many :: Alternative f => f a -> f [a] #

Zero or more.

some :: Alternative f => f a -> f [a] #

One or more.

optional :: Alternative f => f a -> f (Maybe a) #

One or none.

repeat :: ParserSource input => Condition -> Parser input a -> Parser input [a] Source #

repeat the given parser a given amount of time

Unlike some or many, this operation will bring more precision on how many times you wish a parser to be sequenced.

## Repeat Exactly a number of time

repeat (Exactly 6) (takeWhile ((/=) ',') <* element ',')

## Repeat Between lower `@And@` upper times

repeat (Between $ 1 `And` 10) (takeWhile ((/=) ',') <* element ',')

data Condition Source #

Constructors

Between !And 
Exactly !Word 
Instances
Eq Condition Source # 
Instance details

Defined in Foundation.Parser

Show Condition Source # 
Instance details

Defined in Foundation.Parser

data And Source #

Constructors

And !Word !Word 
Instances
Eq And Source # 
Instance details

Defined in Foundation.Parser

Methods

(==) :: And -> And -> Bool #

(/=) :: And -> And -> Bool #

Show And Source # 
Instance details

Defined in Foundation.Parser

Methods

showsPrec :: Int -> And -> ShowS #

show :: And -> String #

showList :: [And] -> ShowS #