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

Streamly.Internal.Data.Parser.ParserK.Type

Contents

Description

CPS style implementation of parsers.

The CPS representation allows linear performance for Applicative, sequenceA, Monad, sequence, and Alternative, 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.

Synopsis

Documentation

newtype Parser m a b Source #

A continuation passing style parser representation.

Constructors

MkParser 

Fields

Instances

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

Defined in Streamly.Internal.Data.Parser.ParserK.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, MonadState s m) => MonadState s (Parser m a) Source # 
Instance details

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

Methods

get :: Parser m a s #

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

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

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

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

Methods

fail :: String -> Parser m a a0 #

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

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

Methods

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

Monad m => Alternative (Parser m a) 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 :: 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] #

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

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

Instance details

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

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

Maps a function over the output of the parser.

Instance details

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

Methods

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

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

Monad m => Monad (Parser m a) 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 m Char 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 m Char 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

(>>=) :: 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 #

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

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

Pre-release

Instance details

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

Methods

mzero :: Parser m a a0 #

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

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

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

Pre-release

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

See fromEffect.

Pre-release

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

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

Pre-release

Conversion

toParserK :: MonadCatch m => Parser m a b -> Parser m a b Source #

Convert a direct style Parser to a CPS style Parser.

Pre-release

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

Convert a CPS style Parser to a direct style Parser.

"initial" returns a continuation which can be called one input at a time using the "step" function.

Pre-release