parsley-core-2.2.0.0: A fast parser combinator library backed by Typed Template Haskell
LicenseBSD-3-Clause
MaintainerJamie Willis
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010
Extensions
  • MonoLocalBinds
  • TemplateHaskell
  • TemplateHaskellQuotes
  • ImplicitParams
  • ScopedTypeVariables
  • AllowAmbiguousTypes
  • UnboxedTuples
  • BangPatterns
  • DisambiguateRecordFields
  • RecordWildCards
  • RecordPuns
  • GADTs
  • GADTSyntax
  • ConstraintKinds
  • PolyKinds
  • DataKinds
  • TypeSynonymInstances
  • FlexibleContexts
  • FlexibleInstances
  • ConstrainedClassMethods
  • MagicHash
  • KindSignatures
  • RankNTypes
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll
  • PatternSynonyms
  • TypeApplications

Parsley.Internal.Backend.Machine.Ops

Description

This module contains all the relevant operations for the evaluation of a machine. These are used by Parsley.Internal.Backend.Machine.Eval to provide the various instruction interpretations.

Since: 1.0.0.0

Synopsis

Core Machine Operations

dup :: Defunc x -> (Defunc x -> Code r) -> Code r Source #

Creates a let-binding that allows the same value to be used multiple times without re-computation.

Since: 1.0.0.0

returnST :: forall s a. a -> ST s a Source #

This is just plain ol' return. It is given a concrete type here so that "Ambiuous Type Error" is avoided in the generated code.

Since: 1.0.0.0

Abstracted Input Operations

sat Source #

Arguments

:: (Defunc Char -> Defunc Bool)

Predicate to test the character with.

-> Code Char

The character to test against.

-> (Defunc Char -> Code b)

Code to execute on success.

-> Code b

Code to execute on failure.

-> Code b 

Given a predicate, a continuation that accepts an updated state Γ, code to execute on failure, and a state γ, tries to read a character from the input within γ, executing the failure code if it does not exist or does not match.

Since: 2.1.0.0

emitLengthCheck Source #

Arguments

:: (?ops :: InputOps (Rep o), PositionOps (Rep o)) 
=> Int

The number of required characters \(n\).

-> Code a

The good continuation if \(n\) characters are available.

-> Code a

The bad continuation if the characters are unavailable.

-> Offset o

The input to test on.

-> Code a 

Emits a length check for a number of characters \(n\) in the most efficient way it can. It takes two continuations a good and a bad: the good is used when the \(n\) characters are available and the bad when they are not.

Since: 1.4.0.0

fetch :: (?ops :: InputOps (Rep o)) => Input o -> (Code Char -> Input o -> Code b) -> Code b Source #

Consumes the next character and adjusts the offset to match.

Since: 1.8.0.0

Register Operations

newΣ :: ΣVar x -> Access -> Defunc x -> (Ctx s o a -> Code (ST s r)) -> Ctx s o a -> Code (ST s r) Source #

Depending on the access type either generates the code for a new register and registers it with the Ctx, or generates a binding with dup and registers that in the Ctx cache.

Since: 1.0.0.0

writeΣ :: ΣVar x -> Access -> Defunc x -> (Ctx s o a -> Code (ST s r)) -> Ctx s o a -> Code (ST s r) Source #

Depending on the access type, either generates the code for a write to a register (and caching that result) or updates the cache with the register's new value.

Since: 1.0.0.0

readΣ :: ΣVar x -> Access -> (Defunc x -> Ctx s o a -> Code (ST s r)) -> Ctx s o a -> Code (ST s r) Source #

Depending on the access type, either generates a read from a register or fetches the value from the cache and feeds it to a continuation.

Since: 1.0.0.0

Handler Operations

Basic handlers and operations

fatal :: AugmentedStaHandler s o a Source #

This is the root-most handler, when it is executed the parser fails immediately by returning Nothing.

Since: 1.2.0.0

raise :: Γ s o xs (Succ n) r a -> Code (ST s (Maybe a)) Source #

Fails by evaluating the next handler with the current input. Makes use of staHandlerEval to make use of static information available about the state of the input (since 1.4.0.0).

Since: 1.0.0.0

Handler preparation

buildHandler Source #

Arguments

:: Γ s o xs n r a

State to execute the handler with.

-> (Γ s o (o ': xs) n r a -> Code (ST s (Maybe a)))

Partial parser accepting the modified state.

-> Word

The unique identifier for the offset on failure.

-> StaHandlerBuilder s o a 

Converts a partially evaluated parser into a handler: this is done by completing the evaluation in the context of a future offset, and taking a captured offset and pushing it to the stack. Returns a StaHandlerBuilder, which takes the captured offset as the first argument.

Since: 1.2.0.0

buildYesHandler :: Γ s o xs n r a -> (Γ s o xs n r a -> Code (ST s (Maybe a))) -> StaYesHandler s o a Source #

Converts a partially evaluated parser into a "yes" handler: this means that the handler always knows that the inputs are equal, so does not require both a captured and a current offset. Otherwise, is similar to buildHandler.

Since: 2.1.0.0

buildIterYesHandler :: Γ s o xs n r a -> (Γ s o xs n r a -> Code (ST s (Maybe a))) -> Word -> StaHandler s o a Source #

Converts a partially evaluated parser into a "yes" handler: this means that the handler always knows that the inputs are equal, so does not require both a captured and a current offset. Otherwise, is similar to buildHandler.

Since: 2.1.0.0

Handler binding

bindAlwaysHandler Source #

Arguments

:: forall s o xs n r a b. HandlerOps o 
=> Γ s o xs n r a

The state from which to capture the offset.

-> Bool

Whether or not a binding is required

-> StaHandlerBuilder s o a

The handler waiting to receive the captured offset and be bound.

-> (Γ s o xs (Succ n) r a -> Code b)

The parser to receive the binding.

-> Code b 

Wraps around bindHandler# to create a binding for "always" handlers, which always perform the same action regardless of if the captured and current offsets match or not.

Since: 1.4.0.0

bindSameHandler Source #

Arguments

:: forall s o xs n r a b. (HandlerOps o, PositionOps (Rep o)) 
=> Γ s o xs n r a

The state from which to capture the offset.

-> Bool

Is a binding required for the matching handler?

-> StaYesHandler s o a

The handler that handles matching input.

-> Bool

Is a binding required for the mismatched handler?

-> StaHandlerBuilder s o a

The handler that handles mismatched input.

-> (Γ s o xs (Succ n) r a -> Code b)

The parser to receive the composite handler.

-> Code b 

Wraps around bindHandler# to create three bindings for a handler that acts differently depending on whether inputs match or not. The three bindings are for the case where they are the same, the case where they differ, and the case where they are unknown (which is defined in terms of the previous two).

Since: 2.1.0.0

Continuation Operations

Basic continuations and operations

halt :: StaCont s o a a Source #

The root-most return continuation, this is used when the top-level parser returns: it returns the result with Just and terminates the entire parser.

Since: 1.2.0.0

noreturn :: StaCont s o a Void Source #

This continuation is used for binding that never return, which is enforced by the Void in the type. This signifies that a binding may only exit on failure, which is the case with iterating parsers.

Since: 1.2.0.0

resume :: StaCont s o a x -> Γ s o (x ': xs) n r a -> Code (ST s (Maybe a)) Source #

Executes a given continuation (which may be a return continuation or a join point) taking the required components from the state Γ.

Since: 1.2.0.0

callWithContinuation Source #

Arguments

:: MarshalOps o 
=> StaSubroutine s o a x

The subroutine sub that will be called.

-> StaCont s o a x

The return continuation for the subroutine.

-> Input o

The input to feed to sub.

-> Vec (Succ n) (AugmentedStaHandler s o a)

The stack from which to obtain the handler to pass to sub.

-> Code (ST s (Maybe a)) 

A form of callCC, this calls a subroutine with a given return continuation passed to it. This may be the current continuation, but also may just be a previous return continuation in the case of a tail call.

Since: 1.8.0.0

callCC Source #

Arguments

:: forall s o xs n r a x. MarshalOps o 
=> Word 
-> StaSubroutine s o a x

The subroutine sub that will be called.

-> (Γ s o (x ': xs) (Succ n) r a -> Code (ST s (Maybe a)))

The return continuation to generate

-> Γ s o xs (Succ n) r a 
-> Code (ST s (Maybe a)) 

Combines suspend and callWithContinuation, simultaneously performing an optimisation on the offset if the subroutine has known input characteristics.

Since: 1.5.0.0

Continuation preparation

suspend Source #

Arguments

:: (Γ s o (x ': xs) n r a -> Code (ST s (Maybe a)))

The partial parser to turn into a return continuation.

-> Γ s o xs n r a

The state to execute the continuation with.

-> (Input# o -> Input o)

Function used to generate the offset

-> StaCont s o a x 

Converts a partial parser into a return continuation in a manner similar to buildHandler.

Since: 1.8.0.0

Join Point Operations

setupJoinPoint Source #

Arguments

:: forall s o xs n r a x. JoinBuilder o 
=> ΦVar x

The name of the binding.

-> Machine s o (x ': xs) n r a

The definition of the binding.

-> Machine s o xs n r a

The scope within which the binding is valid.

-> MachineMonad s o xs n r a 

Wraps around setupJoinPoint# to make a join point and register it into the Ctx.

Since: 1.4.0.0

Iteration Operations

bindIterAlways Source #

Arguments

:: forall s o a. RecBuilder o 
=> Ctx s o a

The context to keep the binding

-> MVar Void

The name of the binding.

-> Machine s o '[] One Void a

The body of the loop.

-> Bool

Does loop exit require a binding?

-> StaHandlerBuilder s o a

What to do after the loop exits (by failing)

-> Input o

The initial offset to provide to the loop

-> Word

The unique name for captured offset and iteration offset

-> Code (ST s (Maybe a)) 

Uses bindIterHandler# and bindIter# to create an iterated parser from its loop body and return continuation. The exit of a loop is done using failure, and this failure does not discriminate whether or not the loop consumed input in its final iteration.

Since: 1.8.0.0

bindIterSame Source #

Arguments

:: forall s o a. (RecBuilder o, HandlerOps o, PositionOps (Rep o)) 
=> Ctx s o a

The context to store the binding in.

-> MVar Void

The name of the binding.

-> Machine s o '[] One Void a

The loop body.

-> Bool

Is a binding required for the matching handler?

-> StaHandler s o a

The handler when input is the same.

-> Bool

Is a binding required for the differing handler?

-> StaHandlerBuilder s o a

The handler when input differs.

-> Input o

The initial offset of the loop.

-> Word

The unique name of the captured offsets and the iteration offset.

-> Code (ST s (Maybe a)) 

Similar to bindIterAlways, but builds a handler that performs in the same way as bindSameHandler.

Since: 2.1.0.0

Recursion Operations

buildRec Source #

Arguments

:: forall rs s o a r. RecBuilder o 
=> MVar r

The name of the binding.

-> Regs rs

The registered required by the binding.

-> Ctx s o a

The context to re-insert the register-less binding

-> Machine s o '[] One r a

The body of the binding.

-> Metadata

The metadata associated with the binding

-> DynFunc rs s o a r 

Wraps around bindRec# to produce a recursive parser binding. This function also provides all the free-registers which are closed over by the binding. This eliminates recursive calls from having to pass all of the same registers each time round.

Since: 1.5.0.0

Marshalling Operations

dynHandler :: forall s o a. MarshalOps o => AugmentedStaHandler s o a -> InputCharacteristic -> DynHandler s o a Source #

Wraps around dynHandler#, but ensures that if the StaHandler originated from a DynHandler itself, that no work is performed.

Takes in an InputCharacteristic, which is used to refine the handler given knowledge about how it might be used.

Since: 1.5.0.0

dynCont :: forall s o a x. MarshalOps o => StaCont s o a x -> DynCont s o a x Source #

Wraps around dynCont#, but ensures that if the StaCont originated from a DynCont itself, that no work is performed.

Since: 1.4.0.0

Log Operations

logHandler :: (?ops :: InputOps (Rep o), LogHandler o) => String -> Ctx s o a -> Γ s o xs (Succ n) ks a -> Word -> StaHandlerBuilder s o a Source #

The specialised handler for the debug combinator. It will fail again after having printed the debug information.

Since: 1.2.0.0

preludeString Source #

Arguments

:: forall s o xs n r a. (?ops :: InputOps (Rep o), LogHandler o) 
=> String

The name as per the debug combinator

-> Char

Either < or > depending on whether we are entering or leaving.

-> Γ s o xs n r a 
-> Ctx s o a 
-> String

String that represents the current status

-> Code String 

Used for the debug instructions and handler, produces the debugging information string.

Since: 1.2.0.0

Convenience Types

type Ops o = (HandlerOps o, JoinBuilder o, RecBuilder o, PositionOps (Rep o), MarshalOps o, LogOps (Rep o)) Source #

A convience bundle of all of the type class constraints.

Since: 1.0.0.0

type LogHandler o = (PositionOps (Rep o), LogOps (Rep o)) Source #

The constraints needed to build a logHandler.

Since: 1.0.0.0

type StaHandlerBuilder s o a = Input o -> StaHandler s o a Source #

A StaHandler that has not yet captured its offset.

Since: 1.2.0.0

type StaYesHandler s o a = Input o -> Code (ST s (Maybe a)) Source #

A "yes-handler" that has not yet captured its offset

Since: 2.1.0.0

Re-exports from Parsley.Internal.Backend.Machine.InputOps

class HandlerOps o Source #

Used to generate a binding for a handler.

Since: 1.4.0.0

Minimal complete definition

bindHandler#

Instances

Instances details
HandlerOps ByteString Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

HandlerOps ByteString Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

HandlerOps Text Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

Methods

bindHandler# :: StaHandler# s Text a -> (DynHandler s Text a -> Code b) -> Code b Source #

HandlerOps Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

Methods

bindHandler# :: StaHandler# s Stream a -> (DynHandler s Stream a -> Code b) -> Code b Source #

HandlerOps CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

HandlerOps Text16 Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

Methods

bindHandler# :: StaHandler# s Text16 a -> (DynHandler s Text16 a -> Code b) -> Code b Source #

HandlerOps [Char] Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

Methods

bindHandler# :: StaHandler# s [Char] a -> (DynHandler s [Char] a -> Code b) -> Code b Source #

HandlerOps (UArray Int Char) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

class JoinBuilder o Source #

Generates join-point bindings.

Since: 1.4.0.0

Minimal complete definition

setupJoinPoint#

Instances

Instances details
JoinBuilder ByteString Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

Methods

setupJoinPoint# :: StaCont# s ByteString a x -> (DynCont s ByteString a x -> Code b) -> Code b Source #

JoinBuilder ByteString Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

Methods

setupJoinPoint# :: StaCont# s ByteString a x -> (DynCont s ByteString a x -> Code b) -> Code b Source #

JoinBuilder Text Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

Methods

setupJoinPoint# :: StaCont# s Text a x -> (DynCont s Text a x -> Code b) -> Code b Source #

JoinBuilder Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

Methods

setupJoinPoint# :: StaCont# s Stream a x -> (DynCont s Stream a x -> Code b) -> Code b Source #

JoinBuilder CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

Methods

setupJoinPoint# :: StaCont# s CharList a x -> (DynCont s CharList a x -> Code b) -> Code b Source #

JoinBuilder Text16 Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

Methods

setupJoinPoint# :: StaCont# s Text16 a x -> (DynCont s Text16 a x -> Code b) -> Code b Source #

JoinBuilder [Char] Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

Methods

setupJoinPoint# :: StaCont# s [Char] a x -> (DynCont s [Char] a x -> Code b) -> Code b Source #

JoinBuilder (UArray Int Char) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

Methods

setupJoinPoint# :: StaCont# s (UArray Int Char) a x -> (DynCont s (UArray Int Char) a x -> Code b) -> Code b Source #

class RecBuilder o Source #

Various functions for creating bindings for recursive parsers.

Since: 1.4.0.0

Minimal complete definition

bindIterHandler#, bindIter#, bindRec#

Instances

Instances details
RecBuilder ByteString Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

RecBuilder ByteString Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

RecBuilder Text Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

Methods

bindIterHandler# :: (Input# Text -> StaHandler# s Text a) -> (Code (Pos -> Rep Text -> Handler# s Text a) -> Code b) -> Code b Source #

bindIter# :: Input# Text -> (Code (Pos -> Rep Text -> ST s (Maybe a)) -> Input# Text -> Code (ST s (Maybe a))) -> Code (ST s (Maybe a)) Source #

bindRec# :: (DynSubroutine s Text a x -> StaSubroutine# s Text a x) -> DynSubroutine s Text a x Source #

RecBuilder Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

RecBuilder CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

RecBuilder Text16 Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

RecBuilder [Char] Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

Methods

bindIterHandler# :: (Input# [Char] -> StaHandler# s [Char] a) -> (Code (Pos -> Rep [Char] -> Handler# s [Char] a) -> Code b) -> Code b Source #

bindIter# :: Input# [Char] -> (Code (Pos -> Rep [Char] -> ST s (Maybe a)) -> Input# [Char] -> Code (ST s (Maybe a))) -> Code (ST s (Maybe a)) Source #

bindRec# :: (DynSubroutine s [Char] a x -> StaSubroutine# s [Char] a x) -> DynSubroutine s [Char] a x Source #

RecBuilder (UArray Int Char) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

class PositionOps (rep :: TYPE r) Source #

Defines operations for manipulating offsets for regular use. These are not tied to the original captured input but instead to the representation of its offset.

Since: 1.0.0.0

Minimal complete definition

same, shiftRight

class MarshalOps o Source #

These operations are responsible for materialising the static handlers and continuations into dynamic forms that can be passed into other bindings at runtime.

Since: 1.4.0.0

Minimal complete definition

dynHandler#, dynCont#

Instances

Instances details
MarshalOps ByteString Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

MarshalOps ByteString Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

MarshalOps Text Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

MarshalOps Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

MarshalOps CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

MarshalOps Text16 Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

MarshalOps [Char] Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

Methods

dynHandler# :: StaHandler# s [Char] a -> DynHandler s [Char] a Source #

dynCont# :: StaCont# s [Char] a x -> DynCont s [Char] a x Source #

MarshalOps (UArray Int Char) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

class LogOps (rep :: TYPE r) Source #

Defines operation used for debugging operations.

Since: 1.0.0.0

Minimal complete definition

shiftLeft, offToInt