| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
DDC.Source.Tetra.Prim
Contents
Description
Definitions of Source Tetra primitive names and operators.
- data Name
- data PrimName
- pattern NameType :: PrimType -> Name
- pattern NameVal :: PrimVal -> Name
- readName :: String -> Maybe Name
- data PrimType
- pattern NameTyCon :: PrimTyCon -> Name
- pattern NameTyConTetra :: PrimTyConTetra -> Name
- data PrimTyCon :: *
- kindPrimTyCon :: PrimTyCon -> Kind Name
- tBool :: Type Name
- tNat :: Type Name
- tInt :: Type Name
- tSize :: Type Name
- tWord :: Int -> Type Name
- tFloat :: Int -> Type Name
- tTextLit :: Type Name
- data PrimTyConTetra
- pattern NameTyConTetraTuple :: Int -> Name
- pattern NameTyConTetraF :: Name
- pattern NameTyConTetraC :: Name
- pattern NameTyConTetraU :: Name
- kindPrimTyConTetra :: PrimTyConTetra -> Type Name
- data PrimVal
- pattern NameLit :: PrimLit -> Name
- pattern NameArith :: PrimArith -> Name
- pattern NameVector :: OpVector -> Name
- pattern NameFun :: OpFun -> Name
- pattern NameError :: OpError -> Name
- data PrimArith :: *
- typePrimArith :: PrimArith -> Type Name
- data OpVector :: *
- typeOpVector :: OpVector -> Type Name
- data OpFun :: *
- typeOpFun :: OpFun -> Type Name
- data OpError :: * = OpErrorDefault
- typeOpError :: OpError -> Type Name
- data PrimLit
- = PrimLitBool !Bool
- | PrimLitNat !Integer
- | PrimLitInt !Integer
- | PrimLitSize !Integer
- | PrimLitWord !Integer !Int
- | PrimLitFloat !Double !Int
- | PrimLitTextLit !Text
- pattern NameLitBool :: Bool -> Name
- pattern NameLitNat :: Integer -> Name
- pattern NameLitInt :: Integer -> Name
- pattern NameLitSize :: Integer -> Name
- pattern NameLitWord :: Integer -> Int -> Name
- pattern NameLitFloat :: Double -> Int -> Name
- pattern NameLitTextLit :: Text -> Name
Names
Names of things used in Disciple Source Tetra.
Primitive Names
Primitive names.
Constructors
| PrimNameType !PrimType | |
| PrimNameVal !PrimVal |
Primitive Types
Primitive types.
Constructors
| PrimTypeTyCon !PrimTyCon | Primitive machine type constructors. |
| PrimTypeTyConTetra !PrimTyConTetra | Primtiive type constructors specific to the Tetra fragment. |
pattern NameTyConTetra :: PrimTyConTetra -> Name Source
Primitive machine type constructors.
data PrimTyCon :: *
Primitive type constructors.
Constructors
| PrimTyConVoid |
|
| PrimTyConBool |
|
| PrimTyConNat |
|
| PrimTyConInt |
|
| PrimTyConSize |
|
| PrimTyConWord Int |
|
| PrimTyConFloat Int |
|
| PrimTyConVec Int |
|
| PrimTyConAddr |
|
| PrimTyConPtr |
|
| PrimTyConTextLit |
|
| PrimTyConTag |
|
kindPrimTyCon :: PrimTyCon -> Kind Name Source
Yield the kind of a type constructor.
Primitive tetra type constructors.
data PrimTyConTetra Source
Primitive type constructors specific to the Tetra language fragment.
Constructors
| PrimTyConTetraTuple !Int |
|
| PrimTyConTetraVector |
|
| PrimTyConTetraF |
|
| PrimTyConTetraC |
|
| PrimTyConTetraU |
|
pattern NameTyConTetraTuple :: Int -> Name Source
pattern NameTyConTetraF :: Name Source
pattern NameTyConTetraC :: Name Source
pattern NameTyConTetraU :: Name Source
kindPrimTyConTetra :: PrimTyConTetra -> Type Name Source
Take the kind of a baked-in data constructor.
Primitive values
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 NameVector :: OpVector -> 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. |
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
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 NameLitNat :: Integer -> Name Source
pattern NameLitInt :: Integer -> Name Source
pattern NameLitSize :: Integer -> Name Source
pattern NameLitWord :: Integer -> Int -> Name Source
pattern NameLitFloat :: Double -> Int -> Name Source
pattern NameLitTextLit :: Text -> Name Source