hsc3-0.19.1: Haskell SuperCollider
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.SC3.UGen.Bindings.Composite

Contents

Description

Common unit generator graphs.

Synopsis

Documentation

asLocalBuf :: ID i => i -> [UGen] -> UGen Source #

Generate a localBuf and use setBuf to initialise it.

balanceStereo :: UGen -> UGen -> UGen -> UGen Source #

balance2 with MCE input.

bLowPass4 :: UGen -> UGen -> UGen -> UGen Source #

24db/oct rolloff - 4th order resonant Low Pass Filter

bHiPass4 :: UGen -> UGen -> UGen -> UGen Source #

24db/oct rolloff - 4th order resonant Hi Pass Filter

bufRdN :: Int -> Rate -> UGen -> UGen -> Loop UGen -> UGen Source #

Buffer reader (no interpolation).

bufRdL :: Int -> Rate -> UGen -> UGen -> Loop UGen -> UGen Source #

Buffer reader (linear interpolation).

bufRdC :: Int -> Rate -> UGen -> UGen -> Loop UGen -> UGen Source #

Buffer reader (cubic interpolation).

changed :: UGen -> UGen -> UGen Source #

Triggers when a value changes

choose :: ID m => m -> UGen -> UGen Source #

mce variant of lchoose.

chooseM :: UId m => UGen -> m UGen Source #

liftUId of choose.

dcons :: ID m => (m, m, m) -> UGen -> UGen -> UGen Source #

Demand rate (:) function.

dconsM :: UId m => UGen -> UGen -> m UGen Source #

Demand rate (:) function.

dynKlang :: Rate -> UGen -> UGen -> UGen -> UGen Source #

Dynamic klang, dynamic sine oscillator bank

dynKlank :: UGen -> UGen -> UGen -> UGen -> UGen -> UGen Source #

Dynamic klank, set of non-fixed resonating filters.

exprange :: UGen -> UGen -> UGen -> UGen Source #

linExp with input range of (-1,1).

in_exprange :: UGen -> (UGen, UGen) -> UGen Source #

Variant of exprange with arguments to make writing post-fix nicer.

fft' :: UGen -> UGen -> UGen Source #

Variant FFT constructor with default values for hop size (0.5), window type (0), active status (1) and window size (0).

ffta :: ID i => i -> UGen -> UGen -> UGen -> UGen -> UGen -> UGen -> UGen Source #

fft variant that allocates localBuf.

let c = ffta 'α' 2048 (soundIn 0) 0.5 0 1 0
in audition (out 0 (ifft c 0 0))

freqShift_hilbert :: UGen -> UGen -> UGen -> UGen Source #

Frequency shifter, in terms of hilbert (see also freqShift).

gateReset :: Num a => a -> a -> a Source #

UGen function to re-trigger an EnvGen envelope. Inputs are gate (as set at EnvGen) and reset. The four state logic is: (1,0)->1 (1,1)->-1 (0,1)->0 (0,0)->0. If the gate input to EnvGen.kr is -1 the envelope ramps to zero in one control period. The reset input sequence 0,1,0 when the gate is open produces (1,-1,1), which resets the envelope.

map (uncurry gateReset) [(1,0),(1,1),(0,1),(0,0)] == [1,-1,0,0]

hilbertFIR :: UGen -> UGen -> UGen Source #

Variant of hilbert using FFT (with a delay) for better results. Buffer should be 2048 or 1024. 2048 = better results, more delay. 1024 = less delay, little choppier results.

ifft' :: UGen -> UGen Source #

Variant ifft with default value for window type.

klanx_spec_f :: (a -> [b]) -> ([b] -> c) -> a -> a -> a -> c Source #

Generalised Klan(kg) specification rule. f unwraps inputs, g/ wraps output.

let r = [220,0.2,0,219,0.1,1,221,0.1,2]
in klanx_spec_f id id [220,219,221] [0.2,0.1,0.1] [0,1,2] == r

klangSpec :: [UGen] -> [UGen] -> [UGen] -> UGen Source #

Format frequency, amplitude and decay time data as required for klank.

klangSpec_k :: Real n => [n] -> [n] -> [n] -> UGen Source #

Variant of klangSpec for non-UGen inputs.

klangSpec_mce :: UGen -> UGen -> UGen -> UGen Source #

Variant of klangSpec for MCE inputs.

klankSpec :: [UGen] -> [UGen] -> [UGen] -> UGen Source #

Format frequency, amplitude and decay time data as required for klank.

klankSpec_k :: Real n => [n] -> [n] -> [n] -> UGen Source #

Variant for non-UGen inputs.

klankSpec_mce :: UGen -> UGen -> UGen -> UGen Source #

Variant of klankSpec for MCE inputs.

lchoose :: ID m => m -> [UGen] -> UGen Source #

Randomly select one of a list of UGens (initialisation rate).

lchooseM :: UId m => [UGen] -> m UGen Source #

liftUId of lchoose.

linExp_b :: UGen -> UGen -> UGen -> UGen Source #

linExp of (-1,1).

linExp_u :: UGen -> UGen -> UGen -> UGen Source #

linExp of (0,1).

linLin :: UGen -> UGen -> UGen -> UGen -> UGen -> UGen Source #

Map from one linear range to another linear range.

linLin_u :: UGen -> UGen -> UGen -> UGen Source #

linLin where source is (0,1).

linLin_b :: UGen -> UGen -> UGen -> UGen Source #

linLin where source is (-1,1).

localIn' :: Int -> Rate -> UGen Source #

Variant with defaults of zero.

makeFadeEnv :: Double -> UGen Source #

Generate an envGen UGen with fadeTime and gate controls.

import Sound.SC3
audition (out 0 (makeFadeEnv 1 * sinOsc AR 440 0 * 0.1))
withSC3 (send (n_set1 (-1) "gate" 0))

mce_gen :: ID z => (Id -> UGen) -> Int -> z -> UGen Source #

mce of map f of id_seq n.

mce_genM :: Applicative f => f UGen -> Int -> f UGen Source #

Monad/applicative variant of mce_gen.

mceN :: UGen -> UGen Source #

Count mce channels.

mix :: UGen -> UGen Source #

Collapse possible mce by summing.

mceMean :: UGen -> UGen Source #

Mix divided by number of inputs.

mixN :: Int -> UGen -> UGen Source #

Mix variant, sum to n channels.

mceFill :: Integral n => Int -> (n -> UGen) -> UGen Source #

Construct an MCE array of UGens.

mceFillInt :: Int -> (Int -> UGen) -> UGen Source #

Type specialised mceFill

listFill_z :: (Integral n, ID z, Enum z) => z -> Int -> (z -> n -> UGen) -> [UGen] Source #

Construct a list of ID UGens.

mceFill_z :: (Integral n, ID z, Enum z) => z -> Int -> (z -> n -> UGen) -> UGen Source #

mixFill :: Integral n => Int -> (n -> UGen) -> UGen Source #

Construct and sum a set of UGens.

mixFillInt :: Int -> (Int -> UGen) -> UGen Source #

Type specialised mixFill

mixFillUGen :: Int -> (UGen -> UGen) -> UGen Source #

Type specialised mixFill

mixFill_z :: (Integral n, ID z, Enum z) => z -> Int -> (z -> n -> UGen) -> UGen Source #

Construct and sum a set of ID UGens.

mixFillM :: (Integral n, Monad m) => Int -> (n -> m UGen) -> m UGen Source #

Monad variant on mixFill.

useq_z :: (ID z, Enum z) => z -> Int -> (z -> UGen -> UGen) -> UGen -> UGen Source #

Apply the ID UGen processor f k times in sequence to i, ie. for k=4 f (f (f (f i))).

mouseButton' :: Rate -> UGen -> UGen -> UGen -> UGen Source #

Variant that is randomly pressed.

mouseR :: ID a => a -> Rate -> UGen -> UGen -> Warp UGen -> UGen -> UGen Source #

Randomised mouse UGen (see also mouseX' and mouseY').

mouseX' :: Rate -> UGen -> UGen -> Warp UGen -> UGen -> UGen Source #

Variant that randomly traverses the mouseX space.

mouseY' :: Rate -> UGen -> UGen -> Warp UGen -> UGen -> UGen Source #

Variant that randomly traverses the mouseY space.

onsetType :: Num a => String -> a Source #

Translate onset type string to constant UGen value.

onsets' :: UGen -> UGen -> UGen -> UGen Source #

Onset detector with default values for minor parameters.

packFFTSpec :: [UGen] -> [UGen] -> UGen Source #

Format magnitude and phase data data as required for packFFT.

partConv_calcAccumSize :: Int -> Int -> Int Source #

Calculate size of accumulation buffer given FFT and IR sizes.

pmOsc :: Rate -> UGen -> UGen -> UGen -> UGen -> UGen Source #

PM oscillator. cf = carrier frequency, mf = modulation frequency, pm = pm-index = 0.0, mp = mod-phase = 0.0

poll' :: UGen -> UGen -> UGen -> UGen -> UGen Source #

Variant of poll that generates an mrg value with the input signal at left, and that allows a constant frequency input in place of a trigger.

privateIn :: Int -> Rate -> UGen -> UGen Source #

Variant of in' offset so zero if the first private bus.

privateOut :: UGen -> UGen -> UGen Source #

Variant of out offset so zero if the first private bus.

pvcollect :: UGen -> Int -> (UGen -> UGen -> Int -> (UGen, UGen)) -> Int -> Int -> UGen -> UGen Source #

Apply function f to each bin of an FFT chain, f receives magnitude, phase and index and returns a (magnitude,phase).

pv_calcPVRecSize :: Double -> Int -> Double -> Double -> Int Source #

dur and hop are in seconds, frameSize and sampleRate in frames, though the latter maybe fractional.

pv_calcPVRecSize 4.2832879818594 1024 0.25 48000.0 == 823299

rand0 :: ID a => a -> UGen -> UGen Source #

rand with left edge set to zero.

rand0M :: UId m => UGen -> m UGen Source #

UId form of rand0.

rand2 :: ID a => a -> UGen -> UGen Source #

rand with left edge set to negative n.

rand2M :: UId m => UGen -> m UGen Source #

UId form of rand2.

rotateStereo :: UGen -> UGen -> UGen Source #

rotate2 with MCE input.

runningSumRMS :: UGen -> UGen -> UGen Source #

RMS variant of runningSum.

selectX :: UGen -> UGen -> UGen Source #

Mix one output from many sources

setBuf' :: UGen -> [UGen] -> UGen -> UGen Source #

Set local buffer values.

silent :: Int -> UGen Source #

Silence.

soundIn :: UGen -> UGen Source #

Zero indexed audio input buses. Optimises case of consecutive UGens.

soundIn (mce2 0 1) == in' 2 AR numOutputBuses
soundIn (mce2 0 2) == in' 1 AR (numOutputBuses + mce2 0 2)

splay :: UGen -> UGen -> UGen -> UGen -> Bool -> UGen Source #

Pan a set of channels across the stereo field.

input, spread:1, level:1, center:0, levelComp:true

sum_opt :: [UGen] -> UGen Source #

Optimised UGen sum function.

tap :: Int -> Rate -> UGen -> UGen -> UGen Source #

Single tap into a delayline. AR only.

tChoose :: ID m => m -> UGen -> UGen -> UGen Source #

Randomly select one of several inputs on trigger.

tChooseM :: UId m => UGen -> UGen -> m UGen Source #

Randomly select one of several inputs.

tLine :: Rate -> UGen -> UGen -> UGen -> UGen -> UGen Source #

Triggered Line, implemented in terms of EnvGen.

tXLine :: Rate -> UGen -> UGen -> UGen -> UGen -> UGen Source #

Triggered xLine, implemented in terms of EnvGen.

triAS :: Int -> UGen -> UGen Source #

Triangle wave as sum of n sines. For partial n, amplitude is (1 / square n) and phase is pi at every other odd partial.

tWChoose :: ID m => m -> UGen -> UGen -> UGen -> UGen -> UGen Source #

Randomly select one of several inputs on trigger (weighted).

tWChooseM :: UId m => UGen -> UGen -> UGen -> UGen -> m UGen Source #

Randomly select one of several inputs (weighted).

unpackFFT :: UGen -> Int -> Int -> Int -> UGen -> [UGen] Source #

Unpack an FFT chain into separate demand-rate FFT bin streams.

varLag_env :: UGen -> UGen -> Envelope_Curve UGen -> Maybe UGen -> UGen Source #

VarLag in terms of envGen. Note: in SC3 curvature and warp are separate arguments.

wrapOut :: Maybe Double -> UGen -> UGen Source #

If z isn't a sink node route to an out node writing to bus. If fadeTime is given multiply by makeFadeEnv.

import Sound.SC3 
audition (wrapOut (Just 1) (sinOsc AR 440 0 * 0.1))
import Sound.OSC 
withSC3 (sendMessage (n_set1 (-1) "gate" 0))

wslib

playBufCF :: Int -> UGen -> UGen -> UGen -> UGen -> Loop UGen -> UGen -> Int -> UGen Source #

Cross-fading version of playBuf.

adc

osc1 :: Rate -> UGen -> UGen -> DoneAction UGen -> UGen Source #

An oscillator that reads through a table once.