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

Feldspar.Core.Representation

Contents

Synopsis

Feldspar expressions

data Feldspar role a whereSource

Feldspar-specific expressions

Constructors

Literal :: (Type a, MetaType () a) => a -> Feldspar (Out ()) a 
Function :: (Typeable (a -> b), MetaType () b) => String -> (a -> b) -> Feldspar (In ra -> Out ()) (a -> b) 
Pair :: (Type a, Type b, MetaType () (a, b)) => Feldspar (In () -> In () -> Out ()) (a -> b -> (a, b)) 
Condition :: MetaType ra a => Feldspar (In () -> In ra -> In ra -> Out ra) (Bool -> a -> a -> a) 
Parallel :: (Type a, MetaType () [a]) => Feldspar (In () -> (Out () -> In ()) -> In () -> Out ()) (Length -> (Index -> a) -> [a] -> [a]) 
Sequential :: (Type a, MetaType () [a], MetaType rst st) => Feldspar (In () -> In rst -> (Out () -> Out rst -> In ((), rst)) -> (Out rst -> In ()) -> Out ()) (Length -> st -> (Index -> st -> (a, st)) -> (st -> [a]) -> [a]) 
ForLoop :: MetaType rst st => Feldspar (In () -> In rst -> (Out () -> Out rst -> In rst) -> Out rst) (Length -> st -> (Index -> st -> st) -> st) 
NoInline :: MetaType rb b => String -> Feldspar ((Out ra -> In rb) -> In ra -> Out rb) ((a -> b) -> a -> b) 
SetLength :: Type a => Feldspar (In () -> In () -> Out ()) (Length -> [a] -> [a]) 
SetIx :: Type a => Feldspar (In () -> In () -> In () -> Out ()) (Index -> a -> [a] -> [a]) 

eqLiteral :: (Typeable a, Typeable b, Eq b) => a -> b -> BoolSource

sameType :: forall a b. (Typeable a, Typeable b) => a -> b -> BoolSource

evalParallel :: Length -> (Index -> a) -> [a] -> [a]Source

evalSequential :: Length -> st -> (Index -> st -> (a, st)) -> (st -> [a]) -> [a]Source

evalForLoop :: Length -> st -> (Index -> st -> st) -> stSource

evalSetLength :: Length -> [a] -> [a]Source

evalSetIx :: Index -> a -> [a] -> [a]Source

Feldspar networks

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
 

newtype Data a Source

A Feldspar program computing a value of type a

Constructors

Data 

Fields

unData :: FeldNetwork (In ()) 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) 

edgeType :: forall a. EdgeSize () a -> TypeRepSource

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

nodeData :: Type a => Size a -> FeldNetwork (Out ()) a -> Data aSource

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

lambda :: (Syntactic a, Syntactic b) => Info a -> (a -> b) -> FeldNetwork (Out (Role a) -> In (Role b)) (Internal a -> Internal b)Source

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.

metaTypes :: forall a ra expr. MetaType ra a => expr (Out ra) a -> [([Int], TypeRep)]Source

resTypes :: FeldNetwork ra a -> [([Int], TypeRep)]Source

List the types of the results produced by a Feldspar expression

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