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

Safe HaskellNone
LanguageHaskell98

DDC.Source.Tetra.Prim

Contents

Description

Definitions of Source Tetra primitive names and operators.

Synopsis

Names

data Name Source

Names of things used in Disciple Source Tetra.

Constructors

NameVar !String

A user defined variable.

NameCon !String

A user defined constructor.

NamePrim !PrimName

Primitive names.

NameHole

A hole used during type inference.

Primitive Names

pattern NameVal :: PrimVal -> Name Source

readName :: String -> Maybe Name Source

Read the name of a variable, constructor or literal.

Primitive Types

data PrimType Source

Primitive types.

Constructors

PrimTypeTyCon !PrimTyCon

Primitive machine type constructors.

PrimTypeTyConTetra !PrimTyConTetra

Primtiive type constructors specific to the Tetra fragment.

Primitive machine type constructors.

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 necessearily enough precision to count every byte of memory.

PrimTyConInt

Int# signed integers. Enough precision to count every object in the heap, but NOT necessearily 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.

PrimTyConSize

Size# unsigned sizes. Enough precision to count every addressable bytes of memory.

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# like Addr#, but with a region and element type annotation. In particular, a value of a type like (Ptr) must be at least 4-byte aligned and point to memory owned by the current process.

PrimTyConTextLit

TextLit# type of a text literal, which is represented as a pointer to the literal data in static memory.

PrimTyConTag

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

kindPrimTyCon :: PrimTyCon -> Kind Name Source

Yield the kind of a type constructor.

tBool :: Type Name Source

Primitive Bool type.

tNat :: Type Name Source

Primitive Nat type.

tInt :: Type Name Source

Primitive Int type.

tSize :: Type Name Source

Primitive Size type.

tWord :: Int -> Type Name Source

Primitive WordN type of the given width.

tFloat :: Int -> Type Name Source

Primitive FloatN type of the given width.

tTextLit :: Type Name Source

Primitive TextLit type.

Primitive tetra type constructors.

data PrimTyConTetra Source

Primitive type constructors specific to the Tetra language fragment.

Constructors

PrimTyConTetraTuple !Int

TupleN#. Tuples.

PrimTyConTetraVector

Vector#. Vectors.

PrimTyConTetraF

F#. Reified function values.

PrimTyConTetraC

C#. Reified function closures.

PrimTyConTetraU

U#. Explicitly unboxed values.

kindPrimTyConTetra :: PrimTyConTetra -> Type Name Source

Take the kind of a baked-in data constructor.

Primitive values

data PrimVal Source

Primitive values.

Constructors

PrimValLit !PrimLit

Primitive literals.

PrimValArith !PrimArith

Primitive arithmetic operators.

PrimValError !OpError

Primitive error handling.

PrimValVector !OpVector

Primitive vector operators.

PrimValFun !OpFun

Primitive function operators.

pattern NameLit :: PrimLit -> Name Source

pattern NameFun :: OpFun -> Name Source

Primitive arithmetic operators.

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 Name Source

Take the type of a primitive arithmetic operator.

Primitive vector operators.

data OpVector :: *

Vector operators.

Constructors

OpVectorAlloc

Allocate a new vector of a given length number of elements.

OpVectorLength

Get the length of a vector, in elements.

OpVectorRead

Read a value from a vector.

OpVectorWrite

Write a value to a vector.

typeOpVector :: OpVector -> Type Name Source

Take the type of a primitive vector operator.

Primitive function operators.

data OpFun :: *

Operators for building function values and closures. The implicit versions work on functions of type (a -> b), while the explicit versions use expliciy closure types like C# (a -> b).

Constructors

OpFunCurry Int

Partially apply a supecombinator to some arguments, producing an implicitly typed closure.

OpFunApply Int

Apply an implicitly typed closure to some more arguments.

OpFunCReify

Reify a function into an explicit functional value.

OpFunCCurry Int

Apply an explicit functional value to some arguments, producing an explicitly typed closure.

OpFunCExtend Int

Extend an explicitly typed closure with more arguments, producing a new closure.

OpFunCApply Int

Apply an explicitly typed closure to some arguments, possibly evaluating the contained function.

Instances

typeOpFun :: OpFun -> Type Name Source

Take the type of a primitive function operator.

Primitive error handling

data OpError :: *

Operators for runtime error reporting.

Constructors

OpErrorDefault

Raise an error due to inexhaustive case expressions.

typeOpError :: OpError -> Type Name Source

Take the type of a primitive error function.

Primitive literals

data PrimLit Source

Constructors

PrimLitBool !Bool

A boolean literal.

PrimLitNat !Integer

A natural literal, with enough precision to count every heap object.

PrimLitInt !Integer

An integer literal, with enough precision to count every heap object.

PrimLitSize !Integer

An unsigned size literal, with enough precision to count every addressable byte of memory.

PrimLitWord !Integer !Int

A word literal, with the given number of bits precison.

PrimLitFloat !Double !Int

A floating point literal, with the given number of bits precision.

PrimLitTextLit !Text

Text literals (UTF-8 encoded)

pattern NameLitBool :: Bool -> Name Source

pattern NameLitWord :: Integer -> Int -> Name Source

pattern NameLitFloat :: Double -> Int -> Name Source