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

Feldspar.Core

Description

The user interface to the core language

Synopsis

Documentation

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.

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) 

class Typeable a => Storable a Source

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

data Data a Source

A wrapper around Expr to allow observable sharing (see Feldspar.Core.Ref).

Instances

Eq (Data a) 
Fractional (Data Float) 
(Num n, Primitive n) => Num (Data n) 
Ord (Data a) 
Primitive a => Show (Data a) 
(NaturalT n, Storable a) => RandomAccess (Data (:> n a)) 
Storable a => Computable (Data a) 
(NaturalT n1, NaturalT n2, Storable a, AccessPattern t1, AccessPattern t2) => Computable (:>> (t1 n1) (:>> (t2 n2) (Data a))) 
(NaturalT n, Storable a, AccessPattern t) => Computable (:>> (t n) (Data a)) 

class Typeable (Internal a) => Computable a Source

Computable types. A computable value completely represents a core program, in such a way that internalize . externalize preserves semantics, but not necessarily syntax.

The terminology used in this class comes from thinking of the Data type as the "internal core language" and the core API as the "external core language".

Associated Types

type Internal a Source

The internal representation of the type a (without the Data constructor).

Instances

Storable a => Computable (Data a) 
(Computable a, Computable b) => Computable (a, b) 
(NaturalT n1, NaturalT n2, Storable a, AccessPattern t1, AccessPattern t2) => Computable (:>> (t1 n1) (:>> (t2 n2) (Data a))) 
(NaturalT n, Storable a, AccessPattern t) => Computable (:>> (t n) (Data a)) 
(Computable a, Computable b, Computable c) => Computable (a, b, c) 
(Computable a, Computable b, Computable c, Computable d) => Computable (a, b, c, d) 

eval :: Computable a => a -> Internal aSource

Evaluation of any Computable type

value :: Primitive a => a -> Data aSource

A primitive value (a program that computes a constant value)

array :: (NaturalT n, Storable a) => ListBased (n :> a) -> Data (n :> a)Source

For example,

 array [[1,2,3],[4,5]] :: Data (D2 :> D4 :> Int)

is a 2x4-element array of Ints, with the first row initialized to [1,2,3] and the second row to [4,5].

size :: (NaturalT n, Storable a) => Data (n :> a) -> [Int]Source

Returns the size of each level of a multi-dimensional array, starting with the outermost level.

getIx :: forall n a. (NaturalT n, Storable a) => Data (n :> a) -> Data Int -> Data aSource

Look up an index in an array

setIx :: forall n a. (NaturalT n, Storable a) => Data (n :> a) -> Data Int -> Data a -> Data (n :> a)Source

setIx arr i a:

Replaces the value at index i in the array arr with the value a.

class RandomAccess a whereSource

Associated Types

type Elem a Source

Methods

(!) :: a -> Data Int -> Elem aSource

Index lookup in random access structures

Instances

(NaturalT n, Storable a) => RandomAccess (Data (:> n a)) 
RandomAccess (:>> (Par n) a) 

noInline :: (Computable a, Computable b) => String -> (a -> b) -> a -> bSource

Constructs a non-primitive, non-inlined function.

The normal way to make a non-primitive function is to use an ordinary Haskell function, for example:

 myFunc x = x * 4 + 5

However, such functions are inevitably inlined into the program expression when applied. noInline can be thought of as a way to protect a function against inlining (but later transformations may choose to inline anyway).

Ideally, it should be posssible to reuse such a function several times, but at the moment this does not work. Every application of a noInline function results in a new copy of the function in the core program.

ifThenElse :: (Computable a, Computable b) => Data Bool -> (a -> b) -> (a -> b) -> a -> bSource

ifThenElse cond thenFunc elseFunc:

Selects between the two functions thenFunc and elseFunc depending on whether the condition cond is true or false.

while :: Computable a => (a -> Data Bool) -> (a -> a) -> a -> aSource

while cont body:

A while-loop. The condition cont determines whether the loop should continue one more iteration. body computes the next state. The result is a function from initial state to final state.

parallel :: (NaturalT n, Storable a) => Data Int -> (Data Int -> Data a) -> Data (n :> a)Source

parallel sz ixf:

Parallel tiling. Computes the elements of a vector. sz is the dynamic size, i.e. how many of the allocated elements that should be computed. The function ixf maps each index to its value.

Since there are no dependencies between the elements, the compiler is free to compute the elements in parallel (or any other order).

class Program a Source

Types that represents core language programs

Instances

Computable a => Program a 
(Computable a, Computable b, Computable c, Computable d, Computable e) => Program (a -> b -> c -> d -> e) 
(Computable a, Computable b, Computable c, Computable d) => Program (a -> b -> c -> d) 
(Computable a, Computable b, Computable c) => Program (a -> b -> c) 
(Computable a, Computable b) => Program (a -> b) 

showCore :: forall a. Program a => a -> StringSource

Shows the core code generated by program.

printCore :: Program a => a -> IO ()Source

printCore = putStrLn . showCore