ajhc-0.8.0.7: Haskell compiler that produce binary through C language

Safe HaskellNone

DataConstructors

Synopsis

Documentation

boxPrimitive :: Monad m => DataTable -> E -> E -> m (E, (ExtType, E))Source

constructionExpressionSource

Arguments

:: DataTable

table of data constructors

-> Name

name of said constructor

-> E

type of eventual constructor

-> E

saturated lambda calculus term

data Constructor Source

Record describing a data type. * is also a data type containing the type constructors, which are unlifted, yet boxed.

deconstructionExpressionSource

Arguments

:: UniqueProducer m 
=> DataTable

table of data constructors

-> Name

name of said constructor

-> E

type of pattern

-> [TVr]

variables to be bound

-> E

body of alt

-> m (Alt E)

resulting alternative

extractIO :: Monad m => E -> m ESource

extractIO' :: E -> ([E], Bool, E)Source

getProduct :: Monad m => DataTable -> E -> m ConstructorSource

return the single constructor of product types

primitiveAliases :: Map Name NameSource

list of declared data types that map directly to primitive real types

slotTypesSource

Arguments

:: DataTable

table of data constructors

-> Name

name of constructor

-> E

type of value

-> [E]

type of each slot

slotTypesHsSource

Arguments

:: DataTable

table of data constructors

-> Name

name of constructor

-> E

type of value

-> [E]

type of each slot

tAbsurd :: E -> ESource

conjured data types, these data types are created as needed and can be of any type, their actual type is encoded in their names.

Absurd - this is a type that it used to default otherwise unconstrained types, it is not special in any particular way but is just an arbitrary type to give to things.

Box - this type can be used to represent any boxed values. It is considered equivalent to all boxed values so is not a very precise type. It is used in the final stages of compilation before core mangling so that optimizations that were previously blocked by type variables can be carried out.

typesCompatable :: forall m. Monad m => E -> E -> m ()Source

updateLit :: DataTable -> Lit e t -> Lit e tSource