ddc-core-tetra-0.4.1.1: Disciplined Disciple Compiler intermediate language.

Safe HaskellNone

DDC.Core.Tetra

Contents

Synopsis

Language profile

profile :: Profile NameSource

Language profile for Disciple Core Tetra.

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.

Checking

checkModule :: Module a Name -> Maybe (Error a)Source

Perform Core Tetra specific checks on a module.

Conversion

saltOfTetraModuleSource

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 Core Tetra module to Core Salt.

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, have saturated function applications, not have over-applied function applications. If not then Error.

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

Names

data Name Source

Names of things used in Disciple Core Tetra.

Constructors

NameVar String

User defined variables.

NameCon String

A user defined constructor.

NameTyConTetra TyConTetra

Baked-in type constructors.

NameDaConTetra DaConTetra

Baked-in data constructors.

NameOpStore OpStore

Baked-in operators.

NamePrimTyCon PrimTyCon

A primitive type constructor.

NamePrimArith PrimArith

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

NamePrimCast PrimCast

Primitive numeric casting operators.

NameLitBool Bool

A boolean literal.

NameLitNat Integer

A natural literal.

NameLitInt Integer

An integer literal.

NameLitWord Integer Int

A word literal.

NameHole

Hole used during type inference.

data TyConTetra Source

Baked-in type constructors.

Constructors

TyConTetraRef

Ref#. Mutable reference.

TyConTetraTuple Int

TupleN#. Tuples.

TyConTetraB

B#. Boxing type constructor. Used to represent boxed numeric values.

TyConTetraU

U#. Unboxed type constructor. Used to represent unboxed numeric values.

data DaConTetra Source

Data Constructors.

Constructors

DaConTetraTuple Int

TN#. Tuple data constructors.

data OpStore Source

Mutable References.

Constructors

OpStoreAllocRef

Allocate a reference.

OpStoreReadRef

Read a reference.

OpStoreWriteRef

Write to a reference.

data PrimTyCon

Primitive type constructors.

Constructors

PrimTyConVoid

Void# the Void type has no values.

PrimTyConBool

Bool# unboxed booleans.

PrimTyConNat

Nat# natural numbers. Enough precision to count every object in the heap, but NOT enough precision to count every byte of memory.

PrimTyConInt

Int# signed integers. Enough precision to count every object in the heap, but NOT enough precision to count every byte of memory. If N is the total number of objects that can exist in the heap, then the range of Int# is at least (-N .. +N) inclusive.

PrimTyConWord Int

WordN# machine words of the given width.

PrimTyConFloat Int

FloatN# floating point numbers of the given width.

PrimTyConVec Int

VecN# a packed vector of N values. This is intended to have kind (Data -> Data), so we use concrete vector types like Vec4.

PrimTyConAddr

Addr# a relative or absolute machine address. Enough precision to count every byte of memory. Unlike pointers below, an absolute Addr# need not refer to memory owned by the current process.

PrimTyConPtr

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

PrimTyConTag

Tag# data constructor tags. Enough precision to count every possible alternative of an enumerated type.

PrimTyConString

String# of UTF8 characters.

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

data PrimArith

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

PrimArithMod

Modulus

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

Name Parsing

readName :: String -> Maybe NameSource

Read the name of a variable, constructor or literal.

readTyConTetra :: String -> Maybe TyConTetraSource

Read the name of a baked-in type constructor.

readDaConTetra :: String -> Maybe DaConTetraSource

Read the name of a baked-in data constructor.

readOpStore :: String -> Maybe OpStoreSource

Read a primitive store operator.

readPrimTyCon :: String -> Maybe PrimTyCon

Read a primitive type constructor.

Words are limited to 8, 16, 32, or 64 bits.

Floats are limited to 32 or 64 bits.

readPrimArith :: String -> Maybe PrimArith

Read a primitive operator.

Name Generation

freshT :: Env Name -> Bind Name -> State Int NameSource

Create a new type variable name that is not in the given environment.

freshX :: Env Name -> Bind Name -> State Int NameSource

Create a new value variable name that is not in the given environment.

Errors

data Error a Source

Fragment specific errors.

Constructors

ErrorMainMissing

Main module does not export a main function.

ErrorMainInvalidMode

Main module exports a main function in an invalid way.

ErrorMainInvalidType (Type Name)

Main module exports a main function with an invalid type.

Instances

Show (Error a) 
Pretty (Error a)