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

Feldspar.Core

Contents

Description

The Feldspar core language

Synopsis

Reexported standard modules

data RealFloat a => Complex a

Complex numbers are an algebraic type.

For a complex number z, abs z is a number with the magnitude of z, but oriented in the positive real direction, whereas signum z has the phase of z, but unit magnitude.

Constructors

!a :+ !a

forms a complex number from its real and imaginary rectangular components.

module Data.Int

module Data.Word

DSL library

Feldspar types

data Range a Source

A bounded range of values of type a

Constructors

Range 

Fields

lowerBound :: a
 
upperBound :: a
 

Instances

Eq a => Eq (Range a) 
BoundedInt a => Num (Range a)

Implements fromInteger as a singletonRange, and implements correct range propagation for arithmetic operations.

Show a => Show (Range a) 
(BoundedInt a, Arbitrary a) => Arbitrary (Range a) 
BoundedInt a => Set (Range a) 
BoundedInt a => FullProp (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) 
(Set a, Set b) => Set (:> a b) 

class (Eq a, Show a, Typeable a, Eq (Size a), Show (Size a), Set (Size a)) => Type a Source

Associated Types

type Size a Source

Instances

Type Bool 
Type Float 
Type Int8 
Type Int16 
Type Int32 
Type Word8 
Type Word16 
Type Word32 
Type () 
Type DefaultInt 
Type DefaultWord 
Type a => Type [a] 
(Type a, RealFloat a) => Type (Complex a) 
(Type a, Type b) => Type (a, b) 
(Type a, Type b, Type c) => Type (a, b, c) 
(Type a, Type b, Type c, Type d) => Type (a, b, c, d) 

fullProp :: FullProp a => aSource

Size propagation function that maps any number of arguments to universal.

Core constructs

data EdgeSize role a Source

A wrapper around Size to make it look like an expression. The Type constraint ensures that edges in a FeldNetwork always have supported types.

Constructors

(Type a, Eq (Size a), Show (Size a)) => EdgeSize 

Fields

edgeSize :: Size a
 

data Data a Source

A Feldspar program computing a value of type a

Instances

Eq (Data a) 
(Fractional' a, Floating a) => Floating (Data a) 
Fractional' a => Fractional (Data a) 
Numeric a => Num (Data a) 
Show (Data a) 
EdgeInfo (Data a) 
Type a => Syntactic (Data a) 
Type a => RandomAccess (Data [a]) 
Type a => ElemWise (Data a) 
Type a => Splittable (Data a) 
Fixable (Data Float) 
Type a => MultiEdge (Data a) Feldspar EdgeSize 
Wrap (Data a) (Data a)

Basic instances to handle Data a input and output. Other instances are located in the concerned libraries.

Type a => Wrap (Vector (Data a)) (Data [a]) 
Type a => Wrap (Matrix a) (Data [[a]]) 
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) (Matrix a) 
Numeric a => Mul (DVector a) (DVector a) 
Numeric a => Mul (DVector a) (Data a) 
Numeric a => Mul (Matrix a) (Matrix a) 
Numeric a => Mul (Matrix a) (DVector a) 
Numeric a => Mul (Matrix a) (Data a) 
Wrap t u => Wrap (Data a -> t) (Data a -> u) 
(Wrap t u, Type a, Nat s) => Wrap (DVector a -> t) (Data' s [a] -> u) 
(Wrap t u, Type a, Nat row, Nat col) => Wrap (Matrix a -> t) (Data' (row, col) [[a]] -> u) 

class (MultiEdge a Feldspar EdgeSize, Set (Info a), Type (Internal a), MetaType (Role a) (Internal a)) => Syntactic a Source

Syntactic is a specialization of the MultiEdge class for Feldspar programs.

Instances

Type a => Syntactic (Data a) 
(Role a ~ (), Info a ~ EdgeSize () (Internal a), Syntactic a) => Syntactic (Vector a) 
Type a => Syntactic (Fix a) 
(Syntactic a, Syntactic b) => Syntactic (a, b) 
Type a => Syntactic (Data' s a) 
(Syntactic a, Syntactic b, Syntactic c) => Syntactic (a, b, c) 
(Syntactic a, Syntactic b, Syntactic c, Syntactic d) => Syntactic (a, b, c, d) 

dataSize :: Type a => Data a -> Size aSource

resizeData :: Type a => Size a -> Data a -> Data aSource

force :: Syntactic a => a -> aSource

Forcing computation

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

Evaluation of Feldspar programs

viewLiteral :: Syntactic a => a -> Maybe (Internal a)Source

Yield the value of a constant program. If the value is not known statically, the result is Nothing.

drawExpr2 :: (Syntactic a, Syntactic b) => (a -> b) -> IO ()Source

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

A program that computes a constant value

array :: Type 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 [[DefaultInt]]

gives an uninitialized 10x20 array of DefaultInt elements.

Example 2:

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

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

cap :: Type a => Size a -> Data a -> Data aSource

function :: (Syntactic a, Type b) => Bool -> String -> (Info a -> Size b) -> (Internal a -> b) -> a -> Data bSource

function1 :: (Type a, Type b) => String -> (Size a -> Size b) -> (a -> b) -> Data a -> Data bSource

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

conditionSource

Arguments

:: Syntactic a 
=> Data Bool

Condition

-> a

"Then" branch

-> a

"Else" branch

-> a 

(?)Source

Arguments

:: Syntactic a 
=> Data Bool

Condition

-> (a, a)

Alternatives

-> a 

ifThenElseSource

Arguments

:: Syntactic a 
=> Data Bool

Condition

-> a

"Then" branch

-> a

"Else" branch

-> a 

Identical to condition. Provided for backwards-compatibility, but will be removed in the future.

parallel'' :: Type a => Bool -> Data Length -> (Data Index -> Data a) -> Data [a] -> Data [a]Source

Parallel array with continuation

parallel' :: Type a => Data Length -> (Data Index -> Data a) -> Data [a] -> Data [a]Source

Parallel array with continuation

parallelSource

Arguments

:: Type a 
=> Data Length

Length of resulting array (outermost level)

-> (Data Index -> Data a)

Function that maps each index in the range [0 .. l-1] to its element

-> Data [a] 

Parallel array

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

forLoopSource

Arguments

:: Syntactic st 
=> Data Length

Number of iterations

-> st

Initial state

-> (Data Index -> st -> st)

Loop body (current index and state to next state)

-> st

Final state

For loop

sequentialSource

Arguments

:: (Type a, Syntactic st) 
=> Data Length 
-> st

Initial state

-> (Data Index -> st -> (Data a, st))

Current loop index and current state to current element and next state

-> (st -> Data [a])

Continuation

-> Data [a] 

noinline :: (Syntactic a, Syntactic b) => String -> (a -> b) -> a -> bSource

Prevent a function from being inlined

noinline2 :: (Syntactic a, Syntactic b, Syntactic c) => String -> (a -> b -> c) -> a -> b -> cSource

setLength :: Type a => Data Length -> Data [a] -> Data [a]Source

Functions

Wrapping