ddc-source-tetra-0.4.1.1: Disciplined Disciple Compiler source language.

Safe HaskellNone

DDC.Source.Tetra.Prim

Synopsis

Documentation

data Name Source

Names of things used in Disciple Source Tetra.

Constructors

NameVar String

A user defined variable.

NameCon String

A user defined constructor.

NameTyConTetra TyConTetra

Baked in data type constructors.

NameOpStore OpStore

Baked in store operators.

NamePrimTyCon PrimTyCon

Primitive type cosntructors.

NamePrimArith PrimArith

Primitive arithmetic, logic and comparison.

NameLitBool Bool

A boolean literal.

NameLitNat Integer

A natural literal.

NameLitInt Integer

An integer literal.

NameLitWord Integer Int

A word literal.

NameHole

A hole used during type inference.

data TyConTetra Source

Baked-in type constructors.

Constructors

TyConTetraRef

Ref#. Mutable reference.

TyConTetraTuple Int

TupleN#. Tuples.

kindTyConTetra :: TyConTetra -> Type NameSource

Take the kind of a baked-in data constructor.

data OpStore

Mutable References.

Constructors

OpStoreAllocRef

Allocate a reference.

OpStoreReadRef

Read a reference.

OpStoreWriteRef

Write to a reference.

typeOpStore :: OpStore -> Maybe (Type Name)Source

Take the type of a primitive arithmetic operator.

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.

kindPrimTyCon :: PrimTyCon -> Kind NameSource

Yield the kind of a type constructor.

tBool :: Type NameSource

Primitive Bool type.

tNat :: Type NameSource

Primitive Nat type.

tInt :: Type NameSource

Primitive Int type.

tWord :: Int -> Type NameSource

Primitive WordN type of the given width.

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

typePrimArith :: PrimArith -> Type NameSource

Take the type of a primitive arithmetic operator.

readName :: String -> Maybe NameSource

Read the name of a variable, constructor or literal.