Ndef as a fx chain: i'm stuck

Sure, that was my first idea, but it’s a pretty leaky abstraction because all your (filter) synths now need to internally know to auto-number their controls. Ideally you want this magic to happen externally of your synth function code and as much as possible transparently, meaning without changing the (filter) synth code much. Just writing ~foo.kr instead of \foo.kr in the synth to access the controls is less leaky in my view. The example I came up with also needing .asSymbol was probably not the best with respect to that least-code-change aspect. I had forgotten about the Symbol vs. String issue, to be honest.

This won’t be enough if your filters e.g. use LocalIn and LocalOut, which mine often do, because you can only have one of those local things per synth so combining such filters with SynthDef.wrap will probably not work even if you manage to get past the control renaming issues. (Faust’s approach to a more purely functional composition abstraction certainly helps work around such issues.)

Generally speaking, it looks like this approach of internally combining previously encapsulated user stuff into bigger SynthDefs isn’t favored much in SC. The simpler philosophy being that you just instantiate them as separate synths and route them as needed on the server.

If you don’t need such internal combining though, it turns out it’s possible to a have simpler step that does a sort of linker-like renaming just on the SynthDef, i.e. not recompiling (==rebuilding the ugen graph) function at all. This isn’t advertised in the help, but it does work properly, if you’re careful to deepCopy the SynthDef before making changes.

// for Ndefs, you may or may not want different \gate in each...
(~makeSDclones = { arg sdt, num, skipCtrlNames = #[\out];
	num.collect { arg i;
		var sdc = sdt.deepCopy;
		sdc.name = sdt.name.asString ++ i; // no eff without asString!
		sdc.allControlNames.do { arg cno;
			if(not(skipCtrlNames.includes(cno.name))) {
				cno.name = (cno.name.asString ++ i);
			} {
				// ("Skipped renaming" + cno.name + "in" + sdc).postln
			}
		};
		sdc // return whole sd clone to be collect-ed
	}
})

// Some tests just generating the clones, nothing sent to server (yet)

d = SynthDef(\alone, { arg out = 0, freq = 111; Out.ar(out, SinOsc.ar(freq)) } )
z = ~makeSDclones.(d, 3)
z.do { arg i; i.post; i.allControlNames.postln }

would post something like

SynthDef:alone0[ ControlName  P 0 out control 0, ControlName  P 1 freq0 control 111 ]
SynthDef:alone1[ ControlName  P 0 out control 0, ControlName  P 1 freq1 control 111 ]
SynthDef:alone2[ ControlName  P 0 out control 0, ControlName  P 1 freq2 control 111 ]

As .collect is “polymorphic” you can pass different things there for renaming e.g. arrays of specific numbers or strings:

~makeSDclones.(d, (1,3..9)) // just odd numbers
~makeSDclones.(d, ["Left", "Right"]) // or some strings etc.

Finally, some actual testing with a NodeProxy sources array.

z.do(_.add) // actually send defs to server

n = NodeProxy(s, \audio, 2)
n[0] = \alone0
n[1] = \alone1
n[2] = \alone2

n.edit // should see 3 controls

NodeProxy’s constructor is smart enough to interpret arrays of symbols as SynthDef names, so there you can just write e.g.

n = NodeProxy(s, \audio, 2, [\alone1, \alone2])

Beware however that something like that might hang the sever with Ndef’s constructor though.


Although a clean solution, this alas still won’t work Ndef-wise with \filter roles, or any roles for that matter (\mix etc.). Contrast

n = NodeProxy(s, \audio, 2)
n[0] = { arg fre1 = 777; 0.5 * SinOsc.ar(fre1) !2}
n[1] = \filter -> { arg in, fre2 = 333; 0.5 * SinOsc.ar(fre2) !2} 
//  fre2 exposed at top level func, so...
n.edit // gui "sees" fre2 and makes slider for it

with

n = NodeProxy(s, \audio, 2)
n[0] = { arg fre1 = 777; 0.5 * SinOsc.ar(fre1) !2}
m = NodeProxy(s, \audio, 2, { arg in, fre2 = 333; 0.5 * SinOsc.ar(fre2) !2})
n[1] = \filter -> { arg in; m.ar(2) } 
n.edit // doesn't see fre2 anymore

n.set(\fre2, 999) // doesn't do a thing either

The issue here is how JITlib treats filter “sub-nodes” in such cases. It won’t import their
own controls if there’s some indirection. Unlike the SynthDef graph builder, NodeProxy (built-in) roles only examine functions. I’m pondering whether a custom role could do better.

If you look at the \filter role implementation in wrapForNodeProxy.sc you can see the problem.
The function on the right side of the Association is SynthDef.wrap-ed. And that only works for
functions and nothing else. There’s alas not a way to SynthDef.wrap another SynthDef, but only
a bare function!

for that I think you could use the inEnvir technique without having to create a new role

Ndef(\test).play

~f = { ~ctrl.ar(1); Silent.ar  };

Ndef(\test).put(0, \filter -> ~f.inEnvir( (ctrl:\a)  ))
Ndef(\test).put(1, \filter -> ~f.inEnvir( (ctrl:\b)  )) 

Ndef(\test).controlNames

It’s funny that the SynthDef ugen builder is less tolerant than the proxy one

SynthDef(\hmm, ~f.inEnvir( (ctrl: \ah) ))

bombs out with an error as I noted a couple of posts above, at the end of that post.


Something that works every time: add a global name mangler to ControlName:

+ ControlName {
	//var <>name, <>index, <>rate, <>defaultValue, <>argNum, <>lag;

	*new { arg name, index, rate, defaultValue, argNum, lag;
		var mangledName; 
		// Warning: this constructor gets called a helluva lot during sclang startup!
		// If you add any debugging postln here, prepare for massive dumps...
		// During sclang startup, the currentEnvironment is nil sometimes, so we have to check that!
		if(currentEnvironment.isNil) { mangledName = name } {
			if(~controlNameMangler.isNil) { mangledName = name } {
				mangledName = ~controlNameMangler.value(name)
			}
		}
		^super.newCopyArgs(mangledName.asSymbol, index, rate, defaultValue, argNum, lag ? 0.0)
	}
}

Tests ok for me with

SynthDef(\alone, { arg out, freq; Out.ar(out, SinOsc.ar(freq)) } )
.allControlNames // no change of course

~mynme = (controlNameMangler: { arg name; name ++ "Woot" })

z = ~mynme.use { SynthDef(\alone, { arg out, freq; Out.ar(out, SinOsc.ar(freq)) } ) }
z.allControlNames // these are suffixed

Temporary global side effects are not much of an issue since sclang is only cooperatively multithreaded. This feature is (ab)used a lot by the SynthDef graph builder, which e.g. has a global classvar buildSynthDef in UGen for the synthdef currently being compiled. That’s how UGen methods knows where to add nodes to.

You may want a smarter name-mangling function that doesn’t suffix \out etc. as I noted (with example code) in a previous post.

Here’s an attempt to use to make the above more useable for SynthDef.wrapping the same function multiple times in the same SynthDef. It turns out this isn’t as easy/useable as I thought, mainly because NamedControl’s auto-deduplication is fighting us here at cross-purposes.

First define a convenience wrapper:

(~swrap = { arg func, suffix;
	var envir  = (controlNameMangler: { arg name; name ++ suffix.postln });
	SynthDef.wrap { envir.use { func.value } }; // This eats args!
})

Then try using it:

~f1 = { arg freq = 333; SinOsc.ar(freq) } // won't work because ~swrap is eating args
d = SynthDef(\LRtest, { Out.ar(0, [~swrap.(~f1, "Left"), ~swrap.(~f1, "Right")]) })
d.allControlNames // nil! (~f1 args were eaten by ~swrap)

~f2 = { SinOsc.ar(\freq.ar(333)) } // won't work because it deduplicates unsuffixed
d = SynthDef(\LRtest, { Out.ar(0, [~swrap.(~f2, "Left"), ~swrap.(~f2, "Right")]) })
d.allControlNames // well, only got Left... because deduplication in NamedControl

~f3 = { SinOsc.ar(Control.names(\freq).kr(333)) } // finally, ok
d = SynthDef(\LRtest, { Out.ar(0, [~swrap.(~f3, "Left"), ~swrap.(~f3, "Right")]) })
d.allControlNames // two controls, finally

d.add;
Ndef(\tLR, \LRtest).edit // ok, 2 ctrls

To make this more useable in the standard idioms, we’d need to hack NamedControl to understand ~controlNameMangler.

1 Like

The combination of inEnvir and a slight modification to the symbol extension for named controls solves this quite nicely for my purposes since I really only use functions and Ndef. The key thing was learning about inEnvir. Thanks.

+ Symbol {

    kr { | val, lag, fixedLag = false, spec |
        var name = "%%".format(this, ~num ?? {""});
		^NamedControl.kr(name, val, lag, fixedLag, spec)
	}

    ar { | val, lag, spec |
        var name = "%%".format(this, ~num ?? {""});
		^NamedControl.ar(name, val, lag, spec)
	}
...
}
1 Like

Note: earlier version was exhibiting a bug with NdefMixer; likely it would have happened with explicit use of ProxySpace as well, although I’ve stayed away from using that one explicitly myself insofar. I’ve added a check for that now in the first method below (Symbol.mangle).

I’ve got the NamedControl pre-mangling duplication check solved, i.e. now it’s a post-mangling check as it should be. It was quite a bit of code to change for that. Basically it needs to flag whether the mangling happened already in NamedControl.

+ Symbol {

	mangle {
		if(currentEnvironment.notNil) {
			if(~controlNameMangler.notNil) {
				// This is mostly a fix for NdefMixer which creates ControlNames
				// while use()-ing ProxySpace. And in ProxySpace every environment
				// variable key is mapped to a non-nil value! Furthermore, default
				// values differ between keys, so can't check even "==" equality
				// with the value mapped to a "random" key. But it's reasonably safe
				// to check that a random key is mapped to a non-nil value, to
				// detect proxy spacess.
				//this.dumpBackTrace;
				if(~aiospd345fjaiohtgXXO.isNil) {
					//("cnm:" + ~controlNameMangler + "this:" + this).postln;
					^~controlNameMangler.value(this).asSymbol.postln
				} {
					// "Detected ProxySpace".postln;
				}
			}
		}
		^this
	}

+ ControlName {

	*new { arg name, index, rate, defaultValue, argNum, lag, preMangled = false;
		^super.newCopyArgs(
			if(preMangled) { name.asSymbol } { name.asSymbol.mangle }, 
			index, rate, defaultValue, argNum, lag ? 0.0)
	}
}


+ SynthDef {

	// this is actually called from Control with a ControlName object
	// after it is built, so it needs no changes really, just noting that here
	addControlName { arg cn;
		controlNames = controlNames.add(cn);
		allControlNames = allControlNames.add(cn);
	}

	// allow incremental building of controls
	// CHANGED: all these (except addNonControl) are called from NamedControl,
	// so they now need to know if preMangled
	addNonControl { arg name, values, preMangled = false;
		this.addControlName(ControlName(name, nil, 'noncontrol',
			values.copy, controlNames.size, 0.0, preMangled));
	}
	addIr { arg name, values, preMangled = false;
		this.addControlName(ControlName(name, controls.size, 'scalar',
			values.copy, controlNames.size, 0.0, preMangled));
	}
	addKr { arg name, values, lags, preMangled = false;
		this.addControlName(ControlName(name, controls.size, 'control',
			values.copy, controlNames.size, lags.copy, preMangled));
	}
	addTr { arg name, values, preMangled = false;
		this.addControlName(ControlName(name, controls.size, 'trigger',
			values.copy, controlNames.size, 0.0, preMangled));
	}
	addAr { arg name, values, preMangled = false;
		this.addControlName(ControlName(name, controls.size, 'audio',
			values.copy, controlNames.size, 0.0, preMangled))
	}

}


+ NamedControl {

	*new { arg name, values, rate, lags, fixedLag = false, spec;
		var res;

		this.initDict;

		 /* just this line is CHANGED in this whole method (but more in init) */
		name = name.asSymbol.mangle;

		if (spec.notNil) {
			spec = spec.asSpec;

			if (values.isNil) {
				values = spec.default;
			};
		};

		res = currentControls.at(name);

		lags = lags.deepCollect(inf, {|elem|
			if (elem == 0) { nil } { elem }
		});

		if (lags.rate == \scalar) {
			fixedLag = true;
		};

		if(res.isNil) {
			values = (values ? 0.0).asArray;
			res = super.newCopyArgs(name, values, lags, rate, fixedLag).init;
			currentControls.put(name, res);
		} {
			values = (values ? res.values).asArray;
			if(res.values != values) {
				Error("NamedControl: cannot have more than one set of "
					"default values in the same control.").throw;
			};
			if(rate.notNil and: { res.rate != rate }) {
				Error("NamedControl: cannot have  more than one set of "
					"rates in the same control.").throw;
			};

		};

		if(res.fixedLag and: lags.notNil) {
			if( res.lags != lags ) {
				Error("NamedControl: cannot have more than one set of "
					"fixed lag values in the same control.").throw;
			} {
				^res.control;
			}
		};

		if(spec.notNil) {
			res.spec = spec; // Set after we've finished without error.
		};

		^if(lags.notNil) {
			res.control.lag(lags).unbubble
		} {
			res.control
		}
	}

	init { /* CHANGED: all callbacks to buildSynthDef need to pass preMangled: true */
		var prefix, str;

		name !? {
			str = name.asString;
			if(str[1] == $_) { prefix = str[0] };
		};

		if(fixedLag && lags.notNil && prefix.isNil) {
			// not sure why next line doesn't pass lags, by the way (might be no-op downstream)
			buildSynthDef.addKr(name, values.unbubble, preMangled: true);
			if(rate === \audio) {
				control = LagControl.ar(values.flat.unbubble, lags)
			} {
				control = LagControl.kr(values.flat.unbubble, lags)
			};
		} {
			if(prefix == $a or: {rate === \audio}) {
				buildSynthDef.addAr(name, values.unbubble, preMangled: true);
				control = AudioControl.ar(values.flat.unbubble);

			} {
				if(prefix == $t or: {rate === \trigger}) {
					buildSynthDef.addTr(name, values.unbubble, preMangled: true);
					control = TrigControl.kr(values.flat.unbubble);
				} {
					if(prefix == $i or: {rate === \scalar}) {
						buildSynthDef.addIr(name, values.unbubble, preMangled: true);
						control = Control.ir(values.flat.unbubble);
					} {
						buildSynthDef.addKr(name, values.unbubble, preMangled: true);
						control = Control.kr(values.flat.unbubble);
					}
				}
			};
		};

		control = control.asArray.reshapeLike(values).unbubble;
	}
}

With all that now this bit works properly:

(~swrap = { arg func, suffix;
	var envir  = (controlNameMangler: { arg name; (name ++ suffix).postln; });
	SynthDef.wrap { envir.use { func.value } }; // This eats args!
})

~f2 = { SinOsc.ar(\freq.ar(333)) } // works now because it deduplicates suffixed
d = SynthDef(\LRtest, { Out.ar(0, [~swrap.(~f2, "Left"), ~swrap.(~f2, "Right")]) })
d.allControlNames

I have a partial, i.e. “manual” fix for the issue of |... args| wrapped functions like inEnvir genates:

// altDefFunc allows the frame of another function to be used to auto-gen contols
// useful when the original function f is wrapped in a { arg ...args; /*stuff*/ f.valueArray(args) }
// or similar which makes the original f def (actual arg names) invisible to the SynthDef graph builder
+ SynthDef {

	*new { arg name, ugenGraphFunc, rates, prependArgs, variants, metadata, altDefFunc;
		^super.newCopyArgs(name.asSymbol).variants_(variants).metadata_(metadata ?? {()}).children_(Array.new(64))
			.build(ugenGraphFunc, rates, prependArgs, altDefFunc)
	}

	build { arg ugenGraphFunc, rates, prependArgs, altDefFunc;
		protect {
			this.initBuild;
			this.buildUgenGraph(ugenGraphFunc, rates, prependArgs, altDefFunc);
			this.finishBuild;
			func = ugenGraphFunc;
		} {
			UGen.buildSynthDef = nil;
		}
	}

	*wrap { arg func, rates, prependArgs, altDefFunc;
		if (UGen.buildSynthDef.isNil) {
			"SynthDef.wrap should be called inside a SynthDef ugenGraphFunc.\n".error;
			^0
		};
		^UGen.buildSynthDef.buildUgenGraph(func, rates, prependArgs, altDefFunc);
	}

	buildUgenGraph { arg func, rates, prependArgs, altDefFunc;
		var result;
		// save/restore controls in case of *wrap
		var saveControlNames = controlNames;

		controlNames = nil;

		prependArgs = prependArgs.asArray;
		this.addControlsFromArgsOfFunc(altDefFunc ? func, rates, prependArgs.size); // subst!!
		result = func.valueArray(prependArgs ++ this.buildControls);

		controlNames = saveControlNames

		^result
	}
}

Some basic tests:

SynthDef(\err, { arg ...args; Out.ar(0, 0) })

SynthDef(\errNoMore, { arg ...args; Out.ar(0, 0) }, altDefFunc: {})
// ok now!

// A more substantive test; real args
(z = SynthDef(\errNoMore,
	{ arg ...args; Out.ar(0, args[0] * SinOsc.ar(args[1])) },
	altDefFunc: { arg amp = 0.2, freq = 222; }))

z.allControlNames
// -> [ ControlName  P 0 amp control 0.2, ControlName  P 1 freq control 222 ]

z.add

Ndef(\zooo, \errNoMore).edit

//// now we can call inEnvir freely as long we can provide the original func as "alt"


f = { ~ctrl.ar(1); Silent.ar  };

SynthDef(\hmmm, f.inEnvir( (ctrl:\ah) )) // err of course

d = SynthDef(\hoho, f.inEnvir( (ctrl:\ah) ), altDefFunc: f)

d.allControlNames // -> [ ControlName  P 0 ah audio 1 ]

I strongly suspect one can use the altDefFunc bit to more directly implement arg name changes too without needing a function recompile. I’ll post about that later. (Basically it allows one change the names of the FunctionDef args for the purpose of SynthDef, whereas the FunctionDef args are alas immutable in sclang.)

I’ve made a bit more progress towards a more useable version of Ndef roles that auto-number their sub-gen params. I’m starting with \mix rather than \filter because it has simple code, so it’s easier to understand the changes. The original looks like this:

			mix: #{ | func, proxy, channelOffset = 0, index |

				{
					var ctl = Control.names(["mix" ++ (index ? 0)]).kr(1.0);
					var sig = SynthDef.wrap(func);
					var curve = if(sig.rate === \audio) { \sin } { \lin };
					var env = EnvGate(i_level: 0, doneAction:2, curve:curve);

					ctl * sig * env

				}.buildForProxy( proxy, channelOffset, index )
			};

For now I’m calling mine \mixN, where is N stands for numbering (I’m open to better name suggestions, as long as they aren’t too long). What I have so far uses all the classs extensions from above, but alas only really works for NamedControls and ContrlName explicit uses, but not for arg controls, for a somewhat subtle reason that I hope to remedy later. I’ll explain the issue with arg controls below the code. I left the postln debugging code in too.

(AbstractPlayControl.buildMethods.put(\mixN,
	#{ | func, proxy, channelOffset = 0, index |
		{
			var ctl = Control.names(["mix" ++ (index ? 0)]).kr(1.0);
			var imangler = { arg name; // can't be closed func due to index access
				("In imangler for" + name).postln;
				// could get these as proxy.internalKeys but that's not entirely correct
				// as these need to determined based on the "proxy" that's on right-hand
				// of the association, but that hasn't been built yet. Will add a version
				// later that supports a ready-made NodeProxy instead of bare function func.
				if(not(#[\out, \i_out, \gate, \fadeTime].includes(name.asSymbol))) {
					name = name.asString ++ index;
					("iMangled::" + name).postln;
				} {
					("Skipped::" + name).postln;
				};
				name
			};
			var menvir = (controlNameMangler: imangler).parent_(currentEnvironment);
			var sig = SynthDef.wrap(func.inEnvir(menvir), altDefFunc: func);
			var curve = if(sig.rate === \audio) { \sin } { \lin };
			var env = EnvGate(i_level: 0, doneAction:2, curve:curve);
			ctl * sig * env
		}.buildForProxy( proxy, channelOffset, index )
}));

So, to test this beast:

Ndef.clear
n = Ndef(\testMixN, { arg amp = 0.2, freq = 222; amp * SinOsc.ar(freq) })

n[3] = \mixN -> { \amp.kr(0.2) * SinOsc.ar(\freq.kr(777)) } 
n.edit // ok; slot 3 param names all get '3' suffix like 'amp3' etc.

n[4] = \mixN -> { arg amp = 0.2, freq = 444; amp * SinOsc.ar(freq) }
// doesn't work; no callbacks to our mangler at all!

The reason why that last line doesn’t work is that in

SynthDef.wrap(func.inEnvir(menvir), altDefFunc: func);

the way wrap (still) works is that it looks at altDefFunc: func and emits all its ControlNames immediately before evaluating func.inEnvir(menvir). So the mangler is not yet set up at that point. I’m pondering what’s the least intrusive way to fix this issue.

Ok, I have a properly working version of \mixN now, meaning it works for both arg and NamedControl. There were two bugs above, actually. The surprisingly easy fix for the arg issuse was to do just

var sig = menvir.use { SynthDef.wrap(func) }; // fix for arg

So the altDef business was actually not that useful or needed here. The second issue was that just with that NdefGui was exploding on the arg version complaining about missing specs. It turns out that I had forgotten a conversion to Symbol on the last line of mangler, which interestingly was only needed for the latter use case. Any how, here’s the fully working version for \mixN; debug postln's commented out.

(AbstractPlayControl.buildMethods.put(\mixN,
	#{ | func, proxy, channelOffset = 0, index |
		{
			var ctl = Control.names(["mix" ++ (index ? 0)]).kr(1.0);
			var imangler = { arg name; // can't be closed func due to index access
				if(not(#[\out, \i_out, \gate, \fadeTime].includes(name.asSymbol))) {
					name = name.asString ++ index;
					// ("iMangled::" + name).postln;
				} {
					// ("Skipped::" + name).postln;
				};
				name.asSymbol // does .asSymbol fix Spec issue in gui? YESSSSS.
			};
			var menvir = (controlNameMangler: imangler).parent_(currentEnvironment);
			var sig = menvir.use { SynthDef.wrap(func) }; // fix for arg
			var curve = if(sig.rate === \audio) { \sin } { \lin };
			var env = EnvGate(i_level: 0, doneAction:2, curve:curve);
			ctl * sig * env
		}.buildForProxy( proxy, channelOffset, index )
}));

So these use cases now both work:

Ndef.clear
n = Ndef(\testMixN, { arg amp = 0.2, freq = 222; amp * SinOsc.ar(freq) })

n[3] = \mixN -> { \amp.kr(0.2) * SinOsc.ar(\freq.kr(777)) } 
n[4] = \mixN -> { arg amp = 0.2, freq = 444; amp * SinOsc.ar(freq) }
n.controlNames do: _.postln
n.edit // works now for both 3 & 4

Here’s the \filter equivalent of that, meaning that does the same index-based auto-renaming:

(AbstractPlayControl.buildMethods.put(\filterN,
	#{ | func, proxy, channelOffset = 0, index |
		var imangler = { arg name;
			if(not(#[\in, \out, \i_out, \gate, \fadeTime].includes(name.asSymbol))) {
				name = name.asString ++ index;
				("F mangled::" + name).postln;
			} {
				("F skipped::" + name).postln;
			};
			name.asSymbol
		};
		var menvir = (controlNameMangler: imangler).parent_(currentEnvironment);
		var ok, ugen;

		if(proxy.isNeutral) {
			ugen = menvir.use { func.value(Silent.ar) };  // prolly doesn't matter
			ok = proxy.initBus(ugen.rate, ugen.numChannels + channelOffset);
			if(ok.not) { Error("NodeProxy input: wrong rate/numChannels").throw }
		};

		{ | out |
			var env, ctl = Control.names(["wet"++(index ? 0)]).kr(1.0);
			menvir.use { // but this does matter
				if(proxy.rate === 'audio') {
					env = ctl * EnvGate(i_level: 0, doneAction:2, curve:\sin);
					XOut.ar(out, env, SynthDef.wrap(func, nil, [In.ar(out, proxy.numChannels)]))
				} {
					env = ctl * EnvGate(i_level: 0, doneAction:2, curve:\lin);
					XOut.kr(out, env, SynthDef.wrap(func, nil, [In.kr(out, proxy.numChannels)]))
			}};
		}.buildForProxy( proxy, channelOffset, index )
}));

Test with something like

Ndef.clear
n = Ndef(\testFiltN, { arg amp = 0.3, freq = 888; amp * SinOsc.ar(freq) })

n[3] = \filterN -> { arg in; in * SinOsc.kr(\freqM.kr(2)) }
n[4] = \filterN -> { arg in, freqM = 9; in * SinOsc.kr(freqM)}

n.controlNames do: _.postln
n.edit 

Seems ok.

I’ve also noticed a small bug in \filter that affects uninitialized proxies. I haven’t fixed that above.

1 Like

hey, i admire your work on this but have a hard time to follow the discussion.
im using the midisynth class from this thread Video Tutorials on MIDI based music production with Supercollider, jackd and DAW - #10 by droptableuser advanced by the oportunity to specify a specific tuning

MidiSynth : Ndef {

    var <synthdef, <hasGate, <instrument;
    var <noteonkey, <noteoffkey, <cckey;

    *new {|key|
        var res = Ndef.dictFor(Server.default).envir[key];
        if (res.isNil) {
            res = super.new(key).prInit;
        };
        ^res;
    }

    prInit {
        noteonkey = "%_noteon".format(this.key).asSymbol;
        noteoffkey = "%_noteff".format(this.key).asSymbol;
        cckey = "%_cc".format(this.key).asSymbol;
        ^this;
    }

	note {|noteChan, note, root(0), tuning|
		MIDIdef.noteOn(noteonkey, {|vel, note, chan|

			var tunedNote = note - root;
			tunedNote = tuning.wrapAt(tunedNote)
			+ tunedNote.trunc(tuning.stepsPerOctave)
			+ root;

			if (this.hasGate) {
				this.put(note, instrument, extraArgs:[
					\freq, tunedNote.midicps, \vel, vel/127, \gate, 1])
			} {
                this.put(note, instrument, extraArgs:[
					\freq, tunedNote.midicps, \vel, vel/127])
            }
        }, noteNum:note, chan:noteChan)
        .fix;

        MIDIdef.noteOff(noteoffkey, {|vel, note, chan|
            if (this.hasGate) {
                this.objects[note].set(\gate, 0);
            }
        }, noteNum:note, chan:noteChan)
        .fix;
    }

    synth {|synth|
        synthdef = SynthDescLib.global.at(synth);
        instrument = synth;
        hasGate = synthdef.hasGate;
        this.prime(synth);
    }

    cc {|ctrl, ccNum, ccChan=0|
        var order = Order.newFromIndices(ctrl.asArray, ccNum.asArray);
        MIDIdef.cc(cckey, {|val, num|
            var ctrl = order[num];
            var spec = if (this.getSpec(ctrl).notNil) {
                this.getSpec(ctrl)
            }{
                [0, 1].asSpec;
            };
            var mapped = spec.map(val/127);
            this.set(ctrl, mapped);
        }, ccNum:ccNum, chan:ccChan)
        .fix;
    }

    disconnect {
        MIDIdef.noteOn(noteonkey).permanent_(false).free;
        MIDIdef.noteOff(noteoffkey).permanent_(false).free;
        MIDIdef.cc(cckey).permanent_(false).free;
    }
}
(
(1..50).do({|partials|
	SynthDef(\additive ++ partials, {

		var sig, freqs, gainEnv;

		gainEnv = EnvGen.ar(Env.adsr(
			\atk.kr(0.07),
			\dec.kr(0.5),
			\sus.kr(1),
			\rel.kr(2),
			curve: \curve.kr(-4)
		), \gate.kr(1), doneAction:2);

		freqs = Array.fill(partials, {|i|
			\freq.kr(20) * (i+1);
		});

		sig = freqs.collect({|freq, i|
			var amps = \decay.kr(0.5) / (i+1);
			SinOsc.ar(freq) * amps;
		});

		sig = Mix(sig);

		sig = sig * gainEnv * \amp.kr(0.3) * \vel.kr(1);
		sig = Splay.ar(sig);
		Out.ar(\out.kr(0), sig)
	}).add;
});
)

(
MidiSynth(\m1).synth(\additive10);

MidiSynth(\m1).note(noteChan:0, root: 7, tuning: Tuning.at(\just)).cc(ctrl:[
	\atk,
	\dec,
	\sus,
	\rel,
	\curve,
	\amp,
	\vel,
	\out,
], ccNum:(1..8), ccChan:0);

MidiSynth(\m1).addSpec(
	\atk, [0.07, 8],
	\dec, [0.5, 4],
	\sus, [0.07, 8],
	\rel, [0.07, 20],
	\curve, [(-4), 4],
	\amp, [0, 1],
	\vel, [0, 1],
	\out, [0, 1],
).edit;
)

and also encountered the issue of using an exisiting SynthDef for an fx chain.
how can this be done without rewriting the fx SynthDef as a function like this:

	~granular_reverb = {
		arg in=0, overlap=0.6, minGrainDur=0.001,
		tFreq=2, tFreqMF=0, tFreqMD=0,
		rate=1, rateMF=0, rateMD=0,
		offset=0.015, offsetMF=0, offsetMD=0;

		var sig, readPos, writePos, grainDur;
		var trig, bufFrames, sndBuf, bufDur;

		var tFreqMod = {
			SinOsc.ar(tFreqMF, Rand(0.0,2pi)) * tFreqMD;
		};

		var rateMod = {
			SinOsc.ar(rateMF, Rand(0.0,2pi)).range(0, rateMD);
		};

		var offsetMod = {
			SinOsc.ar(offsetMF, Rand(0.0,2pi)).range(0, offsetMD);
		};

		tFreq = tFreq + tFreqMod.dup;
		rate = rate - rateMod.dup;

		bufFrames = 2**16;
		sndBuf = {LocalBuf(bufFrames).clear}!2;
		bufDur = BufDur.ir(sndBuf);

		writePos = Phasor.ar(end: bufFrames);

		trig = Impulse.ar(tFreq, [0, \rightTriggerPhase.kr(0.25)]);
		grainDur = max(tFreq.reciprocal * overlap.lag(5), minGrainDur);

		readPos = writePos - 64 / bufFrames - offset - offsetMod.dup;
		readPos = Wrap.ar(readPos, 0, 1);

		sig = GrainBufJ.ar(
			numChannels: 1,
			loop: 1,
			trigger: trig,
			dur: grainDur,
			sndbuf: sndBuf,
			rate: rate,
			pos: readPos,
			interp: 4,
			pan: 0,
		);

		sig = HPF.ar(sig, \grHpf.kr(90));
		sig = LPF.ar(sig, \grLpf.kr(12500));

		// writing granulated sig + input back to grain buffer
		sndBuf.do { |b i|
			BufWr.ar(sig[i] * \feedback.kr(0.1) + in[i], b, writePos)
		};

		sig.tanh;
	};

and then using:

(
MidiSynth(\m1).filter(210, ~granular_reverb).set(

	\rate, 2.00,
	\tFreq, 5.0,
	\offset, 0.15,

	\rateMD, 0.0,
	\tFreqMD, 5.0,
	\offsetMD, 0.0,

	\rateMF, 0.25,
	\tFreqMF, 2.0,
	\offsetMF, 0.15,

	\grHpf, 75.0,
	\grLpf, 9500.0,

	\overlap, 1,
	\rightTriggerPhase, 0.25,
	\feedback, 0.1,

	\wet210, 1,
);
)

to make the fx chain? thanks a lot.

I’m not sure how your code is related to the issue being discussed here, namely how to automagically rename controls of multiple filters running in the same Ndef.

It’s probably best if you asked your question in a separate thread or perhaps in the one discussing that video tutorial. Honestly, I don’t understand exactly what your question is, other than that your code probably doesn’t do what you want, but it’s not clear to me what the latter is.

i also tried to use the SynthDef(\granular_reverb) like this but had to rewrite it to the function ~granular_reverb and use the filter method fo make it work.

im sorry when my programming knowledge is not sufficient enough to follow the discussion.

Did you try this solution posed by @hemiketal in their original question? It works, but the issue was with name-clashes that result from adding multiple copies of the same SynthDef to Ndef slots. It should work fine with just your one slot dedicated to granular_reverb. Something like this:

MidiSynth(\m1).filter(210, SynthDescLib.global.at(\granular_reverb).def.func)

You can’t use the \filter role while specifying a synthdef. So you would just do something like

MidiSynth(\m1).put(210, \granular_reverb)

In your synth you need to define an \out control which will be the private bus created by the Ndef.

If you look at around line 267 here - /usr/share/SuperCollider/SCClassLibrary/JITLib/ProxySpace/wrapForNodeProxy.sc

you can see how Jitlib creates the fx synth from a function so if you follow the same conventions in your own synthdef it should work seemlessly

While writing \mixN and \filterN that use the low-level mangler, I realized that unlike for SynthDef.wrap for which the lower-layer (meaning ControlName and NamedControl) mangler method is the only robust option, just for NodeProxy roles, it’s actually possible to apply the “clean” method I described in my ~makeSDclones earlier with some minor modifications.

This idea works for NodeProxy roles because every \filter, \mix etc. is compiled to a separate ProxySynthDef object, which is actually returned by buildForProxy to AbstractPlayControl.buildMethods where we have easy access to this
ProxySynthDef object after it has been built, but before it is passed back to the NodeProxy. So we can merrily rename its controls in makeSDclones-style before we pass it back.

The advantage of this technique is that just like ~makeSDclones, it requires zero new class extensions!

Here’s how to do it for \mix first, which is the simpler code to understand. I’m going to call this role \mixR for renaming after the ProxySynthDef is built.

(AbstractPlayControl.buildMethods.put(\mixR,
	#{ | func, proxy, channelOffset = 0, index |
		var mixi = "mix" ++ (index ? 0);
		var psd = { // we save this ProxySythnDef an will post-process it!
			var ctl = Control.names([mixi]).kr(1.0);
			var sig = SynthDef.wrap(func);
			var curve = if(sig.rate === \audio) { \sin } { \lin };
			var env = EnvGate(i_level: 0, doneAction:2, curve:curve);
			ctl * sig * env
		}.buildForProxy( proxy, channelOffset, index );
		// we still define this style of control mangler/rename func,
		// but will call it in a different spot than in \mixN
		var postmangler = { arg name;
			name = name.asString;
			if(["out", "i_out", "gate", "fadeTime", mixi].indexOfEqual(name).isNil) {
				name = name.asString ++ index;
				//("renamed::" + name).postln;
			} {
				//("skipped::" + name).postln;
			};
			name.asSymbol
		};
		psd.allControlNames.do { arg cno; cno.name = postmangler.(cno.name) };
		//psd.allControlNames.do(_.postln);
		psd
}));

Test:

Ndef.clear
n = Ndef(\testMixR, { arg amp = 0.2, freq = 222; amp * SinOsc.ar(freq) })

n[3] = \mixR -> { \amp.kr(0.2) * SinOsc.ar(\freq.kr(777)) }
n[4] = \mixR -> { arg amp = 0.2, freq = 444; amp * SinOsc.ar(freq) }

n.controlNames do: _.postln;
n.edit

Instead of writing something like that by hand 2 more times for \filter and \fitlerIn, since AbstractPlayControl.buildMethods gives us direct access to the whole table, we can just
create new functions en-masse by composing the old ones with a “postmangler” for
control names.

(~massPostmaglerInstaller = { arg newRolesSuffix = "M"; // so \mixM etc.
	var targetRoles = #[\mix, \filter, \filterIn];
	var defaultSkipNames = #["out", "i_out", "gate", "fadeTime"];
	var specificSkipNames = (mix: ["mix"], filter: ["wet"], filterIn: ["wet"]);
	var postmangler = { arg name, index, role;
		var skipNames = defaultSkipNames ++ (specificSkipNames[role] +++ index);
		name = name.asString;
		//skipNames.postln;
		if(skipNames.indexOfEqual(name).isNil) {
			name = name.asString ++ index;
			("Renamed::" + name).postln;
		} {
			("Skipped::" + name).postln;
		};
		name.asSymbol
	};
	var wrapperGen = { arg roleName, roleBuildFunc;  // curried targets
		{ arg func, proxy, channelOffset = 0, index;
			var psd = roleBuildFunc.value(func, proxy, channelOffset, index);
			psd.allControlNames.do { arg cno;
				cno.name = postmangler.value(cno.name, index, roleName) };
			psd.allControlNames.do(_.postln);
			psd
		}
	};
	targetRoles.collect { arg roleName;
		var origBuildFunc = AbstractPlayControl.buildMethods[roleName];
		var newBuildFunc = wrapperGen.value(roleName, origBuildFunc);
		var newRoleName = (roleName.asString ++ newRolesSuffix).asSymbol;
		AbstractPlayControl.buildMethods.put(newRoleName, newBuildFunc);
		(newRoleName.asString + "installed").postln;
		[newRoleName, newBuildFunc]  // ret val somewhat irrelevant
	}
})

A modest test of this thingy:

~massPostmaglerInstaller.()
Ndef.clear
n = Ndef(\testM, { arg amp = 0.2, freq = 222; amp * SinOsc.ar(freq) })
n[1] = \mixM -> { \amp.kr(0.2) * SinOsc.ar(\freq.kr(777)) }
n[2] = \mixM -> { arg amp, freq = 444; amp * SinOsc.ar(freq) }
n[11] = \filterM -> { arg in; in * SinOsc.kr(\freq.kr(2)) }
n[12] = \filterInM -> { arg in, freq = 9; in * SinOsc.kr(freq)}
n.edit

As closing thoughts; maybe some kind of index math wouldn’t hurt e.g. above
the three base frequencies and two AM frequencies could get their own counters.
This would need a different approach than just numbering by the Ndef slots,
e.g. a global Bag lookup.

Also I think that with Ndef roles you can only get the effects in linear order, so (sig1 * aM1) + (sig2 * aM2) is not really expressible as a single Ndef filter chain, I think, unless you mess with
multiple channels to trick it somehow with a final down mix and pan.

thanks for your help. its working with MidiSynth(\m1).put(210, \granular_reverb).set(...)
but im not able to get a 100% wet signal. will open another thread.
sorry for interrupting.

based on the code above, i think you would need to change your in arg

arg in=0

with something like

var in = In.ar(\out.kr, 2);

And then for your output if you’re using Out or ReplaceOut use this instead…

XOut.ar(\out.kr, \mix.kr(1), sig.tanh)

I’m not 100% certain but I think this would work, at least this is how I understand JitLib handles the plumbing…

Before I forget about this thread, I’m going to add a “table of contents” here for the several ways to skin this cat that have been discussed above. This will be a bit biased, I admit.

  1. If you only need to change the names of an already complied SynthDef, then you can do this quite safely by changing its .allControlNames, possibly using deepCopy too if you need several instances each with different control names. This is discussed in post #9 as makeSDclones. This techinque alone isn’t too useful for Ndef / NodeProxy roles (like \filer ->), but you can plug the resulting SynthDefs directly into NodeProxy sources slots.

  2. The previous technique can be adapted to NodeProxy roles by writing custom roles that essentially intercept the the ProxySynthDef object returned by .buildForProxy. This method has been discussed in post #20 under the names \mixM. \filterM, and \filterInM where a “mass generator” of such roles was given that can essentially take an existing role and add the automatic renaming functionality to it, producing a new role automagically.

The two related techniques above don’t require any extensions to the SC class library.

  1. If you need to combine several functions that produce SynthDef code into one SynthDef that doesn’t have control name conflicts, then the most general method is to install a mangler that intercepts the ControlNames as they get emitted to the SynthDef graph as it is being compiled. While this method does require some SC extensions, it does buy you the ability to SynthDef.wrap the same function multiple times in the same SynthDef e.g. with suffixed argument names for each invocation. Extension code for this method has been provided in post #13. To emphasize again: in difference to the technique used at the previous two points, this one produces a single resulting SynthDef, possibly from many instances of the same synth function. Although (in hindsight) a bit overkill for NodeProxy roles, this technique can also be used for them, as shown (as another application, if you will) in the 2nd part of post #14 as \mixN and \filterN. (Not much creativity with names, I admit.)

  2. Related to technique 3, you can also mangle the names in the function text code, but this approach is a little more brittle, because it might not find the control names to replace if they don’t show up in the function text directly, because e.g. they are obtained by calling yet another function. This technique has been discussed in post #2.

  3. If you’re willing to restrict yourself to using NamedControls invoked in \sym.kr style, a technique requiring simpler extensions is to alter / extend those Symbol methods a bit to do the mangling, e.g. to lookup some suffix from an environment and use inEnvir to evaluate the function in the right environment to get the suffix. This has been discussed in posts #10 and #12. A variation on this that essentially turns your SynthDef function in a macro of sorts, is to write ~foo.kr instead of \foo.kr and again to use inEnvir style evaluation for the replacement. The last approach requires no extensions whatsoever, but it does require one to change their source code.

I think I didn’t miss any major ideas / approaches discussed above in this summary. If I did, I apologize in advance. And please let me know if that’s the case so I can include the missing bits in this summary (while I can still edit it, that is).

2 Likes

Thank you for all your replies ! I learned a lot. Finally I used the @Avid_Reader solution, very neat!

I can now use fx in any Ndef, I integrated the code in my Param quark. I made a video to show how to build a sequencer GUI, then I use the Ndef fx at minute 8:40

5 Likes

Thanks for the vote of confidence. I haven’t watched your full video, so can you spoil it for the impatient me with respect to which of the above solutions you’ve used, so I can consider packaging it as a quark maybe?


For Ndef slots controls renaming I’ve added a feature to support some shared controls, in the meantime, for my own need. The syntax is a little odd, but it exploits the fact that array building has higher precedence in the sclang parser than ->, so you don’t have type many extra parentheses to force right-associativity. E.g. use case:

~filt = { |sig| Ringz.ar(sig, (\cutoff.kr(1) * 1000) + \lofreq.kr(100), 0.9, 0.5);};

~a = Ndef(\node) { LFSaw.ar(200, 0, 0.05) }; // sets ~a[0]

~a[1] = \filterM -> [~filt, \cutoff]; // only \lofreq will be numbered
~a[2] = \filterM -> [~filt, \cutoff]; // ibid

~a.edit;

\cutoff is shared contorls for both slots as Ndef normally does, but \lofreq is not. Basically, you supply an array whose first element is the ndef function, but the subsequent elements of this are are names of controls that are supposed to be (kept) shared. You can still use non-arrays as arguments, it will just make every control of that slot unique in that case, as in the previous versions of this role generator.

~a[3] = \filterM -> ~filt; // this one gets its separate cutoff too

~a.controlNames do: _.postln
/*
ControlName  P 1 wet1 control 1.0
ControlName  P 4 cutoff control 1
ControlName  P 5 lofreq1 control 100
ControlName  P 1 wet2 control 1.0
ControlName  P 5 lofreq2 control 100
ControlName  P 1 wet3 control 1.0
ControlName  P 4 cutoff3 control 1
ControlName  P 5 lofreq3 control 100
*/

For the curious: a syntax alternative would have been to addUniqueMethod the function so you could have written something like \filterM -> ~filt.common(\cutoff) because . also has higher precedence, but that approach ran into some SC bug with testing for the presence of addUnique-d methods later.)

So, if anybody needs this, here’s version of those Ndef roles that supports those (partially) shared controls, with the array syntax.:

(~massPostmaglerInstaller = { arg newRolesSuffix = "M"; // so \mixM etc.
	var targetRoles = #[\mix, \filter, \filterIn];
	var defaultSkipNames = #["out", "i_out", "gate", "fadeTime"];
	var specificSkipNames = (mix: ["mix"], filter: ["wet"], filterIn: ["wet"]);
	var postmangler = { arg name, index, role, extraSkipNames;
		var skipNames = defaultSkipNames ++ (specificSkipNames[role] +++ index);
		skipNames = skipNames ++ (extraSkipNames.collect {|n| n.asString});
		name = name.asString;
		extraSkipNames.postln;
		skipNames.postln;
		if(skipNames.indexOfEqual(name).isNil) {
			name = name.asString ++ index;
			("Renamed::" + name).postln;
		} {
			("Skipped::" + name).postln;
		};
		name.asSymbol
	};
	var wrapperGen = { arg roleName, roleBuildFunc;  // curried targets
		{ arg func, proxy, channelOffset = 0, index;
			var psd;
			func = func.asArray;
			psd = roleBuildFunc.value(func[0], proxy, channelOffset, index);
			psd.allControlNames.do { arg cno;
				cno.name = postmangler.value(cno.name, index, roleName, func[1..]) };
			psd.allControlNames.do(_.postln);
			psd
		}
	};
	targetRoles.collect { arg roleName;
		var origBuildFunc = AbstractPlayControl.buildMethods[roleName];
		var newBuildFunc = wrapperGen.value(roleName, origBuildFunc);
		var newRoleName = (roleName.asString ++ newRolesSuffix).asSymbol;
		AbstractPlayControl.buildMethods.put(newRoleName, newBuildFunc);
		(newRoleName.asString + "installed").postln;
		[newRoleName, newBuildFunc]  // ret val somewhat irrelevant
	}
};

~massPostmaglerInstaller.()
)

In this case don’t watch the video, I don’t show any internal code, the goal is to show how to create a complex GUI sequencer with FX with only a few lines of high level code

I used the renaming of controlNames, that’s the most easiest, quickest, cleanest solution =) Then I use Ndef(xx)[n] = \cloned_synthname where the synthdef have a In.ar and XOut.ar using the \out argument like you instructed


	cloneSynthDefWithIndexedArguments: { arg self;
		var sdc;
		var synthDef;
		var suffix = self.index;
		var synthDesc;
		synthDesc = SynthDesc(self.synthName);
		if(synthDesc.notNil) {
			synthDef = synthDesc.def;
			sdc = synthDef.deepCopy;
			sdc.name = synthDef.name.asString ++ suffix; // no eff without asString!
			sdc.allControlNames.do { arg cno;
				if(not(self.excludedArgs.includes(cno.name))) {
					cno.name = (cno.name.asString ++ suffix);
				} {
					// ("Skipped renaming" + cno.name + "in" + sdc).postln
				}
			};
			sdc // return whole sd clone to be collect-ed
		} {
			Log(\Param).debug("InsertFx.cloneSynthDefWithIndexedArguments: no synthDef: %", self.synthName);
			nil
		}
	},

Ok, but beware that if you In.ar(\out.ir) in a Ndef presently it has some odd effects like it will play immediately on bus 0. See e.g. this. Unless you’re also [re]numbering \out to \outX, which I’m guessing you might be doing, since you didn’t add exception for ‘out’ in your code.

Thanks I didn’t know this bug. This is not causing real problems for me for the moment because the Ndef is used as a mixer so it produce no sounds on its own ^^
But I have one question, I thought that I must use the name \out else Ndef will not know which control name to set out bus, no ? Or with a numbered suffix, Ndef will also recognize it ?