hdf-0.11: Haskell data flow library for audio processing

Sound.DF.Node

Contents

Description

Data flow nodes.

Synopsis

The Node data type

data R_ID Source

Recursion identifer.

Constructors

R_ID Int 

Instances

data Type Source

Enumeration of types of data on ports.

Instances

data Constant Source

Constant values.

Instances

Eq Constant 
Show Constant

How to display constants.

data Port Source

Port meta data.

Constructors

Port 

Instances

data Node Source

Data flow node.

Constructors

S 

Fields

constant :: Constant
 
A 

Fields

operator :: String
 
inputs :: [Node]
 
outputs :: [Port]
 
R 
P 

Fields

proxy :: Node
 
port :: Int
 
M 

Fields

mleft :: Node
 
mright :: Node
 

Instances

Eq Node 
Floating Node 
Fractional Node 
Num Node 
Ord Node 
Show Node

How to display nodes.

type NodeID = IntSource

Node identifier.

type PortID = IntSource

Port identifier.

mrg :: Node -> Node -> NodeSource

Multiple root graph (alias for M).

Querying data type on ports

constant_type :: Constant -> TypeSource

Type of a constant value.

node_type :: Node -> TypeSource

Type of a node.

Numeric primitives for class instances

n_real_constant :: Double -> NodeSource

Lift constant to node.

n_integer_constant :: Int -> NodeSource

Lift constant to node.

numerical_unary_operator :: String -> Node -> NodeSource

Unary operator over Real and Integer values.

numerical_binary_operator :: String -> Node -> Node -> NodeSource

Binary operator over Real and Integer values.

real_unary_operator :: String -> Node -> NodeSource

Unary operator over Real values.

real_binary_operator :: String -> Node -> Node -> NodeSource

Binary operator over Real values.

n_add :: Node -> Node -> NodeSource

Addition.

n_mul :: Node -> Node -> NodeSource

Multiplication.

n_sub :: Node -> Node -> NodeSource

Subtraction.

n_negate :: Node -> NodeSource

Negation.

n_abs :: Node -> NodeSource

Absolute value.

n_signum :: Node -> NodeSource

Sign of.

n_div :: Node -> Node -> NodeSource

Division.

n_recip :: Node -> NodeSource

Reciprocal.

n_exp :: Node -> NodeSource

Natural exponential.

n_sqrt :: Node -> NodeSource

Square root.

n_log :: Node -> NodeSource

Natural logarithm.

n_pow :: Node -> Node -> NodeSource

p to the power of q.

n_sin :: Node -> NodeSource

Sine.

n_cos :: Node -> NodeSource

Cosine.

n_tan :: Node -> NodeSource

Tangent.

numerical_comparison_operator :: String -> Node -> Node -> NodeSource

Operator from Real or Integer values to a Boolean value.

n_lt :: Node -> Node -> NodeSource

Less than.

n_gte :: Node -> Node -> NodeSource

Greater than or equal to.

n_gt :: Node -> Node -> NodeSource

Greater than.

n_lte :: Node -> Node -> NodeSource

Less than or equal to.

n_max :: Node -> Node -> NodeSource

Maximum.

n_min :: Node -> Node -> NodeSource

Minimum.

n_floor :: Node -> NodeSource

Real valued floor.

n_lrint :: Node -> NodeSource

Integer valued floor.

class Monad m => ID m whereSource

Class of monads generating identifers

Methods

generateID :: m IntSource

Instances

ID IO 

Backward arcs

rec_r :: R_ID -> Constant -> (Node -> (Node, Node)) -> NodeSource

Introduce backward arc with implicit unit delay.

rec :: ID m => Constant -> (Node -> (Node, Node)) -> m NodeSource

Monadic variant of rec_r.

recm :: ID m => Constant -> (Node -> m (Node, Node)) -> m NodeSource

Variant or rec with monadic action in backward arc.