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

Safe HaskellNone
LanguageHaskell98

DDC.Core.Tetra

Contents

Synopsis

Language profile

profile :: Profile Name Source #

Language profile for Disciple Core Tetra.

Program Lexing

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

Lex a string to tokens, using primitive names.

The first argument gives the starting source line number.

lexExpString :: String -> Int -> String -> [Located (Token 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

saltOfTetraModule Source #

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

Tetra 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, have all supers in prenex form, with type parameters before value parameters. 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.

NameExt !Name !String

An extended name.

NameTyConTetra !TyConTetra

Baked-in type constructors.

NameDaConTetra !DaConTetra

Baked-in data constructors.

NameOpError !OpError !Bool

Baked-in runtime error reporting. The flag indicates whether this is the boxed (False) or unboxed (True) version.

NameOpFun !OpFun

Baked-in function operators.

NameOpVector !OpVector !Bool

Baked-in vector operators. The flag indicates whether this is the boxed (False) or unboxed (True) version.

NamePrimTyCon !PrimTyCon

A primitive type constructor.

NamePrimArith !PrimArith !Bool

Primitive arithmetic, logic, comparison and bit-wise operators. The flag indicates whether this is the boxed (False) or unboxed (True) version.

NamePrimCast !PrimCast !Bool

Primitive numeric casting operators. The flat indicates whether this is the boxed (False) or unboxed (True) version.

NameLitBool !Bool

A boolean literal.

NameLitNat !Integer

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

NameLitInt !Integer

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

NameLitSize !Integer

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

NameLitWord !Integer !Int

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

NameLitFloat !Double !Int

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

NameLitChar !Char

A character literal, These are special syntax for a Word32 expressing a Unicode codepoint.

NameLitTextLit !Text

A text literal (UTF-8 encoded) Note that Text and 'TextLit#' are different types. The later is the primitive literal.

NameLitUnboxed !Name

Wrapper to indicate an explicitly unboxed literal.

NameHole

Hole used during type inference.

Instances

Eq Name Source # 

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Ord Name Source # 

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Show Name Source # 

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

data TyConTetra Source #

Baked-in type constructors.

Constructors

TyConTetraTuple Int

TupleN#. Tuples.

TyConTetraVector

Vector#. Vectors of unboxed values.

TyConTetraU

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

TyConTetraF

F# Reified function value.

TyConTetraC

C# Reified function closure.

data OpFun Source #

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

Eq OpFun Source # 

Methods

(==) :: OpFun -> OpFun -> Bool #

(/=) :: OpFun -> OpFun -> Bool #

Ord OpFun Source # 

Methods

compare :: OpFun -> OpFun -> Ordering #

(<) :: OpFun -> OpFun -> Bool #

(<=) :: OpFun -> OpFun -> Bool #

(>) :: OpFun -> OpFun -> Bool #

(>=) :: OpFun -> OpFun -> Bool #

max :: OpFun -> OpFun -> OpFun #

min :: OpFun -> OpFun -> OpFun #

Show OpFun Source # 

Methods

showsPrec :: Int -> OpFun -> ShowS #

show :: OpFun -> String #

showList :: [OpFun] -> ShowS #

data OpVector Source #

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.

data OpError Source #

Operators for runtime error reporting.

Constructors

OpErrorDefault

Raise an error due to inexhaustive case expressions.

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.

pprPrimTyConStem :: PrimTyCon -> Doc #

Pretty print a primitive type constructor, without the # suffix.

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

data PrimCast :: * #

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

PrimCastConvert

Convert a value to a new representation with the same precision.

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

Read the name of a variable, constructor or literal.

readTyConTetra :: String -> Maybe TyConTetra Source #

Read the name of a baked-in type constructor.

readDaConTetra :: String -> Maybe DaConTetra Source #

Read the name of a baked-in data constructor.

readOpFun :: String -> Maybe OpFun Source #

Read a primitive function operator.

readOpVectorFlag :: String -> Maybe (OpVector, Bool) Source #

Read a primitive vector operator, along with the flag that indicates whether this is the boxed or unboxed version.

readOpErrorFlag :: String -> Maybe (OpError, Bool) Source #

Read a primitive error 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.

readPrimTyConStem :: String -> Maybe PrimTyCon #

Read a primitive type constructor, without the # suffix.

readPrimArithFlag :: String -> Maybe (PrimArith, Bool) Source #

Read a primitive operator.

readPrimCastFlag :: String -> Maybe (PrimCast, Bool) Source #

Read a primitive cast operator.

Name Generation

freshT :: Env Name -> Bind Name -> State Int Name Source #

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

freshX :: Env Name -> Bind Name -> State Int Name Source #

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) Source # 

Methods

showsPrec :: Int -> Error a -> ShowS #

show :: Error a -> String #

showList :: [Error a] -> ShowS #

Pretty (Error a) Source # 

Associated Types

data PrettyMode (Error a) :: * #

Methods

pprDefaultMode :: PrettyMode (Error a) #

ppr :: Error a -> Doc #

pprPrec :: Int -> Error a -> Doc #

pprModePrec :: PrettyMode (Error a) -> Int -> Error a -> Doc #