| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Copilot.Core.Type
Contents
Description
Typing for Core.
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, Typed (InnerType t), Flatten t (InnerType 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
- data UType = 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
- tysize :: forall n t. KnownNat n => Type (Array n t) -> Int
- tylength :: forall n t. KnownNat n => Type (Array n t) -> Int
- data Value a = (Typeable t, KnownSymbol s, Show t) => Value (Type t) (Field s t)
- toValues :: Struct a => a -> [Value a]
- data Field (s :: Symbol) t = Field t
- typename :: Struct 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
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 |
class (Show a, Typeable a) => Typed a where Source #
Minimal complete definition
Instances
| Typed Bool Source # | |
Defined in Copilot.Core.Type | |
| Typed Double Source # | |
Defined in Copilot.Core.Type | |
| Typed Float Source # | |
Defined in Copilot.Core.Type | |
| Typed Int8 Source # | |
Defined in Copilot.Core.Type | |
| 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 Word8 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 | |
| (Typeable t, Typed t, KnownNat n, Flatten t (InnerType t), Typed (InnerType t)) => Typed (Array n t) Source # | |
Defined in Copilot.Core.Type | |
A untyped type (no phantom type).
data SimpleType where Source #
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 # | |
Defined in Copilot.Core.Type | |
accessorname :: forall a s t. (Struct a, KnownSymbol s) => (a -> Field s t) -> String Source #