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

Feldspar.Core

Description

The user interface of the core language

Synopsis

Documentation

data Ord a => Range a Source

Constructors

Range 

Fields

lowerBound :: Maybe a
 
upperBound :: Maybe a
 

Instances

Ord a => Eq (Range a) 
(Ord a, Num a) => Num (Range a) 
(Ord a, Show a) => Show (Range a) 
(Arbitrary a, Ord a, Num a) => Arbitrary (Range a) 
(Ord a, Num a) => Monoid (Range a) 
Ord a => Set (Range a) 

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) 

class Typeable a => Storable a Source

Storable types (zero- or higher-level arrays of primitive data).

data Data a Source

A wrapper around Expr to allow observable sharing (see Feldspar.Core.Ref) and for memoizing size information.

Instances

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 Feldspar.Core API as the "external" core language.

Associated Types

type Internal a Source

Data (Internal a) is the internal representation of the type a.

Instances

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

The semantics of any Computable type

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

A program that computes a constant value

array :: Storable a => Size a -> a -> Data aSource

Like value but with an extra Size argument that can be used to increase the size beyond the given data.

Example 1:

 array (10 :> 20 :> universal) [] :: Data [[Int]]

gives an uninitialized 10x20 array of Int elements.

Example 2:

 array (10 :> 20 :> universal) [[1,2,3]] :: Data [[Int]]

gives a 10x20 array whose first row is initialized to [1,2,3].

arrayLen :: Storable a => Data Length -> [a] -> Data [a]Source

size :: forall a. Storable a => Data [a] -> [Range Length]Source

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

cap :: (Storable a, Size a ~ Range b, Ord b) => Range b -> Data a -> Data aSource

getIx :: Storable a => Data [a] -> Data Int -> Data aSource

Look up an index in an array (see also !)

setIx :: Storable a => Data [a] -> Data Int -> Data a -> Data [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 Element a Source

The type of elements in a random access structure

Methods

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

Index lookup in a random access structure

Instances

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

Instances

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 state => (state -> Data Bool) -> (state -> state) -> state -> stateSource

While-loop

while cont body :: state -> state:

  • state is the type of the state.
  • cont determines whether or not to continue based on the current state.
  • body computes the next state from the current state.
  • The result is a function from initial state to final state.

parallel :: Storable a => Data Length -> (Data Int -> Data a) -> Data [a]Source

Parallel array

parallel l ixf:

  • l is the length of the resulting array (outermost level).
  • ifx is a function that maps each index in the range [0 .. l-1] to its element.

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

class Program a Source

Types that represent 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) 
(Computable a, Computable b) => Program (a, b) 
(Computable a, Computable b, Computable c) => Program (a, b, c) 
(Computable a, Computable b, Computable c, Computable d) => Program (a, b, c, d) 

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

Shows the core code generated by the program.

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

Shows the core code with size information as comments.

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

printCore = putStrLn . showCore

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

printCoreWithSize = putStrLn . showCoreWithSize