hdf-0.14: Haskell data flow library for audio processing

Safe HaskellNone

Sound.DF.Uniform.PhT.Node

Contents

Description

Data flow nodes.

Synopsis

Types

data KT ty Source

Constant with phantom type.

Constructors

KT 

Fields

kt_k :: K
 

Instances

Eq (KT ty) 

data DF ty Source

Data flow node with phantom type.

Constructors

DF 

Fields

df_udf :: UDF
 

Instances

Eq (DF ty) 
Floating (DF Float) 
Fractional (DF Float) 
Num n => Num (DF n) 
Eq a => Ord (DF a) 
Eq a => Bits (DF a) 

Construct, destruct & predicate

k_Int32 :: Int32 -> KT Int32Source

Lift Int32 to constant, ie. KT of I.

k_Float :: Float -> KT FloatSource

Lift Float to constant, ie. KT of F.

k_zero :: KT tySource

A zero with unresolved type, ie. KT of F of 0.

df_tbl_size :: DF a -> Maybe IntSource

Tables have a guard point.

mrg :: DF a -> DF () -> DF aSource

Multiple root graph.

Querying data type on ports

Operator cons

mk_a :: String -> [DF a] -> TypeRep -> DF tySource

DF of UDF_P.

unary_operator :: String -> DF a -> DF aSource

Primitive unary operator.

binary_operator :: String -> DF a -> DF a -> DF aSource

Primitive binary operator.

comparison_operator :: String -> DF a -> DF a -> DF BoolSource

Primitive comparator.

sink_node :: String -> [DF a] -> DF ()Source

Primitive sink.

alt_unary_operator :: (String, String) -> DF a -> DF aSource

Primitive unary operator with separate primitives for integral and floating types.

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

Lift list of float to DF Vec.

Ord

df_eq :: DF a -> DF a -> DF BoolSource

==, equal to.

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

<, less than.

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

>=, greater than or equal to.

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

>, greater than.

n_lte :: Num a => DF a -> DF a -> DF BoolSource

<=, less than or equal to.

RealFrac

df_floorf :: DF Float -> DF FloatSource

floorf(3)

df_lrintf :: DF Float -> DF Int32Source

lrintf(3)

df_roundf :: DF Float -> DF FloatSource

roundf(3)

Primitives

out1 :: DF Float -> DF ()Source

Single channel output.

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

Two channel output.

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

Three channel output.

ctl1 :: DF Int32 -> DF FloatSource

Single control input.

select2 :: 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.

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 write.

Backward arcs

rec_r :: R_Id -> KT a -> (DF a -> (DF a, DF a)) -> DF aSource

Introduce backward arc with implicit unit delay.

rec :: UId m => KT a -> (DF a -> (DF a, DF a)) -> m (DF a)Source

Monadic variant of rec_r.

recm :: UId m => KT a -> (DF a -> m (DF a, DF a)) -> m (DF a)Source

Variant or rec with monadic action in backward arc.