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

Streamly.Internal.Data.ParserK

Contents

Description

 
Synopsis

Documentation

chainr :: ParserK b IO a -> ParserK b IO (a -> a -> a) -> a -> ParserK b IO a Source #

chainr p op x is like chainr1 but allows zero or more occurrences of p, separated by op. If there are zero occurrences of p, the value x is returned.

chainl :: ParserK b IO a -> ParserK b IO (a -> a -> a) -> a -> ParserK b IO a Source #

chainl p op x is like chainl1 but allows zero or more occurrences of p, separated by op. If there are zero occurrences of p, the value x is returned.

chainr1 :: ParserK b IO a -> ParserK b IO (a -> a -> a) -> ParserK b IO a Source #

Like chainl1 but parses right associative application of the operator instead of left associative.

>>> num = Parser.decimal
>>> pow = Parser.char '^' *> pure (^)
>>> expr = ParserK.chainr1 (StreamK.toParserK num) (StreamK.toParserK pow)
>>> StreamK.parse expr $ StreamK.fromStream $ Stream.fromList "2^3^2"
Right 512

chainl1 :: ParserK b IO a -> ParserK b IO (a -> a -> a) -> ParserK b IO a Source #

chainl1 p op x parses one or more occurrences of p, separated by op. Returns a value obtained by a left associative application of all functions returned by op to the values returned by p.

>>> num = Parser.decimal
>>> plus = Parser.char '+' *> pure (+)
>>> expr = ParserK.chainl1 (StreamK.toParserK num) (StreamK.toParserK plus)
>>> StreamK.parse expr $ StreamK.fromStream $ Stream.fromList "1+2+3"
Right 6

If you're building full expression parsers with operator precedence and associativity, consider using makeExprParser from the parser-combinators package.

See also deintercalate.

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

data Input a Source #

Constructors

None 
Chunk a 

data Step a (m :: Type -> Type) r Source #

The intermediate result of running a parser step. The parser driver may (1) stop with a final result (Done) with no more inputs to be accepted, (2) generate an intermediate result (Partial) and accept more inputs, (3) generate no result but wait for more input (Continue), (4) or fail with an error (Error).

The Int is a count by which the current stream position should be adjusted before calling the next parsing step.

See the documentation of Step for more details, this has the same semantics.

Pre-release

Constructors

Done !Int r 
Partial !Int (StepParser a m r) 
Continue !Int (StepParser a m r) 
Error !Int String 

Instances

Instances details
Functor m => Functor (Step a m) Source # 
Instance details

Defined in Streamly.Internal.Data.ParserK.Type

Methods

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

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

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

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

Convert a Parser to ParserK.

Pre-release

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

A continuation passing style parser representation.

Constructors

MkParser 

Fields

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 #

data ParseResult b Source #

The parser's result.

Int is the position index in the stream relative to the position on entry i.e. when the parser started running. When the parser enters the position index is zero. If the parser consumed n elements then the new position index would be n. If the parser is backtracking then the position index would be negative.

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.ParserK.Type

Methods

fmap :: (a -> b) -> ParseResult a -> ParseResult b #

(<$) :: a -> ParseResult b -> ParseResult a #

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

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

See fromEffect.

Pre-release

parserDone :: Applicative m => ParseResult b -> Int -> Input a -> m (Step a m b) Source #

A continuation to extract the result when a CPS parser is done.

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

Convert a CPS style ParserK to a direct style Parser.

Pre-release

Deprecated

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