copilot-core-4.3: An intermediate representation for Copilot.
Copyright(c) 2011 National Institute of Aerospace / Galois Inc.
Safe HaskellTrustworthy
LanguageHaskell2010

Copilot.Core.Type

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

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

Instances details
TestEquality Type Source # 
Instance details

Defined in Copilot.Core.Type

Methods

testEquality :: forall (a :: k) (b :: k). Type a -> Type b -> Maybe (a :~: b) #

Show (Type a) Source # 
Instance details

Defined in Copilot.Core.Type

Methods

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

show :: Type a -> String #

showList :: [Type a] -> ShowS #

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

typeOf

Instances

Instances details
Typed Int16 Source # 
Instance details

Defined in Copilot.Core.Type

Typed Int32 Source # 
Instance details

Defined in Copilot.Core.Type

Typed Int64 Source # 
Instance details

Defined in Copilot.Core.Type

Typed Int8 Source # 
Instance details

Defined in Copilot.Core.Type

Typed Word16 Source # 
Instance details

Defined in Copilot.Core.Type

Typed Word32 Source # 
Instance details

Defined in Copilot.Core.Type

Typed Word64 Source # 
Instance details

Defined in Copilot.Core.Type

Typed Word8 Source # 
Instance details

Defined in Copilot.Core.Type

Typed Bool Source # 
Instance details

Defined in Copilot.Core.Type

Typed Double Source # 
Instance details

Defined in Copilot.Core.Type

Typed Float Source # 
Instance details

Defined in Copilot.Core.Type

(Typeable t, Typed t, KnownNat n) => Typed (Array n t) Source # 
Instance details

Defined in Copilot.Core.Type

typeOfDefault :: forall a. (Typed a, Struct a, Generic a, GTypedStruct (Rep a)) => Type a Source #

A default implementation of typeOf that leverages Generic. In order to use this, make sure you derive a Generic instance for your data type and then define typeOf = typeOfDefault in its Typed instance.

data UType Source #

A untyped type (no phantom type).

Constructors

forall a.Typeable a => UType 

Fields

  • uTypeType :: Type a

    Deprecated: This field is deprecated in Copilot 4.1. Use pattern matching instead.

Instances

Instances details
Eq UType Source # 
Instance details

Defined in Copilot.Core.Type

Methods

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

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

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.

Instances

Instances details
Eq SimpleType Source #

Type equality, used to help type inference.

Instance details

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

data Value a Source #

The field of a struct, together with a representation of its type.

Constructors

forall s t.(Typeable t, KnownSymbol s, Show t) => Value (Type t) (Field s t) 

toValues :: Struct a => a -> [Value a] Source #

Transforms all the struct's fields into a list of values.

toValuesDefault :: (Generic a, GStruct (Rep a)) => a -> [Value a] Source #

A default implementation of toValues that leverages Generic. In order to use this, make sure you derive a Generic instance for your data type and then define toValues = toValuesDefault in its Struct instance.

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 

Instances

Instances details
(KnownSymbol s, Show t) => Show (Field s t) Source # 
Instance details

Defined in Copilot.Core.Type

Methods

showsPrec :: Int -> Field s t -> ShowS #

show :: Field s t -> String #

showList :: [Field s t] -> ShowS #

typeName :: Struct a => a -> String Source #

Returns the name of struct in the target language.

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 typeName = typeNameDefault in its Struct instance.

This generates a struct name that consists of the name of the original Haskell data type, but converted to snake_case.

class Struct a Source #

The value of that is a product or struct, defined as a constructor with several fields.

Minimal complete definition

typeName, toValues

fieldName :: forall s t. KnownSymbol s => Field s t -> String Source #

Extract the name of a field.

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:

  1. Check that the name of the Field matches the name of the supplied Value (using sameSymbol).
  2. Check that the type of the Field matches the Type of the supplied Value (using testEquality).
  3. 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 updateField = updateFieldDefault in its Struct instance.

Orphan instances

(Typed t, Struct t) => Show t Source # 
Instance details

Methods

showsPrec :: Int -> t -> ShowS #

show :: t -> String #

showList :: [t] -> ShowS #