Csound Csound-dev Csound-tekno Search About

Re: [Csnd] [EXTERNAL] [Csnd] Tuning issues with the various pluck opcodes

Date2022-08-27 21:00
FromScott Daughtrey
SubjectRe: [Csnd] [EXTERNAL] [Csnd] Tuning issues with the various pluck opcodes
Being one who quite appreciates string sounds such as the bowed and plucked models, I wanted to try out this instrument.  However, as a relative newbie I'm clearly doing something wrong as I can hear plucked notes but they are accompanied by a droning feedback like timbre. I am aware with KS instruments that delay time affects pitch but this droning does not sound typical of fundamental delay feedback in the sense that changing the note pitch (fundamental delay time) does not change the accompanying feedback. Changing the sr changes the pitch of the drone. Any suggestions as to how this should be tamed would be appreciated. Below is how I applied this instr.



-odac 



sr     =        44100  
ksmps  =        32
nchnls =        2
0dbfs  =        1

garvb  init  0   
gadel  init  0   

instr 1

/* now we combine the modern waveguide model
with the ideas developed with the KS model */

ipi = -4*taninv(-1)

iamp = p4
ifun = p5
idec = 12
ipkpos = 0.5  /*0.5 = bridge*/
ipos = 0.01
idts = sr/ifun /* total delay time (samples) */
idtt = int(sr/ifun) /* truncated delay time */
idel = idts/sr /* delay time (secs) */

ifac init 1 /* decay shortening factor (fdb gain) */
is   init 0.5 /* loss filter coefficient */

igf pow 10, -idec/(20*ifun) /* gain required for a certain decay */
ig  = cos(ipi*ifun/sr)  /* unitary gain with s=0.5 */

if igf > ig igoto stretch /* if decay needs lengthening */
ifac = igf/ig /* if decay needs shortening */
goto continue

stretch:  /* this is the LP coefficient calculation to
 provide the required decay stretch */
icosfun = cos(2*ipi*ifun/sr)
ia = 2 - 2*icosfun
ib = 2*icosfun - 2
ic = 1 - igf*igf
id = sqrt(ib*ib - 4*ia*ic)
is1 = (-ib + id)/(ia*2)
is2 = (-ib - id)/(ia*2)
is = (is1 < is2 ? is1 : is2)

continue:
idtt = ((idtt+is) > (idts) ? idtt - 1: idtt)
ifd = (idts - (idtt + is)) /* fractional delay */
icoef = (1-ifd)/(1+ifd) /* allpass coefficient */
kcount line 0, p3, p3 /* time counter */

if kcount > idel kgoto wguide
/* this is the string initial state,
based on a ideal triangle shape
filtered by a gentle lowpass */
awvr linseg 0, ipos*idel/2, -iamp, (1-ipos)*idel, iamp, ipos*idel/2,0,1,0
aexcr = (awvr+delay1(awvr))*0.3


wguide:
adump delayr 1
adel  deltapn idtt
aflt = (adel*(1-is) + delay1(adel)*is)*ifac
alps filter2 aflt,1,1,icoef,1,icoef
ipkpr = (1-ipkpos)*idtt
ipkpl = ipkpos*idtt
apkupr deltapn ipkpr   /* right-going wave pickup */
apkupl deltapn ipkpl   /* left-going wave pickup */
       delayw  aflt+aexcr
aout   dcblock (apkupr+apkupl)*.5
       out     aout
endin




i1   0  4  1  128
i1   2  6  1  256




Csound mailing list
Csound@listserv.heanet.ie
https://listserv.heanet.ie/cgi-bin/wa?A0=CSOUND
Send bugs reports to
        https://github.com/csound/csound/issues
Discussions of bugs and features can be posted here

Date2022-08-27 21:33
FromMichael Saunders
SubjectRe: [Csnd] [EXTERNAL] [Csnd] Tuning issues with the various pluck opcodes
Poor intonation in physical models is a big problem.  They aren't usually musically useful off-the-shelf.  To adapt the built-in opcodes for practical use, I have to do a lot of measurement and tinkering, developing a function for the nominal frequency to send to the opcode as a function of the intended output frequency and the other input parameters.  

In the hopes that this might help other users (and maybe encourage developers to think about intonation), here is what I had to do to make wgbow usable.  Maybe there is a better way, but I've tested this and it works:



opcode  ODbow,a,kkkii
;A wrapper for wgbow that improves its intonation and behavior.
;Note: It's still poorly tuned in (11,12), especially [11.5,12]. Spiccato articulation is impossible with wgbow.
;amplitude [0,1], pitch [4,12], bow pressure [0,1], bow position (ipk), initial frequency (Hz)
;Bow position on string is in terms of harmonic number  [4.34...,40], tasto to ponticello
; -ve=exact value, +ve=adds some random variation (for repeated notes)
; [-1,1] == log scaled on ffitch's recommended range [4.34...,7.86...,40], tasto to ponticello
; -2 == my recommended value and random variation (log scaled between 6.5 & 7)
; Beware of extreme values, especially above oct 11:  they may not sound or may lead to upward octivation (harmonics).
;Initial frequency is given for efficiency.
kamp,kp,kpresIN,ipk,icps1 xin

if0=icps1/8.06;assume lowest frequency is ~1/8 initial: i.e.: I don't expect downward passages of more than 3 8ves.
if0 limit if0,14,28000
;Here's the bowing position, which doesn't seem to affect intonation, thank goodness.  It seems to affect brightness (ponticello vs. tasto) and the comb effect.  
;ffitch's recommendations are: "Usual playing is about 0.127236. The suggested range is 0.025 to 0.23."  
;So these are string fractions (the inverse of how I like to do it, with whole-number denominators so as to indicate the blocked (combed-out) overtone)?  
;Then min,pref,max ==   [4.34782609, 7.85941085856, 40]
;Log_10 of this is [0.63827216428, 0.89538999254, 1.60205999133]  I want to ParamMap this onto [-100,0,100] soft limit
;(good for modulation), yet also produce the overtone number interface...  So, I developed this mapping:
;krat=(kpos<-104?-1/(kpos+100):10^(-ParamMapk(0.63827216428, 0.89538999254, 1.60205999133, -100,100,  kpos, 0))), where kpos is on [-100,0,100].
;I find though, that since the leap into overtones (or upward octivation) depends on the state of the string, it's very difficult to predict the useful limits of position.;
;One possibility is to leave these generic limits, beware of extremes, and hope for the best.
; Another is to make kpos a static ipos.  I find modulation of the position to sound like cheap filter sweeps (better handled with output filters) or nothing (not expressive),
;and since it introduces no problems, I prefer a static ipos.  Say, given or 0=7.85941085856...=0.127236.
;[40, +inf] == 40 + some random variation
;[4.34...,40] == the given position + some random variation
;(1,4.34...) == 4.34... + some random variation
;[-1,1] == log scaled on ffitch's recommended range [4.34...,40], tasto to ponticello
;(-1,-4.34...) == my recommended value and random variation (log scaled between 6.5 & 7)
;[-40, -4.34...] == the given position exactly
;[-40, -inf] == 40 exactly
ipk0=log(4.34782609)
ipk1=log(7.85941085856)
ipk2=log(40)
ipks=(ipk>0?1:-1)
ipkal=log(abs(ipk))
ipkal=(ipkal<=0?ParamMapi(ipk0,ipk1,ipk2,0,1,(ipk+1)/2,0):ipkal);log(1)=0 ;
if (ipks<0 && ipkal<ipk0) then ; my recommendation
ipkal=1.908856163 ;(log(6.5)+log(7))/2, i.e. discouraging the 7th and 13th partials
ipkr=-0.018526993 ;(log(6.5)-log(7))/4, i.e, not completely squelching one for the other
ipkal+=birnd(ipkr)
elseif (ipks>0 && ipk>1) then
ipkalP=log(ipk+.25) ;can go quarterway to the next partial
ipkalM=log(ipk-.25)
ipkal=(ipkalP+ipkalM)/2 ;the middle of the implied range, in log terms
ipkr=(ipkalP-ipkalM)/2
ipkal+=birnd(ipkr)
endif
ipkal limit ipkal, ipk0,ipk2
irat=exp(-ipkal)

;wgbow always plays too sharp and is badly out of tune at high pitches (above about 8.5).  
;I've had to do all of this correction to make it useful.  It's still poorly tuned in (11,12), especially [11.5,12].
;First, here's a table of min,pref,max bowing pressure for every .1 oct from 4 to 12:
giBowPLim ftgenonce 0,0, 256,-2, .8, .8, .8, .4, .4, .6, .8, .6, .6, 1, 1, 1, 1, 1, 1, .6, .6, .6, .8, 1, 1, 1, .8, .6, .8, .4, .4, .4, .4, .8, .4, .4, \
1, .8, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 2.5, 2.5, 2.25, 2.5, 2.25, 2, 2, 2.25, 3.25,  \
3.0, 2.75, 2.5, 2.75, 3.75, 1.1, 1.25, 1.25, 1.25, 1.25, 1.25, 1.5, 1.5, 1.5, 1.5, 1.5, 1.75, 1.25, 1.25, 1.25, 1.25, 1.25, 1.25, 1.25,  \
1.25, 1.25, 1.5, 1.5, 1.75, 1.75, 1.75, 2, 1.5, 1.25, 1.5, 1.75, 1.25, 1.25, 1.75, 1.5, 1.5, 2, 2, 1.75, 1.75, 1.75, 2, 1.75, 2, 2, 2.25,  \
2.25, 2.5, 2.5, 2.5, 2.5, 2.5, 2.5, 2.5, 2.5, 2.75, 2.5, 2.75, 2.25, 2.75, 2.5, 2.75, 3, 3, 2.75, 2.75, 2.625, 3.375, 3.375, 3.25, 3.25,  \
3.5, 3.5, 3, 3, 3.75, 3.75, 3.0, 2.75, 3.0, 3.9, 2.5, 2.75, 2.75, 1.5, 1.5, 1.75, 2, 2, 2.25, 2.5, 2.5, 3.75, 2.5, 2.5, 2.75, 1.75, 1.75, 1.75,  \
1.75, 2, 2, 2.25, 2.5, 2.5, 2.75, 2.75, 3, 2, 1.75, 2.5, 2.75, 2.75, 2.75, 2.5, 2.5, 2.5, 3.25, 3, 2.5, 2.5, 2.75, 3, 3.5, 4, 4.25, 4.5, 4.25,  \
4.75, 4.5, 4.25, 4.25, 4.25, 4.5, 4.5, 4.5, 4.5, 4.25, 4.5, 4.5, 4.75, 4.75, 4.75, 4.75, 4.75, 4.75, 4.5, 4.25, 4.25, 4.25, 4.25, 4.25,  \
4.25, 4.25, 4, 3.75, 4.25, 4.25, 3.5, 3.0, 3.75, 4.0

;scale the bowing pressure onto the region where it does not blow up.
kndx=(kp-4.0049)*10
kpr0 tablei kndx, giBowPLim, 0,0,0
kpr1 tablei kndx+81, giBowPLim, 0,0,0
kpr2 tablei kndx+162, giBowPLim, 0,0,0
kpres ParamMapkk kpr0,kpr1,kpr2, 0,1,kpresIN, 0
;now to calculate the pitch correction.  p_0=p*-W_n(B^(p*-p_r)C(x)ln(B))/ln(B)
;where p_0=nominal pitch, p*=resulting pitch, W_n is the Lambert W function, x=pressure, B(p*)
;f_R,p_R, the reference frequency/pitch = 1485Hz = 10.504887502 oct
;C(x)=beat frequency vs. ipress parameter at the reference frequency.  I think the allowable range, at least at p_R, is ipres on [1,4.62]
;call max well-behaved ipress x_c(p) ?  does it matter?  only if I restrict the range of x according to p*.  
;So, unfortunately, B is a function of the apparent frequency/pitch B(p*)=
;B(f*)=kBx = -166.2378 + 46.15437*kp - 4.186258*kp^2 + 0.125595*kp^3
;The range of this is on (1.82125952527, 2.28233) p=10.1372,12.004887502
;error in pitch at p_R vs. the pressure parameter:
;C(x)=kCx=0.01571733 + 0.01539875*kpres - 0.01052697*kpres^2 + 0.002472625*kpres^3 - 0.0001968064*kpres^4
;now, what is the range of the argument of W_n() in my formula?
;ranges of: B: [1.82,2.29],   C: [.016,.0235],   p*-p_R:  [-6.5,  -2,   1.5]  therefore, the range of the argument is: []
;arg=B^(p*-p_R)*C*ln(B)= karg=log(kBx)*kCx*kBx^(kp-ipref) ;argument to Lambert W function
;W_n(arg)= kW= 0.00002017057 + 0.9962792*karg - 0.8608901*karg^2 ;Lambert W function
;pitch sent to bow=p_0: kpbow=kp-kW/log(kBx)
;so,
;kBx = -166.2378 + 46.15437*kp - 4.186258*kp^2 + 0.125595*kp^3
;kCx=0.01571733 + 0.01539875*kpres - 0.01052697*kpres^2 + 0.002472625*kpres^3 - 0.0001968064*kpres^4
;karg=log(kBx)*kCx*kBx^(kp-ipref) ;argument to Lambert W function
;kW= 0.00002017057 + 0.9962792*karg - 0.8608901*karg^2 ;Lambert W function
;kpbow=kp-kW/log(kBx)
;kcps=cpsoct(kpbow)
ipref=10.504887502;reference pitch
kBx = (kp>10.57524168412?2.140456 + (-33.55319 - 2.140456)/(1 + (kp/10.39056)^248.0945):1.69101 + (2.030742 - 1.69101)/(1 + (kp/10.10483)^97.84136))
kCx=0.01571733 + 0.01539875*kpres - 0.01052697*kpres^2 + 0.002472625*kpres^3 - 0.0001968064*kpres^4
karg=log(kBx)*kCx*kBx^(kp-ipref) ;argument to Lambert W function
kW= 0.00002017057 + 0.9962792*karg - 0.8608901*karg^2 ;Lambert W function
kpbow=kp-kW/log(kBx)
kcps=cpsoct(kpbow)

az wgbow kamp,kcps,kpres,irat, 0,0, giSine,if0;-ve locks it up: initialization can't be skipped

xout az
endop



        opcode ParamMapkk, k, kkkiiki
;map a linear input, x, to an output, y, quadratically, given:
;min y, typical y, max y; minx, max x, x; hard limit? 1=yes
kminy,ktypy,kmaxy,iminx,imaxx,kx,ilimit     xin
kxp=(kx-iminx)/(imaxx-iminx);map input onto [0,1]
ka=2*(kminy+kmaxy-2*ktypy);coefficients...
kb=2*(kmaxy-ktypy-.75*ka)
kout=ka*(kxp^2)+kb*kxp+kminy
if (ilimit!=1) goto end
kout=(kminy<kmaxy?limit(kout,kminy,kmaxy):limit(kout,kmaxy,kminy))
end:        xout kout
        endop

        opcode ParamMapi, i, iiiiiii
;map a linear input, x, to an output, y, quadratically, given:
;min y, typical y, max y; minx, max x, x; hard limit? 1=yes
iminy,itypy,imaxy,iminx,imaxx,ix,ilimit     xin
ixp=(ix-iminx)/(imaxx-iminx);map input onto [0,1]
ia=2*(iminy+imaxy-2*itypy);coefficients...
ib=2*(imaxy-itypy-.75*ia)
iout=ia*(ixp^2)+ib*ixp+iminy
if (ilimit!=1) igoto end
iout=(iminy<imaxy?limit(iout,iminy,imaxy):limit(iout,imaxy,iminy))
end:        xout iout
        endop

...   I wish it were easier to use Csound!
Csound mailing list Csound@listserv.heanet.ie https://listserv.heanet.ie/cgi-bin/wa?A0=CSOUND Send bugs reports to https://github.com/csound/csound/issues Discussions of bugs and features can be posted here

Date2022-08-27 21:44
FromVictor Lazzarini
SubjectRe: [Csnd] [EXTERNAL] [Csnd] Tuning issues with the various pluck opcodes
Ah, there was a line missing to set the excitation to 0.
aexc = 0

I didn’t notice it because I was using MIDI and the problem never showed itself there (since p3 was negative)
Here’s the instrument again, fixed

 
 
-d --midi-key-cps=5 --midi-velocity-amp=4



sr=44100
nchnls=1
0dbfs=1

instr 1

/* now we combine the modern waveguide model
with the ideas developed with the KS model */

ipi = -4*taninv(-1)

iamp = p4
ifun = p5
idec = 12
ipkpos = 0.5
ipos = 0.01
idts = sr/ifun      /* total delay time (samples) */
idtt = int(sr/ifun) /* truncated delay time */
idel = idts/sr      /* delay time (secs) */
 
ifac init 1          /* decay shortening factor (fdb gain) */
is   init 0.5        /* loss filter coefficient */

igf pow 10, -idec/(20*ifun) /* gain required for a certain decay */
ig  = cos(ipi*ifun/sr)      /* unitary gain with s=0.5 */

if igf > ig igoto stretch /* if decay needs lengthening */
ifac = igf/ig             /* if decay needs shortening */
goto continue

stretch:       /* this is the LP coefficient calculation to
                  provide the required decay stretch */       
icosfun = cos(2*ipi*ifun/sr)
ia = 2 - 2*icosfun
ib = 2*icosfun - 2
ic = 1 - igf*igf 
id = sqrt(ib*ib - 4*ia*ic)
is1 = (-ib + id)/(ia*2)
is2 = (-ib - id)/(ia*2)
is = (is1 < is2 ? is1 : is2) 

continue:
idtt = ((idtt+is) > (idts) ? idtt - 1: idtt)
ifd = (idts - (idtt + is))  /* fractional delay */
icoef = (1-ifd)/(1+ifd)  /* allpass coefficient */
kcount timeinsts    /* time counter */

aexcr = 0
if kcount > idel kgoto wguide
/* this is the string initial state,
   based on a ideal triangle shape
   filtered by a gentle lowpass  */
awvr linseg 0, ipos*idel/2, -iamp, (1-ipos)*idel, iamp, ipos*idel/2,0,1,0  
aexcr = (awvr+delay1(awvr))*0.5

wguide:
adump  delayr 1
adel   deltapn idtt
aflt = (adel*(1-is) + delay1(adel)*is)*ifac 
alps filter2 aflt,1,1,icoef,1,icoef
ipkpr = (1-ipkpos)*idtt
ipkpl = ipkpos*idtt
apkupr deltapn ipkpr   /* right-going wave pickup */
apkupl deltapn ipkpl   /* left-going wave pickup */
       delayw    aflt+aexcr
aout  dcblock (apkupr+apkupl)*0.25
      out  aout
endin




i1 0 1 0.5 440




========================
Prof. Victor Lazzarini
Maynooth University
Ireland

> On 27 Aug 2022, at 21:00, Scott Daughtrey  wrote:
> 
> Being one who quite appreciates string sounds such as the bowed and plucked models, I wanted to try out this instrument.  However, as a relative newbie I'm clearly doing something wrong as I can hear plucked notes but they are accompanied by a droning feedback like timbre. I am aware with KS instruments that delay time affects pitch but this droning does not sound typical of fundamental delay feedback in the sense that changing the note pitch (fundamental delay time) does not change the accompanying feedback. Changing the sr changes the pitch of the drone. Any suggestions as to how this should be tamed would be appreciated. Below is how I applied this instr.
> 
> 
> 
> -odac 
> 
> 
> 
> sr     =        44100  
> ksmps  =        32
> nchnls =        2
> 0dbfs  =        1
> 
> garvb  init  0   
> gadel  init  0   
> 
> instr 1
> 
> /* now we combine the modern waveguide model
> with the ideas developed with the KS model */
> 
> ipi = -4*taninv(-1)
> 
> iamp = p4
> ifun = p5
> idec = 12
> ipkpos = 0.5  /*0.5 = bridge*/
> ipos = 0.01
> idts = sr/ifun /* total delay time (samples) */
> idtt = int(sr/ifun) /* truncated delay time */
> idel = idts/sr /* delay time (secs) */
> 
> ifac init 1 /* decay shortening factor (fdb gain) */
> is   init 0.5 /* loss filter coefficient */
> 
> igf pow 10, -idec/(20*ifun) /* gain required for a certain decay */
> ig  = cos(ipi*ifun/sr)  /* unitary gain with s=0.5 */
> 
> if igf > ig igoto stretch /* if decay needs lengthening */
> ifac = igf/ig /* if decay needs shortening */
> goto continue
> 
> stretch:  /* this is the LP coefficient calculation to
> provide the required decay stretch */
> icosfun = cos(2*ipi*ifun/sr)
> ia = 2 - 2*icosfun
> ib = 2*icosfun - 2
> ic = 1 - igf*igf
> id = sqrt(ib*ib - 4*ia*ic)
> is1 = (-ib + id)/(ia*2)
> is2 = (-ib - id)/(ia*2)
> is = (is1 < is2 ? is1 : is2)
> 
> continue:
> idtt = ((idtt+is) > (idts) ? idtt - 1: idtt)
> ifd = (idts - (idtt + is)) /* fractional delay */
> icoef = (1-ifd)/(1+ifd) /* allpass coefficient */
> kcount line 0, p3, p3 /* time counter */
> 
> if kcount > idel kgoto wguide
> /* this is the string initial state,
> based on a ideal triangle shape
> filtered by a gentle lowpass */
> awvr linseg 0, ipos*idel/2, -iamp, (1-ipos)*idel, iamp, ipos*idel/2,0,1,0
> aexcr = (awvr+delay1(awvr))*0.3
> 
> 
> wguide:
> adump delayr 1
> adel  deltapn idtt
> aflt = (adel*(1-is) + delay1(adel)*is)*ifac
> alps filter2 aflt,1,1,icoef,1,icoef
> ipkpr = (1-ipkpos)*idtt
> ipkpl = ipkpos*idtt
> apkupr deltapn ipkpr   /* right-going wave pickup */
> apkupl deltapn ipkpl   /* left-going wave pickup */
>       delayw  aflt+aexcr
> aout   dcblock (apkupr+apkupl)*.5
>       out     aout
> endin
> 
> 
> 
> 
> i1   0  4  1  128
> i1   2  6  1  256
> 
> 
> 
> 
> Csound mailing list
> Csound@listserv.heanet.ie
> https://eur02.safelinks.protection.outlook.com/?url=https%3A%2F%2Flistserv.heanet.ie%2Fcgi-bin%2Fwa%3FA0%3DCSOUND&data=05%7C01%7CVictor.Lazzarini%40mu.ie%7C194d8ed735ba4f0f4e4d08da8866d956%7C1454f5ccbb354685bbd98621fd8055c9%7C0%7C0%7C637972273178226027%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C2000%7C%7C%7C&sdata=LkhM1VNIcZmBVZYdO6RKfWax2Amme65GzbuEcQsLFqE%3D&reserved=0
> Send bugs reports to
>        https://eur02.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com%2Fcsound%2Fcsound%2Fissues&data=05%7C01%7CVictor.Lazzarini%40mu.ie%7C194d8ed735ba4f0f4e4d08da8866d956%7C1454f5ccbb354685bbd98621fd8055c9%7C0%7C0%7C637972273178226027%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C2000%7C%7C%7C&sdata=f5kkLFvnA%2BBifS8ig%2BSzoS7NViQK4K115TMO6TpbSVQ%3D&reserved=0
> Discussions of bugs and features can be posted here


Csound mailing list
Csound@listserv.heanet.ie
https://listserv.heanet.ie/cgi-bin/wa?A0=CSOUND
Send bugs reports to
        https://github.com/csound/csound/issues
Discussions of bugs and features can be posted here