Copyright | (c) 2020 Composewell Technologies |
---|---|
License | BSD-3-Clause |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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.
Documentation
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
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
Instances
Functor ParseResult Source # | Map a function over |
Defined in Streamly.Internal.Data.Parser.ParserK.Type 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
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 # |
|
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