ddc-core-simpl-0.4.1.3: Disciplined Disciple Compiler code transformations.

Safe HaskellSafe-Inferred

DDC.Core.Transform.Boxing

Description

Manage representation of numeric values in a module.

We use three seprate versions of each numeric type. Nat# Numeric index type. B Boxed representation type. U Unboxed representation type.

A numeric index type is the type of pure values like 23#, where pure value means the mathematical value, free from any considerations about how that might be represented at runtime in the physical machine.

The Boxed and Unboxed representation types commit to a specific runtime representation, and have implications for runtime performance and space usage of the compiled program.

The boxing transform takes an input program using just pure values and numeric index types, and refines it to a program that commits to particular representations of those values. In particular, we commit to a particular representation for function arguments and results, which makes the program adhere to a function calling convention that follow-on transformations to lower level languages (like Core Salt) can deal with.

This Boxing transform should do just enough to make the code well-formed with respect to runtime representation. Demand-driven optimisations like local unboxing should be done in follow-on transformations.

We make the following representation commitments, so that the default representation is boxed.

Literal values are wrapped into their boxed representation: 23# => convert Nat] 23#

Use unboxed versions of primitive operators: add] x y => convert Nat Nat#] (add Nat [U] [B] x) (convert Nat Nat#] y))

Case scrutinees are unwrapped when matching against literal patterns: case x of { 0# -> ... } => case convert [B] [Nat -> ... }

After performing this transformation the program is said to use representational types, or be in representational form.

Note: Boxing and Partial Application
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Unlike in Haskell, we do not allow explictly unboxed types in the source program because we don't want to deal with partial applications of functions to unboxed values. With our current setup we always have a version of each function that accepts boxed values, so we never need to do generic application involving unboxed values. Fast-path function specialisations that take unboxed parameters should be created separately, and not replace the existing slow-path, fully boxed version. Taking this approach is possible in a strict language because the boxed and unboxed values have the same semantic meaning. Boxing of values does not imply lifting of the associated semantic domain.

Synopsis

Documentation

data Rep Source

Representation of the values of some type.

Constructors

RepNone

Values of this type cannot be directly represented in the target language. We need to use a boxed or unboxed representation instead.

RepBoxed

Type is represented in boxed form, and thus can instantiate polymorphic types.

RepUnboxed

Type is represented in unboxed form, and thus cannot instantiate polymorphic types.

Instances

Eq Rep 
Ord Rep 
Show Rep 

data Config a n Source

Constructors

Config 

Fields

configIsValueIndexType :: Type n -> Bool

Values of this type needs boxing to make the program representational. This will only be passed types of kind Data.

configIsBoxedType :: Type n -> Bool

Check if this is a boxed representation type.

configIsUnboxedType :: Type n -> Bool

Check if this is an unboxed representation type.

configBoxedOfIndexType :: Type n -> Maybe (Type n)

Get the boxed version of some data type, if any. This will only be passed types where typeNeedsBoxing returns True.

configUnboxedOfIndexType :: Type n -> Maybe (Type n)

Get the unboxed version of some data type, if any. This will only be passed types where typeNeedsBoxing returns True.

configIndexTypeOfBoxed :: Type n -> Maybe (Type n)

Take the index type from a boxed type, if it is one.

configIndexTypeOfUnboxed :: Type n -> Maybe (Type n)

Take the index type from an unboxed type, if it is one.

configValueTypeOfLitName :: n -> Maybe (Type n)

Take the type of a literal name, if there is one.

configValueTypeOfPrimOpName :: n -> Maybe (Type n)

Take the type of a primitive operator name, if it is one. The primops can be polytypic, but must have prenex rank-1 types.

configValueTypeOfForeignName :: n -> Maybe (Type n)

Take the type of a foreign function name, if it is one. The function can be polymorphic, but must have a prenex rank-1 type.

configNameIsUnboxedOp :: n -> Bool

Check if the primop with this name works on unboxed values directly. Operators where this function returns False are assumed to take boxed values for every argument.

configBoxedOfValue :: a -> Exp a n -> Type n -> Maybe (Exp a n)

Wrap a value of the given index type. This will only be passed types where typeNeedsBoxing returns True.

configValueOfBoxed :: a -> Exp a n -> Type n -> Maybe (Exp a n)

Unwrap a boxed value of the given index type. This will only be passed types where typeNeedsBoxing returns True.

configBoxedOfUnboxed :: a -> Exp a n -> Type n -> Maybe (Exp a n)

Box an unboxed value of the given index type. This will only be passed types where typeNeedsBoxing returns True.

configUnboxedOfBoxed :: a -> Exp a n -> Type n -> Maybe (Exp a n)

Unbox a boxed value of the given index type. This will only be passed types where typeNeedsBoxing returns True.

class Boxing c whereSource

Methods

boxing :: (Show n, Show a, Ord n) => Config a n -> c a n -> c a nSource

Rewrite a module to use explitit boxed and unboxed types.