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

Streamly.Internal.Data.Parser.ParserK.Type

Description

CPS style implementation of parsers.

The CPS representation allows linear performance for Applicative, sequence, Monad, Alternative, and choice operations compared to the quadratic complexity of the corresponding direct style operations. However, direct style operations allow fusion with ~10x better performance than CPS.

The direct style representation does not allow for recursive definitions of "some" and "many" whereas CPS allows that.

Applicative and Alternative type class based combinators from the parser-combinators package can also be used with the ParserK type.

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.Parser.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 !(Array 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.Parser.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.Parser.ParserK.Type

Methods

fail :: String -> ParserK a m a0 #

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

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

Methods

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

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

Alternative form of alt. Backtrack and run the second parser if the first one fails.

The "some" and "many" operations of alternative accumulate results in a pure list which is not scalable and streaming. Instead use some and many for fusible operations with composable accumulation of results.

See also alt. This Alternative instance does not fuse, use alt when you need fusion.

Instance details

Defined in Streamly.Internal.Data.Parser.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 #

Applicative form of splitWith. Note that this operation does not fuse, use splitWith when fusion is important.

Instance details

Defined in Streamly.Internal.Data.Parser.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 #

Maps a function over the output of the parser.

Instance details

Defined in Streamly.Internal.Data.Parser.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 make the future parses depend on the previously parsed values.

If we have to parse "a9" or "9a" but not "99" or "aa" we can use the following parser:

backtracking :: MonadCatch m => PR.Parser Char m String
backtracking =
    sequence [PR.satisfy isDigit, PR.satisfy isAlpha]
    <|>
    sequence [PR.satisfy isAlpha, PR.satisfy isDigit]

We know that if the first parse resulted in a digit at the first place then the second parse is going to fail. However, we waste that information and parse the first character again in the second parse only to know that it is not an alphabetic char. By using lookbehind in a Monad composition we can avoid redundant work:

data DigitOrAlpha = Digit Char | Alpha Char

lookbehind :: MonadCatch m => PR.Parser Char m String
lookbehind = do
    x1 <-    Digit <$> PR.satisfy isDigit
         <|> Alpha <$> PR.satisfy isAlpha

    -- Note: the parse depends on what we parsed already
    x2 <- case x1 of
        Digit _ -> PR.satisfy isAlpha
        Alpha _ -> PR.satisfy isDigit

    return $ case x1 of
        Digit x -> [x,x2]
        Alpha x -> [x,x2]

See also concatMap. This monad instance does not fuse, use concatMap when you need fusion.

Instance details

Defined in Streamly.Internal.Data.Parser.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.Parser.ParserK.Type

Methods

mzero :: ParserK a m a0 #

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

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

Convert a raw byte Parser to a chunked ParserK.

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