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

Feldspar.Core.Expr

Description

This module gives a representation core programs as typed expressions (see Expr / Data).

Synopsis

Documentation

data Expr a whereSource

Typed core language expressions. A value of type Expr a is a representation of a program that computes a value of type a.

Constructors

Val :: a -> Expr a 
Variable :: Expr a 
Value :: Storable a => a -> Expr a 
Function :: String -> (a -> b) -> Expr (a -> b) 
Application :: Expr (a -> b) -> Data a -> Expr b 
NoInline :: String -> Ref (a :-> b) -> Data a -> Expr b 
IfThenElse :: Data Bool -> (a :-> b) -> (a :-> b) -> Data a -> Expr b 
While :: (a :-> Bool) -> (a :-> a) -> Data a -> Expr a 
Parallel :: Storable a => Data Length -> (Int :-> a) -> Expr [a] 

data Data a Source

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

Constructors

Typeable a => Data 

Fields

dataSize :: Size a
 
dataRef :: Ref (Expr a)
 

Instances

Eq (Data a) 
(Fractional' a, Numeric a) => Fractional (Data a) 
Numeric a => Num (Data a) 
Ord (Data a) 
Storable a => Show (Data a) 
Storable a => RandomAccess (Data [a]) 
Storable a => Computable (Data a) 
Storable a => Computable (Vector (Data a)) 
Storable a => Computable (Vector (Vector (Data a))) 
ElemWise (Data a) 
FromFloat (Data Float) 
FixFloatLike (Data Float) 
Numeric a => Mul (Data a) (Matrix a) 
Numeric a => Mul (Data a) (DVector a) 
Numeric a => Mul (Data a) (Data a) 
Numeric a => Mul (DVector a) (Data a) 
Numeric a => Mul (Matrix a) (Data a) 
RandomAccess (Data Int -> Data a) 

data a :-> b Source

Constructors

Typeable a => Lambda (Data a -> Data b) (Data a) (Data b) 

exprToData :: Typeable a => Size a -> Expr a -> Data aSource

lambda :: Typeable a => Size a -> (Data a -> Data b) -> a :-> bSource

apply :: (a :-> b) -> Data a -> Data bSource

resultSize :: (a :-> b) -> Size bSource

(|$|) :: Expr (a -> b) -> Data a -> Expr bSource

_function :: Typeable b => String -> (Size a -> Size b) -> (a -> b) -> Data a -> Data bSource

_function2 :: Typeable c => String -> (Size a -> Size b -> Size c) -> (a -> b -> c) -> Data a -> Data b -> Data cSource

_function3 :: Typeable d => String -> (Size a -> Size b -> Size c -> Size d) -> (a -> b -> c -> d) -> Data a -> Data b -> Data c -> Data dSource

_function4 :: Typeable e => String -> (Size a -> Size b -> Size c -> Size d -> Size e) -> (a -> b -> c -> d -> e) -> Data a -> Data b -> Data c -> Data d -> Data eSource

tup2 :: (Typeable a, Typeable b) => Data a -> Data b -> Data (a, b)Source

tup3 :: (Typeable a, Typeable b, Typeable c) => Data a -> Data b -> Data c -> Data (a, b, c)Source

tup4 :: (Typeable a, Typeable b, Typeable c, Typeable d) => Data a -> Data b -> Data c -> Data d -> Data (a, b, c, d)Source

get21 :: Typeable a => Data (a, b) -> Data aSource

get22 :: Typeable b => Data (a, b) -> Data bSource

get31 :: Typeable a => Data (a, b, c) -> Data aSource

get32 :: Typeable b => Data (a, b, c) -> Data bSource

get33 :: Typeable c => Data (a, b, c) -> Data cSource

get41 :: Typeable a => Data (a, b, c, d) -> Data aSource

get42 :: Typeable b => Data (a, b, c, d) -> Data bSource

get43 :: Typeable c => Data (a, b, c, d) -> Data cSource

get44 :: Typeable d => Data (a, b, c, d) -> Data dSource

class Typeable (Internal a) => Computable a whereSource

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.

Methods

internalize :: a -> Data (Internal a)Source

Convert to internal representation

externalize :: Data (Internal a) -> aSource

Convert to external representation

Instances

lowerFun :: (Computable a, Computable b) => (a -> b) -> Data (Internal a) -> Data (Internal b)Source

Lower a function to operate on internal representation.

liftFun :: (Computable a, Computable b) => (Data (Internal a) -> Data (Internal b)) -> a -> bSource

Lift a function to operate on external representation.

evalE :: Expr a -> aSource

The semantics of expressions

evalD :: Data a -> aSource

The semantics of Data

evalF :: (a :-> b) -> a -> bSource

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

function :: (Storable a, Storable b) => String -> (Size a -> Size b) -> (a -> b) -> Data a -> Data bSource

Constructs a one-argument primitive function.

function fun szf f:

  • fun is the name of the function.
  • szf computes the output size from the input size.
  • f gives the evaluation semantics.

function2 :: (Storable a, Storable b, Storable c) => String -> (Size a -> Size b -> Size c) -> (a -> b -> c) -> Data a -> Data b -> Data cSource

A two-argument primitive function

function3 :: (Storable a, Storable b, Storable c, Storable d) => String -> (Size a -> Size b -> Size c -> Size d) -> (a -> b -> c -> d) -> Data a -> Data b -> Data c -> Data dSource

A three-argument primitive function

function4 :: (Storable a, Storable b, Storable c, Storable d, Storable e) => String -> (Size a -> Size b -> Size c -> Size d -> Size e) -> (a -> b -> c -> d -> e) -> Data a -> Data b -> Data c -> Data d -> Data eSource

A four-argument primitive function

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

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.

whileSized :: Computable state => Size (Internal state) -> Size (Internal state) -> (state -> Data Bool) -> (state -> state) -> state -> stateSource

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.