feldspar-language-0.2: A functional embedded language for DSP and parallelism

Feldspar.Core.Types

Contents

Description

Defines types and classes for the data computed by Feldspar programs.

Synopsis

Misc.

data T a Source

Used to pass a type to a function without using undefined.

Constructors

T 

mkT :: a -> T aSource

data a :> b Source

Heterogeneous list

Constructors

a :> b 

Instances

(Eq a, Eq b) => Eq (:> a b) 
(Ord a, Ord b) => Ord (:> a b) 
(Show a, Show b) => Show (:> a b) 
(Monoid a, Monoid b) => Monoid (:> a b) 
(Set a, Set b) => Set (:> a b) 

class Set a whereSource

Methods

universal :: aSource

Instances

Set () 
Ord a => Set (Range a) 
(Set a, Set b) => Set (a, b) 
(Set a, Set b) => Set (:> a b) 
(Set a, Set b, Set c) => Set (a, b, c) 
(Set a, Set b, Set c, Set d) => Set (a, b, c, d) 

Tuples

data Tuple a Source

Untyped representation of nested tuples

Constructors

One a 
Tup [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)

Types

data PrimitiveType Source

Representation of primitive types

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.

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.

listSize :: T a -> Size a -> [Range Length]Source

class (Eq a, Ord a, Monoid (Size a), Set (Size a)) => Typeable a whereSource

Associated Types

type Size a Source

This type provides the necessary extra information to compute a type representation Tuple StorableType from a type a. This is needed because the type a is missing information about sizes of arrays and primitive values.

Methods

typeOf :: Size a -> T a -> Tuple StorableTypeSource

Gives the type representation of a storable value.

Instances

Typeable Bool 
Typeable Float 
Typeable Int 
Typeable () 
Storable a => Typeable [a] 
(Typeable a, Typeable b) => Typeable (a, b) 
(Typeable a, Typeable b, Typeable c) => Typeable (a, b, c) 
(Typeable a, Typeable b, Typeable c, Typeable d) => Typeable (a, b, c, d) 

typeOfStorable :: Storable a => Size a -> T a -> Tuple StorableTypeSource

Default implementation of typeOf for Storable types.

class (Num a, Primitive a, Num (Size a)) => Numeric a Source

Instances