Copyright | (c) 2011 National Institute of Aerospace / Galois Inc. |
---|---|
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Copilot.Core.Type
Contents
Description
All expressions and streams in Core are accompanied by a representation of the types of the underlying expressions used or carried by the streams. This information is needed by the compiler to generate code, since it must initialize variables and equivalent representations for those types in the target languages.
Synopsis
- data Type :: * -> * where
- Bool :: Type Bool
- Int8 :: Type Int8
- Int16 :: Type Int16
- Int32 :: Type Int32
- Int64 :: Type Int64
- Word8 :: Type Word8
- Word16 :: Type Word16
- Word32 :: Type Word32
- Word64 :: Type Word64
- Float :: Type Float
- Double :: Type Double
- Array :: forall n t. (KnownNat n, Typed t) => Type t -> Type (Array n t)
- Struct :: (Typed a, Struct a) => a -> Type a
- class (Show a, Typeable a) => Typed a where
- typeOf :: Type a
- simpleType :: Type a -> SimpleType
- typeOfDefault :: forall a. (Typed a, Struct a, Generic a, GTypedStruct (Rep a)) => Type a
- data UType = forall a.Typeable a => UType {}
- data SimpleType where
- SBool :: SimpleType
- SInt8 :: SimpleType
- SInt16 :: SimpleType
- SInt32 :: SimpleType
- SInt64 :: SimpleType
- SWord8 :: SimpleType
- SWord16 :: SimpleType
- SWord32 :: SimpleType
- SWord64 :: SimpleType
- SFloat :: SimpleType
- SDouble :: SimpleType
- SArray :: Type t -> SimpleType
- SStruct :: SimpleType
- typeSize :: forall n t. KnownNat n => Type (Array n t) -> Int
- typeLength :: forall n t. KnownNat n => Type (Array n t) -> Int
- data Value a = forall s t.(Typeable t, KnownSymbol s, Show t) => Value (Type t) (Field s t)
- toValues :: Struct a => a -> [Value a]
- toValuesDefault :: (Generic a, GStruct (Rep a)) => a -> [Value a]
- data Field (s :: Symbol) t = Field t
- typeName :: Struct a => a -> String
- typeNameDefault :: (Generic a, GDatatype (Rep a)) => a -> String
- class Struct a
- fieldName :: forall s t. KnownSymbol s => Field s t -> String
- accessorName :: forall a s t. (Struct a, KnownSymbol s) => (a -> Field s t) -> String
- updateField :: Struct a => a -> Value t -> a
- updateFieldDefault :: (Generic a, GStruct (Rep a)) => a -> Value t -> a
Documentation
data Type :: * -> * where Source #
A Type representing the types of expressions or values handled by Copilot Core.
Note that both arrays and structs use dependently typed features. In the former, the length of the array is part of the type. In the latter, the names of the fields are part of the type.
Constructors
Bool :: Type Bool | |
Int8 :: Type Int8 | |
Int16 :: Type Int16 | |
Int32 :: Type Int32 | |
Int64 :: Type Int64 | |
Word8 :: Type Word8 | |
Word16 :: Type Word16 | |
Word32 :: Type Word32 | |
Word64 :: Type Word64 | |
Float :: Type Float | |
Double :: Type Double | |
Array :: forall n t. (KnownNat n, Typed t) => Type t -> Type (Array n t) | |
Struct :: (Typed a, Struct a) => a -> Type a |
Instances
class (Show a, Typeable a) => Typed a where Source #
A typed expression, from which we can obtain the two type representations
used by Copilot: Type
and SimpleType
.
Minimal complete definition
Instances
Typed Int16 Source # | |
Defined in Copilot.Core.Type | |
Typed Int32 Source # | |
Defined in Copilot.Core.Type | |
Typed Int64 Source # | |
Defined in Copilot.Core.Type | |
Typed Int8 Source # | |
Defined in Copilot.Core.Type | |
Typed Word16 Source # | |
Defined in Copilot.Core.Type | |
Typed Word32 Source # | |
Defined in Copilot.Core.Type | |
Typed Word64 Source # | |
Defined in Copilot.Core.Type | |
Typed Word8 Source # | |
Defined in Copilot.Core.Type | |
Typed Bool Source # | |
Defined in Copilot.Core.Type | |
Typed Double Source # | |
Defined in Copilot.Core.Type | |
Typed Float Source # | |
Defined in Copilot.Core.Type | |
(Typeable t, Typed t, KnownNat n) => Typed (Array n t) Source # | |
Defined in Copilot.Core.Type |
data SimpleType where Source #
A simple, monomorphic representation of types that facilitates putting variables in heterogeneous lists and environments in spite of their types being different.
Constructors
SBool :: SimpleType | |
SInt8 :: SimpleType | |
SInt16 :: SimpleType | |
SInt32 :: SimpleType | |
SInt64 :: SimpleType | |
SWord8 :: SimpleType | |
SWord16 :: SimpleType | |
SWord32 :: SimpleType | |
SWord64 :: SimpleType | |
SFloat :: SimpleType | |
SDouble :: SimpleType | |
SArray :: Type t -> SimpleType | |
SStruct :: SimpleType |
Instances
Eq SimpleType Source # | Type equality, used to help type inference. |
Defined in Copilot.Core.Type |
typeSize :: forall n t. KnownNat n => Type (Array n t) -> Int Source #
Return the total (nested) size of an array from its type
typeLength :: forall n t. KnownNat n => Type (Array n t) -> Int Source #
Return the length of an array from its type
The field of a struct, together with a representation of its type.
toValues :: Struct a => a -> [Value a] Source #
Transforms all the struct's fields into a list of values.
data Field (s :: Symbol) t Source #
A field in a struct. The name of the field is a literal at the type level.
Constructors
Field t |
typeNameDefault :: (Generic a, GDatatype (Rep a)) => a -> String Source #
A default implementation of typeName
that leverages Generic
. In order
to use this, make sure you derive a Generic
instance for your data type and
then define
in its typeName
= typeNameDefault
Struct
instance.
This generates a struct name that consists of the name of the original Haskell data type, but converted to snake_case.
The value of that is a product or struct, defined as a constructor with several fields.
accessorName :: forall a s t. (Struct a, KnownSymbol s) => (a -> Field s t) -> String Source #
Extract the name of an accessor (a function that returns a field of a struct).
updateField :: Struct a => a -> Value t -> a Source #
Update the value of a struct field. This is only used by the Copilot interpreter.
If you do not plan to use the interpreter, you can omit an implementation
of this method. If you do so, it is recommended that you derive a Generic
instance for the struct data type. This is because in a future release, the
default implementation of updateField
(which will be picked if there is
not a manually written implementation) will be changed to require a
Generic
instance.
In order to implement updateField
, pick one of the following approaches:
- Derive a
Generic
instance for the struct data type and then define
in theupdateField
=updateFieldDefault
Struct
instance. - Manually implement
updateField
by doing the following for eachField
in a struct:
- Check that the name of the
Field
matches the name of the suppliedValue
(usingsameSymbol
). - Check that the type of the
Field
matches theType
of the suppliedValue
(usingtestEquality
). - If both (1) and (2) succeed, update the corresponding struct field using a record update.
For a complete end-to-end example that demonstrates how to manually
implement updateField
and use it in the Copilot interpreter, see the
examples/StructsUpdateField.hs
example in the copilot
library.
updateFieldDefault :: (Generic a, GStruct (Rep a)) => a -> Value t -> a Source #
A default implementation of updateField
that leverages Generic
. In
order to use this, make sure you derive a Generic
instance for your data
type and then define
in its updateField
= updateFieldDefault
Struct
instance.