Feldspar.Core.Types
Description
Defines types and classes for the data computed by Feldspar programs.
- data T a = T
- mkT :: a -> T a
- data a :> b = a :> b
- class Set a where
- universal :: a
- type Length = Int
- data Tuple a
- showTuple :: Tuple String -> String
- tuplePath :: Tuple a -> Tuple [Int]
- data PrimitiveData
- data StorableData
- data PrimitiveType
- data StorableType = StorableType [Range Length] PrimitiveType
- showStorableSize :: StorableType -> String
- class Storable a => Primitive a where
- primitiveData :: a -> PrimitiveData
- primitiveType :: Size a -> T a -> PrimitiveType
- class Typeable a => Storable a where
- storableData :: a -> StorableData
- storableType :: Size a -> T a -> StorableType
- storableSize :: a -> Size a
- listSize :: T a -> Size a -> [Range Length]
- class (Eq a, Ord a, Monoid (Size a), Set (Size a)) => Typeable a where
- typeOfStorable :: Storable a => Size a -> T a -> Tuple StorableType
- class (Num a, Primitive a, Num (Size a)) => Numeric a
Misc.
Heterogeneous list
Constructors
a :> b |
Tuples
Untyped representation of nested tuples
Instances
Functor Tuple | |
Foldable Tuple | |
Traversable Tuple | |
Eq a => Eq (Tuple a) | |
Show a => Show (Tuple a) | |
HaskellValue a => HaskellValue (Tuple a) | |
HaskellType a => HaskellType (Tuple a) |
showTuple :: Tuple String -> StringSource
Shows a nested tuple in Haskell's tuple syntax (e.g "(a,(b,c))"
).
tuplePath :: Tuple a -> Tuple [Int]Source
Replaces each element by its path in the tuple tree. For example:
tuplePath (Tup [One 'a',Tup [One 'b', One 'c']]) == Tup [One [0],Tup [One [1,0],One [1,1]]]
Data
data PrimitiveData Source
Untyped representation of primitive data
data StorableData Source
Untyped representation of storable data (arrays of primitive data)
Constructors
PrimitiveData PrimitiveData | |
StorableData [StorableData] |
Instances
Types
data PrimitiveType Source
Representation of primitive types
Instances
data StorableType Source
Representation of storable types (arrays of primitive types). Array size is given as a list of ranged lengths, starting with outermost array level. Primitive types are treated as zero-dimensional arrays.
Constructors
StorableType [Range Length] PrimitiveType |
Instances
showStorableSize :: StorableType -> StringSource
Shows the size of a storable type.
class Storable a => Primitive a whereSource
Primitive types
Methods
primitiveData :: a -> PrimitiveDataSource
Converts a primitive value to its untyped representation.
primitiveType :: Size a -> T a -> PrimitiveTypeSource
Gives the type representation of a primitive value.
class Typeable a => Storable a whereSource
Storable types (zero- or higher-level arrays of primitive data).
Methods
storableData :: a -> StorableDataSource
Converts a storable value to its untyped representation.
storableType :: Size a -> T a -> StorableTypeSource
Gives the type representation of a storable value.
storableSize :: a -> Size aSource
Gives the size of a storable value.
class (Eq a, Ord a, Monoid (Size a), Set (Size a)) => Typeable a whereSource
Associated Types
This type provides the necessary extra information to compute a type
representation
from a type Tuple
StorableType
a
. This is needed
because the type a
is missing information about sizes of arrays and
primitive values.
typeOfStorable :: Storable a => Size a -> T a -> Tuple StorableTypeSource