hsc3-0.16: Haskell SuperCollider

Safe HaskellSafe
LanguageHaskell98

Sound.SC3.UGen.Graph

Contents

Description

Graph and related types.

Synopsis

Type

type NodeId = Int Source #

Node identifier.

type PortIndex = Int Source #

Port index.

data Graph Source #

Type to represent unit generator graph.

Constructors

Graph 

Fields

Instances

data KType Source #

Enumeration of the four operating rates for controls.

Constructors

K_IR 
K_KR 
K_TR 
K_AR 

Instances

Eq KType Source # 

Methods

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

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

Ord KType Source # 

Methods

compare :: KType -> KType -> Ordering #

(<) :: KType -> KType -> Bool #

(<=) :: KType -> KType -> Bool #

(>) :: KType -> KType -> Bool #

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

max :: KType -> KType -> KType #

min :: KType -> KType -> KType #

Show KType Source # 

Methods

showsPrec :: Int -> KType -> ShowS #

show :: KType -> String #

showList :: [KType] -> ShowS #

data FromPort Source #

Type to represent the left hand side of an edge in a unit generator graph.

data ToPort Source #

A destination port.

Constructors

ToPort NodeId PortIndex 

Instances

type Edge = (FromPort, ToPort) Source #

A connection from FromPort to ToPort.

node_rate :: Node -> Rate Source #

Rate of Node, ie. IR for constants, & see through NodeP.

Building

find_node :: Graph -> NodeId -> Maybe Node Source #

Find Node with indicated NodeId.

node_label :: Node -> String Source #

Generate a label for Node using the type and the node_id.

is_node_c :: Node -> Bool Source #

Is Node a constant.

is_node_k :: Node -> Bool Source #

Is Node a control.

is_node_u :: Node -> Bool Source #

Is Node a UGen.

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

Calculate all edges given a set of NodeU.

graph_maximum_id :: Graph -> NodeId Source #

Find the maximum NodeId used at Graph (this ought normally be the nextId).

ktype :: Rate -> Bool -> KType Source #

Determine class of control given Rate and trigger status.

find_c_p :: Sample -> Node -> Bool Source #

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

push_c :: Sample -> Graph -> (Node, Graph) Source #

Insert a constant Node into the Graph.

mk_node_c :: Constant -> Graph -> (Node, Graph) Source #

Either find existing Constant Node, or insert a new Node.

find_k_p :: String -> Node -> Bool Source #

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

push_k :: Control -> Graph -> (Node, Graph) Source #

Insert a control node into the Graph.

mk_node_k :: Control -> Graph -> (Node, Graph) Source #

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

find_u_p :: UGenParts -> Node -> Bool Source #

Predicate to locate primitive, names must be unique.

push_u :: UGenParts -> Graph -> (Node, Graph) Source #

Insert a primitive NodeU into the Graph.

mk_node_u_acc :: [UGen] -> [Node] -> Graph -> ([Node], Graph) Source #

mk_node_u :: Primitive -> Graph -> (Node, Graph) Source #

Either find existing Primitive node, or insert a new Node.

mk_node_p :: Node -> PortIndex -> Graph -> (Node, Graph) Source #

Proxies do not get stored in the graph.

mk_node :: UGen -> Graph -> (Node, Graph) Source #

Transform UGen into Graph, appending to existing Graph.

prepare_root :: UGen -> UGen Source #

Transform mce nodes to mrg nodes

sort_controls :: [Node] -> [Node] Source #

If controls have been given indices they must be coherent.

mk_graph :: UGen -> Graph Source #

Variant on mk_node starting with an empty graph, reverses the UGen list and sorts the Control list, and adds implicit nodes.

Encoding

type Maps = (Map, [Node], Map, Map, [(KType, Int)]) Source #

node_ktype :: Node -> Maybe KType Source #

Determine KType of a control UGen at NodeU, or not.

mk_ktype_map :: [Node] -> [(KType, Int)] Source #

Map associating KType with UGen index.

ktype_map_lookup :: KType -> [(KType, Int)] -> Int Source #

Lookup KType index from map (erroring variant of lookup).

mk_maps :: Graph -> Maps Source #

Generate Maps translating node identifiers to synthdef indexes.

fetch :: NodeId -> Map -> Int Source #

Locate index in map given node identifer NodeId.

fetch_k :: NodeId -> KType -> [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.

Implicit (Control, MaxLocalBuf)

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

4-tuple to count KTypes.

ks_count :: [Node] -> KS_COUNT Source #

Count the number of controls of each KType.

mk_implicit_ctl :: [Node] -> [Node] Source #

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

add_implicit_ctl :: Graph -> Graph Source #

Add implicit control UGens to Graph.

localbuf_count :: [Node] -> Int Source #

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

add_implicit_buf :: Graph -> Graph Source #

Add implicit maxLocalBufs if not present.

is_implicit_control :: Node -> Bool Source #

Is Node an implicit control UGen?

is_implicit :: Node -> Bool Source #

Is Node implicit?

remove_implicit :: Graph -> Graph Source #

Remove implicit UGens from Graph

Queries

multiple_u_out_edges :: [Edge] -> [FromPort] Source #

List of FromPort_U at e with multiple out edges.

node_descendents :: Graph -> Node -> [Node] Source #

Descendents at Graph of Node.

PV edge accounting

pv_multiple_out_edges :: Graph -> [Node] Source #

List PV Nodes at Graph with multiple out edges.

pv_validate :: Graph -> Graph Source #

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

ugen_to_graph :: UGen -> Graph Source #

Transform a unit generator into a graph.

import Sound.SC3.UGen
ugen_to_graph (out 0 (pan2 (sinOsc AR 440 0) 0.5 0.1))