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

Safe HaskellNone
LanguageHaskell98

Sound.DF.Uniform.Faust

Contents

Description

Faust signal processing block diagram model.

Synopsis

Block diagram data type

type Rec_Id = (Id, Id, TypeRep) Source

The write and read Ids, and the wire type.

data BD Source

Block diagram.

Constructors

Constant (Maybe Id) K 
Prim (Maybe Id) String [TypeRep] (Maybe TypeRep) 
Par BD BD infixl 3 
Seq BD BD infixl 2 
Split BD BD 
Rec (Maybe [Rec_Id]) BD BD 

Instances

Identifiers

bd_id :: BD -> Maybe Id Source

Read identifier.

bd_req_id :: BD -> Id Source

Erroring bd_id.

Pretty printing

bd_pp :: BD -> String Source

Pretty printer for BD.

Diagram types and signature

bd_signature :: BD -> ([TypeRep], [TypeRep]) Source

Diagram type signature, ie. port_ty at ports.

bd_ty :: BD -> [TypeRep] Source

Type of output ports of BD.

bd_ty_uniform :: BD -> Maybe TypeRep Source

Type of uniform output ports of BD.

bd_ty1 :: BD -> Maybe TypeRep Source

Type of singular output port of BD.

Operator synonyms

(~~) :: BD -> BD -> BD infixl 4 Source

Faust uses single tilde, which is reserved by GHC.Exts.

(~.) :: BD -> BD -> BD infixl 3 Source

Faust uses comma, which is reserved by Data.Tuple, and indeed ~, is not legal either.

(~:) :: BD -> BD -> BD infixl 2 Source

Faust uses :, which is reserved by Data.List.

(~<:) :: BD -> BD -> BD infixl 1 Source

Faust uses <:, which is legal, however see ~:>.

(~:>) :: BD -> BD -> BD infixl 1 Source

Faust uses :>, however : is not allowed as a prefix.

draw (graph (par_l [1,2,3,4] ~:> i_mul))
draw (graph (par_l [1,2,3] ~:> i_negate))

Fold and traverse

bd_foldl :: (t -> BD -> t) -> t -> BD -> t Source

Fold over BD, signature as foldl.

bd_traverse :: (st -> BD -> (st, BD)) -> st -> BD -> (st, BD) Source

Traversal with state, signature as mapAccumL.

Introduce node identifiers

rec_ids :: Id -> Int -> [TypeRep] -> [Rec_Id] Source

Rec nodes introduce identifiers for each backward arc. k is the initial Id, n the number of arcs, and ty the arc types.

rec_ids 5 2 [int32_t,float_t] == [(5,6,int32_t),(7,8,float_t)]

bd_set_id :: BD -> (Id, BD) Source

Set identifiers at Constant, Prim, and Rec nodes.

Degree

type Degree = (Int, Int) Source

Node degree as (input,output) pair.

degree :: BD -> Degree Source

Degree of block diagram BD.

Ports

type Port_Index = Int Source

The index of an Input_Port, all outputs are unary.

data Port Source

Port (input or output) at block diagram.

Constructors

Input_Port 
Output_Port 

Fields

port_bd :: BD
 

Instances

ports :: BD -> ([Port], [Port]) Source

The left and right outer ports of a block diagram.

Wires

data Wire_Ty Source

Enumeration of wire types.

Constructors

Normal

Normal forward edge.

Backward Rec_Id

Backward edge.

Implicit_Normal

Implicit wire from recRd to node.

Implicit_Rec

Implicit wire from node to recWr.

Implicit_Backward

Implicit wire from recWr to recRd.

Instances

type Wire = (Port, Port, Wire_Ty) Source

A Wire runs between two Ports.

normal_wires :: [Port] -> [Port] -> [Wire] Source

Set of Normal wires between Ports.

rec_back_wires :: [Rec_Id] -> [Port] -> [Port] -> [Wire] Source

Set of Backward wires between Ports.

wires_immed :: BD -> [Wire] Source

Immediate internal wires of a block diagram.

wires :: BD -> [Wire] Source

Internal wires of a block diagram.

Coherence

wire_coheres :: Wire -> Bool Source

A wire coheres if the port_ty of the left and right hand sides are equal.

bd_non_coherent :: BD -> [Wire] Source

The set of non-coherent wires at diagram.

bd_is_coherent :: BD -> Bool Source

Coherence predicate, ie. is bd_non_coherent empty.

Graph

data Node Source

Primitive block diagram elements.

Instances

actual_id :: Either Id (Id, Id) -> Id Source

Extract the current actual node id from n_prim_id.

node_ty :: Node -> Maybe TypeRep Source

Output type of Node, if out degree non-zero.

node_lift_id :: Node -> (Id, Node) Source

Pair Node Id with node.

node_pp :: Node -> String Source

Pretty printer, and Show instance.

type Edge = (Id, Id, (Port_Index, Wire_Ty)) Source

Primitive edge, left hand Id, right hand side Id, right hand Port_Index and edge type.

type Graph = ([Node], [Edge]) Source

A graph is a list of Node and a list of Edges.

rec_nodes :: [Rec_Id] -> [Node] Source

Implicit rec nodes.

nodes :: Bool -> BD -> [Node] Source

Collect all primitive nodes at a block diagram.

wire_to_edges :: Bool -> Wire -> [Edge] Source

A backward Wire will introduce three implicit edges, a Normal wire introduces one Normal edge.

graph' :: Bool -> BD -> Graph Source

Construct Graph of block diagram, either with or without implicit edges.

graph :: BD -> Graph Source

Construct Graph of block diagram without implicit edges. This graph will include backward arcs if the graph contains recs.

Gr

type Gr = Gr Node (Port_Index, Wire_Ty) Source

FGL graph of BD.

gr :: BD -> Gr Source

Transform BD to Gr.

tsort :: BD -> Graph Source

Topological sort of nodes (via gr).

gr_dot :: BD -> String Source

Make dot rendering of graph at Node.

Drawing

dot_node :: Node -> String Source

Dot description of Node.

wire_colour :: Wire_Ty -> String Source

Wires are coloured according to type.

dot_edge :: Edge -> String Source

Dot description of Edge.

dot_graph :: Graph -> [String] Source

Dot description of Graph.

draw_dot :: String -> IO () Source

Draw dot graph.

Composition

par_l :: [BD] -> BD Source

Fold of Par.

degree (par_l [1,2,3,4]) == (0,4)
draw (graph (par_l [1,2,3,4] ~:> i_mul))

bd_sum :: [BD] -> BD Source

Type-directed sum.

draw (graph (bd_sum [1,2,3,4]))

split_r :: BD -> BD -> Bool Source

Predicate to determine if p can be split onto q.

split_m :: BD -> BD -> Maybe BD Source

split if diagrams cohere.

split :: BD -> BD -> BD infixl 1 Source

split if diagrams cohere, else error. Synonym of ~<:.

merge_degree :: BD -> BD -> Maybe Int Source

If merge is legal, the number of in-edges per port at q.

merge_degree (par_l [1,2,3]) i_negate == Just 3
merge_degree (par_l [1,2,3,4]) i_mul == Just 2

merge_m :: BD -> BD -> Maybe BD Source

merge if diagrams cohere.

merge_m (par_l [1,2,3]) i_negate
merge_m (par_l [1,2,3,4]) i_mul

merge :: BD -> BD -> BD infixl 1 Source

merge if diagrams cohere, else error. Synonym of ~:>.

rec_r :: BD -> BD -> Bool Source

Predicate to determine if p can be rec onto q.

rec_m :: BD -> BD -> Maybe BD Source

rec if diagrams cohere.

rec :: BD -> BD -> BD infixl 4 Source

rec if diagrams cohere, else error. Synonym of ~~.

Constants

i_constant :: Int -> BD Source

Integer constant.

r_constant :: Float -> BD Source

Real constant.

Primitives

u_prim :: TypeRep -> String -> Int -> BD Source

Construct uniform type primitive diagram.

i_add :: BD Source

Adddition, ie. + of Num.

(1 ~. 2) ~: i_add
(1 :: BD) + 2

r_add :: BD Source

Adddition, ie. + of Num.

(1 ~. 2) ~: i_add
(1 :: BD) + 2

i_sub :: BD Source

Subtraction, ie. - of Num.

r_sub :: BD Source

Subtraction, ie. - of Num.

i_mul :: BD Source

Multiplication, ie. * of Num.

r_mul :: BD Source

Multiplication, ie. * of Num.

i_div :: BD Source

Division, ie. div of Integral.

r_div :: BD Source

Division, ie. / of Fractional.

i_abs :: BD Source

Absolute value, ie. abs of Num.

r_abs :: BD Source

Absolute value, ie. abs of Num.

i_negate :: BD Source

Negation, ie. negate of Num.

r_negate :: BD Source

Negation, ie. negate of Num.

i_identity :: BD Source

Identity diagram.

r_identity :: BD Source

Identity diagram.

i32_to_normal_f32 :: BD Source

int32_to_float and then scale to be in (-1,1).

out1 :: BD Source

Single channel output.

degree out1 == (1,0)
bd_signature out1 == ([float_t],[])

Type following primitives

ty_uop :: (BD -> Maybe TypeRep) -> t -> t -> BD -> t Source

Type following unary operator.

ty_binop :: (BD -> Maybe TypeRep) -> t -> t -> BD -> BD -> t Source

Type following binary operator.

ty_add :: BD -> BD -> BD Source

Type following math operator, uniform types.

1.0 `ty_add` 2.0 == r_add
(1 ~. 2) `ty_add` (3 ~. 4) == i_add
1.0 `ty_add` 2 == _|_
draw (graph ((1 ~. 2) - (3 ~. 4)))

ty_div :: BD -> BD -> BD Source

Type following math operator, uniform types.

1.0 `ty_add` 2.0 == r_add
(1 ~. 2) `ty_add` (3 ~. 4) == i_add
1.0 `ty_add` 2 == _|_
draw (graph ((1 ~. 2) - (3 ~. 4)))

ty_mul :: BD -> BD -> BD Source

Type following math operator, uniform types.

1.0 `ty_add` 2.0 == r_add
(1 ~. 2) `ty_add` (3 ~. 4) == i_add
1.0 `ty_add` 2 == _|_
draw (graph ((1 ~. 2) - (3 ~. 4)))

ty_sub :: BD -> BD -> BD Source

Type following math operator, uniform types.

1.0 `ty_add` 2.0 == r_add
(1 ~. 2) `ty_add` (3 ~. 4) == i_add
1.0 `ty_add` 2 == _|_
draw (graph ((1 ~. 2) - (3 ~. 4)))

ty_add1 :: BD -> BD -> BD Source

Type following math operator, singular types.

1.0 `ty_add1` 2.0 == r_add
1.0 `ty_add1` 2 == _|_

ty_div1 :: BD -> BD -> BD Source

Type following math operator, singular types.

1.0 `ty_add1` 2.0 == r_add
1.0 `ty_add1` 2 == _|_

ty_mul1 :: BD -> BD -> BD Source

Type following math operator, singular types.

1.0 `ty_add1` 2.0 == r_add
1.0 `ty_add1` 2 == _|_

Code Gen

cg_k :: [Node] -> [(Id, K)] Source

List of constants for CGen.

node_output :: Node -> Maybe (Var_Ty, Id) Source

Output reference for Node.

node_inputs :: [Edge] -> Node -> [(Var_Ty, Id)] Source

Input references for Node.

Audition

audition_rju :: [Message] -> BD -> IO () Source

Audition graph after sending initialisation messages.

Figures from Quick Reference

fig_3_2 :: BD Source

Figure illustrating ~..

degree fig_3_2 == (2,2)
draw (graph fig_3_2)

fig_3_3 :: BD Source

Figure illustrating ~:.

degree fig_3_3 == (4,1)
bd_signature fig_3_3
draw (graph fig_3_3)

fig_3_4 :: BD Source

Figure illustrating ~<:.

degree fig_3_4 == (0,3)
draw (graph fig_3_4)

fig_3_5 :: BD Source

Figure illustrating ~:>.

degree fig_3_5 == (0,1)
draw (graph fig_3_5)

fig_3_6 :: BD Source

Figure illustrating ~~.

degree fig_3_6 == (0,1)
draw (graph fig_3_6)

fig_3_6' :: BD Source

Variant generating audible graph.

draw (graph fig_3_6')
gr_draw fig_3_6'
audition [] fig_3_6'

i_counter :: BD Source

A counter, illustrating identity diagram.

draw (graph (i_counter ~: i_negate))
gr_draw (i_counter ~: i_negate)

List

adjacent :: [t] -> [(t, t)] Source

Adjacent elements of list.

adjacent [1..4] == [(1,2),(3,4)]

Tuple

bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) Source

Bimap at tuple.

bimap abs negate (-1,1) == (1,-1)