hdf-0.15: HDF: Uniform Rate Audio Signal Processing in Haskell

Safe HaskellNone
LanguageHaskell98

Sound.DF.Uniform.GADT.DF

Contents

Description

Data flow nodes.

Synopsis

DF

data DF a where Source

Data flow node. K = constant, A = array, R = recursion, P = primitive, MRG = mrg.

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 
MCE :: [DF a] -> DF a 
MRG :: 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) 
Typeable (* -> *) DF 

df_typeOf :: K' a => DF a -> TypeRep Source

Typeable instance for DF.

df_typeOf (K (undefined::Int32)) == int32_t
df_typeOf (K (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 String Source

Name of primitive if DF is P0 or P1 etc.

MRG

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

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 Int Source

df_vec_size variant, tables have a guard point.

Operator types

type Unary_Op a = a -> a Source

Unary operator.

type Binary_Op a = a -> a -> a Source

Binary operator.

type Ternary_Op a = a -> a -> a -> a Source

Ternary operator.

type Quaternary_Op a = a -> a -> a -> a -> a Source

Quaternary operator.

type Quinary_Op a = a -> a -> a -> a -> a -> a Source

Quinary operator.

type Senary_Op a = a -> a -> a -> a -> a -> a -> a Source

Senary operator.

Uniform function types

type Binary_Fn i o = i -> i -> o Source

Binary function.

MCE

is_mce :: DF t -> Bool Source

MCE predicate, sees into MRG.

mce_degree :: DF t -> Int Source

MCE degree, sees into MRG.

mce_extend :: Int -> DF t -> [DF t] Source

MCE extension, sees into MRG, will not reduce.

mce2 :: DF a -> DF a -> DF a Source

unmce :: DF t -> [DF t] Source

unmce2 :: Show t => DF t -> (DF t, DF t) Source

lift_mce :: (DF a -> DF b) -> DF a -> DF b Source

lift_mce2 :: (DF a -> DF b -> DF c) -> DF a -> DF b -> DF c Source

mce_extend3 :: DF a -> DF b -> DF c -> ([DF a], [DF b], [DF c]) Source

lift_mce3 :: (DF a -> DF b -> DF c -> DF d) -> DF a -> DF b -> DF c -> DF d Source

Primitive constructors

mk_p1 :: (K' a, K' b) => String -> TypeRep -> DF a -> DF b Source

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

Unary operator.

mk_p2 :: (K' a, K' b, K' c) => String -> TypeRep -> DF a -> DF b -> DF c Source

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

Binary operator.

mk_p3 :: (K' a, K' b, K' c, K' d) => String -> TypeRep -> DF a -> DF b -> DF c -> DF d Source

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 a Source

DF multiply and add.

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

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 Bool Source

==, equal to.

df_lt :: K_Ord a => DF a -> DF a -> DF Bool Source

<, less than.

df_gte :: K_Ord a => DF a -> DF a -> DF Bool Source

>=, greater than or equal to.

df_gt :: K_Ord a => DF a -> DF a -> DF Bool Source

>, greater than.

df_lte :: K_Ord a => DF a -> DF a -> DF Bool Source

<=, less than or equal to.

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

max, select maximum.

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

min, select minimum.

Cast

df_float_to_int32 :: DF Float -> DF Int32 Source

Cast floating point to integer.

df_int32_to_float :: DF Int32 -> DF Float Source

Cast integer to floating point.

i32_to_normal_f32 :: DF Int32 -> DF Float Source

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 Float Source

ceilf(3)

df_floorf :: DF Float -> DF Float Source

floorf(3)

df_lrintf :: DF Float -> DF Int32 Source

lrintf(3), ie. round to nearest integer.

df_roundf :: DF Float -> DF Float Source

roundf(3)

Backward arcs

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

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::Int32) ((\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 b Source

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 Float Source

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.

out :: DF Float -> DF () Source

MCE collapsing output.

ctl1 :: DF Int32 -> DF Float Source

Single control input.

df_and :: DF Bool -> DF Bool -> DF Bool Source

Logical &&.

df_or :: DF Bool -> DF Bool -> DF Bool Source

Logical ||.

df_not :: DF Bool -> DF Bool Source

Logical not.

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

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

w_sample_rate :: DF Float Source

Operating sample rate.

w_kr_nframes :: DF Int32 Source

Number of frames in current control period.

w_kr_edge :: DF Bool Source

True at first frame of each control period.

b_read :: DF Int32 -> DF Int32 -> DF Float Source

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 Float Source

Array read.

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

Array write.

Untyped

df_erase :: K' a => DF a -> UDF Source

Transform typed DF to un-typed UDF.