License | BSD-style |
---|---|
Maintainer | Haskell Foundation |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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
- data Parser input result
- parse :: ParserSource input => Parser input a -> input -> Result input a
- parseFeed :: (ParserSource input, Monad m) => m (Chunk input) -> Parser input a -> input -> m (Result input a)
- parseOnly :: (ParserSource input, Monoid (Chunk input)) => Parser input a -> input -> Either (ParseError input) a
- data Result input result
- = ParseFailed (ParseError input)
- | ParseOk (Chunk input) result
- | ParseMore (Chunk input -> Result input result)
- data ParseError input
- reportError :: ParseError input -> Parser input a
- class (Sequential input, IndexedCollection input) => ParserSource input where
- peek :: ParserSource input => Parser input (Maybe (Element input))
- element :: (ParserSource input, Eq (Element input), Element input ~ Element (Chunk input)) => Element input -> Parser input ()
- anyElement :: ParserSource input => Parser input (Element input)
- elements :: (ParserSource input, Sequential (Chunk input), Element (Chunk input) ~ Element input, Eq (Chunk input)) => Chunk input -> Parser input ()
- string :: String -> Parser String ()
- satisfy :: ParserSource input => Maybe String -> (Element input -> Bool) -> Parser input (Element input)
- satisfy_ :: ParserSource input => (Element input -> Bool) -> Parser input (Element input)
- take :: (ParserSource input, Sequential (Chunk input), Element input ~ Element (Chunk input)) => CountOf (Element (Chunk input)) -> Parser input (Chunk input)
- takeWhile :: (ParserSource input, Sequential (Chunk input)) => (Element input -> Bool) -> Parser input (Chunk input)
- takeAll :: (ParserSource input, Sequential (Chunk input)) => Parser input (Chunk input)
- skip :: ParserSource input => CountOf (Element input) -> Parser input ()
- skipWhile :: (ParserSource input, Sequential (Chunk input)) => (Element input -> Bool) -> Parser input ()
- skipAll :: (ParserSource input, Collection (Chunk input)) => Parser input ()
- (<|>) :: Alternative f => f a -> f a -> f a
- many :: Alternative f => f a -> f [a]
- some :: Alternative f => f a -> f [a]
- optional :: Alternative f => f a -> f (Maybe a)
- repeat :: ParserSource input => Condition -> Parser input a -> Parser input [a]
- data Condition
- data And = And !Word !Word
Documentation
data Parser input result Source #
Foundation's Parser
monad.
Its implementation is based on the parser in memory
.
Instances
ParserSource input => Alternative (Parser input) Source # | |
ParserSource input => Applicative (Parser input) Source # | |
Defined in Foundation.Parser | |
Functor (Parser input) Source # | |
ParserSource input => Monad (Parser input) Source # | |
ParserSource input => MonadPlus (Parser input) Source # | |
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
ParseFailed (ParseError input) | the parser failed with the given |
ParseOk (Chunk input) result | the parser complete successfuly with the remaining |
ParseMore (Chunk input -> Result input result) | the parser needs more input, pass an empty |
data ParseError input Source #
common parser error definition
NotEnough (CountOf (Element input)) | meaning the parser was short of |
NotEnoughParseOnly | The parser needed more data, only when using |
ExpectedElement (Element input) (Element input) | when using |
Expected (Chunk input) (Chunk input) | when using |
Satisfy (Maybe String) | the |
Instances
(Typeable input, Show input) => Exception (ParseError input) Source # | |
Defined in Foundation.Parser toException :: ParseError input -> SomeException # fromException :: SomeException -> Maybe (ParseError input) # displayException :: ParseError input -> String # | |
Show (ParseError String) Source # | |
Defined in Foundation.Parser | |
Show input => Show (ParseError input) Source # | |
Defined in Foundation.Parser showsPrec :: Int -> ParseError input -> ShowS # show :: ParseError input -> String # showList :: [ParseError input] -> ShowS # |
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 #
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 # | |
Defined in Foundation.Parser nullChunk :: String -> Chunk String -> Bool Source # appendChunk :: String -> Chunk String -> String Source # subChunk :: String -> Offset (Element String) -> CountOf (Element String) -> Chunk String Source # spanChunk :: String -> Offset (Element String) -> (Element String -> Bool) -> (Chunk String, Offset (Element String)) Source # | |
ParserSource [a] Source # | |
Defined in Foundation.Parser |
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
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.
It is useful for modelling any computation that is allowed to fail.
Examples
Using the Alternative
instance of Control.Monad.Except, the following functions:
>>>
import Control.Monad.Except
>>>
canFail = throwError "it failed" :: Except String Int
>>>
final = return 42 :: Except String Int
Can be combined by allowing the first function to fail:
>>>
runExcept $ canFail *> final
Left "it failed">>>
runExcept $ optional canFail *> final
Right 42
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 ',')