streamly-0.8.1.1: Dataflow programming and declarative concurrency
Copyright(c) 2020 Composewell Technologies
LicenseBSD-3-Clause
Maintainerstreamly@composewell.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Streamly.Internal.Data.Parser.ParserD

Description

Direct style parser implementation with stream fusion.

Synopsis

Documentation

data Parser m a b Source #

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. If the parser hits the end of input extract is called. It may result in an error or an output value.

Pre-release

Constructors

forall s. Parser (s -> a -> m (Step s b)) (m (Initial s b)) (s -> m b) 

Instances

Instances details
(MonadThrow m, MonadState s m) => MonadState s (Parser m a) Source # 
Instance details

Defined in Streamly.Internal.Data.Parser.ParserD.Type

Methods

get :: Parser m a s #

put :: s -> Parser m a () #

state :: (s -> (a0, s)) -> Parser m a a0 #

(MonadThrow m, MonadReader r m, MonadCatch m) => MonadReader r (Parser m a) Source # 
Instance details

Defined in Streamly.Internal.Data.Parser.ParserD.Type

Methods

ask :: Parser m a r #

local :: (r -> r) -> Parser m a a0 -> Parser m a a0 #

reader :: (r -> a0) -> Parser m a a0 #

MonadThrow m => Monad (Parser m a) Source #

See documentation of Parser.

Instance details

Defined in Streamly.Internal.Data.Parser.ParserD.Type

Methods

(>>=) :: Parser m a a0 -> (a0 -> Parser m a b) -> Parser m a b #

(>>) :: Parser m a a0 -> Parser m a b -> Parser m a b #

return :: a0 -> Parser m a a0 #

Functor m => Functor (Parser m a) Source # 
Instance details

Defined in Streamly.Internal.Data.Parser.ParserD.Type

Methods

fmap :: (a0 -> b) -> Parser m a a0 -> Parser m a b #

(<$) :: a0 -> Parser m a b -> Parser m a a0 #

MonadThrow m => Applicative (Parser m a) Source #

Applicative form of serialWith.

Instance details

Defined in Streamly.Internal.Data.Parser.ParserD.Type

Methods

pure :: a0 -> Parser m a a0 #

(<*>) :: Parser m a (a0 -> b) -> Parser m a a0 -> Parser m a b #

liftA2 :: (a0 -> b -> c) -> Parser m a a0 -> Parser m a b -> Parser m a c #

(*>) :: Parser m a a0 -> Parser m a b -> Parser m a b #

(<*) :: Parser m a a0 -> Parser m a b -> Parser m a a0 #

(MonadThrow m, MonadIO m) => MonadIO (Parser m a) Source # 
Instance details

Defined in Streamly.Internal.Data.Parser.ParserD.Type

Methods

liftIO :: IO a0 -> Parser m a a0 #

MonadCatch m => Alternative (Parser m a) Source #

Alternative instance using alt.

Note: The implementation of <|> is not lazy in the second argument. The following code will fail:

>>> Stream.parse (Parser.satisfy (> 0) <|> undefined) $ Stream.fromList [1..10]
1
Instance details

Defined in Streamly.Internal.Data.Parser.ParserD.Type

Methods

empty :: Parser m a a0 #

(<|>) :: Parser m a a0 -> Parser m a a0 -> Parser m a a0 #

some :: Parser m a a0 -> Parser m a [a0] #

many :: Parser m a a0 -> Parser m a [a0] #

MonadCatch m => MonadPlus (Parser m a) Source #

See documentation of Parser.

Instance details

Defined in Streamly.Internal.Data.Parser.ParserD.Type

Methods

mzero :: Parser m a a0 #

mplus :: Parser m a a0 -> Parser m a a0 -> Parser m a a0 #

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

Constructors

ParseError String 

data Step s b Source #

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

Constructors

Partial Int s

Partial result with an optional backtrack request.

Partial count state means a partial result is available which can be extracted successfully, state is the opaque state of the parser to be supplied to the next invocation of the step operation. The current input position is reset to count elements back and any input before that is dropped from the backtrack buffer.

Continue Int s

Need more input with an optional backtrack request.

Continue count state means the parser has consumed the current input but no new result is generated, state is the next state of the parser. The current input is retained in the backtrack buffer and the input position is reset to count elements back.

Done Int b

Done with leftover input count and result.

Done count result means the parser has finished, it will accept no more input, last count elements from the input are unused and the result of the parser is in result.

Error String

Parser failed without generating any output.

The parsing operation may backtrack to the beginning and try another alternative.

Instances

Instances details
Functor (Step s) Source # 
Instance details

Defined in Streamly.Internal.Data.Parser.ParserD.Type

Methods

fmap :: (a -> b) -> Step s a -> Step s b #

(<$) :: a -> Step s b -> Step s a #

data Initial s b Source #

The type of a Parser's initial action.

Internal

Constructors

IPartial !s

Wait for step function to be called with state s.

IDone !b

Return a result right away without an input.

IError String

Return an error right away without an input.

Instances

Instances details
Bifunctor Initial Source #

first maps on IPartial and second maps on IDone.

Internal

Instance details

Defined in Streamly.Internal.Data.Parser.ParserD.Type

Methods

bimap :: (a -> b) -> (c -> d) -> Initial a c -> Initial b d #

first :: (a -> b) -> Initial a c -> Initial b c #

second :: (b -> c) -> Initial a b -> Initial a c #

Functor (Initial s) Source #

Maps a function over the result held by IDone.

fmap = second

Internal

Instance details

Defined in Streamly.Internal.Data.Parser.ParserD.Type

Methods

fmap :: (a -> b) -> Initial s a -> Initial s b #

(<$) :: a -> Initial s b -> Initial s a #

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

Downgrade to Fold

toFold :: MonadThrow m => Parser m a b -> Fold m a b Source #

See toFold.

Internal

Accumulators

fromFold :: Monad m => Fold m a b -> Parser m a b Source #

See fromFold.

Pre-release

fromPure :: Monad m => b -> Parser m a b Source #

See fromPure.

Pre-release

fromEffect :: Monad m => m b -> Parser m a b Source #

See fromEffect.

Pre-release

die :: MonadThrow m => String -> Parser m a b Source #

See die.

Pre-release

dieM :: MonadThrow m => m String -> Parser m a b Source #

See dieM.

Pre-release

Element parsers

peek :: MonadThrow m => Parser m a a Source #

See peek.

Pre-release

eof :: Monad m => Parser m a () Source #

See eof.

Pre-release

satisfy :: MonadThrow m => (a -> Bool) -> Parser m a a Source #

See satisfy.

Pre-release

next :: Monad m => Parser m a (Maybe a) Source #

See next.

Pre-release

maybe :: MonadThrow m => (a -> Maybe b) -> Parser m a b Source #

See maybe.

Pre-release

either :: MonadThrow m => (a -> Either String b) -> Parser m a b Source #

See either.

Pre-release

Sequence parsers

takeBetween :: MonadCatch m => Int -> Int -> Fold m a b -> Parser m a b Source #

See takeBetween.

Pre-release

takeEQ :: MonadThrow m => Int -> Fold m a b -> Parser m a b Source #

See takeEQ.

Pre-release

takeGE :: MonadThrow m => Int -> Fold m a b -> Parser m a b Source #

See takeGE.

Pre-release

takeP :: Monad m => Int -> Parser m a b -> Parser m a b Source #

See takeP.

Internal

lookAhead :: MonadThrow m => Parser m a b -> Parser m a b Source #

See lookahead.

Pre-release

takeWhile :: Monad m => (a -> Bool) -> Fold m a b -> Parser m a b Source #

See takeWhile.

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

sliceBeginWith :: Monad m => (a -> Bool) -> Fold m a b -> Parser m a b Source #

wordBy :: Monad m => (a -> Bool) -> Fold m a b -> Parser m a b Source #

See wordBy.

groupBy :: Monad m => (a -> a -> Bool) -> Fold m a b -> Parser m a b Source #

See groupBy.

groupByRolling :: Monad m => (a -> a -> Bool) -> Fold m a b -> Parser m a b Source #

groupByRollingEither :: MonadCatch m => (a -> a -> Bool) -> Fold m a b -> Fold m a c -> Parser m a (Either b c) Source #

eqBy :: MonadThrow m => (a -> a -> Bool) -> [a] -> Parser m a () Source #

See eqBy.

Pre-release

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

alt :: Monad m => Parser m x a -> Parser m x a -> Parser m x a Source #

See alt.

Pre-release

Parallel Alternatives

shortest :: Monad m => Parser m x a -> Parser m x a -> Parser m x a Source #

See shortest.

Broken

longest :: MonadCatch m => Parser m x a -> Parser m x a -> Parser m x a Source #

See longest.

Broken

N-ary Combinators

Sequential Collection

sequence :: Fold m b c -> t (Parser m a b) -> Parser m a c Source #

See sequence.

Unimplemented

concatMap :: MonadThrow m => (b -> Parser m a c) -> Parser m a b -> Parser m a c Source #

See concatMap.

Pre-release

Sequential Repetition

count :: Int -> Parser m a b -> Fold m b c -> Parser m a c Source #

See count.

Unimplemented

countBetween :: Int -> Int -> Parser m a b -> Fold m b c -> Parser m a c Source #

See countBetween.

Unimplemented

many :: MonadCatch m => Parser m a b -> Fold m b c -> Parser m a c Source #

See many.

Pre-release

some :: MonadCatch m => Parser m a b -> Fold m b c -> Parser m a c Source #

See some.

Pre-release

manyTill :: MonadCatch m => Fold m b c -> Parser m a b -> Parser m a x -> Parser m a c Source #

See manyTill.

Pre-release

Collection of Alternatives

choice :: (MonadCatch m, Foldable t) => t (Parser m a b) -> Parser m a b Source #

See choice.

Broken