ddc-core-flow-0.4.2.1: Disciplined Disciple Compiler data flow compiler.

Safe HaskellNone
LanguageHaskell98

DDC.Core.Flow.Transform.Rates.Combinators

Description

Converting DDC expressions to and from Combinator Normal Form.

Synopsis

Documentation

data Fun s a Source

Worker function. May only reference scalars in the environment, not arrays. Takes the expression of the function, and a list of the free scalars that are referenced inside it. The expression must be a function from scalar to scalar.

Constructors

Fun ExpF [s] 

Instances

Show s => Show (Fun s a) Source 
(Pretty s, Pretty a) => Pretty (Fun s a) Source 

data Bind s a Source

Array, scalar and external bindings. Array bindings are those whose value is an array, such as map, filter. Scalar bindings have scalar values, currently only fold. External expressions are those that cannot be converted to primitive combinators. The they take a single expression that computes all outputs, with the list of free scalar and array inputs.

Constructors

ABind a (ABind s a) 
SBind s (SBind s a) 
Ext 

Fields

_beOut :: CName s a
 
_beExp :: ExpF
 
_beIns :: ([s], [a])
 

Instances

(Show s, Show a) => Show (Bind s a) Source 
(Pretty s, Pretty a) => Pretty (Bind s a) Source 

data ABind s a Source

An array-valued binding.

Constructors

MapN (Fun s a) [a]

map_n :: (a_1 ... a_n -> b) -> Array a_1 ... Array a_n -> Array b

Filter (Fun s a) a

filter :: (a -> Bool) -> Array a -> Array a

Generate (Scalar s a) (Fun s a)

generate :: Nat -> (Nat -> a) -> Array a

Gather a a

gather :: Array a -> Array Nat -> Array a

Cross a a

cross :: Array a -> Array b -> Array (a, b)

Instances

(Show s, Show a) => Show (ABind s a) Source 

data SBind s a Source

A scalar-valued binding

Constructors

Fold (Fun s a) (Scalar s a) a

fold :: (a -> a -> a) -> a -> Array a -> a

Instances

(Show s, Show a) => Show (SBind s a) Source 

data Scalar s a Source

Scalars can either be a literal such as "0", or a named scalar reference. If it's not a named scalar reference, we need to keep the expression so we can reconstruct it later. (We do not have array literals, so this is only necessary for scalars)

Constructors

Scalar ExpF (Maybe s) 

Instances

Show s => Show (Scalar s a) Source 
(Pretty s, Pretty a) => Pretty (Scalar s a) Source 

data Program s a Source

An entire program/function to find a fusion clustering for

Constructors

Program 

Fields

_ins :: ([s], [a])
 
_binds :: [Bind s a]
 
_outs :: ([s], [a])
 

Instances

(Show s, Show a) => Show (Program s a) Source 
(Pretty s, Pretty a) => Pretty (Program s a) Source 

data CName s a Source

Name of a combinator. This will also be the name of the corresponding node of the graph.

Constructors

NameScalar s 
NameArray a 

Instances

(Eq s, Eq a) => Eq (CName s a) Source 
(Ord s, Ord a) => Ord (CName s a) Source 
(Show s, Show a) => Show (CName s a) Source 
(Pretty s, Pretty a) => Pretty (CName s a) Source 

lookupA :: Eq a => Program s a -> a -> Maybe (ABind s a) Source

lookupS :: Eq s => Program s a -> s -> Maybe (SBind s a) Source

lookupB :: (Eq s, Eq a) => Program s a -> CName s a -> Maybe (Bind s a) Source

envOfBind :: Bind s a -> ([s], [a]) Source

freeOfBind :: Bind s a -> [CName s a] Source

outputsOfCluster :: (Eq s, Eq a) => Program s a -> [CName s a] -> [CName s a] Source

For a given program and list of nodes that will be clustered together, find a list of the nodes that are used afterwards. Only these nodes must be made manifest. The output nodes is a subset of the input cluster nodes.

inputsOfCluster :: (Eq s, Eq a) => Program s a -> [CName s a] -> [CName s a] Source

For a given program and list of nodes that will be clustered together, find a list of the nodes that are used as inputs. The input nodes will not mention any of the cluster nodes.

seriesInputsOfCluster :: (Eq s, Eq a) => Program s a -> [CName s a] -> [a] Source

For a given program and list of nodes that will be clustered together, find a list of the inputs that need to be converted to series. If the cluster is correct, these should all be the same size.