| Safe Haskell | None |
|---|
DDC.Source.Tetra.Prim
- data Name
- = NameVar String
- | NameCon String
- | NameTyConTetra TyConTetra
- | NameOpStore OpStore
- | NamePrimTyCon PrimTyCon
- | NamePrimArith PrimArith
- | NameLitBool Bool
- | NameLitNat Integer
- | NameLitInt Integer
- | NameLitWord Integer Int
- | NameHole
- data TyConTetra
- = TyConTetraRef
- | TyConTetraTuple Int
- kindTyConTetra :: TyConTetra -> Type Name
- data OpStore
- typeOpStore :: OpStore -> Maybe (Type Name)
- data PrimTyCon
- = PrimTyConVoid
- | PrimTyConBool
- | PrimTyConNat
- | PrimTyConInt
- | PrimTyConWord Int
- | PrimTyConFloat Int
- | PrimTyConVec Int
- | PrimTyConAddr
- | PrimTyConPtr
- | PrimTyConTag
- | PrimTyConString
- kindPrimTyCon :: PrimTyCon -> Kind Name
- tBool :: Type Name
- tNat :: Type Name
- tInt :: Type Name
- tWord :: Int -> Type Name
- data PrimArith
- = PrimArithNeg
- | PrimArithAdd
- | PrimArithSub
- | PrimArithMul
- | PrimArithDiv
- | PrimArithMod
- | PrimArithRem
- | PrimArithEq
- | PrimArithNeq
- | PrimArithGt
- | PrimArithGe
- | PrimArithLt
- | PrimArithLe
- | PrimArithAnd
- | PrimArithOr
- | PrimArithShl
- | PrimArithShr
- | PrimArithBAnd
- | PrimArithBOr
- | PrimArithBXOr
- typePrimArith :: PrimArith -> Type Name
- readName :: String -> Maybe Name
Documentation
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 |
|
| TyConTetraTuple Int |
|
Instances
| Eq TyConTetra | |
| Ord TyConTetra | |
| Show TyConTetra | |
| Pretty TyConTetra | |
| NFData TyConTetra |
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 |
|
| PrimTyConBool |
|
| PrimTyConNat |
|
| PrimTyConInt |
|
| PrimTyConWord Int |
|
| PrimTyConFloat Int |
|
| PrimTyConVec Int |
|
| PrimTyConAddr |
|
| PrimTyConPtr |
|
| PrimTyConTag |
|
| PrimTyConString |
These are primitive until we can define our own unboxed types. |
kindPrimTyCon :: PrimTyCon -> Kind NameSource
Yield the kind of a type constructor.
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.