Copyright | (c) 2020 Composewell Technologies |
---|---|
License | BSD-3-Clause |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Direct style parser implementation with stream fusion.
Synopsis
- data Parser m a b = forall s. Parser (s -> a -> m (Step s b)) (m (Initial s b)) (s -> m b)
- newtype ParseError = ParseError String
- data Step s b
- data Initial s b
- rmapM :: Monad m => (b -> m c) -> Parser m a b -> Parser m a c
- fromFold :: Monad m => Fold m a b -> Parser m a b
- fromPure :: Monad m => b -> Parser m a b
- fromEffect :: Monad m => m b -> Parser m a b
- die :: MonadThrow m => String -> Parser m a b
- dieM :: MonadThrow m => m String -> Parser m a b
- peek :: MonadThrow m => Parser m a a
- eof :: Monad m => Parser m a ()
- satisfy :: MonadThrow m => (a -> Bool) -> Parser m a a
- maybe :: MonadThrow m => (a -> Maybe b) -> Parser m a b
- either :: MonadThrow m => (a -> Either String b) -> Parser m a b
- takeBetween :: MonadCatch m => Int -> Int -> Fold m a b -> Parser m a b
- takeEQ :: MonadThrow m => Int -> Fold m a b -> Parser m a b
- takeGE :: MonadThrow m => Int -> Fold m a b -> Parser m a b
- lookAhead :: MonadThrow m => Parser m a b -> Parser m a b
- takeWhile :: Monad m => (a -> Bool) -> Fold m a b -> Parser m a b
- takeWhile1 :: MonadThrow m => (a -> Bool) -> Fold m a b -> Parser m a b
- sliceSepByP :: MonadCatch m => (a -> Bool) -> Parser m a b -> Parser m a b
- sliceBeginWith :: Monad m => (a -> Bool) -> Fold m a b -> Parser m a b
- wordBy :: Monad m => (a -> Bool) -> Fold m a b -> Parser m a b
- groupBy :: Monad m => (a -> a -> Bool) -> Fold m a b -> Parser m a b
- groupByRolling :: Monad m => (a -> a -> Bool) -> Fold m a b -> Parser m a b
- eqBy :: MonadThrow m => (a -> a -> Bool) -> [a] -> Parser m a ()
- span :: Monad m => (a -> Bool) -> Fold m a b -> Fold m a c -> Parser m a (b, c)
- spanBy :: Monad m => (a -> a -> Bool) -> Fold m a b -> Fold m a c -> Parser m a (b, c)
- spanByRolling :: Monad m => (a -> a -> Bool) -> Fold m a b -> Fold m a c -> Parser m a (b, c)
- serialWith :: MonadThrow m => (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c
- split_ :: MonadThrow m => Parser m x a -> Parser m x b -> Parser m x b
- teeWith :: Monad m => (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c
- teeWithFst :: Monad m => (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c
- teeWithMin :: (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c
- deintercalate :: Fold m a y -> Parser m x a -> Fold m b z -> Parser m x b -> Parser m x (y, z)
- alt :: Monad m => Parser m x a -> Parser m x a -> Parser m x a
- shortest :: Monad m => Parser m x a -> Parser m x a -> Parser m x a
- longest :: MonadCatch m => Parser m x a -> Parser m x a -> Parser m x a
- sequence :: Fold m b c -> t (Parser m a b) -> Parser m a c
- concatMap :: MonadThrow m => (b -> Parser m a c) -> Parser m a b -> Parser m a c
- count :: Int -> Parser m a b -> Fold m b c -> Parser m a c
- countBetween :: Int -> Int -> Parser m a b -> Fold m b c -> Parser m a c
- many :: MonadCatch m => Parser m a b -> Fold m b c -> Parser m a c
- some :: MonadCatch m => Parser m a b -> Fold m b c -> Parser m a c
- manyTill :: MonadCatch m => Fold m b c -> Parser m a b -> Parser m a x -> Parser m a c
- choice :: t (Parser m a b) -> Parser m a b
Documentation
A parser is a fold that can fail and is represented as Parser step
initial extract
. Before we drive a parser we call the initial
action to
retrieve the initial state of the fold. The parser driver invokes step
with the state returned by the previous step and the next input element. It
results into a new state and a command to the driver represented by Step
type. The driver keeps invoking the step function until it stops or fails.
At any point of time the driver can call extract
to inspect the result of
the fold. It may result in an error or an output value.
Pre-release
Instances
MonadThrow m => Monad (Parser m a) Source # | See documentation of |
Functor m => Functor (Parser m a) Source # | |
MonadThrow m => Applicative (Parser m a) Source # |
|
Defined in Streamly.Internal.Data.Parser.ParserD.Type | |
MonadCatch m => Alternative (Parser m a) Source # |
Note: The implementation of
|
MonadCatch m => MonadPlus (Parser m a) Source # | See documentation of |
newtype ParseError Source #
This exception is used for two purposes:
- When a parser ultimately fails, the user of the parser is intimated via this exception.
- When the "extract" function of a parser needs to throw an error.
Pre-release
Instances
Show ParseError Source # | |
Defined in Streamly.Internal.Data.Parser.ParserD.Type showsPrec :: Int -> ParseError -> ShowS # show :: ParseError -> String # showList :: [ParseError] -> ShowS # | |
Exception ParseError Source # | |
Defined in Streamly.Internal.Data.Parser.ParserD.Type toException :: ParseError -> SomeException # fromException :: SomeException -> Maybe ParseError # displayException :: ParseError -> String # |
The return type of a Parser
step.
The parse operation feeds the input stream to the parser one element at a
time, representing a parse Step
. The parser may or may not consume the
item and returns a result. If the result is Partial
we can either extract
the result or feed more input to the parser. If the result is Continue
, we
must feed more input in order to get a result. If the parser returns Done
then the parser can no longer take any more input.
If the result is Continue
, the parse operation retains the input in a
backtracking buffer, in case the parser may ask to backtrack in future.
Whenever a 'Partial n' result is returned we first backtrack by n
elements
in the input and then release any remaining backtracking buffer. Similarly,
'Continue n' backtracks to n
elements before the current position and
starts feeding the input from that point for future invocations of the
parser.
If parser is not yet done, we can use the extract
operation on the state
of the parser to extract a result. If the parser has not yet yielded a
result, the operation fails with a ParseError
exception. If the parser
yielded a Partial
result in the past the last partial result is returned.
Therefore, if a parser yields a partial result once it cannot fail later on.
The parser can never backtrack beyond the position where the last partial result left it at. The parser must ensure that the backtrack position is always after that.
Pre-release
Partial Int s | Partial result with an optional backtrack request.
|
Continue Int s | Need more input with an optional backtrack request.
|
Done Int b | Done with leftover input count and result.
|
Error String | Parser failed without generating any output. The parsing operation may backtrack to the beginning and try another alternative. |
The type of a Parser'
s initial action.
Internal
IPartial !s | Wait for step function to be called with state |
IDone !b | Return a result right away without an input. |
IError String | Return an error right away without an input. |
rmapM :: Monad m => (b -> m c) -> Parser m a b -> Parser m a c Source #
Map a monadic function on the output of a parser.
Pre-release
Accumulators
fromEffect :: Monad m => m b -> Parser m a b Source #
See fromEffect
.
Pre-release
Element parsers
Sequence parsers
takeBetween :: MonadCatch m => Int -> Int -> Fold m a b -> Parser m a b Source #
See takeBetween
.
Pre-release
takeWhile1 :: MonadThrow m => (a -> Bool) -> Fold m a b -> Parser m a b Source #
See takeWhile1
.
Pre-release
sliceSepByP :: MonadCatch m => (a -> Bool) -> Parser m a b -> Parser m a b Source #
See sliceSepByP
.
Pre-release
groupByRolling :: Monad m => (a -> a -> Bool) -> Fold m a b -> Parser m a b Source #
See groupByRolling
.
Spanning
span :: Monad m => (a -> Bool) -> Fold m a b -> Fold m a c -> Parser m a (b, c) Source #
span p f1 f2
composes folds f1
and f2
such that f1
consumes the
input as long as the predicate p
is True
. f2
consumes the rest of the
input.
> let span_ p xs = Stream.parse (Parser.span p Fold.toList Fold.toList) $ Stream.fromList xs > span_ (< 1) 1,2,3 > span_ (< 2) 1,2,3 > span_ (< 4) 1,2,3
Pre-release
spanBy :: Monad m => (a -> a -> Bool) -> Fold m a b -> Fold m a c -> Parser m a (b, c) Source #
Break the input stream into two groups, the first group takes the input as
long as the predicate applied to the first element of the stream and next
input element holds True
, the second group takes the rest of the input.
Pre-release
spanByRolling :: Monad m => (a -> a -> Bool) -> Fold m a b -> Fold m a c -> Parser m a (b, c) Source #
Like spanBy
but applies the predicate in a rolling fashion i.e.
predicate is applied to the previous and the next input elements.
Pre-release
Binary Combinators
Sequential Applicative
serialWith :: MonadThrow m => (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c Source #
See serialWith
.
Note: this implementation of serialWith is fast because of stream fusion but has quadratic time complexity, because each composition adds a new branch that each subsequent parse's input element has to go through, therefore, it cannot scale to a large number of compositions. After around 100 compositions the performance starts dipping rapidly beyond a CPS style unfused implementation.
Pre-release
split_ :: MonadThrow m => Parser m x a -> Parser m x b -> Parser m x b Source #
See split_
.
Pre-release
Parallel Applicatives
teeWith :: Monad m => (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c Source #
See teeWith
.
Broken
teeWithFst :: Monad m => (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c Source #
See teeWithFst
.
Broken
teeWithMin :: (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c Source #
See teeWithMin
.
Unimplemented
Sequential Interleaving
deintercalate :: Fold m a y -> Parser m x a -> Fold m b z -> Parser m x b -> Parser m x (y, z) Source #
See deintercalate
.
Unimplemented
Sequential Alternative
Parallel Alternatives
N-ary Combinators
Sequential Collection
concatMap :: MonadThrow m => (b -> Parser m a c) -> Parser m a b -> Parser m a c Source #
See concatMap
.
Pre-release
Sequential Repetition
countBetween :: Int -> Int -> Parser m a b -> Fold m b c -> Parser m a c Source #
See countBetween
.
Unimplemented
manyTill :: MonadCatch m => Fold m b c -> Parser m a b -> Parser m a x -> Parser m a c Source #
See manyTill
.
Pre-release