feldspar-language-0.1: 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

Types as arguments

data T a Source

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

Constructors

T 

numberT :: forall n. IntegerT n => T n -> IntSource

Haskell source code

class HaskellType a whereSource

Types that can represent Haskell types (as source code strings)

Methods

haskellType :: a -> StringSource

Gives the Haskell type denoted by the argument.

class HaskellValue a whereSource

Types that can represent Haskell values (as source code strings)

Methods

haskellValue :: a -> StringSource

Gives the Haskell code denoted by the argument.

Tuples

class NaturalT n => GetTuple n a whereSource

General tuple projection

Associated Types

type Part n a Source

Methods

getTup :: T n -> a -> Part n aSource

Instances

GetTuple D0 (a, b) 
GetTuple D1 (a, b) 
GetTuple D0 (a, b, c) 
GetTuple D1 (a, b, c) 
GetTuple D2 (a, b, c) 
GetTuple D0 (a, b, c, d) 
GetTuple D1 (a, b, c, d) 
GetTuple D2 (a, b, c, d) 
GetTuple D3 (a, b, c, d) 

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 PrimitiveType Source

Representation of primitive types

data PrimitiveData Source

Untyped representation of primitive data

data StorableType Source

Representation of storable types (arrays of primitive data). Array dimensions are given as a list of integers, starting with outermost array level. Primitive types are treated as zero-dimensional arrays.

data StorableData Source

Untyped representation of storable data. Arrays have a length argument that gives the number of elements on the outermost array level. If the data list is shorter than this length, the missing elements are taken to have undefined value. If the data list is longer, the excessive elements are just ignored.

class Storable a => Primitive a Source

Primitive types

data n :> a Source

Array represented as (nested) list. If a is a storable type and n is a type-level natural number, n :> a represents an array of n elements of type a. For example, D3:>D10:>Int is a 3 by 10 array of integers. Arrays constructed using fromList are guaranteed not to contain too many elements in any dimension. If there are too few elements in any dimension, the missing ones are taken to have undefined value.

Constructors

(NaturalT n, Storable a) => ArrayList [a] 

Instances

(NaturalT n, Storable a) => RandomAccess (Data (:> n a)) 
(NaturalT n, Storable a, Eq a) => Eq (:> n a) 
(NaturalT n, Storable a, Ord a) => Ord (:> n a) 
(NaturalT n, Storable a, Show (ListBased a)) => Show (:> n a) 
(NaturalT n, Storable a) => Typeable (:> n a) 
(NaturalT n, Storable a) => Storable (:> n a) 

mapArray :: (NaturalT n, Storable a, Storable b) => (a -> b) -> (n :> a) -> n :> bSource

class Typeable a => Storable a whereSource

Storable types (zero- or higher-level arrays of primitive data). Should be the same set of types as Storable, but this class has no Typeable context, so it doesn't cause a cycle.

Example:

 *Feldspar.Core.Types> toList (replicateArray 3 :: D4 :> D2 :> Int)
 [[3,3],[3,3],[3,3],[3,3]]

Associated Types

type ListBased a :: *Source

List-based representation of a storable type

type Element a :: *Source

The innermost element of a storable type

Methods

replicateArray :: Element a -> aSource

Constructs an array filled with the given element. For primitive types, this is just the identity function.

toList :: a -> ListBased aSource

Converts a storable type to a (zero- or higher-level) nested list.

fromList :: ListBased a -> aSource

Constructs a storable type from a (zero- or higher-level) nested list. The resulting value is guaranteed not to have too many elements in any dimension. Excessive elements are simply cut away.

toData :: a -> StorableDataSource

Converts a storable value to its untyped representation.

class (Eq a, Ord a) => Typeable a whereSource

All supported types of data (nested tuples of storable data)

Methods

typeOf :: T a -> Tuple StorableTypeSource

Gives the representation of the indexing type.

Instances

Typeable Bool 
Typeable Float 
Typeable Int 
Typeable () 
(Typeable a, Typeable b) => Typeable (a, b) 
(NaturalT n, Storable a) => Typeable (:> n a) 
(Typeable a, Typeable b, Typeable c) => Typeable (a, b, c) 
(Typeable a, Typeable b, Typeable c, Typeable d) => Typeable (a, b, c, d) 

isPrimitive :: Typeable a => T a -> BoolSource

Checks if the given type is primitive.