scide: LookupDialog - redo lookup on classes after partial lookup
[supercollider.git] / SCClassLibrary / Common / Audio / UGen.sc
blob2e6f2164569130c7b46b0fd4cc4f33f9294d281e
1 UGen : AbstractFunction {
2         classvar <>buildSynthDef; // the synth currently under construction
3         var <>synthDef;
4         var <>inputs;
5         var <>rate = 'audio';
7         var <>synthIndex = -1, <>specialIndex=0;
9         var <>antecedents, <>descendants, <>widthFirstAntecedents; // topo sorting
11         // instance creation
12         *new1 { arg rate ... args;
13                 if (rate.isKindOf(Symbol).not) { Error("rate must be Symbol.").throw };
14                 ^super.new.rate_(rate).addToSynth.init( *args )
15         }
16         *newFromDesc { arg rate, numOutputs, inputs, specialIndex;
17                 ^super.new.rate_(rate).inputs_(inputs).specialIndex_(specialIndex)
18         }
19         *multiNew { arg ... args;
20                 ^this.multiNewList(args);
21         }
23         *multiNewList { arg args;
24                 var size = 0, newArgs, results;
25                 args = args.asUGenInput(this);
26                 args.do({ arg item;
27                         (item.class == Array).if({ size = max(size, item.size) });
28                 });
29                 if (size == 0) { ^this.new1( *args ) };
30                 newArgs = Array.newClear(args.size);
31                 results = Array.newClear(size);
32                 size.do({ arg i;
33                         args.do({ arg item, j;
34                                 newArgs.put(j, if (item.class == Array, { item.wrapAt(i) },{ item }));
35                         });
36                         results.put(i, this.multiNewList(newArgs));
37                 });
38                 ^results
39         }
41         init { arg ... theInputs;
42                 // store the inputs as an array
43                 inputs = theInputs;
44         }
45         copy {
46                 // you can't really copy a UGen without disturbing the Synth.
47                 // Usually you want the same object. This makes .dup work
48                 ^this
49         }
51         madd { arg mul = 1.0, add = 0.0;
52                 ^MulAdd(this, mul, add);
53         }
54         range { arg lo = 0.0, hi = 1.0;
55                 var mul, add;
56                 if (this.signalRange == \bipolar, {
57                         mul = (hi - lo) * 0.5;
58                         add = mul + lo;
59                 },{
60                         mul = (hi - lo) ;
61                         add = lo;
62                 });
63                 ^MulAdd(this, mul, add);
64         }
65         exprange { arg lo = 0.01, hi = 1.0;
66                 ^if (this.signalRange == \bipolar) {
67                         this.linexp(-1, 1, lo, hi)
68                 } {
69                         this.linexp(0, 1, lo, hi)
70                 };
71         }
73         unipolar { arg mul = 1;
74                 ^this.range(0, mul)
75         }
77         bipolar { arg mul = 1;
78                 ^this.range(mul.neg, mul)
79         }
81         clip { arg lo = 0.0, hi = 1.0;
82                 ^if(rate == \demand){
83                         max(lo, min(hi, this))
84                 }{
85                         Clip.perform(Clip.methodSelectorForRate(rate), this, lo, hi)
86                 }
87         }
89         fold { arg lo = 0.0, hi = 0.0;
90                 ^if(rate == \demand) {
91                         this.notYetImplemented(thisMethod)
92                 } {
93                         Fold.perform(Fold.methodSelectorForRate(rate), this, lo, hi)
94                 }
95         }
96         wrap { arg lo = 0.0, hi = 1.0;
97                 ^if(rate == \demand) {
98                         this.notYetImplemented(thisMethod)
99                 } {
100                         Wrap.perform(Wrap.methodSelectorForRate(rate), this, lo, hi)
101                 }
102         }
104         minNyquist { ^min(this, SampleRate.ir * 0.5) }
106         lag { arg t1=0.1, t2;
107                 ^if(t2.isNil) {
108                         Lag.multiNew(this.rate, this, t1)
109                 } {
110                         LagUD.multiNew(this.rate, this, t1, t2)
111                 }
112         }
113         lag2 { arg t1=0.1, t2;
114                 ^if(t2.isNil) {
115                         Lag2.multiNew(this.rate, this, t1)
116                 } {
117                         Lag2UD.multiNew(this.rate, this, t1, t2)
118                 }
119         }
120         lag3 { arg t1=0.1, t2;
121                 ^if(t2.isNil) {
122                         Lag3.multiNew(this.rate, this, t1)
123                 } {
124                         Lag3UD.multiNew(this.rate, this, t1, t2)
125                 }
126         }
128         lagud { arg lagTimeU=0.1, lagTimeD=0.1;
129                 ^LagUD.multiNew(this.rate, this, lagTimeU, lagTimeD)
130         }
131         lag2ud { arg lagTimeU=0.1, lagTimeD=0.1;
132                 ^Lag2UD.multiNew(this.rate, this, lagTimeU, lagTimeD)
133         }
134         lag3ud { arg lagTimeU=0.1, lagTimeD=0.1;
135                 ^Lag3UD.multiNew(this.rate, this, lagTimeU, lagTimeD)
136         }
138         varlag { arg time=0.1, curvature=0, warp=5, start;
139                 ^VarLag.multiNew(this.rate, this, time, curvature, warp, start)
140         }
142         slew { arg up = 1, down = 1;
143                 ^Slew.multiNew(this.rate, this, up, down)
144         }
146         prune { arg min, max, type;
147                 switch(type,
148                         \minmax, {
149                                 ^this.clip(min, max);
150                         },
151                         \min, {
152                                 ^this.max(min);
153                         },
154                         \max, {
155                                 ^this.min(max);
156                         }
157                 );
158                 ^this
159         }
160         linlin { arg inMin, inMax, outMin, outMax, clip = \minmax;
161                 if (this.rate == \audio) {
162                         ^LinLin.ar(this.prune(inMin, inMax, clip), inMin, inMax, outMin, outMax)
163                 } {
164                         ^LinLin.kr(this.prune(inMin, inMax, clip), inMin, inMax, outMin, outMax)
165                 }
166         }
168         linexp { arg inMin, inMax, outMin, outMax, clip = \minmax;
169                 ^LinExp.multiNew(this.rate, this.prune(inMin, inMax, clip),
170                                                 inMin, inMax, outMin, outMax)
171         }
172         explin { arg inMin, inMax, outMin, outMax, clip = \minmax;
173                 ^(log(this.prune(inMin, inMax, clip)/inMin))
174                         / (log(inMax/inMin)) * (outMax-outMin) + outMin; // no separate ugen yet
175         }
176         expexp { arg inMin, inMax, outMin, outMax, clip = \minmax;
177                 ^pow(outMax/outMin, log(this.prune(inMin, inMax, clip)/inMin)
178                         / log(inMax/inMin)) * outMin;
179         }
181         lincurve { arg inMin = 0, inMax = 1, outMin = 0, outMax = 1, curve = -4, clip = \minmax;
182                 var grow, a, b, scaled;
183                 if (curve.isNumber and: { abs(curve) < 0.25 }) {
184                         ^this.linlin(inMin, inMax, outMin, outMax, clip)
185                 };
186                 grow = exp(curve);
187                 a = outMax - outMin / (1.0 - grow);
188                 b = outMin + a;
189                 scaled = (this.prune(inMin, inMax, clip) - inMin) / (inMax - inMin);
191                 ^b - (a * pow(grow, scaled));
192         }
194         curvelin { arg inMin = 0, inMax = 1, outMin = 0, outMax = 1, curve = -4, clip = \minmax;
195                 var grow, a, b, scaled;
196                 if (curve.isNumber and: { abs(curve) < 0.25 }) {
197                         ^this.linlin(inMin, inMax, outMin, outMax, clip)
198                 };
199                 grow = exp(curve);
200                 a = outMax - outMin / (1.0 - grow);
201                 b = outMin + a;
202                 scaled = (this.prune(inMin, inMax, clip) - inMin) / (inMax - inMin);
204                 ^log((b - scaled) / a) / curve
205         }
207         signalRange { ^\bipolar }
208         @ { arg y; ^Point.new(this, y) } // dynamic geometry support
210         addToSynth {
211                 synthDef = buildSynthDef;
212                 if (synthDef.notNil, { synthDef.addUGen(this) });
213         }
215         collectConstants {
216                 inputs.do({ arg input;
217                         if (input.isNumber, { synthDef.addConstant(input.asFloat)  });
218                 });
219         }
221         isValidUGenInput { ^true }
222         asUGenInput { ^this }
223         asControlInput { Error("can't set a control to a UGen").throw }
224         numChannels { ^1 }
227         checkInputs { ^this.checkValidInputs }
228         checkValidInputs {
229                 inputs.do({arg in,i;
230                         var argName;
231                         if(in.isValidUGenInput.not,{
232                                 argName = this.argNameForInputAt(i) ? i;
233                                 ^"arg: '" ++ argName ++ "' has bad input:" + in;
234                         })
235                 });
236                 ^nil
237         }
239         checkNInputs { arg n;
240                 if (rate == 'audio') {
241                         n.do {| i |
242                                 if (inputs.at(i).rate != 'audio') {
243                                         //"failed".postln;
244                                         ^("input " ++ i ++ " is not audio rate: " + inputs.at(i) + inputs.at(0).rate);
245                                 };
246                         };
247                  };
248                 ^this.checkValidInputs
249         }
251         checkSameRateAsFirstInput {
252                 if (rate !== inputs.at(0).rate) {
253                         ^("first input is not" + rate + "rate: " + inputs.at(0) + inputs.at(0).rate);
254                 };
255                 ^this.checkValidInputs
256         }
258         argNameForInputAt { arg i;
259                 var method = this.class.class.findMethod(this.methodSelectorForRate);
260                 if(method.isNil or: {method.argNames.isNil},{ ^nil });
261                 ^method.argNames.at(i + this.argNamesInputsOffset)
262         }
263         argNamesInputsOffset { ^1 }
264         dumpArgs {
265                 " ARGS:".postln;
266                 inputs.do({ arg in,ini;
267                         ("   " ++ (this.argNameForInputAt(ini) ? ini.asString)++":" + in + in.class).postln
268                 });
269         }
270         degreeToKey { arg scale, stepsPerOctave=12;
271                 ^DegreeToKey.kr(scale, this, stepsPerOctave)
272         }
274         outputIndex { ^0 }
275         writesToBus { ^false }
277         poll { arg trig = 10, label, trigid = -1;
278           ^Poll(trig, this, label, trigid)
279         }
281         dpoll { arg label, run = 1, trigid = -1;
282                 ^Dpoll(this, label, run, trigid)
283         }
285         checkBadValues { arg id = 0, post = 2;
286                         // add the UGen to the tree but keep "this" as the output
287                 CheckBadValues.perform(this.methodSelectorForRate, this, id, post);
288         }
290         *methodSelectorForRate { arg rate;
291                 if(rate == \audio,{ ^\ar });
292                 if(rate == \control, { ^\kr });
293                 if(rate == \scalar, {
294                         if(this.respondsTo(\ir),{
295                                 ^\ir
296                         },{
297                                 ^\new
298                         });
299                 });
300                 if(rate == \demand, { ^\new });
301                 ^nil
302         }
304         *replaceZeroesWithSilence { arg array;
305                 // this replaces zeroes with audio rate silence.
306                 // sub collections are deep replaced
307                 var numZeroes, silentChannels, pos = 0;
309                 numZeroes = array.count({ arg item; item == 0.0 });
310                 if (numZeroes == 0, { ^array });
312                 silentChannels = Silent.ar(numZeroes).asCollection;
313                 array.do({ arg item, i;
314                         var res;
315                         if (item == 0.0, {
316                                 array.put(i, silentChannels.at(pos));
317                                 pos = pos + 1;
318                         }, {
319                                 if(item.isSequenceableCollection, {
320                                         res = this.replaceZeroesWithSilence(item);
321                                         array.put(i, res);
322                                 });
323                         });
324                 });
325                 ^array;
326         }
329         // PRIVATE
330         // function composition
331         composeUnaryOp { arg aSelector;
332                 ^UnaryOpUGen.new(aSelector, this)
333         }
334         composeBinaryOp { arg aSelector, anInput;
335                 if (anInput.isValidUGenInput, {
336                         ^BinaryOpUGen.new(aSelector, this, anInput)
337                 },{
338                         anInput.performBinaryOpOnUGen(aSelector, this);
339                 });
340         }
341         reverseComposeBinaryOp { arg aSelector, aUGen;
342                 ^BinaryOpUGen.new(aSelector, aUGen, this)
343         }
344         composeNAryOp { arg aSelector, anArgList;
345                 ^thisMethod.notYetImplemented
346         }
348         // complex support
350         asComplex { ^Complex.new(this, 0.0) }
351         performBinaryOpOnComplex { arg aSelector, aComplex; ^aComplex.perform(aSelector, this.asComplex) }
353         if { arg trueUGen, falseUGen;
354                 ^(this * (trueUGen - falseUGen)) + falseUGen;
355         }
357         rateNumber {
358                 if (rate == \audio, { ^2 });
359                 if (rate == \control, { ^1 });
360                 if (rate == \demand, { ^3 });
361                 ^0 // scalar
362         }
363         methodSelectorForRate {
364                 if(rate == \audio,{ ^\ar });
365                 if(rate == \control, { ^\kr });
366                 if(rate == \scalar, {
367                         if(this.class.respondsTo(\ir),{
368                                 ^\ir
369                         },{
370                                 ^\new
371                         });
372                 });
373                 if(rate == \demand, { ^\new });
374                 ^nil
375         }
376         writeInputSpec { arg file, synthDef;
377                 file.putInt32(synthIndex);
378                 file.putInt32(this.outputIndex);
379         }
380         writeOutputSpec { arg file;
381                 file.putInt8(this.rateNumber);
382         }
383         writeOutputSpecs { arg file;
384                 this.writeOutputSpec(file);
385         }
386         numInputs { ^inputs.size }
387         numOutputs { ^1 }
389         name {
390                 ^this.class.name.asString;
391         }
392         writeDef { arg file;
393                 file.putPascalString(this.name);
394                 file.putInt8(this.rateNumber);
395                 file.putInt32(this.numInputs);
396                 file.putInt32(this.numOutputs);
397                 file.putInt16(this.specialIndex);
398                 // write wire spec indices.
399                 inputs.do({ arg input;
400                         input.writeInputSpec(file, synthDef);
401                 });
402                 this.writeOutputSpecs(file);
403         }
405 ///////////////////////////////////////////////////////////////
407         initTopoSort {
408                 inputs.do({ arg input;
409                         if (input.isKindOf(UGen), {
410                                 antecedents.add(input.source);
411                                 input.source.descendants.add(this);
412                         });
413                 });
415                 widthFirstAntecedents.do({ arg ugen;
416                         antecedents.add(ugen);
417                         ugen.descendants.add(this);
418                 })
419         }
421         makeAvailable {
422                 if (antecedents.size == 0, {
423                         synthDef.available = synthDef.available.add(this);
424                 });
425         }
427         removeAntecedent { arg ugen;
428                 antecedents.remove(ugen);
429                 this.makeAvailable;
430         }
432         schedule { arg outStack;
433                 descendants.reverseDo({ arg ugen;
434                         ugen.removeAntecedent(this);
435                 });
436                 ^outStack.add(this);
437         }
439         optimizeGraph {}
441         dumpName {
442                 ^synthIndex.asString ++ "_" ++ this.class.name.asString
443         }
445         performDeadCodeElimination {
446                 if (descendants.size == 0) {
447                         this.inputs.do {|a|
448                                 if (a.isKindOf(UGen)) {
449                                         a.descendants.remove(this);
450                                         a.optimizeGraph
451                                 }
452                         };
453                         buildSynthDef.removeUGen(this);
454                         ^true;
455                 };
456                 ^false
457         }
460 // ugen, which has no side effect and can therefore be considered for a dead code elimination
461 // read access to buffers/busses are allowed
462 PureUGen : UGen {
463         optimizeGraph {
464                 super.performDeadCodeElimination
465         }
468 MultiOutUGen : UGen {
469         // a class for UGens with multiple outputs
470         var <channels;
472         *newFromDesc { arg rate, numOutputs, inputs;
473                 ^super.new.rate_(rate).inputs_(inputs).initOutputs(numOutputs, rate)
474         }
476         initOutputs { arg numChannels, rate;
477                 channels = Array.fill(numChannels, { arg i;
478                         OutputProxy(rate, this, i);
479                 });
480                 if (numChannels == 1, {
481                         ^channels.at(0)
482                 });
483                 ^channels
484         }
486         numOutputs { ^channels.size }
487         writeOutputSpecs { arg file;
488                 channels.do({ arg output; output.writeOutputSpec(file); });
489         }
490         synthIndex_ { arg index;
491                 synthIndex = index;
492                 channels.do({ arg output; output.synthIndex_(index); });
493         }
497 OutputProxy : UGen {
498         var <>source, <>outputIndex, <>name;
499         *new { arg rate, itsSourceUGen, index;
500                 ^super.new1(rate, itsSourceUGen, index)
501         }
502         addToSynth {
503                 synthDef = buildSynthDef;
504         }
505         init { arg argSource, argIndex;
506                 source = argSource;
507                 outputIndex = argIndex;
508                 synthIndex = source.synthIndex;
509         }
511         dumpName {
512                 ^this.source.dumpName ++ "[" ++ outputIndex ++ "]"
513         }