Reorganize the project folder structure and how go packages are organized.

Sointu.asm / lib stuff lives at the root folder. There is a folder called "go4k", which is where
all go stuff lives. Following the ideas from https://medium.com/@benbjohnson/standard-package-layout-7cdbc8391fc1
the go4k folder is the "domain-model" of the go side, and should have no dependencies.
It contains Unit, Instrument, Synth interface etc. Putting go4k under a sub-folder is actually
in the spirit of Ben, as go4k adds dependency to the go language.

Bridge ties the domain-model to the sointulib through cgo. It returns C.Synth, but
makes sure the C.Synth implements the Synth interface, so others are able to use the
Synth no matter how it actually is done. MockSynth and WebProxy synth are good
prospects for other implementations of Synth.

It is a bit fuzzy where methods like "Play" that have no dependencies other than domain
model structs should go. They probably should live in the go4k package as well.

The file-organization on the Go-side is not at all finalized. But how packages are broken
into files is mostly a documentation issue; it does not affect the users of the packages at
all.

BTW: The name go4k was chosen because Ben advocated naming the subpackages
according to the dependency they introduce AND because the prototype of 4klang was
called go4k (there are still some defines in the 4klang source revealing this). go4k thus
honors our roots but is also not so bad name: it's the main package of a 4k synth tracker,
written in go.
This commit is contained in:
Veikko Sariola
2020-10-30 22:05:26 +02:00
parent 23e8bc0c5f
commit e0a793ea6d
116 changed files with 530 additions and 635 deletions

View File

@ -0,0 +1,93 @@
%ifdef SU_USE_INTROSPECTION
; Various compile time definitions exported
SECT_DATA(introscn)
%ifdef SU_USE_16BIT_OUTPUT
EXPORT MANGLE_DATA(su_use_16bit_output)
dd 1
%else
EXPORT MANGLE_DATA(su_use_16bit_output)
dd 0
%endif
%ifndef SU_DISABLE_PLAYER
%ifdef MAX_SAMPLES
EXPORT MANGLE_DATA(su_max_samples)
dd MAX_SAMPLES
%endif
%endif
; Arithmetic opcode ids
EXPORT MANGLE_DATA(su_add_id)
dd ADD_ID
EXPORT MANGLE_DATA(su_addp_id)
dd ADDP_ID
EXPORT MANGLE_DATA(su_pop_id)
dd POP_ID
EXPORT MANGLE_DATA(su_loadnote_id)
dd LOADNOTE_ID
EXPORT MANGLE_DATA(su_mul_id)
dd MUL_ID
EXPORT MANGLE_DATA(su_mulp_id)
dd MULP_ID
EXPORT MANGLE_DATA(su_push_id)
dd PUSH_ID
EXPORT MANGLE_DATA(su_xch_id)
dd XCH_ID
; Effect opcode ids
EXPORT MANGLE_DATA(su_distort_id)
dd DISTORT_ID
EXPORT MANGLE_DATA(su_hold_id)
dd HOLD_ID
EXPORT MANGLE_DATA(su_crush_id)
dd CRUSH_ID
EXPORT MANGLE_DATA(su_gain_id)
dd GAIN_ID
EXPORT MANGLE_DATA(su_invgain_id)
dd INVGAIN_ID
EXPORT MANGLE_DATA(su_filter_id)
dd FILTER_ID
EXPORT MANGLE_DATA(su_clip_id)
dd CLIP_ID
EXPORT MANGLE_DATA(su_pan_id)
dd PAN_ID
EXPORT MANGLE_DATA(su_delay_id)
dd DELAY_ID
EXPORT MANGLE_DATA(su_compres_id)
dd COMPRES_ID
; Flowcontrol opcode ids
EXPORT MANGLE_DATA(su_advance_id)
dd SU_ADVANCE_ID
EXPORT MANGLE_DATA(su_speed_id)
dd SPEED_ID
; Sink opcode ids
EXPORT MANGLE_DATA(su_out_id)
dd OUT_ID
EXPORT MANGLE_DATA(su_outaux_id)
dd OUTAUX_ID
EXPORT MANGLE_DATA(su_aux_id)
dd AUX_ID
EXPORT MANGLE_DATA(su_send_id)
dd SEND_ID
; Source opcode ids
EXPORT MANGLE_DATA(su_envelope_id)
dd ENVELOPE_ID
EXPORT MANGLE_DATA(su_noise_id)
dd NOISE_ID
EXPORT MANGLE_DATA(su_oscillat_id)
dd OSCILLAT_ID
EXPORT MANGLE_DATA(su_loadval_id)
dd LOADVAL_ID
EXPORT MANGLE_DATA(su_receive_id)
dd RECEIVE_ID
EXPORT MANGLE_DATA(su_in_id)
dd IN_ID
%endif ; SU_USE_INTROSPECTION

View File

@ -0,0 +1,173 @@
SECT_TEXT(suarithm)
;-------------------------------------------------------------------------------
; POP opcode: remove (discard) the topmost signal from the stack
;-------------------------------------------------------------------------------
; Mono: a -> (empty)
; Stereo: a b -> (empty)
;-------------------------------------------------------------------------------
%if POP_ID > -1
EXPORT MANGLE_FUNC(su_op_pop,0)
%ifdef INCLUDE_STEREO_POP
jnc su_op_pop_mono
fstp st0
su_op_pop_mono:
%endif
fstp st0
ret
%endif
;-------------------------------------------------------------------------------
; ADD opcode: add the two top most signals on the stack
;-------------------------------------------------------------------------------
; Mono: a b -> a+b b
; Stereo: a b c d -> a+c b+d c d
;-------------------------------------------------------------------------------
%if ADD_ID > -1
EXPORT MANGLE_FUNC(su_op_add,0)
%ifdef INCLUDE_STEREO_ADD
jnc su_op_add_mono
fadd st0, st2
fxch
fadd st0, st3
fxch
ret
su_op_add_mono:
%endif
fadd st1
ret
%endif
;-------------------------------------------------------------------------------
; ADDP opcode: add the two top most signals on the stack and pop
;-------------------------------------------------------------------------------
; Mono: a b -> a+b
; Stereo: a b c d -> a+c b+d
;-------------------------------------------------------------------------------
%if ADDP_ID > -1
EXPORT MANGLE_FUNC(su_op_addp,0)
%ifdef INCLUDE_STEREO_ADDP
jnc su_op_addp_mono
faddp st2, st0
faddp st2, st0
ret
su_op_addp_mono:
%endif
faddp st1, st0
ret
%endif
;-------------------------------------------------------------------------------
; LOADNOTE opcode: load the current note, scaled to [-1,1]
;-------------------------------------------------------------------------------
; Mono: (empty) -> n, where n is the note
; Stereo: (empty) -> n n
;-------------------------------------------------------------------------------
%if LOADNOTE_ID > -1
EXPORT MANGLE_FUNC(su_op_loadnote,0)
%ifdef INCLUDE_STEREO_LOADNOTE
jnc su_op_loadnote_mono
call su_op_loadnote_mono
su_op_loadnote_mono:
%endif
fild dword [INP-su_voice.inputs+su_voice.note]
do fmul dword [,c_i128,]
do fsub dword [,c_0_5,] ; s-.5
fadd st0, st0 ; 2*s-1
ret
%endif
;-------------------------------------------------------------------------------
; MUL opcode: multiply the two top most signals on the stack
;-------------------------------------------------------------------------------
; Mono: a b -> a*b a
; Stereo: a b c d -> a*c b*d c d
;-------------------------------------------------------------------------------
%if MUL_ID > -1
EXPORT MANGLE_FUNC(su_op_mul,0)
%ifdef INCLUDE_STEREO_MUL
jnc su_op_mul_mono
fmul st0, st2
fxch
fadd st0, st3
fxch
ret
su_op_mul_mono:
%endif
fmul st1
ret
%endif
;-------------------------------------------------------------------------------
; MULP opcode: multiply the two top most signals on the stack and pop
;-------------------------------------------------------------------------------
; Mono: a b -> a*b
; Stereo: a b c d -> a*c b*d
;-------------------------------------------------------------------------------
%if MULP_ID > -1
EXPORT MANGLE_FUNC(su_op_mulp,0)
%ifdef INCLUDE_STEREO_MULP
jnc su_op_mulp_mono
fmulp st2, st0
fmulp st2, st0
ret
su_op_mulp_mono:
%endif
fmulp st1
ret
%endif
;-------------------------------------------------------------------------------
; PUSH opcode: push the topmost signal on the stack
;-------------------------------------------------------------------------------
; Mono: a -> a a
; Stereo: a b -> a b a b
;-------------------------------------------------------------------------------
%if PUSH_ID > -1
EXPORT MANGLE_FUNC(su_op_push,0)
%ifdef INCLUDE_STEREO_PUSH
jnc su_op_push_mono
fld st1
fld st1
ret
su_op_push_mono:
%endif
fld st0
ret
%endif
;-------------------------------------------------------------------------------
; XCH opcode: exchange the signals on the stack
;-------------------------------------------------------------------------------
; Mono: a b -> b a
; stereo: a b c d -> c d a b
;-------------------------------------------------------------------------------
%if XCH_ID > -1
EXPORT MANGLE_FUNC(su_op_xch,0)
%ifdef INCLUDE_STEREO_XCH
jnc su_op_xch_mono
fxch st0, st2 ; c b a d
fxch st0, st1 ; b c a d
fxch st0, st3 ; d c a b
su_op_xch_mono:
%endif
fxch st0, st1
ret
%endif

View File

@ -0,0 +1,168 @@
;-------------------------------------------------------------------------------
; ADDP related defines
;-------------------------------------------------------------------------------
%assign ADDP_ID -1
%macro USE_ADDP 0
%if ADDP_ID == -1
%assign ADDP_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_addp,0),
%xdefine NUMPARAMS NUMPARAMS 0,
%endif
%endmacro
%macro SU_ADDP 1
USE_ADDP
%xdefine CMDS CMDS ADDP_ID + %1,
%if %1 == STEREO
%define INCLUDE_STEREO_ADDP
%endif
%endmacro
;-------------------------------------------------------------------------------
; ADD related defines
;-------------------------------------------------------------------------------
%assign ADD_ID -1
%macro USE_ADD 0
%if ADD_ID == -1
%assign ADD_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_add,0),
%xdefine NUMPARAMS NUMPARAMS 0,
%endif
%endmacro
%assign ADD_ID -1
%macro SU_ADD 1
USE_ADD
%xdefine CMDS CMDS ADD_ID + %1,
%if %1 == STEREO
%define INCLUDE_STEREO_ADD
%endif
%endmacro
;-------------------------------------------------------------------------------
; POP related defines
;-------------------------------------------------------------------------------
%assign POP_ID -1
%macro USE_POP 0
%if POP_ID == -1
%assign POP_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_pop,0),
%xdefine NUMPARAMS NUMPARAMS 0,
%endif
%endmacro
%macro SU_POP 1
USE_POP
%xdefine CMDS CMDS POP_ID + %1,
%if %1 == STEREO
%define INCLUDE_STEREO_POP
%endif
%endmacro
;-------------------------------------------------------------------------------
; LOADNOTE related defines
;-------------------------------------------------------------------------------
%assign LOADNOTE_ID -1
%macro USE_LOADNOTE 0
%if LOADNOTE_ID == -1
%assign LOADNOTE_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_loadnote,0),
%xdefine NUMPARAMS NUMPARAMS 0,
%endif
%endmacro
%macro SU_LOADNOTE 1
USE_LOADNOTE
%xdefine CMDS CMDS LOADNOTE_ID + %1,
%if %1 == STEREO
%define INCLUDE_STEREO_LOADNOTE
%endif
%endmacro
;-------------------------------------------------------------------------------
; MUL related defines
;-------------------------------------------------------------------------------
%assign MUL_ID -1
%macro USE_MUL 0
%if MUL_ID == -1
%assign MUL_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_mul,0),
%xdefine NUMPARAMS NUMPARAMS 0,
%endif
%endmacro
%macro SU_MUL 1
USE_MUL
%xdefine CMDS CMDS MUL_ID + %1,
%if %1 == STEREO
%define INCLUDE_STEREO_MUL
%endif
%endmacro
;-------------------------------------------------------------------------------
; MULP related defines
;-------------------------------------------------------------------------------
%assign MULP_ID -1
%macro USE_MULP 0
%if MULP_ID == -1
%assign MULP_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_mulp,0),
%xdefine NUMPARAMS NUMPARAMS 0,
%endif
%endmacro
%macro SU_MULP 1
USE_MULP
%xdefine CMDS CMDS MULP_ID + %1,
%if %1 == STEREO
%define INCLUDE_STEREO_MULP
%endif
%endmacro
;-------------------------------------------------------------------------------
; PUSH related defines
;-------------------------------------------------------------------------------
%assign PUSH_ID -1
%macro USE_PUSH 0
%if PUSH_ID == -1
%assign PUSH_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_push,0),
%xdefine NUMPARAMS NUMPARAMS 0,
%endif
%endmacro
%macro SU_PUSH 1
USE_PUSH
%xdefine CMDS CMDS PUSH_ID + %1,
%if %1 == STEREO
%define INCLUDE_STEREO_PUSH
%endif
%endmacro
;-------------------------------------------------------------------------------
; XCH related defines
;-------------------------------------------------------------------------------
%assign XCH_ID -1
%macro USE_XCH 0
%if XCH_ID == -1
%assign XCH_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_xch,0),
%xdefine NUMPARAMS NUMPARAMS 0,
%endif
%endmacro
%macro SU_XCH 1
USE_XCH
%xdefine CMDS CMDS XCH_ID + %1,
%if %1 == STEREO
%define INCLUDE_STEREO_XCH
%endif
%endmacro

View File

@ -0,0 +1,473 @@
;-------------------------------------------------------------------------------
; DISTORT opcode: apply distortion on the signal
;-------------------------------------------------------------------------------
; Mono: x -> x*a/(1-a+(2*a-1)*abs(x)) where x is clamped first
; Stereo: l r -> l*a/(1-a+(2*a-1)*abs(l)) r*a/(1-a+(2*a-1)*abs(r))
;-------------------------------------------------------------------------------
%if DISTORT_ID > -1
SECT_TEXT(sudistrt)
EXPORT MANGLE_FUNC(su_op_distort,0)
%ifdef INCLUDE_STEREO_DISTORT
call su_effects_stereohelper
%define INCLUDE_EFFECTS_STEREOHELPER
%endif
fld dword [INP+su_distort_ports.drive]
%define SU_INCLUDE_WAVESHAPER
; flow into waveshaper
%endif
%ifdef SU_INCLUDE_WAVESHAPER
su_waveshaper:
fxch ; x a
call su_clip
fxch ; a x' (from now on just called x)
fld st0 ; a a x
do fsub dword [,c_0_5,] ; a-.5 a x
fadd st0 ; 2*a-1 a x
fld st2 ; x 2*a-1 a x
fabs ; abs(x) 2*a-1 a x
fmulp st1 ; (2*a-1)*abs(x) a x
fld1 ; 1 (2*a-1)*abs(x) a x
faddp st1 ; 1+(2*a-1)*abs(x) a x
fsub st1 ; 1-a+(2*a-1)*abs(x) a x
fdivp st1, st0 ; a/(1-a+(2*a-1)*abs(x)) x
fmulp st1 ; x*a/(1-a+(2*a-1)*abs(x))
ret
%define SU_INCLUDE_CLIP
%endif ; SU_USE_DST
;-------------------------------------------------------------------------------
; HOLD opcode: sample and hold the signal, reducing sample rate
;-------------------------------------------------------------------------------
; Mono version: holds the signal at a rate defined by the freq parameter
; Stereo version: holds both channels
;-------------------------------------------------------------------------------
%if HOLD_ID > -1
SECT_TEXT(suhold)
EXPORT MANGLE_FUNC(su_op_hold,0)
%ifdef INCLUDE_STEREO_HOLD
call su_effects_stereohelper
%define INCLUDE_EFFECTS_STEREOHELPER
%endif
fld dword [INP+su_hold_ports.freq] ; f x
fmul st0, st0 ; f^2 x
fchs ; -f^2 x
fadd dword [WRK+su_hold_wrk.phase] ; p-f^2 x
fst dword [WRK+su_hold_wrk.phase] ; p <- p-f^2
fldz ; 0 p x
fucomip st1 ; p x
fstp dword [_SP-4] ; t=p, x
jc short su_op_hold_holding ; if (0 < p) goto holding
fld1 ; 1 x
fadd dword [_SP-4] ; 1+t x
fstp dword [WRK+su_hold_wrk.phase] ; x
fst dword [WRK+su_hold_wrk.holdval] ; save holded value
ret ; x
su_op_hold_holding:
fstp st0 ;
fld dword [WRK+su_hold_wrk.holdval] ; x
ret
%endif ; HOLD_ID > -1
;-------------------------------------------------------------------------------
; CRUSH opcode: quantize the signal to finite number of levels
;-------------------------------------------------------------------------------
; Mono: x -> e*int(x/e)
; Stereo: l r -> e*int(l/e) e*int(r/e)
;-------------------------------------------------------------------------------
%if CRUSH_ID > -1
SECT_TEXT(sucrush)
EXPORT MANGLE_FUNC(su_op_crush,0)
%ifdef INCLUDE_STEREO_CRUSH
call su_effects_stereohelper
%define INCLUDE_EFFECTS_STEREOHELPER
%endif
fdiv dword [INP+su_crush_ports.resolution]
frndint
fmul dword [INP+su_crush_ports.resolution]
ret
%endif ; CRUSH_ID > -1
;-------------------------------------------------------------------------------
; GAIN opcode: apply gain on the signal
;-------------------------------------------------------------------------------
; Mono: x -> x*g
; Stereo: l r -> l*g r*g
;-------------------------------------------------------------------------------
%if GAIN_ID > -1
SECT_TEXT(sugain)
%ifdef INCLUDE_STEREO_GAIN
EXPORT MANGLE_FUNC(su_op_gain,0)
fld dword [INP+su_gain_ports.gain] ; g l (r)
jnc su_op_gain_mono
fmul st2, st0 ; g l r/g
su_op_gain_mono:
fmulp st1, st0 ; l/g (r/)
ret
%else
EXPORT MANGLE_FUNC(su_op_gain,0)
fmul dword [INP+su_gain_ports.gain]
ret
%endif
%endif ; GAIN_ID > -1
;-------------------------------------------------------------------------------
; INVGAIN opcode: apply inverse gain on the signal
;-------------------------------------------------------------------------------
; Mono: x -> x/g
; Stereo: l r -> l/g r/g
;-------------------------------------------------------------------------------
%if INVGAIN_ID > -1
SECT_TEXT(suingain)
%ifdef INCLUDE_STEREO_INVGAIN
EXPORT MANGLE_FUNC(su_op_invgain,0)
fld dword [INP+su_invgain_ports.invgain] ; g l (r)
jnc su_op_invgain_mono
fdiv st2, st0 ; g l r/g
su_op_invgain_mono:
fdivp st1, st0 ; l/g (r/)
ret
%else
EXPORT MANGLE_FUNC(su_op_invgain,0)
fdiv dword [INP+su_invgain_ports.invgain]
ret
%endif
%endif ; INVGAIN_ID > -1
;-------------------------------------------------------------------------------
; FILTER opcode: perform low/high/band-pass/notch etc. filtering on the signal
;-------------------------------------------------------------------------------
; Mono: x -> filtered(x)
; Stereo: l r -> filtered(l) filtered(r)
;-------------------------------------------------------------------------------
%if FILTER_ID > -1
SECT_TEXT(sufilter)
EXPORT MANGLE_FUNC(su_op_filter,0)
lodsb ; load the flags to al
%ifdef INCLUDE_STEREO_FILTER
call su_effects_stereohelper
%define INCLUDE_EFFECTS_STEREOHELPER
%endif
fld dword [INP+su_filter_ports.res] ; r x
fld dword [INP+su_filter_ports.freq]; f r x
fmul st0, st0 ; f2 x (square the input so we never get negative and also have a smoother behaviour in the lower frequencies)
fst dword [_SP-4] ; f2 r x
fmul dword [WRK+su_filter_wrk.band] ; f2*b r x
fadd dword [WRK+su_filter_wrk.low] ; f2*b+l r x
fst dword [WRK+su_filter_wrk.low] ; l'=f2*b+l r x
fsubp st2, st0 ; r x-l'
fmul dword [WRK+su_filter_wrk.band] ; r*b x-l'
fsubp st1, st0 ; x-l'-r*b
fst dword [WRK+su_filter_wrk.high] ; h'=x-l'-r*b
fmul dword [_SP-4] ; f2*h'
fadd dword [WRK+su_filter_wrk.band] ; f2*h'+b
fstp dword [WRK+su_filter_wrk.band] ; b'=f2*h'+b
fldz ; 0
%ifdef INCLUDE_LOWPASS
test al, byte LOWPASS
jz short su_op_filter_skiplowpass
fadd dword [WRK+su_filter_wrk.low]
su_op_filter_skiplowpass:
%endif
%ifdef INCLUDE_BANDPASS
test al, byte BANDPASS
jz short su_op_filter_skipbandpass
fadd dword [WRK+su_filter_wrk.band]
su_op_filter_skipbandpass:
%endif
%ifdef INCLUDE_HIGHPASS
test al, byte HIGHPASS
jz short su_op_filter_skiphighpass
fadd dword [WRK+su_filter_wrk.high]
su_op_filter_skiphighpass:
%endif
%ifdef INCLUDE_NEGBANDPASS
test al, byte NEGBANDPASS
jz short su_op_filter_skipnegbandpass
fsub dword [WRK+su_filter_wrk.band]
su_op_filter_skipnegbandpass:
%endif
%ifdef INCLUDE_NEGHIGHPASS
test al, byte NEGHIGHPASS
jz short su_op_filter_skipneghighpass
fsub dword [WRK+su_filter_wrk.high]
su_op_filter_skipneghighpass:
%endif
ret
%endif ; SU_INCLUDE_FILTER
;-------------------------------------------------------------------------------
; CLIP opcode: clips the signal into [-1,1] range
;-------------------------------------------------------------------------------
; Mono: x -> min(max(x,-1),1)
; Stereo: l r -> min(max(l,-1),1) min(max(r,-1),1)
;-------------------------------------------------------------------------------
SECT_TEXT(suclip)
%if CLIP_ID > -1
EXPORT MANGLE_FUNC(su_op_clip,0)
%ifdef INCLUDE_STEREO_CLIP
call su_effects_stereohelper
%define INCLUDE_EFFECTS_STEREOHELPER
%endif
%define SU_INCLUDE_CLIP
; flow into su_doclip
%endif ; CLIP_ID > -1
%ifdef SU_INCLUDE_CLIP
su_clip:
fld1 ; 1 x a
fucomi st1 ; if (1 <= x)
jbe short su_clip_do ; goto Clip_Do
fchs ; -1 x a
fucomi st1 ; if (-1 < x)
fcmovb st0, st1 ; x x a
su_clip_do:
fstp st1 ; x' a, where x' = clamp(x)
ret
%endif ; SU_INCLUDE_CLIP
;-------------------------------------------------------------------------------
; PAN opcode: pan the signal
;-------------------------------------------------------------------------------
; Mono: s -> s*(1-p) s*p
; Stereo: l r -> l*(1-p) r*p
;
; where p is the panning in [0,1] range
;-------------------------------------------------------------------------------
%if PAN_ID > -1
SECT_TEXT(supan)
%ifdef INCLUDE_STEREO_PAN
EXPORT MANGLE_FUNC(su_op_pan,0)
jc su_op_pan_do ; this time, if this is mono op...
fld st0 ; ...we duplicate the mono into stereo first
su_op_pan_do:
fld dword [INP+su_pan_ports.panning] ; p l r
fld1 ; 1 p l r
fsub st1 ; 1-p p l r
fmulp st2 ; p (1-p)*l r
fmulp st2 ; (1-p)*l p*r
ret
%else ; ifndef INCLUDE_STEREO_PAN
EXPORT MANGLE_FUNC(su_op_pan,0)
fld dword [INP+su_pan_ports.panning] ; p s
fmul st1 ; p*s s
fsub st1, st0 ; p*s s-p*s
; Equal to
; s*p s*(1-p)
fxch ; s*(1-p) s*p SHOULD PROBABLY DELETE, WHY BOTHER
ret
%endif ; INCLUDE_STEREO_PAN
%endif ; SU_USE_PAN
;-------------------------------------------------------------------------------
; su_effects_stereohelper: moves the workspace to next, does the filtering for
; right channel (pulling the calling address from stack), rewinds the
; workspace and returns
;-------------------------------------------------------------------------------
%ifdef INCLUDE_EFFECTS_STEREOHELPER
su_effects_stereohelper:
jnc su_effects_stereohelper_mono ; carry is still the stereo bit
add WRK, 16
fxch ; r l
call [_SP] ; call whoever called me...
fxch ; l r
sub WRK, 16 ; move WRK back to where it was
su_effects_stereohelper_mono:
ret ; return to process l/mono sound
%endif
;-------------------------------------------------------------------------------
; DELAY opcode: adds delay effect to the signal
;-------------------------------------------------------------------------------
; Mono: perform delay on ST0, using delaycount delaylines starting
; at delayindex from the delaytable
; Stereo: perform delay on ST1, using delaycount delaylines starting
; at delayindex + delaycount from the delaytable (so the right delays
; can be different)
;-------------------------------------------------------------------------------
%if DELAY_ID > -1
SECT_TEXT(sudelay)
EXPORT MANGLE_FUNC(su_op_delay,0)
lodsw ; al = delay index, ah = delay count
push_registers VAL, COM ; these are non-volatile according to our convention
movzx ebx, al
do{lea _BX,[},MANGLE_DATA(su_delay_times),_BX*2,] ; _BP now points to the right position within delay time table
movzx esi, word [_SP + su_stack.tick + PUSH_REG_SIZE(2)] ; notice that we load word, so we wrap at 65536
mov _CX, PTRWORD [_SP + su_stack.delaywrk + PUSH_REG_SIZE(2)] ; WRK is now the separate delay workspace, as they require a lot more space
%ifdef INCLUDE_STEREO_DELAY
jnc su_op_delay_mono
push _AX ; save _ah (delay count)
fxch ; r l
call su_op_delay_do ; D(r) l process delay for the right channel
pop _AX ; restore the count for second run
fxch ; l D(r)
su_op_delay_mono: ; flow into mono delay
%endif
call su_op_delay_do ; when stereo delay is not enabled, we could inline this to save 5 bytes, but I expect stereo delay to be farely popular so maybe not worth the hassle
mov PTRWORD [_SP + su_stack.delaywrk + PUSH_REG_SIZE(2)],_CX ; move delay workspace pointer back to stack.
pop_registers VAL, COM
%ifdef INCLUDE_DELAY_MODULATION
xor eax, eax
mov dword [WRK+su_unit.ports+su_delay_ports.delaymod], eax ; zero it
%endif
ret
%ifdef INCLUDE_DELAY_MODULATION
%define INCLUDE_DELAY_FLOAT_TIME
%endif
;-------------------------------------------------------------------------------
; su_op_delay_do: executes the actual delay
;-------------------------------------------------------------------------------
; Pseudocode:
; q = dr*x
; for (i = 0;i < count;i++)
; s = b[(t-delaytime[i+offset])&65535]
; q += s
; o[i] = o[i]*da+s*(1-da)
; b[t] = f*o[i] +p^2*x
; Perform dc-filtering q and output q
;-------------------------------------------------------------------------------
su_op_delay_do: ; x y
fld st0
fmul dword [INP+su_delay_ports.pregain] ; p*x y
fmul dword [INP+su_delay_ports.pregain] ; p*p*x y
fxch ; y p*p*x
fmul dword [INP+su_delay_ports.dry] ; dr*y p*p*x
su_op_delay_loop:
%ifdef INCLUDE_DELAY_FLOAT_TIME ; delaytime modulation or note syncing require computing the delay time in floats
fild word [_BX] ; k dr*y p*p*x, where k = delay time
%ifdef INCLUDE_DELAY_NOTETRACKING
test ah, 1 ; note syncing is the least significant bit of ah, 0 = ON, 1 = OFF
jne su_op_delay_skipnotesync
fild dword [INP-su_voice.inputs+su_voice.note]
do fmul dword [,c_i12,]
call MANGLE_FUNC(su_power,0)
fdivp st1, st0 ; use 10787 for delaytime to have neutral transpose
su_op_delay_skipnotesync:
%endif
%ifdef INCLUDE_DELAY_MODULATION
fld dword [WRK+su_unit.ports+su_delay_ports.delaymod]
do fmul dword [,c_32767,] ; scale it up, as the modulations would be too small otherwise
faddp st1, st0
%define USE_C_32767
%endif
fistp dword [_SP-4] ; dr*y p*p*x, dword [_SP-4] = integer amount of delay (samples)
mov edi, esi ; edi = esi = current time
sub di, word [_SP-4] ; we perform the math in 16-bit to wrap around
%else
mov edi, esi
sub di, word [_BX] ; we perform the math in 16-bit to wrap around
%endif
fld dword [_CX+su_delayline_wrk.buffer+_DI*4]; s dr*y p*p*x, where s is the sample from delay buffer
fadd st1, st0 ; s dr*y+s p*p*x (add comb output to current output)
fld1 ; 1 s dr*y+s p*p*x
fsub dword [INP+su_delay_ports.damp] ; 1-da s dr*y+s p*p*x
fmulp st1, st0 ; s*(1-da) dr*y+s p*p*x
fld dword [INP+su_delay_ports.damp] ; da s*(1-da) dr*y+s p*p*x
fmul dword [_CX+su_delayline_wrk.filtstate] ; o*da s*(1-da) dr*y+s p*p*x, where o is stored
faddp st1, st0 ; o*da+s*(1-da) dr*y+s p*p*x
fst dword [_CX+su_delayline_wrk.filtstate] ; o'=o*da+s*(1-da), o' dr*y+s p*p*x
fmul dword [INP+su_delay_ports.feedback] ; f*o' dr*y+s p*p*x
fadd st0, st2 ; f*o'+p*p*x dr*y+s p*p*x
fstp dword [_CX+su_delayline_wrk.buffer+_SI*4]; save f*o'+p*p*x to delay buffer
add _BX,2 ; move to next index
add _CX, su_delayline_wrk.size ; go to next delay delay workspace
sub ah, 2
jg su_op_delay_loop ; if ah > 0, goto loop
fstp st1 ; dr*y+s1+s2+s3+...
; DC-filtering
fld dword [_CX+su_delayline_wrk.dcout] ; o s
do fmul dword [,c_dc_const,] ; c*o s
fsub dword [_CX+su_delayline_wrk.dcin] ; c*o-i s
fxch ; s c*o-i
fst dword [_CX+su_delayline_wrk.dcin] ; i'=s, s c*o-i
faddp st1 ; s+c*o-i
do fadd dword [,c_0_5,] ; add and sub small offset to prevent denormalization
do fsub dword [,c_0_5,]
fst dword [_CX+su_delayline_wrk.dcout] ; o'=s+c*o-i
ret
%define USE_C_DC_CONST
%endif ; DELAY_ID > -1
;-------------------------------------------------------------------------------
; COMPRES opcode: push compressor gain to stack
;-------------------------------------------------------------------------------
; Mono: push g on stack, where g is a suitable gain for the signal
; you can either MULP to compress the signal or SEND it to a GAIN
; somewhere else for compressor side-chaining.
; Stereo: push g g on stack, where g is calculated using l^2 + r^2
;-------------------------------------------------------------------------------
%if COMPRES_ID > -1
SECT_TEXT(sucompr)
EXPORT MANGLE_FUNC(su_op_compressor,0)
fdiv dword [INP+su_compres_ports.invgain]; l/g, we'll call this pre inverse gained signal x from now on
fld st0 ; x x
fmul st0, st0 ; x^2 x
%ifdef INCLUDE_STEREO_COMPRES
jnc su_op_compressor_mono
fld st2 ; r x^2 l/g r
fdiv dword [INP+su_compres_ports.invgain]; r/g, we'll call this pre inverse gained signal y from now on
fst st3 ; y x^2 l/g r/g
fmul st0, st0 ; y^2 x^2 l/g r/g
faddp st1, st0 ; y^2+x^2 l/g r/g
call su_op_compressor_mono ; So, for stereo, we square both left & right and add them up
fld st0 ; and return the computed gain two times, ready for MULP STEREO
ret
su_op_compressor_mono:
%endif
fld dword [WRK+su_compres_wrk.level] ; l x^2 x
fucomi st0, st1
setnb al ; if (st0 >= st1) al = 1; else al = 0;
fsubp st1, st0 ; x^2-l x
call su_nonlinear_map ; c x^2-l x, c is either attack or release parameter mapped in a nonlinear way
fmulp st1, st0 ; c*(x^2-l) x
fadd dword [WRK+su_compres_wrk.level] ; l+c*(x^2-l) x // we could've kept level in the stack and save a few bytes, but su_env_map uses 3 stack (c + 2 temp), so the stack was getting quite big.
fst dword [WRK+su_compres_wrk.level] ; l'=l+c*(x^2-l), l' x
fld dword [INP+su_compres_ports.threshold] ; t l' x
fmul st0, st0 ; t*t l' x
fxch ; l' t*t x
fucomi st0, st1 ; if l' < t*t
fcmovb st0, st1 ; l'=t*t
fdivp st1, st0 ; t*t/l' x
fld dword [INP+su_compres_ports.ratio] ; r t*t/l' x
do fmul dword [,c_0_5,] ; p=r/2 t*t/l' x
fxch ; t*t/l' p x
fyl2x ; p*log2(t*t/l') x
jmp MANGLE_FUNC(su_power,0) ; 2^(p*log2(t*t/l')) x
; tail call ; Equal to:
; (t*t/l')^p x
; if ratio is at minimum => p=0 => 1 x
; if ratio is at maximum => p=0.5 => t/x => t/x*x=t
%endif ; COMPRES_ID > -1

View File

@ -0,0 +1,383 @@
;-------------------------------------------------------------------------------
; Filter (LOWPASS, BANDPASS...) effect related defines
;-------------------------------------------------------------------------------
%assign FILTER_ID -1
%macro USE_FILTER 0
%if FILTER_ID == -1
%assign FILTER_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_filter,0),
%xdefine NUMPARAMS NUMPARAMS 2,
%endif
%endmacro
%define LOWPASS 0x40
%define BANDPASS 0x20
%define HIGHPASS 0x10
%define NEGBANDPASS 0x08
%define NEGHIGHPASS 0x04
%macro SU_FILTER 4
db %2
db %3
db %4
USE_FILTER
%xdefine CMDS CMDS FILTER_ID + %1,
%if %1 == STEREO
%define INCLUDE_STEREO_FILTER
%endif
%if (%4) & LOWPASS == LOWPASS
%define INCLUDE_LOWPASS
%endif
%if (%4) & BANDPASS == BANDPASS
%define INCLUDE_BANDPASS
%endif
%if (%4) & HIGHPASS == HIGHPASS
%define INCLUDE_HIGHPASS
%endif
%if (%4) & NEGBANDPASS == NEGBANDPASS
%define INCLUDE_NEGBANDPASS
%endif
%if (%4) & NEGHIGHPASS == NEGHIGHPASS
%define INCLUDE_NEGHIGHPASS
%endif
%endmacro
%define FREQUENCY(val) val
%define RESONANCE(val) val
%define FLAGS(val) val
struc su_filter_ports
.freq resd 1
.res resd 1
endstruc
struc su_filter_wrk
.low resd 1
.high resd 1
.band resd 1
endstruc
;-------------------------------------------------------------------------------
; PAN effect related defines
;-------------------------------------------------------------------------------
%assign PAN_ID -1
%macro USE_PAN 0
%if PAN_ID == -1
%assign PAN_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_pan,0),
%xdefine NUMPARAMS NUMPARAMS 1,
%endif
%endmacro
%macro SU_PAN 2
db %2
USE_PAN
%xdefine CMDS CMDS PAN_ID + %1,
%if %1 == STEREO
%define INCLUDE_STEREO_PAN
%endif
%endmacro
%define PANNING(val) val
struc su_pan_ports
.panning resd 1
endstruc
;-------------------------------------------------------------------------------
; DISTORT effect related defines
;-------------------------------------------------------------------------------
%assign DISTORT_ID -1
%macro USE_DISTORT 0
%if DISTORT_ID == -1
%assign DISTORT_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_distort,0),
%xdefine NUMPARAMS NUMPARAMS 1,
%endif
%endmacro
%macro SU_DISTORT 2
db %2
USE_DISTORT
%xdefine CMDS CMDS DISTORT_ID + %1,
%if %1 == STEREO
%define INCLUDE_STEREO_DISTORT
%endif
%endmacro
%define DRIVE(val) val
struc su_distort_ports
.drive resd 1
endstruc
;-------------------------------------------------------------------------------
; HOLD effect related defines
;-------------------------------------------------------------------------------
%assign HOLD_ID -1
%macro USE_HOLD 0
%if HOLD_ID == -1
%assign HOLD_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_hold,0),
%xdefine NUMPARAMS NUMPARAMS 1,
%endif
%endmacro
%macro SU_HOLD 2
db %2
USE_HOLD
%xdefine CMDS CMDS HOLD_ID + %1,
%if %1 == STEREO
%define INCLUDE_STEREO_HOLD
%endif
%endmacro
%define HOLDFREQ(val) val
struc su_hold_ports
.freq resd 1
endstruc
struc su_hold_wrk
.phase resd 1
.holdval resd 1
endstruc
;-------------------------------------------------------------------------------
; CRUSH effect related defines
;-------------------------------------------------------------------------------
%assign CRUSH_ID -1
%macro USE_CRUSH 0
%if CRUSH_ID == -1
%assign CRUSH_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_crush,0),
%xdefine NUMPARAMS NUMPARAMS 1,
%endif
%endmacro
%macro SU_CRUSH 2
db %2
USE_CRUSH
%xdefine CMDS CMDS CRUSH_ID + %1,
%if %1 == STEREO
%define INCLUDE_STEREO_CRUSH
%endif
%endmacro
%define RESOLUTION(val) val
struc su_crush_ports
.resolution resd 1
endstruc
;-------------------------------------------------------------------------------
; GAIN effect related defines
;-------------------------------------------------------------------------------
%assign GAIN_ID -1
%macro USE_GAIN 0
%if GAIN_ID == -1
%assign GAIN_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_gain,0),
%xdefine NUMPARAMS NUMPARAMS 1,
%endif
%endmacro
%macro SU_GAIN 2
db %2
USE_GAIN
%xdefine CMDS CMDS GAIN_ID + %1,
%if %1 == STEREO
%define INCLUDE_STEREO_GAIN
%endif
%endmacro
%define GAIN(val) val
struc su_gain_ports
.gain resd 1
endstruc
;-------------------------------------------------------------------------------
; INVGAIN effect related defines
;-------------------------------------------------------------------------------
%assign INVGAIN_ID -1
%macro USE_INVGAIN 0
%if INVGAIN_ID == -1
%assign INVGAIN_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_invgain,0),
%xdefine NUMPARAMS NUMPARAMS 1,
%endif
%endmacro
%macro SU_INVGAIN 2
db %2
USE_INVGAIN
%xdefine CMDS CMDS INVGAIN_ID + %1,
%if %1 == STEREO
%define INCLUDE_STEREO_INVGAIN
%endif
%endmacro
%define INVGAIN(val) val
struc su_invgain_ports
.invgain resd 1
endstruc
;-------------------------------------------------------------------------------
; CLIP effect related defines
;-------------------------------------------------------------------------------
%assign CLIP_ID -1
%macro USE_CLIP 0
%if CLIP_ID == -1
%assign CLIP_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_clip,0),
%xdefine NUMPARAMS NUMPARAMS 0,
%endif
%endmacro
%macro SU_CLIP 1
USE_CLIP
%xdefine CMDS CMDS CLIP_ID + %1,
%if %1 == STEREO
%define INCLUDE_STEREO_CLIP
%endif
%endmacro
;-------------------------------------------------------------------------------
; Delay effect related defines
;-------------------------------------------------------------------------------
%assign DELAY_ID -1
%macro USE_DELAY 0
%if DELAY_ID == -1
%assign DELAY_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_delay,0),
%xdefine NUMPARAMS NUMPARAMS 4,
%endif
%endmacro
%define MAX_DELAY 65536 ; warning: this is pretty much fixed, as we use 16-bit math to wraparound the delay buffers
%assign NUM_DELAY_LINES 0
%macro SU_DELAY 7
db %2
db %3
db %4
db %5
db %6
db %7
USE_DELAY
%xdefine CMDS CMDS DELAY_ID + %1,
%assign NUM_DELAY_LINES NUM_DELAY_LINES + %7 * (1+%1)
%if %1 == STEREO
%define INCLUDE_STEREO_DELAY
%endif
%if (%7) & NOTETRACKING == 0
%define INCLUDE_DELAY_NOTETRACKING
%define INCLUDE_DELAY_FLOAT_TIME
%endif
%endmacro
%macro BEGIN_DELTIMES 0
SECT_DATA(sudeltim)
EXPORT MANGLE_DATA(su_delay_times)
%endmacro
%define END_DELTIMES
%macro DELTIME 1-*
%rep %0
dw %1
%rotate 1
%endrep
%endmacro
%define PREGAIN(val) val
%define DRY(val) val
%define FEEDBACK(val) val
%define DEPTH(val) val
%define DAMP(val) val
%define DELAY(val) val
%define COUNT(val) (2*val-1)
%define NOTETRACKING 1
struc su_delay_ports
.pregain resd 1
.dry resd 1
.feedback resd 1
.damp resd 1
.freq resd 1
.delaymod resd 1 ; note that this is not converted from integer, only modulated
endstruc
struc su_delayline_wrk
.dcin resd 1
.dcout resd 1
.filtstate resd 1
.buffer resd MAX_DELAY
.size
endstruc
;-------------------------------------------------------------------------------
; COMPRES effect related defines
;-------------------------------------------------------------------------------
%assign COMPRES_ID -1
%macro USE_COMPRES 0
%if COMPRES_ID == -1
%assign COMPRES_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_compressor,0),
%xdefine NUMPARAMS NUMPARAMS 5,
%endif
%endmacro
%macro SU_COMPRES 6
db %2
db %3
db %4
db %5
db %6
USE_COMPRES
%xdefine CMDS CMDS COMPRES_ID + %1,
%if %1 == STEREO
%define INCLUDE_STEREO_COMPRES
%endif
%endmacro
%define ATTAC(val) val
%define RELEASE(val) val
%define INVGAIN(val) val
%define THRESHOLD(val) val
%define RATIO(val) val
struc su_compres_ports
.attack resd 1
.release resd 1
.invgain resd 1
.threshold resd 1
.ratio resd 1
endstruc
struc su_compres_wrk
.level resd 1
endstruc

View File

@ -0,0 +1,65 @@
;-------------------------------------------------------------------------------
; ADVANCE opcode: advances from one voice to next
;-------------------------------------------------------------------------------
; Checks if this was the last voice of current instrument. If so, moves to
; next opcodes and updates the stack to reflect the instrument change.
; If this instrument has more voices to process, rolls back the COM and VAL
; pointers to where they were when this instrument started.
;
; There is no stereo version.
;-------------------------------------------------------------------------------
SECT_TEXT(suopadvn)
EXPORT MANGLE_FUNC(su_op_advance,0)
%ifdef INCLUDE_POLYPHONY
mov WRK, [_SP+su_stack.wrk] ; WRK points to start of current voice
add WRK, su_voice.size ; move to next voice
mov [_SP+su_stack.wrk], WRK ; update the pointer in the stack to point to the new voice
mov ecx, [_SP+su_stack.voiceno] ; ecx = how many voices remain to process
dec ecx ; decrement number of voices to process
bt dword [_SP+su_stack.polyphony], ecx ; if voice bit of su_polyphonism not set
jnc su_op_advance_next_instrument ; goto next_instrument
mov VAL, PTRWORD [_SP+su_stack.val] ; if it was set, then repeat the opcodes for the current voice
mov COM, PTRWORD [_SP+su_stack.com]
su_op_advance_next_instrument:
mov PTRWORD [_SP+su_stack.val], VAL ; save current VAL as a checkpoint
mov PTRWORD [_SP+su_stack.com], COM ; save current COM as a checkpoint
su_op_advance_finish:
mov [_SP+su_stack.voiceno], ecx
ret
%else
mov WRK, PTRWORD [_SP+su_stack.wrk] ; WRK = wrkptr
add WRK, su_voice.size ; move to next voice
mov PTRWORD [_SP+su_stack.wrk], WRK ; update stack
dec PTRWORD [_SP+su_stack.voiceno] ; voices--
ret
%endif
;-------------------------------------------------------------------------------
; SPEED opcode: modulate the speed (bpm) of the song based on ST0
;-------------------------------------------------------------------------------
; Mono: adds or subtracts the ticks, a value of 0.5 is neutral & will7
; result in no speed change.
; There is no STEREO version.
;-------------------------------------------------------------------------------
%if SPEED_ID > -1
SECT_TEXT(suspeed)
EXPORT MANGLE_FUNC(su_op_speed,0)
do fmul dword [,c_bpmscale,] ; (2*s-1)*64/24, let's call this p from now on
call MANGLE_FUNC(su_power,0) ; 2^p, this is how many ticks we should be taking
fld1 ; 1 2^p
fsubp st1, st0 ; 2^p-1, the player is advancing 1 tick by its own
fadd dword [WRK+su_speed_wrk.remainder] ; t+2^p-1, t is the remainder from previous rounds as ticks have to be rounded to 1
push _AX
fist dword [_SP] ; Main stack: k=int(t+2^p-1)
fisub dword [_SP] ; t+2^p-1-k, the remainder
pop _AX
add dword [_SP+su_stack.rowtick], eax ; add the whole ticks to row tick count
fstp dword [WRK+su_speed_wrk.remainder] ; save the remainder for future
ret
%define USE_C_BPMSCALE
%endif

View File

@ -0,0 +1,21 @@
;-------------------------------------------------------------------------------
; SPEED related defines
;-------------------------------------------------------------------------------
%assign SPEED_ID -1
%macro USE_SPEED 0
%if SPEED_ID == -1
%assign SPEED_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_speed,0),
%xdefine NUMPARAMS NUMPARAMS 0,
%endif
%endmacro
%macro SU_SPEED 0
USE_SPEED
%xdefine CMDS CMDS SPEED_ID, ; there is no stereo variant I can think of
%endmacro
struc su_speed_wrk
.remainder resd 1
endstruc

View File

@ -0,0 +1,125 @@
;-------------------------------------------------------------------------------
; OUT opcode: outputs and pops the signal
;-------------------------------------------------------------------------------
; Mono: add ST0 to main left port
; Stereo: also add ST1 to main right port
;-------------------------------------------------------------------------------
%if OUT_ID > -1
SECT_TEXT(suopout)
EXPORT MANGLE_FUNC(su_op_out,0) ; l r
mov _AX, [_SP + su_stack.synth]
%ifdef INCLUDE_STEREO_OUT
jnc su_op_out_mono
call su_op_out_mono
add _AX, 4
su_op_out_mono:
%endif
fmul dword [INP + su_out_ports.gain] ; g*l
fadd dword [_AX + su_synthworkspace.left] ; g*l+o
fstp dword [_AX + su_synthworkspace.left] ; o'=g*l+o
ret
%endif ; SU_OUT_ID > -1
;-------------------------------------------------------------------------------
; OUTAUX opcode: outputs to main and aux1 outputs and pops the signal
;-------------------------------------------------------------------------------
; Mono: add outgain*ST0 to main left port and auxgain*ST0 to aux1 left
; Stereo: also add outgain*ST1 to main right port and auxgain*ST1 to aux1 right
;-------------------------------------------------------------------------------
%if OUTAUX_ID > -1
SECT_TEXT(suoutaux)
EXPORT MANGLE_FUNC(su_op_outaux,0) ; l r
mov _AX, [_SP + su_stack.synth]
%ifdef INCLUDE_STEREO_OUTAUX
jnc su_op_outaux_mono
call su_op_outaux_mono
add _AX, 4
su_op_outaux_mono:
%endif
fld st0 ; l l
fmul dword [INP + su_outaux_ports.outgain] ; g*l
fadd dword [_AX + su_synthworkspace.left] ; g*l+o
fstp dword [_AX + su_synthworkspace.left] ; o'=g*l+o
fmul dword [INP + su_outaux_ports.auxgain] ; h*l
fadd dword [_AX + su_synthworkspace.aux] ; h*l+a
fstp dword [_AX + su_synthworkspace.aux] ; a'=h*l+a
ret
%endif ; SU_OUTAUX_ID > -1
;-------------------------------------------------------------------------------
; AUX opcode: outputs the signal to aux (or main) port and pops the signal
;-------------------------------------------------------------------------------
; Mono: add gain*ST0 to left port
; Stereo: also add gain*ST1 to right port
;-------------------------------------------------------------------------------
%if AUX_ID > -1
SECT_TEXT(suopaux)
EXPORT MANGLE_FUNC(su_op_aux,0) ; l r
lodsb
mov _DI, [_SP + su_stack.synth]
%ifdef INCLUDE_STEREO_AUX
jnc su_op_aux_mono
call su_op_aux_mono
add _DI, 4
su_op_aux_mono:
%endif
fmul dword [INP + su_aux_ports.gain] ; g*l
fadd dword [_DI + su_synthworkspace.left + _AX*4] ; g*l+o
fstp dword [_DI + su_synthworkspace.left + _AX*4] ; o'=g*l+o
ret
%endif ; SU_AUX_ID > -1
;-------------------------------------------------------------------------------
; SEND opcode: adds the signal to a port
;-------------------------------------------------------------------------------
; Mono: adds signal to a memory address, defined by a word in VAL stream
; Stereo: also add right signal to the following address
;-------------------------------------------------------------------------------
%if SEND_ID > -1
SECT_TEXT(susend)
EXPORT MANGLE_FUNC(su_op_send,0)
lodsw
mov _CX, [_SP + su_stack.wrk]
%ifdef INCLUDE_STEREO_SEND
jnc su_op_send_mono
mov _DI, _AX
inc _AX ; send the right channel first
fxch ; r l
call su_op_send_mono ; (r) l
mov _AX, _DI ; move back to original address
test _AX, SEND_POP ; if r was not popped and is still in the stack
jnz su_op_send_mono
fxch ; swap them back: l r
su_op_send_mono:
%endif
%ifdef INCLUDE_GLOBAL_SEND
test _AX, SEND_GLOBAL
jz su_op_send_skipglobal
mov _CX, [_SP + su_stack.synth]
su_op_send_skipglobal:
%endif
test _AX, SEND_POP ; if the SEND_POP bit is not set
jnz su_op_send_skippush
fld st0 ; duplicate the signal on stack: s s
su_op_send_skippush: ; there is signal s, but maybe also another: s (s)
fld dword [INP+su_send_ports.amount] ; a l (l)
do fsub dword [,c_0_5,] ; a-.5 l (l)
fadd st0 ; g=2*a-1 l (l)
and _AX, 0x0000ffff - SEND_POP - SEND_GLOBAL ; eax = send address
fmulp st1, st0 ; g*l (l)
fadd dword [_CX + _AX*4] ; g*l+L (l),where L is the current value
fstp dword [_CX + _AX*4] ; (l)
ret
%endif ; SU_USE_SEND > -1

View File

@ -0,0 +1,124 @@
;-------------------------------------------------------------------------------
; OUT structs
;-------------------------------------------------------------------------------
%assign OUT_ID -1
%macro USE_OUT 0
%if OUT_ID == -1
%assign OUT_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_out,0),
%xdefine NUMPARAMS NUMPARAMS 1,
%endif
%endmacro
%macro SU_OUT 2
db %2
USE_OUT
%xdefine CMDS CMDS OUT_ID+%1,
%if %1 == STEREO
%define INCLUDE_STEREO_OUT
%endif
%endmacro
%define GAIN(val) val
struc su_out_ports
.gain resd 1
endstruc
;-------------------------------------------------------------------------------
; OUTAUX structs
;-------------------------------------------------------------------------------
%assign OUTAUX_ID -1
%macro USE_OUTAUX 0
%if OUTAUX_ID == -1
%assign OUTAUX_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_outaux,0),
%xdefine NUMPARAMS NUMPARAMS 2,
%endif
%endmacro
%macro SU_OUTAUX 3
db %2
db %3
USE_OUTAUX
%xdefine CMDS CMDS OUTAUX_ID+%1,
%if %1 == STEREO
%define INCLUDE_STEREO_OUTAUX
%endif
%endmacro
%define OUTGAIN(val) val
%define AUXGAIN(val) val
struc su_outaux_ports
.outgain resd 1
.auxgain resd 1
endstruc
;-------------------------------------------------------------------------------
; AUX defines
;-------------------------------------------------------------------------------
%assign AUX_ID -1
%macro USE_AUX 0
%if AUX_ID == -1
%assign AUX_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_aux,0),
%xdefine NUMPARAMS NUMPARAMS 1,
%endif
%endmacro
%macro SU_AUX 3
db %2
db %3
USE_AUX
%xdefine CMDS CMDS AUX_ID+%1,
%if %1 == STEREO
%define INCLUDE_STEREO_AUX
%endif
%endmacro
%define CHANNEL(val) val
struc su_aux_ports
.gain resd 1
endstruc
;-------------------------------------------------------------------------------
; SEND structs
;-------------------------------------------------------------------------------
%assign SEND_ID -1
%macro USE_SEND 0
%if SEND_ID == -1
%assign SEND_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_send,0),
%xdefine NUMPARAMS NUMPARAMS 1,
%endif
%endmacro
%macro SU_SEND 3
db %2
dw %3
USE_SEND
%xdefine CMDS CMDS SEND_ID + %1,
%if %1 == STEREO
%define INCLUDE_STEREO_SEND
%endif
%if (%3) & SEND_GLOBAL == SEND_GLOBAL
%define INCLUDE_GLOBAL_SEND
%endif
%endmacro
%define AMOUNT(val) val
%define LOCALPORT(unit,port) ((unit+1)*su_unit.size + su_unit.ports)/4 + port
%define GLOBALPORT(voice,unit,port) SEND_GLOBAL + (su_synthworkspace.voices+voice*su_voice.size+su_voice.workspace+unit*su_unit.size + su_unit.ports)/4 + port
%define OUTPORT 0
%define SEND_POP 0x8000
%define SEND_GLOBAL 0x4000
struc su_send_ports
.amount resd 1
endstruc

View File

@ -0,0 +1,419 @@
;-------------------------------------------------------------------------------
; ENVELOPE opcode: pushes an ADSR envelope value on stack [0,1]
;-------------------------------------------------------------------------------
; Mono: push the envelope value on stack
; Stereo: push the envelope valeu on stack twice
;-------------------------------------------------------------------------------
%if ENVELOPE_ID > -1
SECT_TEXT(suenvelo)
EXPORT MANGLE_FUNC(su_op_envelope,0)
%ifdef INCLUDE_STEREO_ENVELOPE
jnc su_op_envelope_mono
call su_op_envelope_mono
fld st0
ret
su_op_envelope_mono:
%endif
mov eax, dword [INP-su_voice.inputs+su_voice.release] ; eax = su_instrument.release
test eax, eax ; if (eax == 0)
je su_op_envelope_process ; goto process
mov dword [WRK+su_env_work.state], ENV_STATE_RELEASE ; [state]=RELEASE
su_op_envelope_process:
mov eax, dword [WRK+su_env_work.state] ; al=[state]
fld dword [WRK+su_env_work.level] ; x=[level]
cmp al, ENV_STATE_SUSTAIN ; if (al==SUSTAIN)
je short su_op_envelope_leave2 ; goto leave2
su_op_envelope_attac:
cmp al, ENV_STATE_ATTAC ; if (al!=ATTAC)
jne short su_op_envelope_decay ; goto decay
call su_nonlinear_map ; a x, where a=attack
faddp st1, st0 ; a+x
fld1 ; 1 a+x
fucomi st1 ; if (a+x<=1) // is attack complete?
fcmovnb st0, st1 ; a+x a+x
jbe short su_op_envelope_statechange ; else goto statechange
su_op_envelope_decay:
cmp al, ENV_STATE_DECAY ; if (al!=DECAY)
jne short su_op_envelope_release ; goto release
call su_nonlinear_map ; d x, where d=decay
fsubp st1, st0 ; x-d
fld dword [INP+su_env_ports.sustain] ; s x-d, where s=sustain
fucomi st1 ; if (x-d>s) // is decay complete?
fcmovb st0, st1 ; x-d x-d
jnc short su_op_envelope_statechange ; else goto statechange
su_op_envelope_release:
cmp al, ENV_STATE_RELEASE ; if (al!=RELEASE)
jne short su_op_envelope_leave ; goto leave
call su_nonlinear_map ; r x, where r=release
fsubp st1, st0 ; x-r
fldz ; 0 x-r
fucomi st1 ; if (x-r>0) // is release complete?
fcmovb st0, st1 ; x-r x-r, then goto leave
jc short su_op_envelope_leave
su_op_envelope_statechange:
inc dword [WRK+su_env_work.state] ; [state]++
su_op_envelope_leave:
fstp st1 ; x', where x' is the new value
fst dword [WRK+su_env_work.level] ; [level]=x'
su_op_envelope_leave2:
fmul dword [INP+su_env_ports.gain] ; [gain]*x'
ret
%endif ; SU_USE_ENVELOPE
;-------------------------------------------------------------------------------
; NOISE opcode: creates noise
;-------------------------------------------------------------------------------
; Mono: push a random value [-1,1] value on stack
; Stereo: push two (differeent) random values on stack
;-------------------------------------------------------------------------------
%if NOISE_ID > -1
SECT_TEXT(sunoise)
EXPORT MANGLE_FUNC(su_op_noise,0)
mov _CX,_SP
%ifdef INCLUDE_STEREO_NOISE
jnc su_op_noise_mono
call su_op_noise_mono
su_op_noise_mono:
%endif
imul eax, [_CX + su_stack.randseed],16007
mov [_CX + su_stack.randseed],eax
fild dword [_CX + su_stack.randseed]
do fidiv dword [,c_RandDiv,]
fld dword [INP+su_noise_ports.shape]
call su_waveshaper
fld dword [INP+su_noise_ports.gain]
fmulp st1, st0
ret
%define SU_INCLUDE_WAVESHAPER
%endif
;-------------------------------------------------------------------------------
; OSCILLAT opcode: oscillator, the heart of the synth
;-------------------------------------------------------------------------------
; Mono: push oscillator value on stack
; Stereo: push l r on stack, where l has opposite detune compared to r
;-------------------------------------------------------------------------------
%if OSCILLAT_ID > -1
SECT_TEXT(suoscill)
EXPORT MANGLE_FUNC(su_op_oscillat,0)
lodsb ; load the flags
fld dword [INP+su_osc_ports.detune] ; e, where e is the detune [0,1]
do fsub dword [,c_0_5,] ; e-.5
fadd st0, st0 ; d=2*e-.5, where d is the detune [-1,1]
%ifdef INCLUDE_STEREO_OSCILLAT
jnc su_op_oscillat_mono
fld st0 ; d d
call su_op_oscillat_mono ; r d
add WRK, 4 ; state vars: r1 l1 r2 l2 r3 l3 r4 l4, for the unison osc phases
fxch ; d r
fchs ; -d r, negate the detune for second round
su_op_oscillat_mono:
%endif
%ifdef INCLUDE_UNISONS
push_registers _AX, WRK, _AX
fldz ; 0 d
fxch ; d a=0, "accumulated signal"
su_op_oscillat_unison_loop:
fst dword [_SP] ; save the current detune, d. We could keep it in fpu stack but it was getting big.
call su_op_oscillat_single ; s a
faddp st1, st0 ; a+=s
test al, UNISON4
je su_op_oscillat_unison_out
add WRK, 8
fld dword [INP+su_osc_ports.phaseofs] ; p s
do fadd dword [,c_i12,] ; p s, add some little phase offset to unison oscillators so they don't start in sync
fstp dword [INP+su_osc_ports.phaseofs] ; s note that this changes the phase for second, possible stereo run. That's probably ok
fld dword [_SP] ; d s
do fmul dword [,c_0_5,] ; .5*d s // negate and halve the detune of each oscillator
fchs ; -.5*d s // negate and halve the detune of each oscillator
dec eax
jmp short su_op_oscillat_unison_loop
su_op_oscillat_unison_out:
pop_registers _AX, WRK, _AX
ret
su_op_oscillat_single:
%endif
fld dword [INP+su_osc_ports.transpose]
do fsub dword [,c_0_5,]
do fdiv dword [,c_i128,]
faddp st1
test al, byte LFO
jnz su_op_oscillat_skipnote
fiadd dword [INP-su_voice.inputs+su_voice.note] ; // st0 is note, st1 is t+d offset
su_op_oscillat_skipnote:
do fmul dword [,c_i12,]
call MANGLE_FUNC(su_power,0)
test al, byte LFO
jz short su_op_oscillat_normalize_note
do fmul dword [,c_lfo_normalize,] ; // st0 is now frequency for lfo
jmp short su_op_oscillat_normalized
su_op_oscillat_normalize_note:
do fmul dword [,c_freq_normalize,] ; // st0 is now frequency
su_op_oscillat_normalized:
fadd dword [WRK+su_osc_wrk.phase]
fst dword [WRK+su_osc_wrk.phase]
fadd dword [INP+su_osc_ports.phaseofs]
%ifdef INCLUDE_SAMPLES
test al, byte SAMPLE
jz short su_op_oscillat_not_sample
call su_oscillat_sample
jmp su_op_oscillat_shaping ; skip the rest to avoid color phase normalization and colorloading
su_op_oscillat_not_sample:
%endif
fld1
fadd st1, st0
fxch
fprem
fstp st1
fld dword [INP+su_osc_ports.color] ; // c p
; every oscillator test included if needed
%ifdef INCLUDE_SINE
test al, byte SINE
jz short su_op_oscillat_notsine
call su_oscillat_sine
su_op_oscillat_notsine:
%endif
%ifdef INCLUDE_TRISAW
test al, byte TRISAW
jz short su_op_oscillat_not_trisaw
call su_oscillat_trisaw
su_op_oscillat_not_trisaw:
%endif
%ifdef INCLUDE_PULSE
test al, byte PULSE
jz short su_op_oscillat_not_pulse
call su_oscillat_pulse
su_op_oscillat_not_pulse:
%endif
%ifdef INCLUDE_GATE
test al, byte GATE
jz short su_op_oscillat_not_gate
call su_oscillat_gate
jmp su_op_oscillat_gain ; skip waveshaping as the shape parameter is reused for gateshigh
su_op_oscillat_not_gate:
%endif
su_op_oscillat_shaping:
; finally, shape the oscillator and apply gain
fld dword [INP+su_osc_ports.shape]
call su_waveshaper
su_op_oscillat_gain:
fld dword [INP+su_osc_ports.gain]
fmulp st1, st0
ret
%define SU_INCLUDE_WAVESHAPER
%endif
; PULSE
%ifdef INCLUDE_PULSE
SECT_TEXT(supulse)
su_oscillat_pulse:
fucomi st1 ; // c p
fld1
jnc short su_oscillat_pulse_up ; // +1 c p
fchs ; // -1 c p
su_oscillat_pulse_up:
fstp st1 ; // +-1 p
fstp st1 ; // +-1
ret
%endif
; TRISAW
%ifdef INCLUDE_TRISAW
SECT_TEXT(sutrisaw)
su_oscillat_trisaw:
fucomi st1 ; // c p
jnc short su_oscillat_trisaw_up
fld1 ; // 1 c p
fsubr st2, st0 ; // 1 c 1-p
fsubrp st1, st0 ; // 1-c 1-p
su_oscillat_trisaw_up:
fdivp st1, st0 ; // tp'/tc
fadd st0 ; // 2*''
fld1 ; // 1 2*''
fsubp st1, st0 ; // 2*''-1
ret
%endif
; SINE
%ifdef INCLUDE_SINE
SECT_TEXT(susine)
su_oscillat_sine:
fucomi st1 ; // c p
jnc short su_oscillat_sine_do
fstp st1
fsub st0, st0 ; // 0
ret
su_oscillat_sine_do
fdivp st1, st0 ; // p/c
fldpi ; // pi p
fadd st0 ; // 2*pi p
fmulp st1, st0 ; // 2*pi*p
fsin ; // sin(2*pi*p)
ret
%endif
%ifdef INCLUDE_GATE
SECT_TEXT(sugate)
su_oscillat_gate:
fxch ; p c
fstp st1 ; p
do fmul dword [,c_16,] ; 16*p
push _AX
push _AX
fistp dword [_SP] ; s=int(16*p), stack empty
fld1 ; 1
pop _AX
and al, 0xf ; ax=int(16*p) & 15, stack: 1
bt word [VAL-4],ax ; if bit ax of the gate word is set
jc go4kVCO_gate_bit ; goto gate_bit
fsub st0, st0 ; stack: 0
go4kVCO_gate_bit: ; stack: 0/1, let's call it x
fld dword [WRK+su_osc_wrk.gatestate] ; g x, g is gatestate, x is the input to this filter 0/1
fsub st1 ; g-x x
do fmul dword [,c_dc_const,] ; c(g-x) x
faddp st1, st0 ; x+c(g-x)
fst dword [WRK+su_osc_wrk.gatestate]; g'=x+c(g-x)
pop _AX ; Another way to see this (c~0.996)
ret ; g'=cg+(1-c)x
; This is a low-pass to smooth the gate transitions
%define USE_C_16
%define USE_C_DC_CONST
%endif
; SAMPLES
%ifdef INCLUDE_SAMPLES
SECT_TEXT(suoscsam)
su_oscillat_sample: ; p
push_registers _AX,_DX,_CX,_BX ; edx must be saved, eax & ecx if this is stereo osc
push _AX
mov al, byte [VAL-4] ; reuse "color" as the sample number
do{lea _DI, [}, MANGLE_DATA(su_sample_offsets), _AX*8,]; edi points now to the sample table entry
do fmul dword [,c_samplefreq_scaling,] ; p*r
fistp dword [_SP]
pop _DX ; edx is now the sample number
movzx ebx, word [_DI + su_sample_offset.loopstart] ; ecx = loopstart
sub edx, ebx ; if sample number < loop start
jl su_oscillat_sample_not_looping ; then we're not looping yet
mov eax, edx ; eax = sample number
movzx ecx, word [_DI + su_sample_offset.looplength] ; edi is now the loop length
xor edx, edx ; div wants edx to be empty
div ecx ; edx is now the remainder
su_oscillat_sample_not_looping:
add edx, ebx ; sampleno += loopstart
add edx, dword [_DI + su_sample_offset.start]
do fild word [,MANGLE_DATA(su_sample_table),_DX*2,]
do fdiv dword [,c_32767,]
pop_registers _AX,_DX,_CX,_BX
ret
%define USE_C_32767
%define USE_C_SAMPLEFREQ_SCALING
%endif
;-------------------------------------------------------------------------------
; LOADVAL opcode
;-------------------------------------------------------------------------------
; Mono: push 2*v-1 on stack, where v is the input to port "value"
; Stereo: push 2*v-1 twice on stack
;-------------------------------------------------------------------------------
%if LOADVAL_ID > -1
SECT_TEXT(suloadvl)
EXPORT MANGLE_FUNC(su_op_loadval,0)
%ifdef INCLUDE_STEREO_LOADVAL
jnc su_op_loadval_mono
call su_op_loadval_mono
su_op_loadval_mono:
%endif
fld dword [INP+su_load_val_ports.value] ; v
do fsub dword [,c_0_5,]
fadd st0 ; 2*v-1
ret
%endif ; SU_USE_LOAD_VAL
;-------------------------------------------------------------------------------
; RECEIVE opcode
;-------------------------------------------------------------------------------
; Mono: push l on stack, where l is the left channel received
; Stereo: push l r on stack
;-------------------------------------------------------------------------------
%if RECEIVE_ID > -1
SECT_TEXT(sureceiv)
EXPORT MANGLE_FUNC(su_op_receive,0)
lea _CX, [WRK+su_unit.ports]
%ifdef INCLUDE_STEREO_RECEIVE
jnc su_op_receive_mono
xor eax,eax
fld dword [_CX+su_receive_ports.right]
mov dword [_CX+su_receive_ports.right],eax
su_op_receive_mono:
%else
xor eax,eax
%endif
fld dword [_CX+su_receive_ports.left]
mov dword [_CX+su_receive_ports.left],eax
ret
%endif ; RECEIVE_ID > -1
;-------------------------------------------------------------------------------
; IN opcode: inputs and clears a global port
;-------------------------------------------------------------------------------
; Mono: push the left channel of a global port (out or aux)
; Stereo: also push the right channel (stack in l r order)
;-------------------------------------------------------------------------------
%if IN_ID > -1
SECT_TEXT(suopin)
EXPORT MANGLE_FUNC(su_op_in,0)
lodsb
%ifdef INCLUDE_STEREO_IN
mov _DI, [_SP + su_stack.synth]
jnc su_op_in_mono
call su_op_in_right
su_op_in_mono:
sub _DI, 4
su_op_in_right:
xor ecx, ecx
fld dword [_DI + su_synthworkspace.right + _AX*4]
mov dword [_DI + su_synthworkspace.right + _AX*4], ecx
%else
xor ecx, ecx
mov _DI, [_SP + su_stack.synth]
fld dword [_DI + su_synthworkspace.left + _AX*4]
mov dword [_DI + su_synthworkspace.left + _AX*4], ecx
%endif
ret
%endif ; SU_IN_ID > -1

View File

@ -0,0 +1,262 @@
;-------------------------------------------------------------------------------
; ENVELOPE structs
;-------------------------------------------------------------------------------
%assign ENVELOPE_ID -1
%macro USE_ENVELOPE 0
%if ENVELOPE_ID == -1
%assign ENVELOPE_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_envelope,0),
%xdefine NUMPARAMS NUMPARAMS 5,
%endif
%endmacro
%macro SU_ENVELOPE 6
db %2
db %3
db %4
db %5
db %6
USE_ENVELOPE
%xdefine CMDS CMDS ENVELOPE_ID+%1,
%if %1 == STEREO
%define INCLUDE_STEREO_ENVELOPE
%endif
%endmacro
%define ATTAC(val) val
%define DECAY(val) val
%define SUSTAIN(val) val
%define RELEASE(val) val
%define GAIN(val) val
struc su_env_ports
.attac resd 1
.decay resd 1
.sustain resd 1
.release resd 1
.gain resd 1
endstruc
struc su_env_work
.state resd 1
.level resd 1
endstruc
%define ENV_STATE_ATTAC 0
%define ENV_STATE_DECAY 1
%define ENV_STATE_SUSTAIN 2
%define ENV_STATE_RELEASE 3
%define ENV_STATE_OFF 4
;-------------------------------------------------------------------------------
; OSCILLAT structs
;-------------------------------------------------------------------------------
%assign OSCILLAT_ID -1
%macro USE_OSCILLAT 0
%if OSCILLAT_ID == -1
%assign OSCILLAT_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_oscillat,0),
%xdefine NUMPARAMS NUMPARAMS 6,
%endif
%endmacro
%define SAMPLE 0x80
%define SINE 0x40
%define TRISAW 0x20
%define PULSE 0x10
%define LFO 0x08
%define GATE 0x04
%define UNISON2 0x01
%define UNISON3 0x02 ; Warning, UNISON3 and UNISON4 do not work with gate at the moment, as they use the same state variable
%define UNISON4 0x03
%macro SU_OSCILLAT 8
db %2
db %3
db %4
db %5
db %6
db %7
db %8
USE_OSCILLAT
%xdefine CMDS CMDS OSCILLAT_ID + %1,
%if %1 == STEREO
%define INCLUDE_STEREO_OSCILLAT
%endif
%if (%8) & SINE == SINE
%define INCLUDE_SINE
%endif
%if (%8) & TRISAW == TRISAW
%define INCLUDE_TRISAW
%endif
%if (%8) & PULSE == PULSE
%define INCLUDE_PULSE
%endif
%if (%8) & GATE == GATE
%define INCLUDE_GATE
%endif
%if (%8) & SAMPLE == SAMPLE
%define INCLUDE_SAMPLES
%endif
%if (%8) & UNISON4 > 0
%define INCLUDE_UNISONS
%endif
%endmacro
struc su_osc_ports
.transpose resd 1
.detune resd 1
.phaseofs resd 1
.color resd 1
.shape resd 1
.gain resd 1
endstruc
struc su_osc_wrk
.phase resd 1
.gatestate equ 16 ; we put is late so only UNISON3 and UNISON4 are unusable with gate
endstruc
%define TRANSPOSE(val) val
%define DETUNE(val) val
%define PHASE(val) val
%define GATESLOW(val) val
%define GATESHIGH(val) val
%define COLOR(val) val
%define SAMPLENO(val) val
%define SHAPE(val) val
%define FLAGS(val) val
;-------------------------------------------------------------------------------
; Sample related defines
;-------------------------------------------------------------------------------
%macro BEGIN_SAMPLE_OFFSETS 0
SECT_DATA(susamoff)
EXPORT MANGLE_DATA(su_sample_offsets)
%endmacro
%macro SAMPLE_OFFSET 3
dd %1
dw %2
dw %3
%endmacro
%define START(val) val
%define LOOPSTART(val) val
%define LOOPLENGTH(val) val
%define END_SAMPLE_OFFSETS
struc su_sample_offset ; length conveniently 8, so easy to index
.start resd 1
.loopstart resw 1
.looplength resw 1
endstruc
;-------------------------------------------------------------------------------
; NOISE structs
;-------------------------------------------------------------------------------
%assign NOISE_ID -1
%macro USE_NOISE 0
%if NOISE_ID == -1
%assign NOISE_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_noise,0),
%xdefine NUMPARAMS NUMPARAMS 2,
%endif
%endmacro
%macro SU_NOISE 3
db %2
db %3
USE_NOISE
%xdefine CMDS CMDS NOISE_ID + %1,
%if %1 == STEREO
%define INCLUDE_STEREO_NOISE
%endif
%endmacro
struc su_noise_ports
.shape resd 1
.gain resd 1
endstruc
;-------------------------------------------------------------------------------
; LOAD_VAL structs
;-------------------------------------------------------------------------------
%assign LOADVAL_ID -1
%macro USE_LOAD_VAL 0
%if LOADVAL_ID == -1
%assign LOADVAL_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_loadval,0),
%xdefine NUMPARAMS NUMPARAMS 1,
%endif
%endmacro
%macro SU_LOADVAL 2
db %2
USE_LOAD_VAL
%xdefine CMDS CMDS LOADVAL_ID+%1,
%if %1 == STEREO
%define INCLUDE_STEREO_LOADVAL
%endif
%endmacro
%define VALUE(val) val
struc su_load_val_ports
.value resd 1
endstruc
;-------------------------------------------------------------------------------
; RECEIVE structs
;-------------------------------------------------------------------------------
%assign RECEIVE_ID -1
%macro USE_RECEIVE 0
%if RECEIVE_ID == -1
%assign RECEIVE_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_receive,0),
%xdefine NUMPARAMS NUMPARAMS 0,
%endif
%endmacro
%macro SU_RECEIVE 1
USE_RECEIVE
%xdefine CMDS CMDS RECEIVE_ID+%1,
%if %1 == STEREO
%define INCLUDE_STEREO_RECEIVE
%endif
%endmacro
struc su_receive_ports
.left resd 1
.right resd 1
endstruc
;-------------------------------------------------------------------------------
; IN defines
;-------------------------------------------------------------------------------
%assign IN_ID -1
%macro USE_IN 0
%if IN_ID == -1
%assign IN_ID CUR_ID
%assign CUR_ID CUR_ID + 2
%xdefine OPCODES OPCODES MANGLE_FUNC(su_op_in,0),
%xdefine NUMPARAMS NUMPARAMS 0,
%endif
%endmacro
%macro SU_IN 2
db %2
USE_IN
%xdefine CMDS CMDS IN_ID+%1,
%if %1 == STEREO
%define INCLUDE_STEREO_IN
%endif
%endmacro

View File

@ -30,14 +30,11 @@ typedef struct SynthWorkspace {
struct Voice Voices[32];
} SynthWorkspace;
typedef struct SynthState {
typedef struct Synth {
struct SynthWorkspace SynthWrk;
struct DelayWorkspace DelayWrks[64]; // let's keep this as 64 for now, so the delays take 16 meg. If that's too little or too much, we can change this in future.
unsigned int RandSeed;
unsigned int GlobalTick;
} SynthState;
typedef struct Synth {
unsigned char Commands[32 * 64];
unsigned char Values[32 * 64 * 8];
unsigned int Polyphony;
@ -59,35 +56,14 @@ typedef struct Synth {
extern void CALLCONV su_load_gmdls(void);
#endif
// int su_render(Synth* synth,SynthState* synthState, float* buffer, int samples):
// Renders 'samples' number of 'samples' to the 'buffer', using 'synth'.
// Modifies 'synthState' and fills the 'buffer'.
//
// Parameters:
// synth pointer to the synthesizer used. Won't get modified by the call.
// synthState pointer to current synthState. RandSeed should be > 0 e.g. 1
// buffer audio sample buffer, L R L R ...
// samples maximum number of samples to be rendered. WARNING: buffer
// should have a length of 2 * samples as the audio is stereo.
//
// Returns error code:
// 0 everything ok
// (returns always 0 as no errors are implemented yet)
int CALLCONV su_render(Synth* synth,SynthState* synthState, float* buffer, int samples);
// int su_render_time(Synth* synth,SynthState* synthState, float* buffer, int* samples, int* time):
// int su_render(Synth* synth, float* buffer, int* samples, int* time):
// Renders samples until 'samples' number of samples are reached or 'time' number of
// modulated time ticks are reached, whichever happens first. 'samples' and 'time' are
// are passed by reference as the function modifies to tell how many samples were
// actually rendered and how many time ticks were actually advanced.
//
// Parameters:
// synth pointer to the synthesizer used. Won't get modified by the call.
// synthState pointer to current synthState. RandSeed should be > 0 e.g. 1
// Also synthState->SamplesPerRow cannot be 0 or nothing will be
// rendered; either set it to INT32_MAX to always render full
// buffer, or something like SAMPLE_RATE * 60 / (BPM * 4) for
// having 4 rows per beat.
// synth pointer to the synthesizer used. RandSeed should be > 0 e.g. 1
// buffer audio sample buffer, L R L R ...
// samples pointer to the maximum number of samples to be rendered.
// buffer should have a length of 2 * maxsamples as the audio
@ -104,7 +80,7 @@ int CALLCONV su_render(Synth* synth,SynthState* synthState, float* buffer, int s
// Returns error code:
// 0 everything ok
// (no actual errors implemented yet)
int CALLCONV su_render_time(Synth* synth,SynthState* synthState, float* buffer, int* samples, int* time);
int CALLCONV su_render(Synth* synth, float* buffer, int* samples, int* time);
// Arithmetic opcode ids
extern const int su_add_id;

View File

@ -0,0 +1,540 @@
%if BITS == 64
%define WRK rbp ; alias for unit workspace
%define VAL rsi ; alias for unit values (transformed/untransformed)
%define COM rbx ; alias for instrument opcodes
%define INP rdx ; alias for transformed inputs
%define _AX rax ; push and offsets have to be r* on 64-bit and e* on 32-bit
%define _BX rbx
%define _CX rcx
%define _DX rdx
%define _SP rsp
%define _SI rsi
%define _DI rdi
%define _BP rbp
%define PTRSIZE 8
%define PTRWORD qword
%define RESPTR resq
%define DPTR dq
%macro do 2
mov r9, qword %2
%1 r9
%endmacro
%macro do 3
mov r9, qword %2
%1 r9 %3
%endmacro
%macro do 4
mov r9, qword %2
%1 r9+%3 %4
%endmacro
%macro do 5
mov r9, qword %2
lea r9, [r9+%3]
%1 r9+%4 %5
%endmacro
%macro push_registers 1-*
%rep %0
push %1
%rotate 1
%endrep
%endmacro
%macro pop_registers 1-*
%rep %0
%rotate -1
pop %1
%endrep
%endmacro
%define PUSH_REG_SIZE(n) (n*8)
%ifidn __OUTPUT_FORMAT__,win64
%define render_prologue push_registers rcx,rdi,rsi,rbx,rbp ; rcx = ptr to buf. rdi,rsi,rbx,rbp nonvolatile
%macro render_epilogue 0
pop_registers rcx,rdi,rsi,rbx,rbp
ret
%endmacro
%else ; 64 bit mac & linux
%define render_prologue push_registers rdi,rbx,rbp ; rdi = ptr to buf. rbx & rbp nonvolatile
%macro render_epilogue 0
pop_registers rdi,rbx,rbp
ret
%endmacro
%endif
%else
%define WRK ebp ; alias for unit workspace
%define VAL esi ; alias for unit values (transformed/untransformed)
%define COM ebx ; alias for instrument opcodes
%define INP edx ; alias for transformed inputs
%define _AX eax
%define _BX ebx
%define _CX ecx
%define _DX edx
%define _SP esp
%define _SI esi
%define _DI edi
%define _BP ebp
%define PTRSIZE 4
%define PTRWORD dword
%define RESPTR resd
%define DPTR dd
%macro do 2
%1 %2
%endmacro
%macro do 3
%1 %2 %3
%endmacro
%macro do 4
%1 %2+%3 %4
%endmacro
%macro do 5
%1 %2+%3+%4 %5
%endmacro
%macro push_registers 1-*
pushad ; in 32-bit mode, this is the easiest way to store all the registers
%endmacro
%macro pop_registers 1-*
popad
%endmacro
%define PUSH_REG_SIZE(n) 32
%define render_prologue pushad ; stdcall & everything nonvolatile except eax, ecx, edx
%macro render_epilogue 0
popad
ret 4 ; clean the passed parameter from stack.
%endmacro
%endif
section .text ; yasm throws section redeclaration warnings if strucs are defined without a plain .text section
struc su_stack ; the structure of stack _as the units see it_
.retaddr RESPTR 1
%if BITS == 32 ; we dump everything with pushad, so this is unused in 32-bit
RESPTR 1
%endif
.val RESPTR 1
.wrk RESPTR 1
%if BITS == 32 ; we dump everything with pushad, so this is unused in 32-bit
RESPTR 1
%endif
.com RESPTR 1
.synth RESPTR 1
.delaywrk RESPTR 1
%if BITS == 32 ; we dump everything with pushad, so this is unused in 32-bit
RESPTR 1
%endif
.retaddrvm RESPTR 1
.voiceno RESPTR 1
%ifdef INCLUDE_POLYPHONY
.polyphony RESPTR 1
%endif
.output_sound
.rowtick RESPTR 1 ; which tick within this row are we at
.update_voices
.row RESPTR 1 ; which total row of the song are we at
.tick RESPTR 1 ; which total tick of the song are we at
.randseed RESPTR 1
%ifdef INCLUDE_MULTIVOICE_TRACKS
.voicetrack RESPTR 1
%endif
.render_epilogue
%if BITS == 32
RESPTR 8 ; registers
.retaddr_pl RESPTR 1
%elifidn __OUTPUT_FORMAT__,win64
RESPTR 4 ; registers
%else
RESPTR 2 ; registers
%endif
.bufferptr RESPTR 1
.size
endstruc
;===============================================================================
; Uninitialized data: The one and only synth object
;===============================================================================
SECT_BSS(susynth)
su_synth_obj resb su_synthworkspace.size
%if DELAY_ID > -1 ; if we use delay, then the synth obj should be immediately followed by the delay workspaces
resb NUM_DELAY_LINES*su_delayline_wrk.size
%endif
;===============================================================================
; The opcode table jump table. This is constructed to only include the opcodes
; that are used so that the jump table is as small as possible.
;===============================================================================
SECT_DATA(suoptabl)
su_synth_commands DPTR OPCODES
;===============================================================================
; The number of transformed parameters each opcode takes
;===============================================================================
SECT_DATA(suparcnt)
su_opcode_numparams db NUMPARAMS
;-------------------------------------------------------------------------------
; su_run_vm function: runs the entire virtual machine once, creating 1 sample
;-------------------------------------------------------------------------------
; Input: su_synth_obj.left : Set to 0 before calling
; su_synth_obj.right : Set to 0 before calling
; _CX : Pointer to delay workspace (if needed)
; _DX : Pointer to synth object
; COM : Pointer to command stream
; VAL : Pointer to value stream
; WRK : Pointer to the last workspace processed
; _DI : Number of voices to process
; Output: su_synth_obj.left : left sample
; su_synth_obj.right : right sample
; Dirty: everything
;-------------------------------------------------------------------------------
SECT_TEXT(surunvm)
EXPORT MANGLE_FUNC(su_run_vm,0)
push_registers _CX, _DX, COM, WRK, VAL ; save everything to stack
su_run_vm_loop: ; loop until all voices done
movzx edi, byte [COM] ; edi = command byte
inc COM ; move to next instruction
add WRK, su_unit.size ; move WRK to next unit
shr edi, 1 ; shift out the LSB bit = stereo bit
mov INP, [_SP+su_stack.wrk-PTRSIZE] ; reset INP to point to the inputs part of voice
add INP, su_voice.inputs
xor ecx, ecx ; counter = 0
xor eax, eax ; clear out high bits of eax, as lodsb only sets al
su_transform_values_loop:
do{cmp cl, byte [},su_opcode_numparams,_DI,] ; compare the counter to the value in the param count table
je su_transform_values_out
lodsb ; load the byte value from VAL stream
push _AX ; push it to memory so FPU can read it
fild dword [_SP] ; load the value to FPU stack
do fmul dword [,c_i128,] ; divide it by 128 (0 => 0, 128 => 1.0)
fadd dword [WRK+su_unit.ports+_CX*4] ; add the modulations in the current workspace
fstp dword [INP+_CX*4] ; store the modulated value in the inputs section of voice
xor eax, eax
mov dword [WRK+su_unit.ports+_CX*4], eax ; clear out the modulation ports
pop _AX
inc ecx
jmp su_transform_values_loop
su_transform_values_out:
bt dword [COM-1],0 ; LSB of COM = stereo bit => carry
do call [,su_synth_commands,_DI*PTRSIZE,] ; call the function corresponding to the instruction
cmp dword [_SP+su_stack.voiceno-PTRSIZE],0 ; do we have more voices to process?
jne su_run_vm_loop ; if there's more voices to process, goto vm_loop
pop_registers _CX, _DX, COM, WRK, VAL ; pop everything from stack
ret
;-------------------------------------------------------------------------------
; su_nonlinear_map function: returns 2^(-24*x) of parameter number _AX
;-------------------------------------------------------------------------------
; Input: _AX : parameter number (e.g. for envelope: 0 = attac, 1 = decay...)
; INP : pointer to transformed values
; Output: st0 : 2^(-24*x), where x is the parameter in the range 0-1
;-------------------------------------------------------------------------------
SECT_TEXT(supower)
%if ENVELOPE_ID > -1 || COMPRES_ID > -1
su_nonlinear_map:
fld dword [INP+_AX*4] ; x, where x is the parameter in the range 0-1
do fimul dword [,c_24,] ; 24*x
fchs ; -24*x
; flow into Power function, which outputs 2^(-24*x)
%endif
;-------------------------------------------------------------------------------
; su_power function: computes 2^x
;-------------------------------------------------------------------------------
; Input: st0 : x
; Output: st0 : 2^x
;-------------------------------------------------------------------------------
EXPORT MANGLE_FUNC(su_power,0)
fld1 ; 1 x
fld st1 ; x 1 x
fprem ; mod(x,1) 1 x
f2xm1 ; 2^mod(x,1)-1 1 x
faddp st1,st0 ; 2^mod(x,1) x
fscale ; 2^mod(x,1)*2^trunc(x) x
; Equal to:
; 2^x x
fstp st1 ; 2^x
ret
%ifndef SU_DISABLE_PLAYER
;-------------------------------------------------------------------------------
; output_sound macro: used by the render function to write sound to buffer
;-------------------------------------------------------------------------------
; The macro contains the ifdef hell to handle 16bit output and clipping cases
; to keep the main function more readable
; Stack : sample row pushad output_ptr
;-------------------------------------------------------------------------------
%macro output_sound 0
%ifndef SU_USE_16BIT_OUTPUT
%ifndef SU_CLIP_OUTPUT ; The modern way. No need to clip; OS can do it.
mov _DI, [_SP+su_stack.bufferptr - su_stack.output_sound] ; edi containts ptr
mov _SI, PTRWORD su_synth_obj + su_synthworkspace.left
movsd ; copy left channel to output buffer
movsd ; copy right channel to output buffer
mov [_SP+su_stack.bufferptr - su_stack.output_sound], _DI ; save back the updated ptr
lea _DI, [_SI-8]
xor eax, eax
stosd ; clear left channel so the VM is ready to write them again
stosd ; clear right channel so the VM is ready to write them again
%else
mov _SI, qword [_SP+su_stack.bufferptr - su_stack.output_sound] ; esi points to the output buffer
xor _CX,_CX
xor eax,eax
%%loop: ; loop over two channels, left & right
do fld dword [,su_synth_obj+su_synthworkspace.left,_CX*4,]
call su_clip
fstp dword [_SI]
do mov dword [,su_synth_obj+su_synthworkspace.left,_CX*4,{],eax} ; clear the sample so the VM is ready to write it
add _SI,4
cmp ecx,2
jl %%loop
mov dword [_SP+su_stack.bufferptr - su_stack.output_sound], _SI ; save esi back to stack
%endif
%else ; 16-bit output, always clipped. This is a bit legacy method.
mov _SI, [_SP+su_stack.bufferptr - su_stack.output_sound] ; esi points to the output buffer
mov _DI, PTRWORD su_synth_obj+su_synthworkspace.left
mov ecx, 2
%%loop: ; loop over two channels, left & right
fld dword [_DI]
call su_clip
do fmul dword [,c_32767,]
push _AX
fistp dword [_SP]
pop _AX
mov word [_SI],ax ; // store integer converted right sample
xor eax,eax
stosd
add _SI,2
loop %%loop
mov [_SP+su_stack.bufferptr - su_stack.output_sound], _SI ; save esi back to stack
%define USE_C_32767
%endif
%endmacro
;-------------------------------------------------------------------------------
; su_render_song function: the entry point for the synth
;-------------------------------------------------------------------------------
; Has the signature su_render_song(void *ptr), where ptr is a pointer to
; the output buffer. Renders the compile time hard-coded song to the buffer.
; Stack: output_ptr
;-------------------------------------------------------------------------------
SECT_TEXT(surensng)
EXPORT MANGLE_FUNC(su_render_song,PTRSIZE) ; Stack: ptr
render_prologue
xor eax, eax
%ifdef INCLUDE_MULTIVOICE_TRACKS
push VOICETRACK_BITMASK
%endif
push 1 ; randseed
push _AX ; global tick time
su_render_rowloop: ; loop through every row in the song
push _AX ; Stack: row pushad ptr
call su_update_voices ; update instruments for the new row
xor eax, eax ; ecx is the current sample within row
su_render_sampleloop: ; loop through every sample in the row
push _AX ; Stack: sample row pushad ptr
%ifdef INCLUDE_POLYPHONY
push POLYPHONY_BITMASK ; does the next voice reuse the current opcodes?
%endif
push MAX_VOICES
mov _DX, PTRWORD su_synth_obj ; _DX points to the synth object
mov COM, PTRWORD MANGLE_DATA(su_commands) ; COM points to vm code
mov VAL, PTRWORD MANGLE_DATA(su_params) ; VAL points to unit params
%if DELAY_ID > -1
lea _CX, [_DX + su_synthworkspace.size - su_delayline_wrk.filtstate]
%endif
lea WRK, [_DX + su_synthworkspace.voices] ; WRK points to the first voice
call MANGLE_FUNC(su_run_vm,0) ; run through the VM code
pop _AX
%ifdef INCLUDE_POLYPHONY
pop _AX
%endif
output_sound ; *ptr++ = left, *ptr++ = right
pop _AX
inc dword [_SP + PTRSIZE] ; increment global time, used by delays
inc eax
cmp eax, SAMPLES_PER_ROW
jl su_render_sampleloop
pop _AX ; Stack: pushad ptr
inc eax
cmp eax, TOTAL_ROWS
jl su_render_rowloop
%ifdef INCLUDE_MULTIVOICE_TRACKS
add _SP, su_stack.render_epilogue - su_stack.tick ; rewind the remaining tack
%else
pop _AX
pop _AX
%endif
render_epilogue
;-------------------------------------------------------------------------------
; su_update_voices function: polyphonic & chord implementation
;-------------------------------------------------------------------------------
; Input: eax : current row within song
; Dirty: pretty much everything
;-------------------------------------------------------------------------------
SECT_TEXT(suupdvce)
%ifdef INCLUDE_MULTIVOICE_TRACKS
su_update_voices: ; Stack: retaddr row
xor edx, edx
mov ebx, PATTERN_SIZE ; we could do xor ebx,ebx; mov bl,PATTERN_SIZE, but that would limit patternsize to 256...
div ebx ; eax = current pattern, edx = current row in pattern
do{lea _SI, [},MANGLE_DATA(su_tracks),_AX,] ; esi points to the pattern data for current track
xor eax, eax ; eax is the first voice of next track
xor ebx, ebx ; ebx is the first voice of current track
mov _BP, PTRWORD su_synth_obj ; ebp points to the current_voiceno array
su_update_voices_trackloop:
movzx eax, byte [_SI] ; eax = current pattern
imul eax, PATTERN_SIZE ; eax = offset to current pattern data
do{movzx eax,byte [},MANGLE_DATA(su_patterns),_AX,_DX,] ; eax = note
push _DX ; Stack: ptrnrow
xor edx, edx ; edx=0
mov ecx, ebx ; ecx=first voice of the track to be done
su_calculate_voices_loop: ; do {
bt dword [_SP + su_stack.voicetrack - su_stack.update_voices + 2*PTRSIZE],ecx ; test voicetrack_bitmask// notice that the incs don't set carry
inc edx ; edx++ // edx=numvoices
inc ecx ; ecx++ // ecx=the first voice of next track
jc su_calculate_voices_loop ; } while bit ecx-1 of bitmask is on
push _CX ; Stack: next_instr ptrnrow
cmp al, HLD ; anything but hold causes action
je short su_update_voices_nexttrack
mov cl, byte [_BP]
mov edi, ecx
add edi, ebx
shl edi, MAX_UNITS_SHIFT + 6 ; each unit = 64 bytes and there are 1<<MAX_UNITS_SHIFT units + small header
do inc dword [,su_synth_obj+su_synthworkspace.voices+su_voice.release,_DI,] ; set the voice currently active to release; notice that it could increment any number of times
cmp al, HLD ; if cl < HLD (no new note triggered)
jl su_update_voices_nexttrack ; goto nexttrack
inc ecx ; curvoice++
cmp ecx, edx ; if (curvoice >= num_voices)
jl su_update_voices_skipreset
xor ecx,ecx ; curvoice = 0
su_update_voices_skipreset:
mov byte [_BP],cl
add ecx, ebx
shl ecx, MAX_UNITS_SHIFT + 6 ; each unit = 64 bytes and there are 1<<MAX_UNITS_SHIFT units + small header
do{lea _DI,[},su_synth_obj+su_synthworkspace.voices,_CX,]
stosd ; save note
mov ecx, (su_voice.size - su_voice.release)/4
xor eax, eax
rep stosd ; clear the workspace of the new voice, retriggering oscillators
su_update_voices_nexttrack:
pop _BX ; ebx=first voice of next instrument, Stack: ptrnrow
pop _DX ; edx=patrnrow
add _SI, MAX_PATTERNS
inc _BP
do{cmp _BP,},su_synth_obj+MAX_TRACKS
jl su_update_voices_trackloop
ret
%else ; INCLUDE_MULTIVOICE_TRACKS not defined -> one voice per track ve_SIon
su_update_voices: ; Stack: retaddr row
xor edx, edx
xor ebx, ebx
mov bl, PATTERN_SIZE
div ebx ; eax = current pattern, edx = current row in pattern
do{lea _SI, [},MANGLE_DATA(su_tracks),_AX,]; esi points to the pattern data for current track
mov _DI, PTRWORD su_synth_obj+su_synthworkspace.voices
mov bl, MAX_TRACKS ; MAX_TRACKS is always <= 32 so this is ok
su_update_voices_trackloop:
movzx eax, byte [_SI] ; eax = current pattern
imul eax, PATTERN_SIZE ; eax = offset to current pattern data
do{movzx eax, byte [}, MANGLE_DATA(su_patterns),_AX,_DX,] ; ecx = note
cmp al, HLD ; anything but hold causes action
je short su_update_voices_nexttrack
inc dword [_DI+su_voice.release] ; set the voice currently active to release; notice that it could increment any number of times
jb su_update_voices_nexttrack ; if cl < HLD (no new note triggered) goto nexttrack
su_update_voices_retrigger:
stosd ; save note
mov ecx, (su_voice.size - su_voice.release)/4 ; could be xor ecx, ecx; mov ch,...>>8, but will it actually be smaller after compression?
xor eax, eax
rep stosd ; clear the workspace of the new voice, retriggering oscillators
jmp short su_update_voices_skipadd
su_update_voices_nexttrack:
add _DI, su_voice.size
su_update_voices_skipadd:
add _SI, MAX_PATTERNS
dec ebx
jnz short su_update_voices_trackloop
ret
%endif ;INCLUDE_MULTIVOICE_TRACKS
%endif ; SU_DISABLE_PLAYER
;-------------------------------------------------------------------------------
; Include the rest of the code
;-------------------------------------------------------------------------------
%include "opcodes/arithmetic_footer.inc"
%include "opcodes/flowcontrol_footer.inc"
%include "opcodes/sources_footer.inc"
%include "opcodes/sinks_footer.inc"
; warning: at the moment effects has to be assembled after
; sources, as sources.asm defines SU_USE_WAVESHAPER
; if needed.
%include "opcodes/effects_footer.inc"
%include "introspection_footer.inc"
%ifidn __OUTPUT_FORMAT__,win64
%include "win64/gmdls_win64_footer.inc"
%endif
%ifidn __OUTPUT_FORMAT__,win32
%include "win32/gmdls_win32_footer.inc"
%endif
;-------------------------------------------------------------------------------
; Constants
;-------------------------------------------------------------------------------
SECT_DATA(suconst)
c_24 dd 24
c_i128 dd 0.0078125
c_RandDiv dd 65536*32768
c_0_5 dd 0.5
c_i12 dd 0x3DAAAAAA
c_lfo_normalize dd 0.000038
c_freq_normalize dd 0.000092696138 ; // 220.0/(2^(69/12)) / 44100.0
%ifdef USE_C_DC_CONST
c_dc_const dd 0.99609375 ; R = 1 - (pi*2 * frequency /samplerate)
%endif
%ifdef USE_C_32767
c_32767 dd 32767.0
%endif
%ifdef USE_C_BPMSCALE
c_bpmscale dd 2.666666666666 ; 64/24, 24 values will be double speed, so you can go from ~ 1/2.5 speed to 2.5x speed
%endif
%ifdef USE_C_16
c_16 dd 16.0
%endif
%ifdef USE_C_SAMPLEFREQ_SCALING
c_samplefreq_scaling dd 84.28074964676522 ; o = 0.000092696138, n = 72, f = 44100*o*2**(n/12), scaling = 22050/f <- so note 72 plays at the "normal rate"
%endif

View File

@ -0,0 +1,265 @@
%ifndef SOINTU_INC
%define SOINTU_INC
; You will have to define a BPM for your song, e.g.
; %define BPM 100
%macro EXPORT 1
global %1
%1
%endmacro
%ifidn __OUTPUT_FORMAT__,win32
; on win32, function f with n parameters is mangled as "_f@n"
%define MANGLE_FUNC(f,n) _ %+ f %+ @ %+ n
%define WIN_OR_MAC
%assign BITS 32
; On windows and mac, data label d is mangled as "_d"
%define MANGLE_DATA(d) _ %+ d
%endif
%ifidn __OUTPUT_FORMAT__,win64
; on win32, function f with n parameters is mangled as "_f@n"
%define MANGLE_FUNC(f,n) f
%define WIN_OR_MAC
%assign BITS 64
; On windows and mac, data label d is mangled as "_d"
%define MANGLE_DATA(d) d
%endif
%ifidn __OUTPUT_FORMAT__,elf
; on linux, function f with n parameters is mangled as "f"
%define MANGLE_FUNC(f,n) f
; On linux, data label d is mangled as "d"
%define MANGLE_DATA(d) d
%assign BITS 32
%endif
%ifidn __OUTPUT_FORMAT__,elf64
%define MANGLE_FUNC(f,n) f
%define MANGLE_DATA(d) d
%assign BITS 64
%endif
%ifidn __OUTPUT_FORMAT__,macho32
; on mac, function f with x parameters is mangled as "_f"
%define MANGLE_FUNC(f,n) _f
%define WIN_OR_MAC
; On windows and mac, data label d is mangled as "_d"
%define MANGLE_DATA(d) _ %+ d
%endif
%ifdef WIN_OR_MAC
; Windows has crinkler so one may put everything in custom sections to aid crinkler.
; Maybe mac users need it too
%ifndef DISABLE_SECTIONS
%define SECT_BSS(n) section . %+ n bss align=1
%define SECT_DATA(n) section . %+ n data align=1
%define SECT_TEXT(n) section . %+ n code align=1
%else
%define SECT_BSS(n) section .bss align=1
%define SECT_DATA(n) section .data align=1
%define SECT_TEXT(n) section .code align=1
%endif
%else
; Linux
%ifndef DISABLE_SECTIONS
%define SECT_BSS(n) section .bss. %+ n nobits alloc noexec write align=1
%define SECT_DATA(n) section .data. %+ n progbits alloc noexec write align=1
%define SECT_TEXT(n) section .text. %+ n progbits alloc exec nowrite align=1
%else
%define SECT_BSS(n) section .bss. nobits alloc noexec write align=1
%define SECT_DATA(n) section .data. progbits alloc noexec write align=1
%define SECT_TEXT(n) section .text. progbits alloc exec nowrite align=1
%endif
%endif
%ifdef SU_USE_16BIT_OUTPUT
%define SU_INCLUDE_CLIP
%endif
%assign CUR_ID 2
%define CMDS ; CMDS is empty at first, no commands defined
%define OPCODES MANGLE_FUNC(su_op_advance,0),
%define NUMPARAMS 0,
%define SU_ADVANCE_ID 0
%define MONO 0
%define STEREO 1
section .text ; yasm throws section redeclaration warnings if strucs are defined without a plain .text section
%include "opcodes/flowcontrol_header.inc"
%include "opcodes/arithmetic_header.inc"
%include "opcodes/effects_header.inc"
%include "opcodes/sources_header.inc"
%include "opcodes/sinks_header.inc"
;-------------------------------------------------------------------------------
; synth defines
;-------------------------------------------------------------------------------
%define MAX_DELAY 65536
%assign MAX_UNITS_SHIFT 6
%assign MAX_UNITS ((1 << MAX_UNITS_SHIFT)-1) ; this is carefully chosen to align su_unit to 2^n boundary
%define ABSOLUTE_MAX_VOICES 32
%ifndef SAMPLE_RATE
%define SAMPLE_RATE 44100
%endif
%ifndef HLD
%define HLD 1
%endif
%define TOTAL_ROWS (MAX_PATTERNS*PATTERN_SIZE)
%define SAMPLES_PER_ROW (SAMPLE_RATE*4*60/(BPM*16))
%define MAX_SAMPLES (SAMPLES_PER_ROW*TOTAL_ROWS)
%macro BEGIN_PATCH 0
SECT_DATA(params)
EXPORT MANGLE_DATA(su_params)
%endmacro
%macro END_PATCH 0 ; After the patch is finished, saves the accumulated commands
SECT_DATA(sucomnds)
EXPORT MANGLE_DATA(su_commands)
db CMDS
%endmacro
%define POLYPHONY_BITMASK 0
%assign MAX_VOICES 0
%assign MAX_TRACKS 0
%macro BEGIN_INSTRUMENT 1
; increment MAX_VOICES equal to %1 and construct the POLYPHONY_BITMASK so that
; for every except the last, the bit is on
%rep %1-1
%assign POLYPHONY_BITMASK (POLYPHONY_BITMASK << 1) + 1
%assign MAX_VOICES MAX_VOICES + 1
%endrep
%assign POLYPHONY_BITMASK (POLYPHONY_BITMASK << 1)
%assign MAX_VOICES MAX_VOICES + 1 ; the last voice increment, without adding one bit to the mask
%if MAX_VOICES > 32
%error Error: cannot have more than 32 voices!
%endif
%if %1 > 1
%define INCLUDE_POLYPHONY
%endif
%endmacro
%define VOICES(val) val
%define TRACKS(val) val
%macro END_INSTRUMENT 0
%xdefine CMDS CMDS SU_ADVANCE_ID,
%endmacro
%assign PATTERN_LENGTH -1
%macro BEGIN_PATTERNS 0
SECT_DATA(supatrns)
EXPORT MANGLE_DATA(su_patterns)
%define USE_PLAYER
%endmacro
%define END_PATTERNS
%assign PATTERN_SIZE -1
%macro PATTERN 1-*
%rep %0
db %1
%rotate 1
%endrep
%if %0 >= 256
%error 'Pattern size should be < 256'
%endif
%if PATTERN_SIZE == -1
%assign PATTERN_SIZE %0
%else
%if %0 != PATTERN_SIZE
%error 'All patterns should have the same length!'
%endif
%endif
%endmacro
%macro BEGIN_TRACKS 0
SECT_DATA(sutracks)
EXPORT MANGLE_DATA(su_tracks)
%define USE_PLAYER
%endmacro
%assign MAX_PATTERNS -1
%assign MAX_TRACKS 0
%assign VOICETRACK_BITMASK 0
%assign VOICETRACK_COUNT 0
%macro TRACK 2-* ; first param number of voices, rest are the patterns
%rep %0-1
db %2
%rotate 1
%endrep
%rotate 1
%if MAX_PATTERNS == -1
%assign MAX_PATTERNS %0-1
%else
%if %0-1 != MAX_PATTERNS
%error 'All tracks should have same number of patterns!'
%endif
%endif
%assign MAX_TRACKS MAX_TRACKS + 1
%if MAX_TRACKS > 32
%error Error: cannot have more than 32 tracks!
%endif
; increment MAX_TRACKS equal to %2 and construct the CHORD_BITMASK so that
; for every track except the last track of an instrument, the bit is on
%rep %1-1
%assign VOICETRACK_BITMASK VOICETRACK_BITMASK + (1 << VOICETRACK_COUNT)
%assign VOICETRACK_COUNT VOICETRACK_COUNT + 1
%endrep
%assign VOICETRACK_COUNT VOICETRACK_COUNT + 1 ; the last voice increment, without adding bit mask
%if VOICETRACK_COUNT > 32
%error Error: cannot have more than a total of 32 voices assigned to tracks.
%endif
%if %1 > 1
%define INCLUDE_MULTIVOICE_TRACKS
%endif
%endmacro
%define END_TRACKS
;-------------------------------------------------------------------------------
; unit struct
;-------------------------------------------------------------------------------
struc su_unit
.state resd 8
.ports resd 8
.size
endstruc
;-------------------------------------------------------------------------------
; voice struct
;-------------------------------------------------------------------------------
struc su_voice
.note resd 1
.release resd 1
.inputs resd 8
.reserved resd 6 ; this is done to so the whole voice is 2^n long, see polyphonic player
.workspace resb MAX_UNITS * su_unit.size
.size
endstruc
;-------------------------------------------------------------------------------
; synthworkspace struct
;-------------------------------------------------------------------------------
struc su_synthworkspace
.curvoices resb 32 ; these are used by the multitrack player to store which voice is playing on which track
.left resd 1
.right resd 1
.aux resd 6 ; 3 auxiliary signals
.voices resb ABSOLUTE_MAX_VOICES * su_voice.size
.size
endstruc
%endif ; SOINTU_INC

View File

@ -0,0 +1,39 @@
%ifdef INCLUDE_GMDLS
%define SAMPLE_TABLE_SIZE 3440660 ; size of gmdls
extern _OpenFile@12 ; requires windows
extern _ReadFile@20 ; requires windows
SECT_TEXT(sugmdls)
EXPORT MANGLE_FUNC(su_load_gmdls,0)
mov edx, MANGLE_DATA(su_sample_table)
mov ecx, su_gmdls_path1
su_gmdls_pathloop:
push 0 ; OF_READ
push edx ; &ofstruct, blatantly reuse the sample table
push ecx ; path
call _OpenFile@12 ; eax = OpenFile(path,&ofstruct,OF_READ)
add ecx, su_gmdls_path2 - su_gmdls_path1 ; if we ever get to third, then crash
cmp eax, -1 ; eax == INVALID?
je su_gmdls_pathloop
push 0 ; NULL
push edx ; &bytes_read, reusing sample table again; it does not matter that the first four bytes are trashed
push SAMPLE_TABLE_SIZE ; number of bytes to read
push edx ; here we actually pass the sample table to readfile
push eax ; handle to file
call _ReadFile@20 ; Readfile(handle,&su_sample_table,SAMPLE_TABLE_SIZE,&bytes_read,NULL)
ret
SECT_DATA(sugmpath)
su_gmdls_path1:
db 'drivers/gm.dls',0
su_gmdls_path2:
db 'drivers/etc/gm.dls',0
SECT_BSS(susamtbl)
EXPORT MANGLE_DATA(su_sample_table) resb SAMPLE_TABLE_SIZE ; size of gmdls.
%endif

View File

@ -0,0 +1,43 @@
%ifdef INCLUDE_GMDLS
%define SAMPLE_TABLE_SIZE 3440660 ; size of gmdls
extern OpenFile ; requires windows
extern ReadFile ; requires windows
SECT_TEXT(sugmdls)
EXPORT MANGLE_FUNC(su_load_gmdls,0)
; Win64 ABI: RCX, RDX, R8, and R9
sub rsp, 40 ; Win64 ABI requires "shadow space" + space for one parameter.
mov rdx, PTRWORD MANGLE_DATA(su_sample_table)
mov rcx, PTRWORD su_gmdls_path1
su_gmdls_pathloop:
xor r8,r8 ; OF_READ
push rdx ; &ofstruct, blatantly reuse the sample table
push rcx
call OpenFile ; eax = OpenFile(path,&ofstruct,OF_READ)
pop rcx
add rcx, su_gmdls_path2 - su_gmdls_path1 ; if we ever get to third, then crash
pop rdx
cmp eax, -1 ; ecx == INVALID?
je su_gmdls_pathloop
movsxd rcx, eax
mov qword [rsp+32],0
mov r9, rdx
mov r8d, SAMPLE_TABLE_SIZE ; number of bytes to read
call ReadFile ; Readfile(handle,&su_sample_table,SAMPLE_TABLE_SIZE,&bytes_read,NULL)
add rsp, 40 ; shadow space, as required by Win64 ABI
ret
SECT_DATA(sugmpath)
su_gmdls_path1:
db 'drivers/gm.dls',0
su_gmdls_path2:
db 'drivers/etc/gm.dls',0
SECT_BSS(susamtbl)
EXPORT MANGLE_DATA(su_sample_table) resb SAMPLE_TABLE_SIZE ; size of gmdls.
%endif