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

Feldspar.Core.Expr

Contents

Description

This module represents core programs as typed expressions (see Expr / Data). The idea is for programmers to use an interface based on Data, while back-end tools use the Graph representation. The function toGraph is used to convert between the two representations.

Synopsis

Expressions

data Data a Source

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

Constructors

Typeable a => Data (Ref (Expr a)) 

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)) 

ref :: Typeable a => Expr a -> Data aSource

data Expr a whereSource

Typed core language expressions. A value of type Expr a can be thought of as a representation of a program that computes a value of type a.

Constructors

Input :: Expr a 
Value :: Storable a => a -> Expr a 
Tuple2 :: Data a -> Data b -> Expr (a, b) 
Tuple3 :: Data a -> Data b -> Data c -> Expr (a, b, c) 
Tuple4 :: Data a -> Data b -> Data c -> Data d -> Expr (a, b, c, d) 
GetTuple :: GetTuple n a => T n -> Data a -> Expr (Part n a) 
Function :: String -> (a -> b) -> Data a -> Expr b 
NoInline :: (Typeable a, Typeable b) => String -> Ref (Data a -> Data b) -> Data a -> Expr b 
IfThenElse :: (Typeable a, Typeable b) => Data Bool -> (Data a -> Data b) -> (Data a -> Data b) -> Data a -> Expr b 
While :: Typeable a => (Data a -> Data Bool) -> (Data a -> Data a) -> Data a -> Expr a 
Parallel :: (NaturalT n, Storable a) => Data Int -> (Data Int -> Data a) -> Expr (n :> a) 

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

Associated Types

type Internal a Source

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

Methods

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

Convert to internal representation

externalize :: Data (Internal a) -> aSource

Convert to external representation

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) 

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

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

evalE :: Expr a -> aSource

The semantics of expressions

evalD :: Data a -> aSource

Evaluation of Data

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

Evaluation of any Computable type

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

Internal function for constructing storable values.

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.

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

A one-argument primitive function. The first argument is the name of the function, and the second argument gives its evaluation semantics.

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

A two-argument function

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

A three-argument function

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

A four-argument function

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

A one-argument function with constant folding

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

A two-argument function with constant folding

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

A three-argument function with constant folding

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

A four-argument function with constant folding

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).

Graph conversion

data Info Source

Constructors

Info 

Fields

index :: NodeId

Next id

visited :: Map Unique NodeId

Visited references mapped to their id

type GraphBuilder a = WriterT [Node] (State Info) aSource

Monad for making graph building easier

node :: forall a. Typeable a => Data a -> Function -> Tuple Source -> Tuple StorableType -> GraphBuilder ()Source

Declare a node

sourceNode :: Data a -> Function -> GraphBuilder ()Source

Declare a source node (one with no inputs)

source :: forall a. [Int] -> Data a -> GraphBuilder SourceSource

buildSubFun :: forall a b. (Typeable a, Typeable b) => (Data a -> Data b) -> GraphBuilder InterfaceSource

toGraphD :: (Typeable a, Typeable b) => (Data a -> Data b) -> GraphSource

class Program a whereSource

Types that represents core language programs

Methods

toGraph :: a -> GraphSource

Converts a program to a Graph

hasArg :: T a -> BoolSource

Returns whether or not the program has an argument. This is needed because the Graph type always assumes the existence of an input. So for programs without input, the Graph representation will have a "dummy" input, which is indistinguishable from a real input.

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