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

Safe HaskellNone
LanguageHaskell98

Sound.DF.Uniform.UDF

Contents

Description

Untyped DF.

Synopsis

Documentation

data R_Id Source

Recursion identifier.

Constructors

R_Id Id 

Instances

data UDF Source

Un-typed data-flow node. K = constant, A = array, R = recursion, P = primitive, MRG = multiple root graph.

Constructors

UDF_K 

Fields

udf_k :: K
 
UDF_A 

Fields

udf_a :: Vec Float
 
UDF_R R_Id (Either K (UDF, UDF)) 
UDF_P String TypeRep [UDF] 
UDF_MRG UDF UDF 

Instances

udf_concise :: UDF -> String Source

Concise pretty printer for UDF.

udf_k' :: UDF -> Maybe K Source

Maybe variant of udf_k.

udf_elem :: UDF -> [UDF] Source

List elements in left biased order.

udf_typeOf :: UDF -> TypeRep Source

Output type of UDF.

udf_traverse :: (st -> UDF -> (st, UDF)) -> st -> UDF -> (st, UDF) Source

Traversal with state, signature as mapAccumL.

Graph

type Port_Index = Int Source

Index for input port.

type Node = (Id, UDF) Source

A node is a UDF with associated Id.

data Edge_Ty Source

Enumeration of Edge types.

Constructors

Normal_Edge 
Rec_Wr_Edge Id

Edge to recWr node

Rec_Rd_Edge Id

Edge from recRd node

Implicit_Edge Int

Edge to recRd node (from recWr)

Instances

edge_ty_concise :: Edge_Ty -> String Source

Pretty printer for Edge_Ty, and Show instance.

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

Edge from left hand side node to right hand side port.

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

A graph is a list of Nodes and Edges.

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

A variant graph form associating the list of in edges with each Node.

label :: [Node] -> UDF -> Id Source

Read label of node.

source :: [Node] -> UDF -> Id Source

Transform node to source, see through UDF_R (rec) and UDF_MRG (mrg).

udf_edge_ty :: UDF -> Edge_Ty Source

Type of out edge of UDF.

edges :: [Node] -> UDF -> [Edge] Source

List incoming node edges.

match_rec :: R_Id -> Node -> Bool Source

True if Node is Right form of UDF_R with indicated R_Id.

implicit_edge :: [Node] -> Node -> Maybe Edge Source

Implicit edge from wR to rW.

is_orphan_edge :: [Node] -> Edge -> Bool Source

An Edge is orphaned if it refers to a Node that is not in the node list.

vgraph_impl :: Graph -> Graph Source

Transform the actual graph into a viewing graph by adding implicit edges from recWr to recRd nodes.

find_in_edge_m :: [Edge] -> (Id, Port_Index) -> Maybe Edge Source

Find edge with indicated right hand side port.

find_in_edge :: [Edge] -> (Id, Port_Index) -> Edge Source

Variant of find_in_edge_m that errors.

solve_rec_edge :: Int -> [Edge] -> (Id, Port_Index) -> (Int, Id) Source

Trace in edges until arrival at a Rec_Wr_Edge that is not proceeded by an Implicit_Edge. This traces the depth of the chain, however that is not currently drawn.

vgraph_direct :: Graph -> Graph Source

Transform the actual graph into a viewing graph by deleting recWr and recRd nodes and drawing a direct backward edge.

analyse :: [UDF] -> Analysis Source

Label nodes and list incoming edges. Multiple-root and multiple-channel nodes are erased.

analyse (udf_elem c)

graph :: UDF -> Graph Source

Generate graph (node list and edge list).

import Sound.DF.Uniform.GADT
import qualified Sound.DF.Uniform.UDF as U
let g = iir1 (0.0::Float) (+) 1
let c = df_erase g
map U.udf_concise (U.udf_elem c)
> [recWr,df_add:Float,1.0,recRd:0.0,df_add:Float,1.0,recRd:0.0]
U.vgraph_direct (U.graph c)
> ([(1,wR_1),(2,df_add:Float),(3,1.0),(4,rR_1:0.0)]
> ,[(2,1,0),(3,2,0),(4,2,1)])
U.draw c

FGL Graph

type Gr = Gr UDF (Port_Index, Edge_Ty) Source

FGL graph with UDF label.

type Gr' = Gr String (Port_Index, Edge_Ty) Source

FGL graph with pretty-printed UDF label.

udf_gr :: Graph -> Gr Source

Generate Gr.

udf_gr' :: Graph -> Gr' Source

Generate Gr'.

tsort :: UDF -> [UDF] Source

Topological sort of nodes (via udf_gr).

Code Gen

node_vars :: Node -> [Var] Source

List of required variable declarations.

node_c_call :: (Node, [Edge]) -> Maybe C_Call Source

Possible c-call code statement.

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

Constant nodes.

Graph Drawing

dot_ar :: [UDF] -> [Either Int K] Source

Make dot_rec arguments input.

dot_node :: Node -> String Source

Dot notation of Node.

edge_ty_colour :: Edge_Ty -> String Source

Edges are coloured according to their type.

dot_edge :: Edge -> String Source

Dot notation of Edge.

dot_graph :: Graph -> [String] Source

Dot notation of Graph.

dot_draw :: String -> IO () Source

View dot graph.

draw :: UDF -> IO () Source

Draw graph, transformed by vgraph_direct.

draw' :: UDF -> IO () Source

Draw graph, transformed by vgraph_impl.

Gr Drawing

gr_dot :: UDF -> String Source

Make dot rendering of graph at Node, via vgraph_direct.

gr_dot' :: UDF -> String Source

Make dot rendering of graph at Node, via vgraph_impl.

gr_draw :: UDF -> IO () Source

Draw graph, via gr_dot.

gr_draw' :: UDF -> IO () Source

Draw graph, via gr_dot'.

Audition

audition :: [Message] -> UDF -> IO () Source

Audition graph after sending initialisation messages.

audition_sc3 :: [Message] -> UDF -> IO () Source

Audition graph after sending initialisation messages.

audition_text :: Int -> UDF -> IO () Source

Audition at text-dl.