hdf-0.7: Haskell data flow library for audio processing

Sound.DF

Contents

Synopsis

Interaction with jack.dl server

b_alloc :: Int -> Int -> OSCSource

Allocate buffer.

g_load :: Int -> String -> OSCSource

Load graph.

g_unload :: Int -> OSCSource

Load graph.

with_jack_dl :: (UDP -> IO a) -> IO aSource

Run action with UDP link to jack.dl.

audition :: [OSC] -> Node -> IO ()Source

Audition graph n after sending initialisation messages is.

C code generator

code_gen :: Node -> StringSource

Generate C code for graph.

dl_gen :: FilePath -> Node -> IO ()Source

Generate C code, write file disk and call GNU C compiler to build shared library.

Graph drawing

view :: Node -> IO ()Source

Draw graph using graphviz.

Graph analysis

nodes :: Node -> [Node]Source

List of nodes, in left biased order.

label :: [(NodeID, Node)] -> Node -> NodeIDSource

Read label of node.

source :: [(NodeID, Node)] -> Node -> (NodeID, PortID)Source

Transform node to source, see through rec_r and proxy and mrg.

type Edge = ((NodeID, PortID), (NodeID, PortID))Source

Edge between ports.

edges :: [(NodeID, Node)] -> Node -> [Edge]Source

List incoming node edges,

analyse :: [Node] -> [((NodeID, Node), [Edge])]Source

Label nodes and list edges. Proxy and multiple-root nodes are erased.

mod_e :: Edge -> (NodeID, NodeID, (PortID, PortID))Source

Transform edge into form required by fgl.

graph :: Node -> Gr Node (PortID, PortID)Source

Generate graph.

tsort :: Node -> [Node]Source

Topological sort of nodes (via graph).

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 of monads generating identifers

class Monad m => ID m whereSource

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.

Primitive unit generators

uniform_operator :: Type -> Int -> String -> [Node] -> NodeSource

Uniform input type operator.

out1 :: Node -> NodeSource

Single channel output.

out2 :: (Node, Node) -> NodeSource

Two channel output.

out3 :: (Node, Node, Node) -> NodeSource

Three channel output.

sample_rate :: NodeSource

Operating sample rate.

eq :: Node -> Node -> NodeSource

Equal to.

select2 :: Node -> Node -> Node -> NodeSource

If p then q else r.

logical_operator :: String -> Node -> Node -> NodeSource

Binary boolean valued operator.

n_and :: Node -> Node -> NodeSource

Logical and.

n_or :: Node -> Node -> NodeSource

Logical or.

b_read :: Node -> Node -> NodeSource

Buffer read.

b_write :: Node -> Node -> Node -> NodeSource

Buffer write.

white_noise_u :: Node -> NodeSource

White noise (0, 1).

Ordinary unit generators

pan2 :: Node -> Node -> (Node, Node)Source

Linear pan.

swap :: a -> b -> (b, a)Source

Reversed tuple constructor, (ie. flip (,))

split :: a -> (a, a)Source

Duplicate a value into a tuple.

unit_delay :: ID m => Constant -> Node -> m NodeSource

Single sample delay with indicated initial value.

iir1 :: ID m => Constant -> (Node -> Node -> Node) -> Node -> m NodeSource

Single place infinte impulse response filter with indicated initial value.

iir2 :: ID m => (Node -> Node -> Node -> Node) -> Node -> m NodeSource

Two place infinte impulse response filter.

fir1 :: ID m => (Node -> Node -> Node) -> Node -> m NodeSource

Single place finte impulse response filter.

fir2 :: ID m => (Node -> Node -> Node -> Node) -> Node -> m NodeSource

Two place finte impulse response filter.

biquad :: ID m => (Node -> Node -> Node -> Node -> Node -> Node) -> Node -> m NodeSource

Ordinary biquad filter section.

counter :: ID m => Constant -> Node -> m NodeSource

Counter from indicated initial value.

radians_per_sample :: NodeSource

Environment value, equal to two_pi / sample_rate.

hz_to_incr :: Node -> Node -> Node -> NodeSource

r = cycle (two-pi), hz = frequency, sr = sample rate

two_pi :: Floating a => aSource

Two pi.

clipr :: Node -> Node -> NodeSource

If 'q >= p' then 'q - p' else q.

phasor :: ID m => Constant -> Node -> Node -> m NodeSource

r = right hand edge, ip = initial phase, x = increment

sin_osc :: ID m => Node -> Double -> m NodeSource

Sine oscillator, f = frequency in hz.

lf_saw :: ID m => Node -> Double -> m NodeSource

Non-band limited sawtooth oscillator.

lf_pulse :: ID m => Node -> Double -> Node -> m NodeSource

Non-band limited pulse oscillator, w = width (0,1).

midi_cps :: Floating a => a -> aSource

Midi note number to cycles per second.

mul_add :: Num a => a -> a -> a -> aSource

Multiply and add.

calc_fb :: Floating a => a -> a -> aSource

delay :: ID m => Node -> Node -> Node -> m NodeSource

Delay.

buf_comb_n :: ID m => Node -> Node -> Node -> Node -> m NodeSource

Comb filter.

rlpf :: ID m => Node -> Node -> Node -> m NodeSource

Resonant low pass filter, f = frequency, r = resonance.

clip2 :: Node -> Node -> NodeSource

Constrain p in (-q, q).

white_noise :: Node -> NodeSource

White noise (-1, 1).

white_noise_m :: ID m => m NodeSource

White noise (-1, 1).

brown_noise_m :: ID m => m NodeSource

Brown noise (-1, 1).

bpz2 :: ID m => Node -> m NodeSource

Two zero fixed midpass filter.

brz2 :: ID m => Node -> m NodeSource

Two zero fixed midcut filter.

lpz1 :: ID m => Node -> m NodeSource

Two point average filter

lpz2 :: ID m => Node -> m NodeSource

Two zero fixed lowpass filter

one_pole :: ID m => Node -> Node -> m NodeSource

One pole filter.

one_zero :: ID m => Node -> Node -> m NodeSource

One zero filter.

sos :: ID m => Node -> Node -> Node -> Node -> Node -> Node -> m NodeSource

Second order filter section.

impulse :: ID m => Node -> Double -> m NodeSource

Impulse oscillator (non band limited).

resonz :: ID m => Node -> Node -> Node -> m NodeSource

Two pole resonant filter.

latch :: ID m => Node -> Node -> m NodeSource

Sample and hold.

lin_lin :: Fractional a => a -> a -> a -> a -> a -> aSource

Linear range conversion.

lin_exp :: Floating a => a -> a -> a -> a -> a -> aSource

Exponential range conversion.

decay :: ID m => Node -> Node -> m NodeSource

Exponential decay.

decay2 :: ID m => Node -> Node -> Node -> m NodeSource

Exponential decay (equvalent to decay dcy - decay atk).

delay1 :: ID m => Node -> m NodeSource

Single sample delay.

delay2 :: ID m => Node -> m NodeSource

Two sample delay.

lag :: ID m => Node -> Node -> m NodeSource

Simple averaging filter.

lag2 :: ID m => Node -> Node -> m NodeSource

Nested lag filter.

lag3 :: ID m => Node -> Node -> m NodeSource

Twice nested lag filter.