parsley-core-1.6.0.0: A fast parser combinator library backed by Typed Template Haskell
LicenseBSD-3-Clause
MaintainerJamie Willis
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Parsley.Internal.Backend.Machine.Instructions

Description

This contains the instructions and satelite datatypes for representing parsers at the lowest CPS-form level. These are indexed by multiple types, which are documented in the source (if not on Haddock!).

Since: 1.0.0.0

Synopsis

Main Instructions

data Instr (o :: Type) (k :: [Type] -> Nat -> Type -> Type -> Type) (xs :: [Type]) (n :: Nat) (r :: Type) (a :: Type) where Source #

This represents the instructions of the machine, in CPS form as an indexed functor.

When an instruction has a Succ in the type, it indicates that it is capable of failing.

Since: 1.4.0.0

Constructors

Ret

This instruction returns from either calls or the entire parser at the top-level.

Since: 1.0.0.0

Fields

  • :: Instr o k '[x] n x a
     
Push

Pushes a value onto the stack, which is required by the continuation parameter.

Since: 1.0.0.0

Fields

  • :: Defunc x

    Value to push.

  • -> k (x ': xs) n r a

    Machine requiring value.

  • -> Instr o k xs n r a
     
Pop

Removes a value from the stack, so it is the correct shape for the continuation parameter.

Since: 1.0.0.0

Fields

  • :: k xs n r a
     
  • -> Instr o k (x ': xs) n r a
     
Lift2

Applies a function to the top two elements of the stack, converting them to something else and pushing it back on.

Since: 1.0.0.0

Fields

  • :: Defunc (x -> y -> z)

    Function to apply.

  • -> k (z ': xs) n r a

    Machine requiring new value.

  • -> Instr o k (y ': (x ': xs)) n r a
     
Sat

Reads a character so long as it matches a given predicate. If it does not, or no input is available, this instruction fails.

Since: 1.0.0.0

Fields

Call

Calls another let-bound parser.

Since: 1.0.0.0

Fields

  • :: MVar x

    The binding to invoke.

  • -> k (x ': xs) (Succ n) r a

    Continuation to do after the call.

  • -> Instr o k xs (Succ n) r a
     
Jump

Jumps to another let-bound parser tail-recursively.

Since: 1.0.0.0

Fields

Empt

Fails unconditionally.

Since: 1.0.0.0

Fields

Commit

Discards a failure handler, so that it is no longer in scope.

Since: 1.0.0.0

Fields

  • :: k xs n r a

    Next machine, which will not require the discarded handler.

  • -> Instr o k xs (Succ n) r a
     
Catch

Registers a handler to deal with possible failure in the given machine.

Since: 1.4.0.0

Fields

  • :: k xs (Succ n) r a

    Machine where failure is handled by the handler.

  • -> Handler o k (o ': xs) n r a

    The handler to register.

  • -> Instr o k xs n r a
     
Tell

Pushes the current input offset onto the stack.

Since: 1.0.0.0

Fields

  • :: k (o ': xs) n r a

    The machine that accepts the input.

  • -> Instr o k xs n r a
     
Seek

Pops the input offset off of the stack and makes that the current input offset.

Since: 1.0.0.0

Fields

  • :: k xs n r a

    Machine to continue with new input.

  • -> Instr o k (o ': xs) n r a
     
Case

Picks one of two continuations based on whether a Left or Right is on the stack.

Since: 1.0.0.0

Fields

  • :: k (x ': xs) n r a

    Machine to execute if Left on stack.

  • -> k (y ': xs) n r a

    Machine to execute if Right on stack.

  • -> Instr o k (Either x y ': xs) n r a
     
Choices

Given a collection of predicates and machines, this instruction will execute the first machine for which the corresponding predicate returns true for the value on the top of the stack.

Since: 1.0.0.0

Fields

  • :: [Defunc (x -> Bool)]

    A list of predicates to try.

  • -> [k xs n r a]

    A corresponding list of machines.

  • -> k xs n r a

    A default machine to execute if no predicates match.

  • -> Instr o k (x ': xs) n r a
     
Iter

Sets up an iteration, where the second argument is executed repeatedly until it fails, which is handled by the given handler. The use of Void indicates that Ret is illegal within the loop.

Since: 1.0.0.0

Fields

  • :: MVar Void

    The name of the binding.

  • -> k '[] One Void a

    The body of the loop: it cannot return "normally".

  • -> Handler o k (o ': xs) n r a

    The handler for the loop's exit.

  • -> Instr o k xs n r a
     
Join

Jumps to a given join point.

Since: 1.0.0.0

Fields

  • :: ΦVar x

    The join point to jump to.

  • -> Instr o k (x ': xs) n r a
     
MkJoin

Sets up a new join point binding.

Since: 1.0.0.0

Fields

  • :: ΦVar x

    The name of the binding that can be referred to later.

  • -> k (x ': xs) n r a

    The body of the join point binding.

  • -> k xs n r a

    The scope within which the binding is valid.

  • -> Instr o k xs n r a
     
Swap

Swaps the top two elements on the stack

Since: 1.0.0.0

Fields

  • :: k (x ': (y ': xs)) n r a

    The machine that requires the reversed stack.

  • -> Instr o k (y ': (x ': xs)) n r a
     
Dup

Duplicates the top value on the stack. May produce a let-binding.

Since: 1.0.0.0

Fields

  • :: k (x ': (x ': xs)) n r a

    Machine that requires doubled element.

  • -> Instr o k (x ': xs) n r a
     
Make

Initialises a new register for use within the continuation. Initial value is on the stack.

Since: 1.0.0.0

Fields

  • :: ΣVar x

    The name of the new register.

  • -> Access

    Whether or not the register is "concrete".

  • -> k xs n r a

    The scope within which the register is accessible.

  • -> Instr o k (x ': xs) n r a
     
Get

Pushes the value contained within a register onto the stack.

Since: 1.0.0.0

Fields

  • :: ΣVar x

    Name of the register to read.

  • -> Access

    Whether or not the value is cached.

  • -> k (x ': xs) n r a

    The machine that requires the value.

  • -> Instr o k xs n r a
     
Put

Places the value on the top of the stack into a given register.

Since: 1.0.0.0

Fields

  • :: ΣVar x

    Name of the register to update.

  • -> Access

    Whether or not the value needs to be stored in a concrete register.

  • -> k xs n r a
     
  • -> Instr o k (x ': xs) n r a
     
LogEnter

Begins a debugging scope, the inner scope requires two handlers, the first is the log handler itself, and then the second is the "real" fail handler for when the log handler is executed.

Since: 1.0.0.0

Fields

  • :: String

    The message to be printed.

  • -> k xs (Succ (Succ n)) r a

    The machine to be debugged.

  • -> Instr o k xs (Succ n) r a
     
LogExit

Ends the log scope after a succesful execution.

Since: 1.0.0.0

Fields

  • :: String

    The message to be printed.

  • -> k xs n r a

    The machine that follows.

  • -> Instr o k xs n r a
     
MetaInstr

Executes a meta-instruction, which is interacting with implementation specific static information.

Since: 1.0.0.0

Fields

  • :: MetaInstr n

    A meta-instruction to perform.

  • -> k xs n r a

    The machine that follows.

  • -> Instr o k xs n r a
     

Instances

Instances details
IFunctor4 (Instr o) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Instructions

Methods

imap4 :: forall a x b (i :: [Type]) (j :: Nat) k. (forall (i' :: [Type]) (j' :: Nat) k'. a i' j' k' x -> b i' j' k' x) -> Instr o a i j k x -> Instr o b i j k x Source #

Show (Fix4 (Instr o) xs n r a) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Instructions

Methods

showsPrec :: Int -> Fix4 (Instr o) xs n r a -> ShowS #

show :: Fix4 (Instr o) xs n r a -> String #

showList :: [Fix4 (Instr o) xs n r a] -> ShowS #

Auxilliary Types

data Handler (o :: Type) (k :: [Type] -> Nat -> Type -> Type -> Type) (xs :: [Type]) (n :: Nat) (r :: Type) (a :: Type) where Source #

There are two types of organic handlers within parsley, which are captured by this type, which is also an IFunctor and wraps around Instr.

Since: 1.4.0.0

Constructors

Same

These handlers have two distinct behaviours depending on whether the captured offset matches the current offset or not.

Since: 1.4.0.0

Fields

  • :: k xs n r a

    Execute when the input matches, notice that the captured offset is discarded since it is equal to the current.

  • -> k (o ': xs) n r a

    Execute when the input does not match, the resulting behaviour could use the captured or current input.

  • -> Handler o k (o ': xs) n r a
     
Always :: k (o ': xs) n r a -> Handler o k (o ': xs) n r a

These handlers are unconditional on the input, and will always do the same thing regardless of the input provided.

Since: 1.4.0.0

Instances

Instances details
IFunctor4 (Handler o) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Instructions

Methods

imap4 :: forall a x b (i :: [Type]) (j :: Nat) k. (forall (i' :: [Type]) (j' :: Nat) k'. a i' j' k' x -> b i' j' k' x) -> Handler o a i j k x -> Handler o b i j k x Source #

Show (Handler o (Const4 (String -> String) :: [Type] -> Nat -> Type -> Type -> Type) (o ': xs) n r a) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Instructions

Methods

showsPrec :: Int -> Handler o (Const4 (String -> String)) (o ': xs) n r a -> ShowS #

show :: Handler o (Const4 (String -> String)) (o ': xs) n r a -> String #

showList :: [Handler o (Const4 (String -> String)) (o ': xs) n r a] -> ShowS #

data Access Source #

This determines whether or not an interaction with an register should be materialised in the generated code or not.

Since: 1.0.0.0

Constructors

Hard

Register exists at runtime and this interaction will use it.

Soft

Register may not exist, and the interaction should be with cache regardless.

Instances

Instances details
Show Access Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Instructions

data MetaInstr (n :: Nat) where Source #

These are meta-instructions, which interact with static information to direct the code-generation process. They are not formally part of parsley's semantics and can be omitted from an implementation without consequence.

Since: 1.0.0.0

Constructors

AddCoins :: Coins -> MetaInstr (Succ n)

Adds coins to the piggy-bank system (see Parsley.Internal.Backend.Machine.Types.Context for more information). If there are coins already available, add a piggy-bank, otherwise generate a length check and add the coins.

A handler is required, in case the length check fails.

Since: 1.5.0.0

RefundCoins :: Coins -> MetaInstr n

Refunds to the piggy-bank system (see Parsley.Internal.Backend.Machine.Types.Context for more information). This always happens for free, and is added straight to the coins.

Since: 1.5.0.0

DrainCoins :: Coins -> MetaInstr (Succ n)

Remove coins from piggy-bank system (see Parsley.Internal.Backend.Machine.Types.Context for more information) This is used to pay for more expensive calls to bindings with known required input.

A handler is required, as there may not be enough coins to pay the cost and a length check causes a failure.

Since: 1.5.0.0

GiveBursary :: Coins -> MetaInstr n

Refunds to the piggy-bank system (see Parsley.Internal.Backend.Machine.Types.Context for more information). This always happens for free, and is added straight to the coins. Unlike RefundCoins this cannot reclaim input, nor is is subtractive in the analysis.

Since: 1.5.0.0

PrefetchChar :: Bool -> MetaInstr (Succ n)

Fetches a character to read in advance. This is used to factor out a common token from alternatives. The boolean argument represents whether or not the read is covered by a factored length check, or requires its own.

Since: 1.5.0.0

BlockCoins :: MetaInstr n

True meta instruction: does nothing except for reset coin count during coin analysis.

Since: 1.6.0.0

Instances

Instances details
Show (MetaInstr n) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Instructions

Smart Instructions

_App :: Fix4 (Instr o) (y ': xs) n r a -> Instr o (Fix4 (Instr o)) (x ': ((x -> y) ': xs)) n r a Source #

Applies a value on the top of the stack to a function on the second-most top of the stack.

Since: 1.0.0.0

_Fmap :: Defunc (x -> y) -> Fix4 (Instr o) (y ': xs) n r a -> Instr o (Fix4 (Instr o)) (x ': xs) n r a Source #

Adjusts the value on the top of the stack with the given function.

Since: 1.0.0.0

_Modify :: ΣVar x -> Fix4 (Instr o) xs n r a -> Instr o (Fix4 (Instr o)) ((x -> x) ': xs) n r a Source #

Updates the value in a given register using the function on the top of the stack.

Since: 1.0.0.0

_Make :: ΣVar x -> k xs n r a -> Instr o k (x ': xs) n r a Source #

Smart-instruction for Make that uses a Hard access.

Since: 1.0.0.0

_Put :: ΣVar x -> k xs n r a -> Instr o k (x ': xs) n r a Source #

Smart-instruction for Put that uses a Hard access.

Since: 1.0.0.0

_Get :: ΣVar x -> k (x ': xs) n r a -> Instr o k xs n r a Source #

Smart-instruction for Get that uses a Hard access.

Since: 1.0.0.0

Smart Meta-Instructions

addCoins :: Coins -> Fix4 (Instr o) xs (Succ n) r a -> Fix4 (Instr o) xs (Succ n) r a Source #

Smart-constuctor around AddCoins.

Since: 1.5.0.0

refundCoins :: Coins -> Fix4 (Instr o) xs n r a -> Fix4 (Instr o) xs n r a Source #

Smart-constuctor around RefundCoins.

Since: 1.5.0.0

drainCoins :: Coins -> Fix4 (Instr o) xs (Succ n) r a -> Fix4 (Instr o) xs (Succ n) r a Source #

Smart-constuctor around DrainCoins.

Since: 1.5.0.0

giveBursary :: Coins -> Fix4 (Instr o) xs n r a -> Fix4 (Instr o) xs n r a Source #

Smart-constuctor around RefundCoins.

Since: 1.5.0.0

prefetchChar :: Bool -> Fix4 (Instr o) xs (Succ n) r a -> Fix4 (Instr o) xs (Succ n) r a Source #

Smart-constructor around PrefetchChar.

Since: 1.5.0.0

blockCoins :: Fix4 (Instr o) xs (Succ n) r a -> Fix4 (Instr o) xs (Succ n) r a Source #

Smart-constructor around PrefetchChar.

Since: 1.6.0.0