ddc-core-salt-0.3.1.1: Disciplined Disciple Compiler C code generator.

Safe HaskellNone

DDC.Core.Lite

Contents

Description

Disciple Core Lite.

This is a desugared version of Disciple Core that has all the polymorphism of System-F2 along with algebraic data types. It does not yet support user-defined data types, but has Units, Ints, Pairs and Lists baked in.

Lite exposes arithmetic primops like add, but no store or control primops. Code written in Lite cannot corrupt the heap, assuming the implementation of the Salt primitives it uses (and compiler) is correct.

Synopsis

Language profile

profile :: Profile NameSource

Profile for Disciple Core Lite.

Conversion

saltOfLiteModuleSource

Arguments

:: Show a 
=> Platform

Platform specification.

-> Config

Runtime configuration.

-> DataDefs Name

Data type definitions.

-> KindEnv Name

Kind environment.

-> TypeEnv Name

Type environment.

-> Module (AnTEC a Name) Name

Lite module to convert.

-> Either (Error a) (Module a Name)

Salt module.

Convert a Disciple Core Lite module to Disciple Core Salt.

Case expressions on algebraic data values are converted into ones that just check the tag, while data constructors are unfolded into explicit allocation and field initialization primops.

The input module needs to be: well typed, fully named with no deBruijn indices, have all functions defined at top-level, have type annotations on every bound variable and constructor, be a-normalised. If not then Error.

The output code contains: debruijn indices. These then need to be eliminated before it will pass the Salt fragment checks.

data Error a Source

Things that can go wrong during the conversion.

Constructors

ErrorMainHasNoMain

The Main module has no main function.

ErrorMalformed String

Found unexpected AST node, like LWithRegion.

ErrorMistyped (Exp (AnTEC a Name) Name)

The program is definately not well typed.

ErrorNotNormalized String

The program wasn't in a-normal form.

ErrorBotAnnot

The program has bottom (missing) type annotations.

ErrorUnexpectedSum

Found an unexpected type sum.

ErrorInvalidBinder Name

An invalid name used in a binding position

ErrorInvalidBound (Bound Name)

An invalid name used in a bound position

ErrorInvalidAlt

An invalid name used for the constructor of an alternative.

Instances

Show a => Pretty (Error a) 

Names

data Name Source

Names of things used in Disciple Core Lite.

Constructors

NameVar String

User defined variables.

NameCon String

A user defined constructor.

NameEffectTyCon EffectTyCon

Baked in effect type constructors.

NameDataTyCon DataTyCon

Baked in data type constructors.

NamePrimDaCon PrimDaCon

A primitive data constructor.

NamePrimTyCon PrimTyCon

A primitive type constructor.

NamePrimArith PrimArith

Primitive arithmetic, logic, comparison and bit-wise operators.

NamePrimCast PrimCast

Primitive casting between numeric types.

NameLitBool Bool

An unboxed boolean literal

NameLitNat Integer

An unboxed natural literal.

NameLitInt Integer

An unboxed integer literal.

NameLitWord Integer Int

An unboxed word literal

data DataTyCon Source

Baked-in data type constructors.

Constructors

DataTyConUnit

Unit type constructor.

DataTyConBool

Bool type constructor.

DataTyConNat

Nat type constructor.

DataTyConInt

Int type constructor.

DataTyConPair

Pair type constructor.

DataTyConList

List type constructor.

data PrimTyCon Source

Primitive type constructors.

Constructors

PrimTyConVoid

Void# the Void type has no values.

PrimTyConBool

Bool# unboxed booleans.

PrimTyConNat

Nat# natural numbers. Big enough to count every addressable byte in the store.

PrimTyConInt

Int# signed integers.

PrimTyConWord Int

WordN# machine words of the given width.

PrimTyConFloat Int

FloatN# floating point numbers of the given width.

PrimTyConTag

Tag# data constructor tags.

PrimTyConAddr

Addr# raw machine addresses. Unlike pointers below, a raw Addr# need not to refer to memory owned by the current process.

PrimTyConPtr

Ptr# should point to a well-formed object owned by the current process.

PrimTyConString

String# of UTF8 characters.

These are primitive until we can define our own unboxed types.

data PrimDaCon Source

Baked-in data constructors.

Constructors

PrimDaConUnit

Unit data constructor ().

PrimDaConBoolU

B# data constructor.

PrimDaConNatU

N# data constructor.

PrimDaConIntU

I# data constructor.

PrimDaConPr

Pr data construct (pairs).

PrimDaConNil

Nil data constructor (lists).

PrimDaConCons

Cons data constructor (lists).

data PrimArith Source

Primitive arithmetic, logic, and comparison opretors. We expect the backend/machine to be able to implement these directly.

For the Shift Right operator, the type that it is used at determines whether it is an arithmetic (with sign-extension) or logical (no sign-extension) shift.

Constructors

PrimArithNeg

Negation

PrimArithAdd

Addition

PrimArithSub

Subtraction

PrimArithMul

Multiplication

PrimArithDiv

Division

PrimArithRem

Remainder

PrimArithEq

Equality

PrimArithNeq

Negated Equality

PrimArithGt

Greater Than

PrimArithGe

Greater Than or Equal

PrimArithLt

Less Than

PrimArithLe

Less Than or Equal

PrimArithAnd

Boolean And

PrimArithOr

Boolean Or

PrimArithShl

Shift Left

PrimArithShr

Shift Right

PrimArithBAnd

Bit-wise And

PrimArithBOr

Bit-wise Or

PrimArithBXOr

Bit-wise eXclusive Or

data PrimCast Source

Primitive cast between two types.

The exact set of available casts is determined by the target platform. For example, you can only promote a Nat# to a Word32# on a 32-bit system. On a 64-bit system the Nat# type is 64-bits wide, so casting it to a Word32# would be a truncation.

Constructors

PrimCastPromote

Promote a value to one of similar or larger width, without loss of precision.

PrimCastTruncate

Truncate a value to a new width, possibly losing precision.

Name Parsing

readName :: String -> Maybe NameSource

Read the name of a variable, constructor or literal.

Program Lexing

lexModuleString :: String -> Int -> String -> [Token (Tok Name)]Source

Lex a string to tokens, using primitive names.

The first argument gives the starting source line number.

lexExpString :: String -> Int -> String -> [Token (Tok Name)]Source

Lex a string to tokens, using primitive names.

The first argument gives the starting source line number.