streamly-core
Copyright(c) 2023 Composewell Technologies
LicenseBSD-3-Clause
Maintainerstreamly@composewell.com
Stabilitypre-release
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Streamly.Data.ParserK

Description

See the general notes about parsing in the Streamly.Data.Parser module. This (ParserK) module implements a Continuation Passing Style (CPS) wrapper over the fused Streamly.Data.Parser module. It is a faster CPS parser than attoparsec.

The ParserK type represents a stream-consumer as a composition of function calls, therefore, a function call overhead is incurred at each composition. It is reasonably fast in general but may be a few times slower than the fused Parser type. However, unlike fused parsers, it allows for scalable dynamic composition, especially, ParserK can be used in recursive calls. Operations like splitWith on ParserK type have linear (O(n)) performance with respect to the number of compositions.

ParserK is preferred over the fused Parser when extensive applicative, alternative and monadic composition is required, or when recursive or dynamic composition of parsers is required. ParserK also allows efficient parsing of a stream of byte arrays, it can also break the input stream into a parse result and the remaining stream so that the stream can be parsed independently in segments.

How to parse a stream?

All the fused parsers from the Streamly.Data.Parser module can be converted to the CPS ParserK, for use with different types of parser drivers, using the toParserK combinators - Streamly.Data.Array.toParserK, Streamly.Data.StreamK.toParserK, and Streamly.Data.Array.Generic.toParserK

To parse a stream of unboxed arrays, use Streamly.Data.Array.parse for running the parser, this is the preferred and most efficient way to parse chunked input. The Streamly.Data.Array.parseBreak function returns the remaining stream as well along with the parse result.

To parse a stream of boxed arrays, use Streamly.Data.Array.Generic.parse or Streamly.Data.Array.Generic.parseBreak to run the parser.

To parse a stream of individual elements, use Streamly.Data.StreamK.parse and Streamly.Data.StreamK.parseBreak to run the parser.

Applicative Composition

Applicative parsers are simpler but we cannot use lookbehind as we can in the monadic parsers.

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

>>> -- parse p1 : p2 : []
>>> token p1 p2 = ((:) <$> p1 <*> ((:) <$> p2 <*> pure []))
>>> :{
backtracking :: Monad m => ParserK Char m String
backtracking = StreamK.toParserK $
    token (Parser.satisfy isDigit) (Parser.satisfy isAlpha) -- e.g. "9a"
    <|>
    token (Parser.satisfy isAlpha) (Parser.satisfy isDigit) -- e.g. "a9"
:}

Monadic Composition

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

In the previous example, 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 make dynamic decisions based on previously parsed information and avoid redundant work:

>>> data DigitOrAlpha = Digit Char | Alpha Char
>>> :{
lookbehind :: Monad m => ParserK Char m String
lookbehind = do
    x1 <- StreamK.toParserK $
             Digit <$> Parser.satisfy isDigit
         <|> Alpha <$> Parser.satisfy isAlpha
    -- Note: the parse depends on what we parsed already
    x2 <- StreamK.toParserK $
          case x1 of
             Digit _ -> Parser.satisfy isAlpha
             Alpha _ -> Parser.satisfy isDigit
    return $ case x1 of
        Digit x -> [x,x2]
        Alpha x -> [x,x2]
:}

Experimental APIs

Please refer to Streamly.Internal.Data.ParserK for functions that have not yet been released.

Synopsis

Setup

To execute the code examples provided in this module in ghci, please run the following commands first.

>>> :m
>>> import Control.Applicative ((<|>))
>>> import Data.Char (isDigit, isAlpha)
>>> import Streamly.Data.Parser (Parser)
>>> import Streamly.Data.ParserK (ParserK)
>>> import qualified Streamly.Data.Parser as Parser
>>> import qualified Streamly.Data.ParserK as ParserK
>>> import qualified Streamly.Data.Stream as Stream
>>> import qualified Streamly.Data.StreamK as StreamK
>>> import qualified Streamly.Unicode.Parser as Parser

For APIs that have not been released yet.

>>> import qualified Streamly.Internal.Data.ParserK as ParserK

Parser Type

data ParserK a (m :: Type -> Type) b Source #

A continuation passing style parser representation.

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 #

Parsers

fromPure :: forall b a (m :: Type -> Type). 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 :: forall a (m :: Type -> Type) b. String -> ParserK a m b Source #

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

Pre-release

Deprecated

fromFold :: forall (m :: Type -> Type) a b. (MonadIO m, Unbox a) => Fold m a b -> ParserK (Array a) m b Source #

Deprecated: Please use "Array.toParserK . Parser.fromFold" instead.

fromParser :: forall (m :: Type -> Type) a b. (MonadIO m, Unbox a) => Parser a m b -> ParserK (Array a) m b Source #

Deprecated: Please use "Array.toParserK" instead.

adapt :: forall (m :: Type -> Type) a b. Monad m => Parser a m b -> ParserK a m b Source #

Deprecated: Please use toParserK instead.

Convert a Parser to ParserK.

Pre-release

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

Deprecated: Use Streamly.Data.Array.toParserK

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

Deprecated: Use Streamly.Data.Array.Generic.toParserK