hdf-0.14: Haskell data flow library for audio processing

Safe HaskellNone

Sound.DF.Uniform.GADT.DF

Contents

Description

Data flow nodes.

Synopsis

DF

data DF a whereSource

Data flow node.

Constructors

K :: K' a => a -> DF a 
A :: Vec Float -> DF (Vec Float) 
R :: K' a => R_Id -> TypeRep -> Either a (DF b, DF a) -> DF b 
P0 :: K' a => String -> TypeRep -> DF a 
P1 :: (K' a, K' b) => String -> TypeRep -> DF a -> DF b 
P2 :: (K' a, K' b, K' c) => String -> TypeRep -> DF a -> DF b -> DF c 
P3 :: (K' a, K' b, K' c, K' d) => String -> TypeRep -> DF a -> DF b -> DF c -> DF d 
M :: K' a => DF a -> DF () -> DF a 

Instances

Floating (DF Float) 
Fractional (DF Float) 
K_Num a => Num (DF a) 
Show a => Show (DF a) 
K' a => Typeable (DF a) 

df_typeOf :: K' a => DF a -> TypeRepSource

Typeable instance for DF.

 df_typeOf (C (undefined::Int32)) == int32_t
 df_typeOf (C (undefined::Float)) == float_t
 df_typeOf (A undefined) == vec_float_t
 df_typeOf (0::DF Int32) == int32_t
 df_typeOf (0.0::DF Float) == float_t

df_primitive :: DF a -> Maybe StringSource

Name of primitive if DF is P0 or P1 etc.

MRG

mrg :: K' a => DF a -> DF () -> DF aSource

Multiple root graph (alias for M).

DF Vec

df_vec :: V_Id -> [Float] -> DF (Vec Float)Source

DF Vec constructor.

df_vec_m :: UId m => [Float] -> m (DF (Vec Float))Source

Monadic DF Vec constructor.

df_tbl_size :: DF a -> Maybe IntSource

df_vec_size variant, tables have a guard point.

Operator types

type Unary_Op a = a -> aSource

Unary operator.

type Binary_Op a = a -> a -> aSource

Binary operator.

type Ternary_Op a = a -> a -> a -> aSource

Ternary operator.

type Quaternary_Op a = a -> a -> a -> a -> aSource

Quaternary operator.

type Quinary_Op a = a -> a -> a -> a -> a -> aSource

Quinary operator.

type Senary_Op a = a -> a -> a -> a -> a -> a -> aSource

Senary operator.

Uniform function types

type Binary_Fn i o = i -> i -> oSource

Binary function.

Primitive constructors

mk_uop :: K' a => String -> Unary_Op (DF a)Source

Unary operator.

mk_binop :: K' a => String -> Binary_Op (DF a)Source

Binary operator.

mk_ternaryop :: K' a => String -> Ternary_Op (DF a)Source

Binary operator.

df_mul_add :: K_Num a => DF a -> DF a -> DF a -> DF aSource

DF multiply and add.

df_add_optimise :: K_Num a => DF a -> DF a -> DF aSource

Optimising addition primitive. If either input is a multiplier node, unfold to a multiplier-add node.

 df_add_optimise (2 * 3) (4::DF Int32)
 df_add_optimise (2::DF Int32) (3 * 4)

Bits

Ord

df_eq :: K_Ord a => DF a -> DF a -> DF BoolSource

==, equal to.

df_lt :: K_Ord a => DF a -> DF a -> DF BoolSource

<, less than.

df_gte :: K_Ord a => DF a -> DF a -> DF BoolSource

>=, greater than or equal to.

df_gt :: K_Ord a => DF a -> DF a -> DF BoolSource

>, greater than.

df_lte :: K_Ord a => DF a -> DF a -> DF BoolSource

<=, less than or equal to.

df_max :: K_Ord a => DF a -> DF a -> DF aSource

max, select maximum.

df_min :: K_Ord a => DF a -> DF a -> DF aSource

min, select minimum.

Cast

df_float_to_int32 :: DF Float -> DF Int32Source

Cast floating point to integer.

df_int32_to_float :: DF Int32 -> DF FloatSource

Cast integer to floating point.

i32_to_normal_f32 :: DF Int32 -> DF FloatSource

Scale Int32 to (-1,1) normalised Float.

 maxBound == (2147483647::Int32)

Integral

df_mod :: Binary_Op (DF Int32)Source

Integral modulo, ie. mod.

df_fmodf :: Binary_Op (DF Float)Source

Floating point modulo, ie. Foreign.C.Math fmodf.

RealFrac

df_ceilf :: DF Float -> DF FloatSource

ceilf(3)

df_floorf :: DF Float -> DF FloatSource

floorf(3)

df_lrintf :: DF Float -> DF Int32Source

lrintf(3)

df_roundf :: DF Float -> DF FloatSource

roundf(3)

Backward arcs

rec_r :: K' a => R_Id -> a -> (DF a -> (DF b, DF a)) -> DF bSource

Introduce backward arc with implicit unit delay.

The function receives the previous output as input, initially y0, and returns a (feed-forward,feed-backward) pair.

 rec_r (R_Id 0) (0::Int) ((\i->(i,i)) . (+) 1)
 rec_r (R_Id 0) (0.0::Float) ((\i->(i,i)) . (+) 1.0)

rec_m :: (K' a, UId m) => a -> (DF a -> (DF b, DF a)) -> m (DF b)Source

Monadic variant of rec_r.

rec_h :: (K' a, Show b) => a -> (DF a -> (DF b, DF a)) -> DF bSource

Hash-eq variant of rec_r.

rec_mM :: (K' a, UId m) => a -> (DF a -> m (DF b, DF a)) -> m (DF b)Source

Variant of rec_m with monadic action in backward arc.

Primitives

in1 :: DF FloatSource

Single channel input (channel 0).

out1 :: DF Float -> DF ()Source

Single channel output (channel 0).

out2 :: DF Float -> DF Float -> DF ()Source

Two channel output (channels 1 & 2).

out3 :: DF Float -> DF Float -> DF Float -> DF ()Source

Three channel output.

ctl1 :: DF Int32 -> DF FloatSource

Single control input.

df_and :: DF Bool -> DF Bool -> DF BoolSource

Logical &&.

df_or :: DF Bool -> DF Bool -> DF BoolSource

Logical ||.

df_not :: DF Bool -> DF BoolSource

Logical not.

select2 :: K' a => DF Bool -> DF a -> DF a -> DF aSource

If p then q else r. p must have type bool, and q and r must have equal types.

w_sample_rate :: DF FloatSource

Operating sample rate.

w_kr_nframes :: DF Int32Source

Number of frames in current control period.

w_kr_edge :: DF BoolSource

True at first frame of each control period.

b_read :: DF Int32 -> DF Int32 -> DF FloatSource

Buffer read, read from buffer p at index q.

b_write :: DF Int32 -> DF Int32 -> DF Float -> DF ()Source

Buffer write, write to buffer p at index q value r.

a_read :: DF (Vec Float) -> DF Int32 -> DF FloatSource

Array read.

a_write :: DF (Vec Float) -> DF Int32 -> DF Float -> DF ()Source

Array writ.

Untyped

df_erase :: K' a => DF a -> UDFSource

Transform typed DF to un-typed UDF.