copilot-core-3.0: An intermediate representation for Copilot.

Safe HaskellSafe
LanguageHaskell2010

Copilot.Core.Type

Contents

Description

Typing for Core.

Synopsis

Documentation

data Type :: * -> * where Source #

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, Typed (InnerType t), Flatten t (InnerType t)) => Type t -> Type (Array n t) 
Struct :: (Typed a, Struct a) => a -> Type a 
Instances
EqualType Type Source # 
Instance details

Defined in Copilot.Core.Type

Methods

(=~=) :: Type a -> Type b -> Maybe (Equal a b) Source #

class (Show a, Typeable a) => Typed a where Source #

Minimal complete definition

typeOf

Instances
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

Typed Int8 Source # 
Instance details

Defined in Copilot.Core.Type

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 Word8 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

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

Defined in Copilot.Core.Type

data UType Source #

A untyped type (no phantom type).

Constructors

Typeable a => UType 

Fields

Instances
Eq UType Source # 
Instance details

Defined in Copilot.Core.Type

Methods

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

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

tysize :: forall n t. KnownNat n => Type (Array n t) -> Int Source #

tylength :: forall n t. KnownNat n => Type (Array n t) -> Int Source #

data Value a Source #

Constructors

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

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

data Field (s :: Symbol) t Source #

Constructors

Field t 
Instances
(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 #

class Struct a Source #

Minimal complete definition

typename, toValues

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

accessorname :: forall a s t. (Struct a, KnownSymbol s) => (a -> Field s t) -> String Source #

Orphan instances

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

Methods

showsPrec :: Int -> t -> ShowS #

show :: t -> String #

showList :: [t] -> ShowS #