Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
- type Port_Index = Int
- data From_Port
- = From_Port_C {
- from_port_nid :: Id
- | From_Port_K { }
- | From_Port_U { }
- = From_Port_C {
- data To_Port = To_Port {}
- type U_Edge = (From_Port, To_Port)
- data U_Node
- u_node_is_c :: U_Node -> Bool
- u_node_is_k :: U_Node -> Bool
- u_node_is_u :: U_Node -> Bool
- u_node_k_to_control :: U_Node -> Control
- u_node_user_name :: U_Node -> String
- data U_Graph = U_Graph {
- ug_next_id :: Id
- ug_constants :: [U_Node]
- ug_controls :: [U_Node]
- ug_ugens :: [U_Node]
- port_idx_or_zero :: From_Port -> Port_Index
- is_from_port_u :: From_Port -> Bool
- is_u_node_c :: U_Node -> Bool
- is_u_node_c_of :: Sample -> U_Node -> Bool
- is_u_node_k :: U_Node -> Bool
- is_u_node_k_of :: String -> U_Node -> Bool
- is_u_node_u :: U_Node -> Bool
- u_node_k_cmp :: U_Node -> U_Node -> Ordering
- u_node_sort :: [U_Node] -> [U_Node]
- u_node_k_eq :: U_Node -> U_Node -> Bool
- u_node_rate :: U_Node -> Rate
- u_node_label :: U_Node -> String
- u_node_in_edges :: U_Node -> [U_Edge]
- u_node_from_port :: U_Node -> From_Port
- u_node_sort_controls :: [U_Node] -> [U_Node]
- u_node_ktype :: U_Node -> Maybe K_Type
- u_node_is_control :: U_Node -> Bool
- u_node_is_implicit_control :: U_Node -> Bool
- u_node_is_implicit :: U_Node -> Bool
- u_node_localbuf_count :: [U_Node] -> Int
- u_node_fetch_k :: Id -> K_Type -> [U_Node] -> Int
- type U_Node_NoId = (Rate, String, [From_Port], [Output], Special, UgenId)
- u_node_eq_noid :: U_Node_NoId -> U_Node -> Bool
- u_node_mk_ktype_map :: [U_Node] -> [(K_Type, Int)]
- type U_NODE_KS_COUNT = (Int, Int, Int, Int)
- u_node_ks_count :: [U_Node] -> U_NODE_KS_COUNT
- u_node_mk_implicit_ctl :: [U_Node] -> [U_Node]
- u_edge_multiple_out_edges :: [U_Edge] -> [From_Port]
- ug_edges :: U_Graph -> [U_Edge]
- ug_empty_graph :: U_Graph
- ug_maximum_id :: U_Graph -> Id
- ug_find_node :: U_Graph -> Id -> Maybe U_Node
- ug_from_port_node :: U_Graph -> From_Port -> Maybe U_Node
- ug_from_port_node_err :: U_Graph -> From_Port -> U_Node
- ug_push_c :: Sample -> U_Graph -> (U_Node, U_Graph)
- ug_mk_node_c :: Constant -> U_Graph -> (U_Node, U_Graph)
- ug_push_k :: Control -> U_Graph -> (U_Node, U_Graph)
- ug_mk_node_k :: Control -> U_Graph -> (U_Node, U_Graph)
- ug_push_u :: U_Node_NoId -> U_Graph -> (U_Node, U_Graph)
- ug_mk_node_rec :: [Ugen] -> [U_Node] -> U_Graph -> ([U_Node], U_Graph)
- ug_mk_node_u :: Primitive Ugen -> U_Graph -> (U_Node, U_Graph)
- ug_mk_node_p :: U_Node -> Port_Index -> U_Graph -> (U_Node, U_Graph)
- ug_mk_node :: Ugen -> U_Graph -> (U_Node, U_Graph)
- ug_add_implicit_ctl :: U_Graph -> U_Graph
- ug_add_implicit_buf :: U_Graph -> U_Graph
- ug_add_implicit :: U_Graph -> U_Graph
- ug_remove_implicit :: U_Graph -> U_Graph
- u_node_descendents :: U_Graph -> U_Node -> [U_Node]
- ug_pv_multiple_out_edges :: U_Graph -> [U_Node]
- ug_pv_check :: U_Graph -> Maybe String
- ug_pv_validate :: U_Graph -> U_Graph
- ugen_to_graph_direct :: Ugen -> U_Graph
- ugen_to_graph :: Ugen -> U_Graph
- ug_stat_ln :: U_Graph -> [String]
- ug_stat :: U_Graph -> String
- ug_ugen_indices :: (Num n, Enum n) => String -> U_Graph -> [n]
Types
type Port_Index = Int Source #
Port index.
Type to represent the left hand side of an edge in a unit generator graph. C = constant, K = control, U = ugen.
Instances
A destination port.
Sum-type to represent nodes in unit generator graph. _C = constant, _K = control, _U = ugen, _P = proxy.
U_Node_C | |
| |
U_Node_K | |
| |
U_Node_U | |
| |
U_Node_P | |
|
u_node_is_c :: U_Node -> Bool Source #
u_node_is_k :: U_Node -> Bool Source #
u_node_is_u :: U_Node -> Bool Source #
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
Type to represent a unit generator graph.
U_Graph | |
|
Ports
port_idx_or_zero :: From_Port -> Port_Index Source #
Get port_idx
for From_Port_U
, else 0
.
is_from_port_u :: From_Port -> Bool Source #
Is From_Port
From_Port_U
.
Nodes
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_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_cmp :: U_Node -> U_Node -> Ordering Source #
Compare U_Node_K
values on
u_node_k_type
.
u_node_rate :: U_Node -> Rate Source #
u_node_label :: U_Node -> String Source #
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_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_Type
s, 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_empty_graph :: U_Graph Source #
The empty 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
.
Graph (Construct from Ugen)
ug_push_k :: Control -> U_Graph -> (U_Node, U_Graph) Source #
Insert a control node 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.
Implicit
ug_add_implicit_buf :: U_Graph -> U_Graph Source #
Add implicit maxLocalBufs
if not present.
Graph (Queries)
PV edge accounting
ug_pv_multiple_out_edges :: U_Graph -> [U_Node] Source #
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.
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))
ugen_to_graph :: Ugen -> U_Graph Source #
Stat
ug_stat_ln :: U_Graph -> [String] Source #
Simple statistical analysis of a unit generator graph.