Safe Haskell | None |
---|
DDC.Core.Tetra.Prim
Contents
- data Name
- = NameVar String
- | NameCon String
- | NameTyConTetra TyConTetra
- | NameDaConTetra DaConTetra
- | NameOpStore OpStore
- | NamePrimTyCon PrimTyCon
- | NamePrimArith PrimArith
- | NamePrimCast PrimCast
- | NameLitBool Bool
- | NameLitNat Integer
- | NameLitInt Integer
- | NameLitWord Integer Int
- | NameHole
- isNameHole :: Name -> Bool
- isNameLit :: Name -> Bool
- readName :: String -> Maybe Name
- takeTypeOfLitName :: Name -> Maybe (Type Name)
- takeTypeOfPrimOpName :: Name -> Maybe (Type Name)
- data TyConTetra
- = TyConTetraRef
- | TyConTetraTuple Int
- | TyConTetraB
- | TyConTetraU
- readTyConTetra :: String -> Maybe TyConTetra
- kindTyConTetra :: TyConTetra -> Type Name
- data DaConTetra = DaConTetraTuple Int
- readDaConTetra :: String -> Maybe DaConTetra
- typeDaConTetra :: DaConTetra -> Type Name
- data OpStore
- readOpStore :: String -> Maybe OpStore
- typeOpStore :: OpStore -> Type Name
- data PrimTyCon
- = PrimTyConVoid
- | PrimTyConBool
- | PrimTyConNat
- | PrimTyConInt
- | PrimTyConWord Int
- | PrimTyConFloat Int
- | PrimTyConVec Int
- | PrimTyConAddr
- | PrimTyConPtr
- | PrimTyConTag
- | PrimTyConString
- readPrimTyCon :: String -> Maybe PrimTyCon
- kindPrimTyCon :: PrimTyCon -> Kind Name
- data PrimArith
- = PrimArithNeg
- | PrimArithAdd
- | PrimArithSub
- | PrimArithMul
- | PrimArithDiv
- | PrimArithMod
- | PrimArithRem
- | PrimArithEq
- | PrimArithNeq
- | PrimArithGt
- | PrimArithGe
- | PrimArithLt
- | PrimArithLe
- | PrimArithAnd
- | PrimArithOr
- | PrimArithShl
- | PrimArithShr
- | PrimArithBAnd
- | PrimArithBOr
- | PrimArithBXOr
- readPrimArith :: String -> Maybe PrimArith
- typePrimArith :: PrimArith -> Type Name
- data PrimCast
- readPrimCast :: String -> Maybe PrimCast
- typePrimCast :: PrimCast -> Type Name
Names and lexing.
Names of things used in Disciple Core Tetra.
Constructors
NameVar String | User defined variables. |
NameCon String | A user defined constructor. |
NameTyConTetra TyConTetra | Baked-in type constructors. |
NameDaConTetra DaConTetra | Baked-in data constructors. |
NameOpStore OpStore | Baked-in operators. |
NamePrimTyCon PrimTyCon | A primitive type constructor. |
NamePrimArith PrimArith | Primitive arithmetic, logic, comparison and bit-wise operators. |
NamePrimCast PrimCast | Primitive numeric casting operators. |
NameLitBool Bool | A boolean literal. |
NameLitNat Integer | A natural literal. |
NameLitInt Integer | An integer literal. |
NameLitWord Integer Int | A word literal. |
NameHole | Hole used during type inference. |
isNameHole :: Name -> BoolSource
Check whether a name is NameHole
.
takeTypeOfLitName :: Name -> Maybe (Type Name)Source
Get the type associated with a literal name.
takeTypeOfPrimOpName :: Name -> Maybe (Type Name)Source
Take the type of a primitive operator.
Baked-in type constructors.
data TyConTetra Source
Baked-in type constructors.
Constructors
TyConTetraRef |
|
TyConTetraTuple Int |
|
TyConTetraB |
|
TyConTetraU |
|
Instances
Eq TyConTetra | |
Ord TyConTetra | |
Show TyConTetra | |
Pretty TyConTetra | |
NFData TyConTetra |
readTyConTetra :: String -> Maybe TyConTetraSource
Read the name of a baked-in type constructor.
kindTyConTetra :: TyConTetra -> Type NameSource
Take the kind of a baked-in type constructor.
Baked-in data constructors.
data DaConTetra Source
Data Constructors.
Constructors
DaConTetraTuple Int |
|
Instances
Eq DaConTetra | |
Ord DaConTetra | |
Show DaConTetra | |
Pretty DaConTetra | |
NFData DaConTetra |
readDaConTetra :: String -> Maybe DaConTetraSource
Read the name of a baked-in data constructor.
typeDaConTetra :: DaConTetra -> Type NameSource
Yield the type of a baked-in data constructor.
Baked-in store operators.
Mutable References.
Constructors
OpStoreAllocRef | Allocate a reference. |
OpStoreReadRef | Read a reference. |
OpStoreWriteRef | Write to a reference. |
readOpStore :: String -> Maybe OpStoreSource
Read a primitive store operator.
typeOpStore :: OpStore -> Type NameSource
Take the type of a primitive store operator.
Primitive type constructors.
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. |
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.
kindPrimTyCon :: PrimTyCon -> Kind NameSource
Yield the kind of a type constructor.
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 |
readPrimArith :: String -> Maybe PrimArith
Read a primitive operator.
typePrimArith :: PrimArith -> Type NameSource
Take the type of a primitive arithmetic operator.
Primitive numeric casts.
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. |
readPrimCast :: String -> Maybe PrimCast
typePrimCast :: PrimCast -> Type NameSource
Take the type of a primitive numeric cast operator.