parsley-core-1.4.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.Types.Statics

Description

This module contains the types that represent statically known information that can be refined and manipulated within a single compilation unit: i.e. not crossing recursion or call boundaries.

Since: 1.4.0.0

Synopsis

Handlers

type StaHandler# s o a = Code (Rep o) -> Code (ST s (Maybe a)) Source #

This represents the translation of Handler# but where the static function structure has been exposed. This allows for β-reduction on handlers, a simple form of inlining optimisation.

Since: 1.4.0.0

data StaHandler s o a Source #

Compared with StaHandler#, this type allows for the encoding of various static properties of handlers which can be carried around during the lifetime of the handlers. This information allows the engine to optimise more aggressively, leveraging domain-specific optimisation data.

Note that StaHandlerCase is not exposed, but is potentially three handlers: one for unknown offset cases, one for offset known to be the same, and another for offset known to be different (see mkStaHandlerFull).

Since: 1.4.0.0

Constructors

StaHandler 

Fields

  • (Maybe (Offset o))

    The statically bound offset for this handler, if available.

  • !(StaHandlerCase s o a)

    The static function representing this handler when offsets are incomparable.

  • (Maybe (DynHandler s o a))

    The dynamic handler that has been wrapped in this handler, if available.

StaHandler Builders

The following functions are builders of StaHandler.

mkStaHandler :: Offset o -> StaHandler# s o a -> StaHandler s o a Source #

Augments a StaHandler# with information about what the offset is that the handler has captured. This is a purely static handler, which is not derived from a dynamic one.

Since: 1.4.0.0

mkStaHandlerNoOffset :: StaHandler# s o a -> StaHandler s o a Source #

Converts a StaHandler# into a StaHandler without any information about the captured offset. This is a purely static handler, not derived from a dynamic one.

Since: 1.4.0.0

mkStaHandlerDyn :: forall s o a. Maybe (Offset o) -> DynHandler s o a -> StaHandler s o a Source #

Converts a DynHandler into a StaHandler taking into account the possibility that captured offset information is available. The dynamic handler used to construct this static handler is maintained as the origin of the handler. This means if it is converted back the conversion is free.

Since: 1.4.0.0

mkStaHandlerFull Source #

Arguments

:: forall s o a. Offset o

The offset captured by the creation of the handler.

-> DynHandler s o a

The full handler, which can be used when offsets are incomparable and must perform the check.

-> Code (ST s (Maybe a))

The code that is executed when the captured offset matches the input.

-> DynHandler s o a

The handler to be executed when offsets are known not to match.

-> StaHandler s o a

A handler that carries this information around for later refinement.

When the behaviours of a handler given input that matches or does not match its captured offset are known, this function can be used to construct a StaHandler that stores this information. This can in turn be used in conjunction with staHandlerEval to statically refine the application of a handler to its argument.

Since: 1.4.0.0

StaHandler Interpreters

The following functions interpret or extract information from StaHandler.

staHandler# :: StaHandler s o a -> StaHandler# s o a Source #

Given a static handler, extracts the underlying handler which has "forgotten" any static domain-specific information it had been attached to.

Since: 1.4.0.0

staHandlerEval :: StaHandler s o a -> Offset o -> Code (ST s (Maybe a)) Source #

Unlike staHandler#, which returns a handler that accepts Code (Rep o), this function accepts a full Offset, which can be used to refine the outcome of the execution of the handler as follows:

  • If the handler has a registered captured offset, and these offsets are comparable:

    • If the offsets are equal, use the code to be executed on matching offset (See mkStaHandlerFull)
    • If the offsets are not equal, invoke the sub-handler, skipping the if check (see mkStaHandlerFull)
  • If the handler is missing a captured offset, or they are incomparable (from different sources) then execute the full handler, which will perform a runtime check for equivalence.

Since: 1.4.0.0

Return Continuations

type StaCont# s o a x = Code x -> Code (Rep o) -> Code (ST s (Maybe a)) Source #

This represents the translation of Cont# but where the static function structure has been exposed. This allows for β-reduction on continuations, a simple form of inlining optimisation.

Since: 1.4.0.0

data StaCont s o a x Source #

Compared with StaCont#, this type also bundles the static continuation with its dynamic origin, if available.

Since: 1.4.0.0

Constructors

StaCont (StaCont# s o a x) (Maybe (DynCont s o a x)) 

mkStaCont :: StaCont# s o a x -> StaCont s o a x Source #

Wraps a StaCont# up, under the knowledge that it is purely static and not derived from any dynamic continuation.

Since: 1.4.0.0

mkStaContDyn :: DynCont s o a x -> StaCont s o a x Source #

Converts a DynCont into a StaCont. The dynamic continuation used to construct this static continuation is maintained as the origin of the continuation. This means if it is converted back the conversion is free.

Since: 1.4.0.0

staCont# :: StaCont s o a x -> StaCont# s o a x Source #

Given a static continuation, extracts the underlying continuation which has "forgotten" any static domain-specific information it had been attached to.

Since: 1.4.0.0

Subroutines

data QSubroutine s o a x Source #

Wraps a StaFunc with its free registers, which are kept existential.

Since: 1.4.0.0

Constructors

forall rs. QSubroutine (StaFunc rs s o a x) (Regs rs) 

type StaSubroutine s o a x = DynCont s o a x -> Code (Rep o) -> DynHandler s o a -> Code (ST s (Maybe a)) Source #

This represents the translation of Subroutine# but where the static function structure has been exposed. This allows for β-reduction on subroutines, a simple form of inlining optimisation: useful for iteration.

Since: 1.4.0.0

type family StaFunc (rs :: [Type]) s o a x where ... Source #

This represents the translation of Func but where the static function structure has been exposed. This allows for β-reduction on subroutines with registers, a simple form of inlining optimisation.

Since: 1.4.0.0

Equations

StaFunc '[] s o a x = StaSubroutine s o a x 
StaFunc (r ': rs) s o a x = Code (STRef s r) -> StaFunc rs s o a x 

qSubroutine :: forall s o a x rs. DynFunc rs s o a x -> Regs rs -> QSubroutine s o a x Source #

Converts a DynFunc that relies on zero or more free registers into a QSubroutine, where the registers are existentially bounds to the function.

Since: 1.4.0.0