Konami VRC6 Sound Engine Help

NES Programming
Post Reply
puppydrum64
Posts: 34
Joined: Thu Apr 22, 2021 9:30 pm

Konami VRC6 Sound Engine Help

Post by puppydrum64 » Sat May 01, 2021 4:36 pm

I'm using the Nerdy Nights Tutorial for a sound engine. It works for the standard 2a03 channels but I'm trying to upgrade it to work with Konami VRC6 expanded audio. It stopped working once I added in the chapter 6 features, and I don't know why. The 2A03 sounds play as normal.

http://nerdy-nights.nes.science/#audio_tutorial-6

Below is the main program file.

Code: Select all

	org $BFF0

	db "NES",$1a		;ID
	db $01				;Rom pages (16k each)
	db $0				;CHR-ROM pages
	db %10000010		;mmmmFTBM		mmmm = mapper no bottom 4 bits , Four screen vram layout, Trainer at &7000, Battery ram at &6000, Mirror (0=horiz, 1=vert)
	db %00010000		;mmmm--PV 		mapper (top 4 bits...  Pc10 arcade, Vs unisystem )
	db 0				;Ram pages	(this might not be set up correctly)
	db 0,0,0,0,0,0,0	;			(this might not be set up correctly)
	;THIS CARTRIDGE USES MAPPER 24 WHICH WAS ALSO USED BY THE JAPANESE VERSION OF CASTLEVANIA 3
	
temp				equ $00
temp1				equ $01
temp2				equ $02
temp3				equ $03
temp4				equ	$04
temp5				equ $05
temp6				equ $06
sound_pointer		equ $10	;$11 reserved for +1
z_Regs 		equ $40

z_HL equ z_Regs
z_L  equ z_Regs
z_H  equ z_Regs+1

z_BC equ z_Regs+2
z_C  equ z_Regs+2
z_B  equ z_Regs+3

z_DE equ z_Regs+4
z_E  equ z_Regs+4
z_D  equ z_Regs+5

gamepad				equ $50		;Controller 1 buttons pressed
gamepad2			equ $51		;Controller 2 buttons pressed
musicloop			equ $70
vblanked 			equ $7F		;Zero page address of Vblank count
SpPage 				equ $0100	
UserRam 			equ $200
SoundRam			equ $300	;include "\SrcNES\2a03_sound_engine.asm"

PPUCTRL				equ $2000	;VPHB SINN
PPUMASK				equ $2001	;BGRs bMmG
PPUSTATUS			equ $2002	;VSO- ----
OAMADDR				equ $2003
OAMDATA				equ $2004
PPUSCROLL			equ $2005
PPUADDR				equ $2006
PPUDATA				equ $2007
OAMDMA				equ $4014
APUCTRL				equ $4015
CONTROLLER1			equ $4016
CONTROLLER2			equ $4017

VRC6_PULSE1_CTRL	equ $9000
VRC6_PULSE2_CTRL 	equ $A000
SAW_ACCUM 			equ $B000
VRC6_PULSE1_FREQ_LO equ $9001
VRC6_PULSE2_FREQ_LO	equ $a001
SAW_FREQ_LO 		equ $b001
VRC6_PULSE1_FREQ_HI equ $9002
VRC6_PULSE2_FREQ_HI equ $a002
SAW_FREQ_HI 		equ $b002
IRQ_LATCH			equ $f000
IRQ_CTRL			equ $f001
IRQ_ACK				equ $f002

Bit0 equ	LookupBits+0
Bit1 equ	LookupBits+1
Bit2 equ	LookupBits+2
Bit3 equ	LookupBits+3
Bit4 equ	LookupBits+4
Bit5 equ	LookupBits+5
Bit6 equ	LookupBits+6
Bit7 equ	LookupBits+7

LookupBits: 	db %00000001,%00000010,%00000100,%00001000,%00010000,%00100000,%01000000,%10000000
LookupMaskBits: db %11111110,%11111101,%11111011,%11110111,%11101111,%11011111,%10111111,%01111111


nmihandler:				;This procuedure runs after each frame (See footer.asm)
	php
	pha     ;save registers
    txa
    pha
    tya
    pha
	
	
	
	LDA #0
	STA vblanked
	
	jsr sound_play_frame
	
	
	
	pla     ;restore registers
    tay
    pla
    tax
    pla
	plp
	rti

irqhandler:
	rti					;Do nothing

RESET:		;this section of code written by Joe Granato www.thenew8bitheroes.com
	SEI		;ignore interrupts for the reset
	LDA #$00	; load the number 00
	STA $2000	; disables NMI
	STA $2001	; disables rendering
	STA $4010	; disables DMC IRQ 
	STA $4015	; disables APU sound
	LDA #$40	; Loads the number 64
	STA $4017	; disables the APU IRQ
	CLD			; disables decimal mode 
	LDX	#$FF		
	TXS			; initializes the stack
	
;5. First vblank wait
	; what is vblank?
	; NES draws scan lines from top to bottom.  During the time it takes
	; for the light beam to move back up to the top is a waiting period
	; called vblank...it gives us time to update what is drawn to the screen.
	bit $2002
vBlankWait1:
	bit $2002
	BPL vBlankWait1
	
;6. Clear all ram 
	;LDA #$00
	LDX #$00
clrMemLoop:
	LDA #$00
	STA $0000,x
	STA $0100,x 
	;; skip 200, this is where the sprites are drawn
	;; we'll set them to $FE to draw them off screen
	STA $0300,x
	STA $0400,x
	STA $0500,x
	STA $0600,x
	STA $0700,x
	LDA #$FE		; instead of zero, write #$FE to 0200,x
	STA $0200,x		; to place sprites off screen
	INX
	BNE clrMemLoop
	
;7. Second vblank 
vBlankWait2:
	bit $2002
	BPL vBlankWait2

;8 Enable audio
	jsr sound_init

;9 Enable NMI
	LDA #%10010000	; turn on NMI, set sprites $0000, bkg to $1000
	STA $2000
	LDA #%00011110
	STA $2001
	
	LDA #$00
	STA $2005
	STA $2005
	;;DON'T TURN ON RENDERING UNTIL FIRST GRAPHICS ARE DRAWN.
	
	
	


;;;;;;;;;;;;;;;;;;;;;;;

;YOUR CODE GOES HERE
	lda #$01
	JSR sound_load

;;;;;;;;;;;;;;;;;;;;;;;

infloop:
	jmp infloop 	;prevents CPU jam while no code is present
	

	;include "\SrcNES\2a03_sound_engine_TEMPO.asm"
	include "\SrcNES\vrc6_tempo.asm"
	org $FFFA
	dw nmihandler			;FFFA - Interrupt handler
	dw RESET				;FFFC - Entry point
	dw irqhandler				;FFFE - IRQ Handler
And this is the file \SrcNES\vrc6_tempo.asm:

Code: Select all

;SOUND ENGINE CREATED BY NERDY_NIGHTS
;NOTE TABLE BY CELIUS

;SOUND RAM
sound_disable_flag 		equ $0300
sfx_playing 			equ $0301
sfx_index				equ $0302
sfx_index_vrc6 			equ $0303
sound_frame_counter		equ $0304
sound_temp1				equ	$0305
sound_temp2				equ $0306
sound_sq1_old			equ $0307
sound_sq2_old 			equ $0308
current_song			equ $0309


;CHANNEL CONSTANTS
SQUARE_1  EQU $00
SQUARE_2  EQU $01
TRIANGLE  EQU $02
NOISE 	  EQU $03
DPCM	  EQU $04
PULSE_1	  EQU $05
PULSE_2	  EQU $06
SAWTOOTH  EQU $07

;STREAM NUMBER CONSTANTS - USED TO INDEX INTO STREAM VARIABLES
MUSIC_SQ1 EQU $00
MUSIC_SQ2 EQU $01
MUSIC_TRI EQU $02
MUSIC_NOI EQU $03
MUSIC_DMC EQU $04
MUSIC_PL1 EQU $05
MUSIC_PL2 EQU $06
MUSIC_SAW EQU $07
SFX_1	  EQU $08
SFX_2	  EQU $09




;STREAM VARIABLES
stream_curr_sound 	EQU $0310     ;current song/sfx loaded
stream_status	 	EQU $031A        ;status byte.   bit0: (1: stream enabled; 0: stream disabled)
stream_channel		EQU $0324        ;what channel is this stream playing on?
stream_ptr_LO		EQU $032E         ;low byte of pointer to data stream
stream_ptr_HI		EQU $0338        ;high byte of pointer to data stream
stream_vol_duty		EQU $0342       ;stream volume/duty settings
stream_note_LO		EQU $034C       ;low 8 bits of period for the current note on a stream
stream_note_HI		EQU $0356	;high 3 bits of period for the current note on a stream 
stream_tempo		EQU	$0360
stream_ticker_total	EQU $036A	
stream_length_ctr	EQU $0374	;note length counter
stream_note_length	EQU	$037E


;APU BUFFER
soft_apu_ports		EQU $0388


soft4000			EQU $0388
soft4001			EQU $0389				
soft4002			EQU $038a				
soft4003			EQU $038b				
soft4004			EQU $038c				
soft4005			EQU $038d				
soft4006			EQU $038e				
soft4007			EQU $038f				
soft4008			EQU $0390				
soft4009			EQU $0391
soft400a			EQU $0392
soft400b			EQU $0393
soft400c			EQU $0394
soft400d			EQU $0395
soft400e			EQU $0396
soft400f			EQU $0397
soft9000			EQU $0398	;+16
soft9001			EQU $0399	;+17
soft9002			EQU $039A	;+18
softA000			EQU $039B	;+19
softA001			EQU $039C	;+20
softA002			EQU $039D	;+21
softB000			EQU $039E	;+22
softB001			EQU $039F	;+23
softB002			EQU $03A0	;+24

	include "\SrcNES\vrc6_macros.asm"		;Macros intended for use with the Konami VRC6 audio system.
	
	;VASM refused to compile the game if I used a custom macro so it went unused though the
	file was left in.
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;	
sound_init:
    lda #$0F
    sta $4015   ;enable Square 1, Square 2, Triangle and Noise channels
    
    lda #$00
    sta sound_disable_flag  ;clear disable flag
    ;later, if we have other variables we want to initialize, we will do that here.
    lda #$FF
    sta sound_sq1_old   ;initializing these to $FF ensures that the first notes of the first song isn't skipped
    sta sound_sq2_old
se_silence:
    lda #$30
    sta soft_apu_ports      ;set Square 1 volume to 0
    sta soft_apu_ports+4    ;set Square 2 volume to 0
    sta soft_apu_ports+12   ;set Noise volume to 0
    lda #$80
    sta soft_apu_ports+8     ;silence Triangle
	lda #$00
	sta soft_apu_ports+18	;silence pulse 1 vrc6
	sta soft_apu_ports+21	;silence pulse 2 vrc6
	sta soft_apu_ports+24	;silence sawtooth vrc6
    rts
    
sound_disable:
    lda #$00
    sta $4015   ;disable all channels
    lda #$01
    sta sound_disable_flag  ;set disable flag
	
	lda $9002
	and #$7f    ;turn bit 7 off, disabling channel
	sta $9002
	
	lda $a002
	and #$7f    ;turn bit 7 off, disabling channel
	sta $a002
	
	lda $b002
	and #$7f    ;turn bit 7 off, disabling channel
	sta $b002
    rts
    
;-------------------------------------
; load_sound will prepare the sound engine to play a song or sfx.
;   input:
;       A: song/sfx number to play
sound_load:
    sta sound_temp1         ;save song number
    asl a                   ;multiply by 2.  We are indexing into a table of pointers (words)
    tay
    lda song_headers, y     ;setup the pointer to our song header
    sta sound_pointer
    lda song_headers+1, y
    sta sound_pointer+1
    
    ldy #$00
    lda (sound_pointer),y      ;read the first byte: # streams
    sta sound_temp2         ;store in a temp variable.  We will use this as a loop counter: how many streams to read stream headers for
    iny
sound_load_loop:
    lda (sound_pointer),y      ;stream number
    tax                     ;stream number acts as our variable index
    iny
    
    lda (sound_pointer),y      ;status byte.  1equ enable, 0equdisable
    sta stream_status, x
    beq NextStream        ;if status byte is 0, stream disabled, so we are done
    iny
    
    lda (sound_pointer),y      ;channel number
    sta stream_channel, x
    iny
    
    lda (sound_pointer),y      ;initial duty and volume settings
    sta stream_vol_duty, x
    iny
    
    lda (sound_pointer),y      ;pointer to stream data.  Little endian, so low byte first
    sta stream_ptr_LO, x
    iny
    
    lda (sound_pointer),y
    sta stream_ptr_HI, x
    iny
    
    lda (sound_pointer),y
    sta stream_tempo, x
    
    lda #$A0
    sta stream_ticker_total, x
    
    lda #$01
    sta stream_length_ctr,x
NextStream:
    iny
    
    lda sound_temp1         ;song number
    sta stream_curr_sound, x
    
    dec sound_temp2         ;our loop counter
    bne sound_load_loop
    rts

;--------------------------
; sound_play_frame advances the sound engine by one frame
sound_play_frame:
    lda sound_disable_flag
    bne doneSPF   ;if disable flag is set, don't advance a frame

    jsr se_silence  ;silence all channels.  se_set_apu will set volume later for all channels that are enabled.
                    ;the purpose of this subroutine call is to silence channels that aren't used by any streams.
    
    ldx #$00
sound_play_frame_loop:
    lda stream_status, x
    and #$01    ;check whether the stream is active
    beq exit_SPF_loop  ;if the stream isn't active, skip it
    
    ;add the tempo to the ticker total.  If there is a FF-> 0 transition, there is a tick
    lda stream_ticker_total, x
    clc
    adc stream_tempo, x
    sta stream_ticker_total, x
    bcc SetBuffer    ;carry clear equ no tick.  if no tick, we are done with this stream
    
    dec stream_length_ctr, x   ;else there is a tick. decrement the note length counter
    bne SetBuffer    ;if counter is non-zero, our note isn't finished playing yet
    lda stream_note_length, x   ;else our note is finished. reload the note length counter
    sta stream_length_ctr, x
    
    jsr se_fetch_byte   ;read the next byte from the data stream
    
SetBuffer:
    jsr se_set_temp_ports   ;copy the current stream's sound data for the current frame into our temporary APU vars (soft_apu_ports)
exit_SPF_loop:
    inx
    cpx #$0A
    bne exit_SPF_loop
    jsr se_set_apu      ;copy the temporary APU variables (soft_apu_ports) to the real APU ports ($4000, $4001, etc)
doneSPF:
    rts

;--------------------------
; se_fetch_byte reads one byte from a sound data stream and handles it
;   input: 
;       X: stream number    
se_fetch_byte:
    lda stream_ptr_LO, x
    sta sound_pointer
    lda stream_ptr_HI, x
    sta sound_pointer+1
    
    ldy #$00
goFetch:
    lda (sound_pointer),y
    bpl PlayNote                ;if < #$80, it's a Note
    cmp #$A0
    bcc NoteLength         ;else if < #$A0, it's a Note Length
sefb_opcode:                     ;else it's an opcode
    ;do Opcode stuff
    cmp #$FF
    bne end_fetchbyte
    lda stream_status, x    ;if $FF, end of stream, so disable it and silence
    and #%11111110
    sta stream_status, x    ;clear enable flag in status byte
    
    lda stream_channel, x
    cmp #TRIANGLE
    beq sefb_silence_tri        ;triangle is silenced differently from squares and noise
    lda #$30                ;squares and noise silenced with #$30
    bne sefb_silence_channel
sefb_silence_tri:
    lda #$80                ;triangle silenced with #$80
sefb_silence_channel:
    sta stream_vol_duty, x  ;store silence value in the stream's volume variable.
    jmp sefb_UpdatePointer     ;done
NoteLength:
    ;do note length stuff
    and #%01111111          ;chop off bit7
    sty sound_temp1         ;save Y because we are about to destroy it
    tay
    lda note_length_table, y    ;get the note length count value
    sta stream_note_length, x
    sta stream_length_ctr, x   ;stick it in our note length counter
    ldy sound_temp1         ;restore Y
    iny                     ;set index to next byte in the stream
    jmp goFetch              ;fetch another byte
PlayNote:
    ;do Note stuff
    sty sound_temp1     ;save our index into the data stream
    asl a
    tay
    lda note_table, y
    sta stream_note_LO, x
    lda note_table+1, y
    sta stream_note_HI, x
    ldy sound_temp1     ;restore data stream index

    ;check if it's a rest and modify the status flag appropriately
    jsr se_check_rest    
sefb_UpdatePointer:
    iny
    tya
    clc
    adc stream_ptr_LO, x
    sta stream_ptr_LO, x
    bcc end_fetchbyte
    inc stream_ptr_HI, x
end_fetchbyte:
    rts

;--------------------------------------------------
; se_check_rest will read a byte from the data stream and
;       determine if it is a rest or not.  It will set or clear the current
;       stream's rest flag accordingly.
;       input:
;           X: stream number
;           Y: data stream index
se_check_rest:
    lda (sound_pointer),y  ;read the note byte again
    cmp #rest
    bne isNotRest
    lda stream_status, x
    ora #%00000010  ;set the rest bit in the status byte
    bne Store  ;this will always branch.  bne is cheaper than a jmp.
isNotRest:
    lda stream_status, x
    and #%11111101  ;clear the rest bit in the status byte
Store:
    sta stream_status, x
    rts
    
;----------------------------------------------------
; se_set_temp_ports will copy a stream's sound data to the temporary apu variables
;      input:
;           X: stream number
se_set_temp_ports:
    lda stream_channel, x
	cmp #PULSE_1
	beq handlePulse1
	cmp #PULSE_2
	beq handlePulse2
	cmp #SAWTOOTH
	beq handleSawtooth
	jmp sstp_notVRC6
handlePulse1:
	lda stream_vol_duty,x
	sta soft9000
	lda stream_note_LO
	sta soft9001
	lda stream_note_HI
	ora #%10000000
	sta soft9002
	JMP StreamStatusCheck
handlePulse2:
	lda stream_vol_duty,x
	sta softA000
	lda stream_note_LO
	sta softA001
	lda stream_note_HI
	ora #%10000000
	sta softA002
	JMP StreamStatusCheck
handleSawtooth:
	lda stream_vol_duty,x
	sta softB000
	lda stream_note_LO
	sta softB001
	lda stream_note_HI
	ora #%10000000
	sta softB002
	JMP StreamStatusCheck

StreamStatusCheck:
	lda stream_status, x
    and #%00000010
    beq done_SSTP       ;if clear, no rest, so quit
	
sstp_notVRC6:
    asl a
    asl a
    tay
    
    lda stream_vol_duty, x
    sta soft_apu_ports, y       ;vol

	
    lda #$08
    sta soft_apu_ports+1, y     ;sweep
    
    lda stream_note_LO, x
    sta soft_apu_ports+2, y     ;period LO

	
    lda stream_note_HI, x
    sta soft_apu_ports+3, y     ;period HI
    

    ;check the rest flag. if set, overwrite volume with silence value 
    lda stream_status, x
    and #%00000010
    beq done_SSTP       ;if clear, no rest, so quit
    lda stream_channel, x
    cmp #TRIANGLE   ;if triangle, silence with #$80
    beq isTriangle       ;else, silence with #$30
    lda #$30        
    bne Store2		;always branches, uses fewer bytes than a jump
isTriangle:
    lda #$80
Store2:    
    sta soft_apu_ports, y
done_SSTP:
    rts    

;--------------------------
; se_set_apu copies the temporary RAM ports to the APU ports
se_set_apu:
ssapu_square1:
    lda soft_apu_ports+0
    sta $4000
    lda soft_apu_ports+1
    sta $4001
    lda soft_apu_ports+2
    sta $4002
    lda soft_apu_ports+3
    cmp sound_sq1_old       ;compare to last write
    beq ssapu_square2            ;don't write this frame if they were equal
    sta $4003
    sta sound_sq1_old       ;save the value we just wrote to $4003
ssapu_square2:
    lda soft_apu_ports+4
    sta $4004
    lda soft_apu_ports+5
    sta $4005
    lda soft_apu_ports+6
    sta $4006
    lda soft_apu_ports+7
    cmp sound_sq2_old
    beq ssapu_triangle
    sta $4007
    sta sound_sq2_old       ;save the value we just wrote to $4007
ssapu_triangle:
    lda soft_apu_ports+8
    sta $4008
    lda soft_apu_ports+10   ;there is no $4009, so we skip it
    sta $400A
    lda soft_apu_ports+11
    sta $400B
ssapu_noise:
    lda soft_apu_ports+12
    sta $400C
    lda soft_apu_ports+14   ;there is no $400D, so we skip it
    sta $400E
    lda soft_apu_ports+15
    sta $400F
    rts
ssapu_pulse1:
	lda soft9000
	sta $9000
	lda soft9001
	sta $9001
	lda soft9002
	sta $9002
	rts
ssapu_pulse2:
	lda softA000
	sta $a000
	lda softA001
	sta $a001
	lda softA002
	sta $a002
	rts
ssapu_saw:
	lda softB000
	sta $b000
	lda softB001
	sta $b001
	lda softB002
	sta $b002
	rts
	
    
NUM_SONGS equ $06 ;if you add a new song, change this number.    
                ;headers.asm checks this number in its song_up and song_down subroutines
                ;to determine when to wrap around.

;this is our pointer table.  Each entry is a pointer to a song header                
song_headers:
    dw song0_header  ;this is a silence song.  See song0.i for more details
    dw song1_header  ;evil, demented notes
    dw song2_header  ;a sound effect.  Try playing it over the other songs.
    dw song3_header  ;a little chord progression.
    dw song4_header  ;a new song taking advantage of note lengths and rests
    dw song5_header  ;another sound effect played at a very fast tempo.
    
    include "note_table_tempo.i" ;period lookup table for notes
    include "note_length_table_tempo.i"
    include "song0_tempo.i"  ;holds the data for song 0 (header and data streams)
    include "song1_tempo.i"  ;holds the data for song 1
    include "song2_tempo.i"
    include "song3_TEST.i"
    include "song4_tempo.i"
    include "song5_tempo.i"
At this point in the tutorial the code is very long and convoluted so it's becoming incredibly difficult to spot where the code breaks down. In addition, attempting to run this cart on Mesen results in a dark green screen and no audio at all (instead of a black screen and 2A03 audio on Nestopia)

Post Reply

Return to “Nintendo Entertainment System / Famicom Assembly Programming”