hsc3-0.11: Haskell SuperCollider

Sound.SC3.UGen.UGen

Contents

Description

UGen data structure representation and associated functions.

Synopsis

UGen Id type and functions

data UGenId Source

Data type for internalised identifier at UGen.

Constructors

NoId 
UserId 

Fields

userId :: (String, Int)
 
SystemId 

Fields

systemId :: Int
 

Instances

isNoId :: UGenId -> BoolSource

Predicate for NoId.

isUserId :: UGenId -> BoolSource

Predicate for UserId.

isSystemId :: UGenId -> BoolSource

Predicate for SystemId.

hash :: Hashable32 a => a -> IntSource

Hash value to Int.

Unit Generator type

UGen graph functions

ugenTraverse :: (UGen -> UGen) -> UGen -> UGenSource

Depth first traversal of graph at u applying f to each node.

ugenFoldr :: (UGen -> a -> a) -> a -> UGen -> aSource

Right fold of UGen graph.

UGen graph Id reassignment

ugenIds :: UGen -> [UGenId]Source

Collect Ids at UGen graph

ugenReplaceIds :: [(UGenId, UGenId)] -> UGen -> UGenSource

Recursive replacement of UGenIds according to table.

ugenProtectUserId :: Int -> UGen -> UGenSource

Protect user specified UGen Ids.

uprotect :: ID a => a -> UGen -> UGenSource

uprotect' :: ID a => a -> [UGen] -> [UGen]Source

Variant of uprotect with subsequent identifiers derived by incrementing initial identifier.

uclone' :: ID a => a -> Int -> UGen -> [UGen]Source

Make n parallel instances of UGen with protected identifiers.

uclone :: ID a => a -> Int -> UGen -> UGenSource

mce variant of uclone'.

ucompose :: ID a => a -> [UGen -> UGen] -> UGen -> UGenSource

Left to right UGen function composition with user id protection.

useq :: ID a => a -> Int -> (UGen -> UGen) -> UGen -> UGenSource

Make n sequential instances of f with protected Ids.

ugenIncrUserId :: Int -> UGen -> UGenSource

Increment user specified UGen Ids.

udup' :: Int -> UGen -> [UGen]Source

Duplicate u n times, increment user assigned Ids.

udup :: Int -> UGen -> UGenSource

mce variant of udup'.

UGen ID Instance

hashUGen :: UGen -> IntSource

Hash function for unit generators.

type Output = RateSource

Unit generator output descriptor.

newtype Special Source

Operating mode of unary and binary operators.

Constructors

Special Int 

Instances

Unit generator node constructors

constant :: Real a => a -> UGenSource

Constant value node constructor.

control :: Rate -> String -> Double -> UGenSource

Control input node constructor.

Note that if the name begins with a t_ prefix the control is not converted to a triggered control. Please see tr_control.

tr_control :: String -> Double -> UGenSource

Triggered (kr) control input node constructor.

mce :: [UGen] -> UGenSource

Multiple channel expansion node constructor.

mrg2 :: UGen -> UGen -> UGenSource

Multiple root graph node constructor.

proxy :: UGen -> Int -> UGenSource

Unit generator proxy node constructor.

Unit generator node predicates

isMCE :: UGen -> BoolSource

Multiple channel expansion node predicate.

isConstant :: UGen -> BoolSource

Constant node predicate.

ugenType :: UGen -> UGenTypeSource

Constant node predicate.

Multiple channel expansion

mce2 :: UGen -> UGen -> UGenSource

Multiple channel expansion for two inputs.

mce2c :: UGen -> (UGen, UGen)Source

Extract two channels from possible MCE.

clone :: UId m => Int -> m UGen -> m UGenSource

Clone a unit generator (mce . replicateM).

mceDegree :: UGen -> IntSource

Number of channels to expand to.

mceExtend :: Int -> UGen -> [UGen]Source

Extend UGen to specified degree.

mceInputTransform :: [UGen] -> Maybe [[UGen]]Source

Apply MCE transform to a list of inputs.

mceBuild :: ([UGen] -> UGen) -> [UGen] -> UGenSource

Build a UGen after MCE transformation of inputs.

mceMap :: (UGen -> UGen) -> UGen -> UGenSource

Apply a function to each channel at a unit generator.

mceEdit :: ([UGen] -> [UGen]) -> UGen -> UGenSource

Apply UGen list operation on MCE contents.

mceReverse :: UGen -> UGenSource

Reverse order of channels at MCE.

mceChannel :: Int -> UGen -> UGenSource

Obtain indexed channel at MCE.

mceChannels :: UGen -> [UGen]Source

Output channels of UGen as a list.

mceTranspose :: UGen -> UGenSource

Transpose rows and columns, ie. {{a,b},{c,d}} to {{a,c},{b,d}}.

mceSum :: UGen -> UGenSource

Collapse mce by summing (see also mix and mixN).

Multiple root graphs

mrg :: [UGen] -> UGenSource

Multiple root graph constructor.

Unit generator function builders

proxify :: UGen -> UGenSource

Apply proxy transformation if required.

rateOf :: UGen -> RateSource

Determine the rate of a UGen.

is_sink :: UGen -> BoolSource

True if input is a sink UGen, ie. has no outputs.

check_input :: UGen -> UGenSource

Ensure input UGen is valid, ie. not a sink.

mkUGen :: Maybe ([Double] -> Double) -> [Rate] -> Maybe Rate -> String -> [UGen] -> Int -> Special -> UGenId -> UGenSource

Construct proxied and multiple channel expanded UGen.

all_rates :: [Rate]Source

Set of all Rate values.

mkOperator :: ([Double] -> Double) -> String -> [UGen] -> Int -> UGenSource

Operator UGen constructor.

mkUnaryOperator :: Unary -> (Double -> Double) -> UGen -> UGenSource

Unary math constructor with constant optimization.

mkBinaryOperator :: Binary -> (Double -> Double -> Double) -> UGen -> UGen -> UGenSource

Binary math constructor with constant optimization.

mk_osc :: [Rate] -> UGenId -> Rate -> String -> [UGen] -> Int -> UGenSource

Oscillator constructor with constrained set of operating Rates.

mkOsc :: Rate -> String -> [UGen] -> Int -> UGenSource

Oscillator constructor with all_rates.

mkOscR :: [Rate] -> Rate -> String -> [UGen] -> Int -> UGenSource

Oscillator constructor, rate restricted variant.

toUserId :: ID a => String -> a -> UGenIdSource

Transform String and ID to a UserId.

mkOscId :: ID a => a -> Rate -> String -> [UGen] -> Int -> UGenSource

Oscillator constructor, setting identifier.

mk_osc_mce :: UGenId -> Rate -> String -> [UGen] -> UGen -> Int -> UGenSource

Provided UGenId variant of mkOscMCE.

mkOscMCE :: Rate -> String -> [UGen] -> UGen -> Int -> UGenSource

Variant oscillator constructor with MCE collapsing input.

mkOscMCEId :: ID a => a -> Rate -> String -> [UGen] -> UGen -> Int -> UGenSource

Variant oscillator constructor with MCE collapsing input.

mk_filter :: [Rate] -> UGenId -> String -> [UGen] -> Int -> UGenSource

Rate constrained filter UGen constructor.

mkFilter :: String -> [UGen] -> Int -> UGenSource

Filter UGen constructor.

mkFilterR :: [Rate] -> String -> [UGen] -> Int -> UGenSource

Filter UGen constructor.

mkFilterId :: ID a => a -> String -> [UGen] -> Int -> UGenSource

Filter UGen constructor.

mkFilterKeyed :: String -> Int -> [UGen] -> Int -> UGenSource

Variant filter with rate derived from keyed input.

mk_filter_mce :: [Rate] -> UGenId -> String -> [UGen] -> UGen -> Int -> UGenSource

Provided UGenId filter with mce input.

mkFilterMCER :: [Rate] -> String -> [UGen] -> UGen -> Int -> UGenSource

Variant filter constructor with MCE collapsing input.

mkFilterMCE :: String -> [UGen] -> UGen -> Int -> UGenSource

Variant filter constructor with MCE collapsing input.

mkFilterMCEId :: ID a => a -> String -> [UGen] -> UGen -> Int -> UGenSource

Variant filter constructor with MCE collapsing input.

mkInfo :: String -> UGenSource

Information unit generators are very specialized.