Copyright | (c) 2023 Composewell Technologies |
---|---|
License | BSD-3-Clause |
Maintainer | streamly@composewell.com |
Stability | pre-release |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Parsers using Continuation Passing Style (CPS). See notes in Streamly.Data.Parser module to know when to use this module.
To run a ParserK
use parseChunks
.
Parser Type
A continuation passing style parser representation. A continuation of
Step
s, 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.
Instances
Monad m => MonadFail (ParserK a m) Source # | |
Defined in Streamly.Internal.Data.Parser.ParserK.Type | |
MonadIO m => MonadIO (ParserK a m) Source # | |
Defined in Streamly.Internal.Data.Parser.ParserK.Type | |
Monad m => Alternative (ParserK a m) Source # |
The "some" and "many" operations of alternative accumulate results in a pure
list which is not scalable and streaming. Instead use
See also |
Monad m => Applicative (ParserK a m) Source # |
|
Defined in Streamly.Internal.Data.Parser.ParserK.Type | |
Functor m => Functor (ParserK a m) Source # | Maps a function over the output of the parser. |
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]
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 data DigitOrAlpha = Digit Char | Alpha Char lookbehind :: MonadCatch m => PR.Parser Char m String lookbehind = do x1 <- Digit See also |
Monad m => MonadPlus (ParserK a m) Source # |
|
Parsers
Conversions
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
Without Input
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