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

Feldspar.DSL.Network

Description

This module defines computational networks.

Synopsis

Documentation

data Out role Source

Empty type denoting an "out" role

Instances

data In role Source

Empty type denoting an "in" role

Instances

Typeable1 In 
EdgeInfo (Network edge node (In ()) a) 
Typeable a => MultiEdge (Network edge node (In ()) a) node edge 

data Connection edge node role a whereSource

Expression transformer for representing network connections.

Constructors

Node :: node role a -> Connection edge node role a 
Edge :: edge () a -> Connection edge node (Out () -> In ()) (a -> a) 
Group2 :: Connection e n (In ra -> In rb -> In (ra, rb)) (a -> b -> (a, b)) 
Group3 :: Connection e n (In ra -> In rb -> In rc -> In (ra, rb, rc)) (a -> b -> c -> (a, b, c)) 
Group4 :: Connection e n (In ra -> In rb -> In rc -> In rd -> In (ra, rb, rc, rd)) (a -> b -> c -> d -> (a, b, c, d)) 
Match21 :: Connection e n (Out (ra, rb) -> Out ra) ((a, b) -> a) 
Match22 :: Connection e n (Out (ra, rb) -> Out rb) ((a, b) -> b) 
Match31 :: Connection e n (Out (ra, rb, rc) -> Out ra) ((a, b, c) -> a) 
Match32 :: Connection e n (Out (ra, rb, rc) -> Out rb) ((a, b, c) -> b) 
Match33 :: Connection e n (Out (ra, rb, rc) -> Out rc) ((a, b, c) -> c) 
Match41 :: Connection e n (Out (ra, rb, rc, rd) -> Out ra) ((a, b, c, d) -> a) 
Match42 :: Connection e n (Out (ra, rb, rc, rd) -> Out rb) ((a, b, c, d) -> b) 
Match43 :: Connection e n (Out (ra, rb, rc, rd) -> Out rc) ((a, b, c, d) -> c) 
Match44 :: Connection e n (Out (ra, rb, rc, rd) -> Out rd) ((a, b, c, d) -> d) 

Instances

(ExprShow edge, ExprShow node) => ExprShow (Connection edge node) 
Eval node => Eval (Connection edge node) 
ExprEq node => ExprEq (Connection edge node) 
(ExprEq edge, ExprEq node) => Eq (Connection edge node role a) 
EdgeInfo (Network edge node (In ()) a) 
Typeable a => MultiEdge (Network edge node (In ()) a) node edge 

type Network edge node = Lam (Connection edge node)Source

A computational network

A value of type (Network edge node (In role) a) is called a in-edge, and a value of type (Network edge node (Out role) a) is called a out-edge.

It is assumed that the node type is designed such that it is impossible to construct a in-edge that is an (nested) application of a Node. This means that a value of type (Network edge node (In ()) a) can only be constructed by

Inject (Edge ...) :$: ...

It also means that values of type (Network edge node (In role) a) are always (nested) applications of Edge, Group2, Group3 or Group4.

This ensures that all functions in this module are total.

Note that the edge information will be ignored when comparing two networks using exprEq.

class EdgeInfo a whereSource

This class should be thought of as roughly equivalent to MultiEdge. The difference is that EdgeInfo has fewer constraints.

Associated Types

type Info a Source

Methods

edgeInfo :: a -> Info aSource

Instances

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

class (Typeable (Role a), Typeable (Internal a), EdgeInfo a) => MultiEdge a node edge | a -> node edge whereSource

Types that can be converted to/from network edges. Instances must fulfill prop_edge1 and prop_edge2.

Associated Types

type Role a Source

type Internal a Source

Methods

toEdge :: a -> Network edge node (In (Role a)) (Internal a)Source

fromInEdge :: Network edge node (In (Role a)) (Internal a) -> aSource

fromOutEdge :: Info a -> Network edge node (Out (Role a)) (Internal a) -> aSource

Instances

Type a => MultiEdge (Data a) Feldspar EdgeSize 
(Role a ~ (), Info a ~ EdgeSize () (Internal a), Syntactic a) => MultiEdge (Vector a) Feldspar EdgeSize 
Type a => MultiEdge (Fix a) Feldspar EdgeSize 
(MultiEdge a node edge, MultiEdge b node edge) => MultiEdge (a, b) node edge 
Type a => MultiEdge (Data' s a) Feldspar EdgeSize 
(MultiEdge a node edge, MultiEdge b node edge, MultiEdge c node edge) => MultiEdge (a, b, c) node edge 
(MultiEdge a node edge, MultiEdge b node edge, MultiEdge c node edge, MultiEdge d node edge) => MultiEdge (a, b, c, d) node edge 
Typeable a => MultiEdge (Network edge node (In ()) a) node edge 

prop_edge1 :: forall a node edge. (Eval node, MultiEdge a node edge, Eq (Internal a)) => Network edge node (In (Role a)) (Internal a) -> BoolSource

prop_edge2 :: forall a node edge. (Eval node, MultiEdge a node edge, Eq (Internal a)) => Info a -> Network edge node (Out (Role a)) (Internal a) -> BoolSource

undoEdge :: Network edge node (In ()) a -> Network edge node (Out ()) aSource

Remove an Edge application

edgeCast :: (MultiEdge a node edge, MultiEdge b node edge, Internal a ~ Internal b, Role a ~ Role b) => a -> bSource

Cast between two MultiEdge types that have the same internal representation.

mapEdge :: forall app edge node ra a. Applicative app => (forall b. [Int] -> Network edge node (In ()) b -> app b) -> Network edge node (In ra) a -> app aSource

Applies a function to each Edge in an in-edge, and collects the result in an applicative functor. The applied function receives the path of the edge as an argument.

listEdge :: forall edge node ra a b. (forall c. [Int] -> Network edge node (In ()) c -> b) -> Network edge node (In ra) a -> [b]Source

Applies a function to each Edge in an in-edge, and collects the results in a list. The applied function receives the path of the edge as an argument.

matchPath :: Network edge node (Out ()) a -> [Int]Source

Lists the match constructors of an out-edge

countEdges :: Network edge node (In role) a -> IntSource

Count the number of "single" edges (i.e. edges with role In ())

isMatch :: Connection edge node (ra -> rb) (a -> b) -> BoolSource

traceVar :: Network edge node (Out ()) a -> Maybe IdentSource

isNode :: Network edge node ra a -> BoolSource

isEdge :: Network edge node ra a -> BoolSource