hsc3-0.20: Haskell SuperCollider
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.Sc3.Ugen.Graph

Description

U_Graph and related types.

The Ugen type is recursive, inputs to Ugens are Ugens.

This makes writing Ugen graphs simple, but manipulating them awkward.

Ugen equality is structural, and can be slow to determine for some Ugen graph structures.

A U_Node is a non-recursive notation for a Ugen, all U_Nodes have unique identifiers.

A U_Graph is constructed by a stateful traversal of a Ugen.

A U_Graph is represented as a partioned (by type) set of U_Nodes, edges are implicit.

Synopsis

Types

type Port_Index = Int Source #

Port index.

data From_Port Source #

Type to represent the left hand side of an edge in a unit generator graph. C = constant, K = control, U = ugen.

Instances

Instances details
Show From_Port Source # 
Instance details

Defined in Sound.Sc3.Ugen.Graph

Eq From_Port Source # 
Instance details

Defined in Sound.Sc3.Ugen.Graph

data To_Port Source #

A destination port.

Constructors

To_Port 

Instances

Instances details
Show To_Port Source # 
Instance details

Defined in Sound.Sc3.Ugen.Graph

Eq To_Port Source # 
Instance details

Defined in Sound.Sc3.Ugen.Graph

Methods

(==) :: To_Port -> To_Port -> Bool #

(/=) :: To_Port -> To_Port -> Bool #

type U_Edge = (From_Port, To_Port) Source #

A connection from From_Port to To_Port.

data U_Node Source #

Sum-type to represent nodes in unit generator graph. _C = constant, _K = control, _U = ugen, _P = proxy.

Instances

Instances details
Show U_Node Source # 
Instance details

Defined in Sound.Sc3.Ugen.Graph

Eq U_Node Source # 
Instance details

Defined in Sound.Sc3.Ugen.Graph

Methods

(==) :: U_Node -> U_Node -> Bool #

(/=) :: U_Node -> U_Node -> Bool #

u_node_k_to_control :: U_Node -> Control Source #

Convert from U_Node_K to Control (ie. discard index).

u_node_user_name :: U_Node -> String Source #

Derive "user" name for U_Node

data U_Graph Source #

Type to represent a unit generator graph.

Constructors

U_Graph 

Instances

Instances details
Show U_Graph Source # 
Instance details

Defined in Sound.Sc3.Ugen.Graph

Ports

port_idx_or_zero :: From_Port -> Port_Index Source #

Get port_idx for From_Port_U, else 0.

Nodes

is_u_node_c :: U_Node -> Bool Source #

Is U_Node a constant.

is_u_node_c_of :: Sample -> U_Node -> Bool Source #

Predicate to determine if U_Node is a constant with indicated value.

is_u_node_k :: U_Node -> Bool Source #

Is U_Node a control.

is_u_node_k_of :: String -> U_Node -> Bool Source #

Predicate to determine if U_Node is a control with indicated name. Names must be unique.

u_node_k_eq :: U_Node -> U_Node -> Bool Source #

Equality test, error if not U_Node_K.

u_node_rate :: U_Node -> Rate Source #

Rate of U_Node, ie. InitialisationRate for constants. See through U_Node_P. Not used at hsc3 but used by hsc3-dot &etc.

u_node_label :: U_Node -> String Source #

Generate a label for U_Node using the type and the u_node_id.

u_node_in_edges :: U_Node -> [U_Edge] Source #

Calculate all in edges for a U_Node_U.

u_node_sort_controls :: [U_Node] -> [U_Node] Source #

If controls have been given indices they must be coherent.

u_node_ktype :: U_Node -> Maybe K_Type Source #

Determine K_Type of a control Ugen at U_Node_U, or not.

u_node_is_control :: U_Node -> Bool Source #

Is U_Node a control Ugen?

u_node_is_implicit_control :: U_Node -> Bool Source #

Is U_Node an implicit control Ugen?

u_node_is_implicit :: U_Node -> Bool Source #

Is U_Node implicit?

u_node_localbuf_count :: [U_Node] -> Int Source #

Zero if no local buffers, or if maxLocalBufs is given.

u_node_fetch_k :: Id -> K_Type -> [U_Node] -> Int Source #

Controls are a special case. We need to know not the overall index but the index in relation to controls of the same type.

type U_Node_NoId = (Rate, String, [From_Port], [Output], Special, UgenId) Source #

All the elements of a U_Node_U, except the u_node_id.

u_node_eq_noid :: U_Node_NoId -> U_Node -> Bool Source #

Predicate to locate primitive, names must be unique.

u_node_mk_ktype_map :: [U_Node] -> [(K_Type, Int)] Source #

Make map associating K_Type with Ugen index.

Nodes (Implicit)

type U_NODE_KS_COUNT = (Int, Int, Int, Int) Source #

4-tuple to count K_Types, ie. (InitialisationRate,ControlRate,TriggerRate,AudioRate).

u_node_ks_count :: [U_Node] -> U_NODE_KS_COUNT Source #

Count the number of controls of each K_Type.

u_node_mk_implicit_ctl :: [U_Node] -> [U_Node] Source #

Construct implicit control unit generator U_Nodes. Unit generators are only constructed for instances of control types that are present.

Edges

u_edge_multiple_out_edges :: [U_Edge] -> [From_Port] Source #

List of From_Port_U at e with multiple out edges.

Graph

ug_edges :: U_Graph -> [U_Edge] Source #

Calculate all edges of a U_Graph.

ug_maximum_id :: U_Graph -> Id Source #

Find the maximum Id used at U_Graph. It is an error if this is not ug_next_id.

ug_find_node :: U_Graph -> Id -> Maybe U_Node Source #

Find U_Node with indicated Id.

Graph (Construct from Ugen)

ug_push_c :: Sample -> U_Graph -> (U_Node, U_Graph) Source #

Insert a constant U_Node into the U_Graph.

ug_mk_node_c :: Constant -> U_Graph -> (U_Node, U_Graph) Source #

Either find existing Constant U_Node, or insert a new U_Node. Brackets are discarded.

ug_push_k :: Control -> U_Graph -> (U_Node, U_Graph) Source #

Insert a control node into the U_Graph.

ug_mk_node_k :: Control -> U_Graph -> (U_Node, U_Graph) Source #

Either find existing Control U_Node, or insert a new U_Node.

ug_push_u :: U_Node_NoId -> U_Graph -> (U_Node, U_Graph) Source #

Insert a primitive U_Node_U into the U_Graph.

ug_mk_node_rec :: [Ugen] -> [U_Node] -> U_Graph -> ([U_Node], U_Graph) Source #

Recursively traverse set of Ugen calling ug_mk_node.

ug_mk_node_u :: Primitive Ugen -> U_Graph -> (U_Node, U_Graph) Source #

Run ug_mk_node_rec at inputs and either find existing primitive node or insert a new one. Brackets are discarded.

ug_mk_node_p :: U_Node -> Port_Index -> U_Graph -> (U_Node, U_Graph) Source #

Proxies do not get stored in the graph. Proxies are always of U nodes.

ug_mk_node :: Ugen -> U_Graph -> (U_Node, U_Graph) Source #

Transform Ugen into U_Graph, appending to existing U_Graph. Allow rhs of Mrg node to be Mce (splice all nodes into graph).

Implicit

ug_add_implicit_ctl :: U_Graph -> U_Graph Source #

Add implicit control Ugens to U_Graph.

ug_add_implicit_buf :: U_Graph -> U_Graph Source #

Add implicit maxLocalBufs if not present.

ug_remove_implicit :: U_Graph -> U_Graph Source #

Remove implicit Ugens from U_Graph

Graph (Queries)

PV edge accounting

ug_pv_multiple_out_edges :: U_Graph -> [U_Node] Source #

List PV U_Nodes at U_Graph with multiple out edges.

ug_pv_check :: U_Graph -> Maybe String Source #

Error string if graph has an invalid PV subgraph, ie. multiple out edges at PV node not connecting to Unpack1FFT & PackFFT, else Nothing.

ug_pv_validate :: U_Graph -> U_Graph Source #

Variant that runs error as required.

Ugen to U_Graph

ugen_to_graph_direct :: Ugen -> U_Graph Source #

Transform a unit generator into a graph. ug_mk_node begins with an empty graph, then reverses the resulting Ugen list and sorts the Control list, and finally adds implicit nodes and validates PV sub-graphs.

import Sound.Sc3 
ugen_to_graph (out 0 (pan2 (sinOsc ar 440 0) 0.5 0.1))

Stat

ug_stat_ln :: U_Graph -> [String] Source #

Simple statistical analysis of a unit generator graph.

Indices

ug_ugen_indices :: (Num n, Enum n) => String -> U_Graph -> [n] Source #

Find indices of all instances of the named Ugen at Graph. The index is required when using u_cmd.