License | BSD-3-Clause |
---|---|
Maintainer | Jamie Willis |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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
- type StaHandler# s o a = Input# o -> Code (ST s (Maybe a))
- data StaHandler s o a
- data AugmentedStaHandler s o a
- data StaHandlerCase s (o :: Type) a
- fromStaHandler# :: StaHandler# s o a -> StaHandler s o a
- fromDynHandler :: forall s o a. DynHandler s o a -> StaHandler s o a
- staHandler# :: StaHandler s o a -> StaHandler# s o a
- augmentHandler :: Maybe (Input o) -> StaHandler s o a -> AugmentedStaHandler s o a
- augmentHandlerSta :: Maybe (Input o) -> StaHandler# s o a -> AugmentedStaHandler s o a
- augmentHandlerDyn :: forall s o a. Maybe (Input o) -> DynHandler s o a -> AugmentedStaHandler s o a
- augmentHandlerFull :: Input o -> StaHandler s o a -> Code (ST s (Maybe a)) -> StaHandler s o a -> AugmentedStaHandler s o a
- staHandlerEval :: (DynOps o, ?flags :: Flags) => AugmentedStaHandler s o a -> Input o -> Code (ST s (Maybe a))
- staHandlerCharacteristicSta :: AugmentedStaHandler s o a -> InputCharacteristic -> StaHandler# s o a
- staHandlerCharacteristicDyn :: AugmentedStaHandler s o a -> (StaHandler# s o a -> DynHandler s o a) -> InputCharacteristic -> DynHandler s o a
- type StaCont# s o a x = Code x -> Input# o -> Code (ST s (Maybe a))
- data StaCont s o a x = StaCont (StaCont# s o a x) !(Maybe (DynCont s o a x))
- mkStaCont :: StaCont# s o a x -> StaCont s o a x
- mkStaContDyn :: forall o s a x. DynCont s o a x -> StaCont s o a x
- staCont# :: StaCont s o a x -> StaCont# s o a x
- data QSubroutine s o a x = forall rs. QSubroutine !(StaFunc rs s o a x) !(Regs rs)
- data StaSubroutine s o a x
- type StaSubroutine# s o a x = DynCont s o a x -> DynHandler s o a -> Input# o -> Code (ST s (Maybe a))
- type family StaFunc (rs :: [Type]) s o a x where ...
- qSubroutine :: forall s o a x rs. DynFunc rs s o a x -> Regs rs -> Metadata -> QSubroutine s o a x
- mkStaSubroutine :: StaSubroutine# s o a x -> StaSubroutine s o a x
- mkStaSubroutineMeta :: Metadata -> StaSubroutine# s o a x -> StaSubroutine s o a x
- staSubroutine# :: StaSubroutine s o a x -> StaSubroutine# s o a x
- meta :: StaSubroutine s o a x -> Metadata
Handlers
type StaHandler# s o a = Input# 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.8.0.0
data StaHandler s o a Source #
Encapsulates a static handler with its possible dynamic origin for costless conversion.
Since: 1.7.0.0
data AugmentedStaHandler 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.
Since: 1.7.0.0
data StaHandlerCase s (o :: Type) a Source #
Represents 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 augmentHandlerFull
).
Since: 1.7.0.0
StaHandler
Operations
fromStaHandler# :: StaHandler# s o a -> StaHandler s o a Source #
Builds a StaHandler
out of a StaHandler#
, assumed to have no dynamic component.
Since: 1.7.0.0
fromDynHandler :: forall s o a. DynHandler s o a -> StaHandler s o a Source #
Builds a StaHandler
out of a DynHandler
, which is converted in the process.
Since: 1.7.0.0
staHandler# :: StaHandler s o a -> StaHandler# s o a Source #
Extracts the raw static component out of a static handler.
Since: 1.7.0.0
AugmentedStaHandler
Builders
The following functions are builders of AugmentedStaHandler
.
augmentHandler :: Maybe (Input o) -> StaHandler s o a -> AugmentedStaHandler s o a Source #
Augments a static handler with information about its captured offset.
Since: 1.7.0.0
augmentHandlerSta :: Maybe (Input o) -> StaHandler# s o a -> AugmentedStaHandler 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.8.0.0
augmentHandlerDyn :: forall s o a. Maybe (Input o) -> DynHandler s o a -> AugmentedStaHandler s o a Source #
Converts a DynHandler
into a
AugmentedStaHandler
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.7.0.0
:: Input o | The offset captured by the creation of the handler. |
-> StaHandler 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. |
-> StaHandler s o a | The handler to be executed when offsets are known not to match. |
-> AugmentedStaHandler 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
AugmentedStaHandler
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.7.0.0
AugmentedStaHandler
Interpreters
The following functions interpret or extract information from StaHandler
.
staHandlerEval :: (DynOps o, ?flags :: Flags) => AugmentedStaHandler s o a -> Input o -> Code (ST s (Maybe a)) Source #
Unlike staHandler#
, which returns a handler that accepts
, this
function accepts a full Input
oOffset
,
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
augmentHandlerFull
) - If the offsets are not equal, invoke the sub-handler, skipping the if check (see
augmentHandlerFull
)
- If the offsets are equal, use the code to be executed on matching offset (See
- 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.7.0.0
staHandlerCharacteristicSta :: AugmentedStaHandler s o a -> InputCharacteristic -> StaHandler# s o a Source #
Selects the correct case out of a AugmentedStaHandler
depending on what the InputCharacteristic
that
governs the use of the handler is. This means that it can select any of the three cases. Extracts the
static handler out of the result.
Since: 1.7.0.0
staHandlerCharacteristicDyn :: AugmentedStaHandler s o a -> (StaHandler# s o a -> DynHandler s o a) -> InputCharacteristic -> DynHandler s o a Source #
Selects the correct case out of a AugmentedStaHandler
depending on what the InputCharacteristic
that
governs the use of the handler is. This means that it can select any of the three cases. Extracts a
dynamic result out of the static handler given a conversion function.
Since: 1.7.0.0
Return Continuations
type StaCont# s o a x = Code x -> Input# 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.8.0.0
Compared with StaCont#
, this type also bundles the static continuation
with its dynamic origin, if available.
Since: 1.4.0.0
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 :: forall o s a x. DynCont s o a x -> StaCont s o a x Source #
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
forall rs. QSubroutine !(StaFunc rs s o a x) !(Regs rs) |
data StaSubroutine s o a x Source #
Packages a StaSubroutine#
along with statically determined metadata that describes it derived from
static analysis.
Since: 1.5.0.0
type StaSubroutine# s o a x = DynCont s o a x -> DynHandler s o a -> Input# o -> 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.8.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
Subroutine Builders
qSubroutine :: forall s o a x rs. DynFunc rs s o a x -> Regs rs -> Metadata -> 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.5.0.0
mkStaSubroutine :: StaSubroutine# s o a x -> StaSubroutine s o a x Source #
Converts a StaSubroutine#
into a StaSubroutine
by providing the empty meta.
Since: 1.5.0.0
mkStaSubroutineMeta :: Metadata -> StaSubroutine# s o a x -> StaSubroutine s o a x Source #
Converts a StaSubroutine#
into a StaSubroutine
by providing its metadata.
Since: 1.5.0.0
Subroutine Extractors
staSubroutine# :: StaSubroutine s o a x -> StaSubroutine# s o a x Source #
Extracts the underlying subroutine.
meta :: StaSubroutine s o a x -> Metadata Source #
Extracts the metadata from a subroutine.