License | BSD-style |
---|---|
Maintainer | Haskell Foundation |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
The current implementation is mainly, if not copy/pasted, inspired from
memory
's Parser.
A very simple bytearray parser related to Parsec and Attoparsec
Simple example:
> parse ((,,) <$> take 2 <*> element 0x20 <*> (elements "abc" *> anyElement)) "xx abctest" ParseOK "est" ("xx", 116)
- newtype Parser input a = Parser {}
- data Result input a
- data ParserError input
- = Expected {
- expectedInput :: !input
- receivedInput :: !input
- | DoesNotSatify
- | NotEnough
- | MonadFail String
- = Expected {
- parse :: Sequential input => Parser input a -> input -> Result input a
- parseFeed :: (Sequential input, Monad m) => m (Maybe input) -> Parser input a -> input -> m (Result input a)
- parseOnly :: (Typeable input, Show input, Sequential input, Element input ~ Char) => Parser input a -> input -> a
- hasMore :: Sequential input => Parser input Bool
- element :: (Sequential input, Eq (Element input)) => Element input -> Parser input ()
- satisfy :: Sequential input => (Element input -> Bool) -> Parser input (Element input)
- anyElement :: Sequential input => Parser input (Element input)
- elements :: (Show input, Eq input, Sequential input) => input -> Parser input ()
- string :: String -> Parser String ()
- take :: Sequential input => CountOf (Element input) -> Parser input input
- takeWhile :: Sequential input => (Element input -> Bool) -> Parser input input
- takeAll :: Sequential input => Parser input input
- skip :: Sequential input => CountOf (Element input) -> Parser input ()
- skipWhile :: Sequential input => (Element input -> Bool) -> Parser input ()
- skipAll :: Sequential input => Parser input ()
- optional :: Alternative f => f a -> f (Maybe a)
- many :: Alternative f => forall a. f a -> f [a]
- some :: Alternative f => forall a. f a -> f [a]
- (<|>) :: Alternative f => forall a. f a -> f a -> f a
- data Count
- data Condition
- repeat :: Sequential input => Condition -> Parser input a -> Parser input [a]
Documentation
Simple parsing result, that represent respectively:
- failure: with the error message
- continuation: that need for more input data
- success: the remaining unparsed data and the parser value
data ParserError input Source #
Expected | |
| |
DoesNotSatify | some bytes didn't satisfy predicate |
NotEnough | not enough data to complete the parser |
MonadFail String | only use in the event of Monad.fail function |
run the Parser
parse :: Sequential input => Parser input a -> input -> Result input a Source #
Run a Parser on a ByteString and return a Result
parseFeed :: (Sequential input, Monad m) => m (Maybe 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 :: (Typeable input, Show input, Sequential input, Element input ~ Char) => Parser input a -> 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).
Parser methods
element :: (Sequential input, Eq (Element input)) => Element input -> Parser input () Source #
Parse a specific `Element input` at current position
if the `Element input` is different than the expected one, this parser will raise a failure.
satisfy :: Sequential input => (Element input -> Bool) -> Parser input (Element input) Source #
take one element if satisfy the given predicate
anyElement :: Sequential input => Parser input (Element input) Source #
Get the next `Element input` from the parser
elements :: (Show input, Eq input, Sequential input) => input -> Parser input () Source #
Parse a sequence of elements from current position
if the following `Element input` don't match the expected
input
completely, the parser will raise a failure
take :: Sequential input => CountOf (Element input) -> Parser input input Source #
Take @n elements from the current position in the stream
takeWhile :: Sequential input => (Element input -> Bool) -> Parser input input Source #
Take elements while the @predicate hold from the current position in the stream
takeAll :: Sequential input => Parser input input Source #
Take the remaining elements from the current position in the stream
skip :: Sequential input => CountOf (Element input) -> Parser input () Source #
Skip @n elements from the current position in the stream
skipWhile :: Sequential input => (Element input -> Bool) -> Parser input () Source #
Skip `Element input` while the @predicate hold from the current position in the stream
skipAll :: Sequential input => Parser input () Source #
Skip all the remaining `Element input` from the current position in the stream
utils
optional :: Alternative f => f a -> f (Maybe a) #
One or none.
many :: Alternative f => forall a. f a -> f [a] #
Zero or more.
some :: Alternative f => forall a. f a -> f [a] #
One or more.
(<|>) :: Alternative f => forall a. f a -> f a -> f a #
An associative binary operation
repeat :: Sequential input => Condition -> Parser input a -> Parser input [a] Source #
repeat the given Parser a given amount of time
If you know you want it to exactly perform a given amount of time:
```
repeat (Exactly Twice) (element a
)
```
If you know your parser must performs from 0 to 8 times:
``` repeat (Between Never (Other 8)) ```
- This interface is still WIP* but went handy when writting the IPv4/IPv6 parsers.