streamly-core-0.2.2: Streaming, parsers, arrays, serialization and more
Copyright(c) 2020 Composewell Technologies
LicenseBSD-3-Clause
Maintainerstreamly@composewell.com
Stabilityexperimental
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Streamly.Internal.Data.ParserK

Description

 
Synopsis

Documentation

data Step a m r Source #

The intermediate result of running a parser step. The parser driver may stop with a final result, pause with a continuation to resume, or fail with an error.

See ParserD docs. This is the same as the ParserD Step except that it uses a continuation in Partial and Continue constructors instead of a state in case of ParserD.

Pre-release

Constructors

Done !Int r 
Partial !Int (Input a -> m (Step a m r)) 
Continue !Int (Input a -> m (Step a m r)) 
Error !Int String 

Instances

Instances details
Functor m => Functor (Step a m) Source # 
Instance details

Defined in Streamly.Internal.Data.ParserK.Type

Methods

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

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

data Input a Source #

Constructors

None 
Chunk a 

data ParseResult b Source #

The parser's result.

Int is the position index into the current input array. Could be negative. Cannot be beyond the input array max bound.

Pre-release

Constructors

Success !Int !b 
Failure !Int !String 

Instances

Instances details
Functor ParseResult Source #

Map a function over Success.

Instance details

Defined in Streamly.Internal.Data.ParserK.Type

Methods

fmap :: (a -> b) -> ParseResult a -> ParseResult b #

(<$) :: a -> ParseResult b -> ParseResult a #

newtype ParserK a m b Source #

A continuation passing style parser representation. A continuation of Steps, each step passes a state and a parse result to the next Step. The resulting Step may carry a continuation that consumes input a and results in another Step. Essentially, the continuation may either consume input without a result or return a result with no further input to be consumed.

Constructors

MkParser 

Fields

Instances

Instances details
Monad m => MonadFail (ParserK a m) Source # 
Instance details

Defined in Streamly.Internal.Data.ParserK.Type

Methods

fail :: String -> ParserK a m a0 #

MonadIO m => MonadIO (ParserK a m) Source # 
Instance details

Defined in Streamly.Internal.Data.ParserK.Type

Methods

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

Monad m => Alternative (ParserK a m) Source #

p1 <|> p2 passes the input to parser p1, if it succeeds, the result is returned. However, if p1 fails, the parser driver backtracks and tries the same input on the alternative parser p2, returning the result if it succeeds.

Instance details

Defined in Streamly.Internal.Data.ParserK.Type

Methods

empty :: ParserK a m a0 #

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

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

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

Monad m => Applicative (ParserK a m) Source #

f <$> p1 <*> p2 applies parsers p1 and p2 sequentially to an input stream. The first parser runs and processes the input, the remaining input is then passed to the second parser. If both parsers succeed, their outputs are applied to the function f. If either parser fails, the operation fails.

Instance details

Defined in Streamly.Internal.Data.ParserK.Type

Methods

pure :: a0 -> ParserK a m a0 #

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

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

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

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

Functor m => Functor (ParserK a m) Source #

Map a function on the result i.e. on b in Parser a m b.

Instance details

Defined in Streamly.Internal.Data.ParserK.Type

Methods

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

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

Monad m => Monad (ParserK a m) Source #

Monad composition can be used for lookbehind parsers, we can dynamically compose new parsers based on the results of the previously parsed values.

Instance details

Defined in Streamly.Internal.Data.ParserK.Type

Methods

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

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

return :: a0 -> ParserK a m a0 #

Monad m => MonadPlus (ParserK a m) Source #

mzero is same as empty, it aborts the parser. mplus is same as <|>, it selects the first succeeding parser.

Instance details

Defined in Streamly.Internal.Data.ParserK.Type

Methods

mzero :: ParserK a m a0 #

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

adaptC :: (Monad m, Unbox a) => Parser a m b -> ParserK (Array a) m b Source #

Convert an element Parser to a chunked ParserK. A chunked parser is more efficient than an element parser.

Pre-release

adapt :: Monad m => Parser a m b -> ParserK a m b Source #

Convert a Parser to ParserK.

Pre-release

adaptCG :: Monad m => Parser a m b -> ParserK (Array a) m b Source #

A generic adaptC. Similar to adaptC but is not constrained to Unbox types.

Pre-release

fromPure :: b -> ParserK a m b Source #

A parser that always yields a pure value without consuming any input.

Pre-release

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

See fromEffect.

Pre-release

die :: String -> ParserK a m b Source #

A parser that always fails with an error message without consuming any input.

Pre-release