demo: dni counting

This commit is contained in:
Vince Weaver 2024-06-19 10:23:20 -04:00
parent b99c902f55
commit 39dfe21ba3
19 changed files with 4554 additions and 190 deletions

View File

@ -5,23 +5,35 @@ B2D = ../../utils/bmp2dhr/b2d
PNG_TO_40x48D = ../../utils/gr-utils/png_to_40x48d
PNG_TO_40x96 = ../../utils/gr-utils/png_to_40x96
TOKENIZE = ../../utils/asoft_basic-utils/tokenize_asoft
LINKERSCRIPTS = ../../linker_scripts/
EMPTY = ../../empty_disk/
all: numbers.dsk
numbers.dsk: HELLO NUMBERS
numbers.dsk: HELLO NUMBERS PLASMA
cp $(EMPTY)/empty.dsk numbers.dsk
$(DOS33) -y numbers.dsk SAVE A HELLO
$(DOS33) -y numbers.dsk BSAVE -a 0x2000 NUMBERS
$(DOS33) -y numbers.dsk BSAVE -a 0x4000 PLASMA
###
PLASMA: plasma.o
ld65 -o PLASMA plasma.o -C $(LINKERSCRIPTS)/apple2_4000.inc
plasma.o: plasma.s \
zp.inc hardware.inc
ca65 -o plasma.o plasma.s -l plasma.lst
####
NUMBERS: numbers.o
ld65 -o NUMBERS numbers.o -C ../../linker_scripts/apple2_2000.inc
ld65 -o NUMBERS numbers.o -C $(LINKERSCRIPTS)/apple2_2000.inc
numbers.o: numbers.s \
print_dni_numbers.s \
zp.inc hardware.inc number_sprites.inc
ca65 -o numbers.o numbers.s -l numbers.lst

View File

@ -36,6 +36,7 @@ PTRIG = $C070
;; BASIC ROUTINES
NORMAL = $F273
HGR = $F3E2
;; MONITOR ROUTINES
@ -43,6 +44,7 @@ HLINE = $F819 ;; HLINE Y,$2C at A
VLINE = $F828 ;; VLINE A,$2D at Y
CLRSCR = $F832 ;; Clear low-res screen
CLRTOP = $F836 ;; clear only top of low-res screen
GBASCALC= $F847 ;; take Y-coord/2 in A, put address in GBASL/H ( a trashed, C clear)
SETCOL = $F864 ;; COLOR=A
ROM_TEXT2COPY = $F962 ;; iigs
TEXT = $FB36

View File

@ -1,2 +1,3 @@
5 HOME
120 PRINT CHR$(4);"BRUN NUMBERS"
100 PRINT CHR$(4);"CATALOG"
120 PRINT CHR$(4);"BRUN PLASMA"

43
demos/dni/inc_base5.s Normal file
View File

@ -0,0 +1,43 @@
; four-digit base 5 increment
inc_base5:
inc NUMBER_LOW
lda NUMBER_LOW
and #$f
cmp #5
bne inc_base5_done
clc
lda NUMBER_LOW
adc #$b
sta NUMBER_LOW
lda NUMBER_LOW
cmp #$50
bne inc_base5_done
; if here, overflow to top byte
lda #0
sta NUMBER_LOW
inc NUMBER_HIGH
lda NUMBER_HIGH
and #$f
cmp #5
bne inc_base5_done
clc
lda NUMBER_HIGH
adc #$b
sta NUMBER_HIGH
lda NUMBER_HIGH
cmp #$50
bne inc_base5_done
lda #$0
sta NUMBER_HIGH
inc_base5_done:
rts

View File

@ -0,0 +1,87 @@
;================================
;================================
; mockingboard interrupt handler
;================================
;================================
; On Apple II/6502 the interrupt handler jumps to address in 0xfffe
; This is in the ROM, which saves the registers
; on older IIe it saved A to $45 (which could mess with DISK II)
; newer IIe doesn't do that.
; It then calculates if it is a BRK or not (which trashes A)
; Then it sets up the stack like an interrupt and calls 0x3fe
; Note: the IIc is much more complicated
; its firmware tries to decode the proper source
; based on various things, including screen hole values
; we bypass that by switching out ROM and replacing the
; $fffe vector with this, but that does mean we have
; to be sure status flag and accumulator set properly
interrupt_handler:
php ; save status flags
cld ; clear decimal mode
pha ; save A ; 3
; A is saved in $45 by firmware
txa
pha ; save X
tya
pha ; save Y
; inc $0404 ; debug (flashes char onscreen)
.include "pt3_lib_irq_handler.s"
jmp exit_interrupt
;=================================
; Finally done with this interrupt
;=================================
quiet_exit:
stx DONE_PLAYING
jsr clear_ay_both
ldx #$ff ; also mute the channel
stx AY_REGISTERS+7 ; just in case
exit_interrupt:
pla
tay ; restore Y
pla
tax ; restore X
pla ; restore a ; 4
; on II+/IIe (but not IIc) we need to do this?
interrupt_smc:
lda $45 ; restore A
plp
rti ; return from interrupt ; 6
;============
; typical
; ???? cycles
;=============================
; Disable Interrupt
;=============================
; disables all the 6522 timer interrupts
mockingboard_disable_interrupt:
sei ; disable interrupts just in case
lda #$40 ; Continuous interrupts, don't touch PB7
disable_irq_smc1:
sta MOCK_6522_ACR ; ACR register
lda #$7F ; clear all interrupt flags
disable_irq_smc2:
sta MOCK_6522_IER ; IER register (interrupt enable)
rts

BIN
demos/dni/mA2E_3.pt3 Normal file

Binary file not shown.

View File

@ -82,188 +82,8 @@ base5_inc_done:
jmp number_loop
;=====================
draw_full_dni_number:
; ldx #1
; stx LEADING_ZERO
lda NUMBER_HIGH
beq draw_only_low_dni_number
; drawing high number
; ldx #0
; stx LEADING_ZERO
jsr draw_dni_number
; adjust for right number
lda #14
bne draw_low_dni_number ; bra
draw_only_low_dni_number:
lda #7
draw_low_dni_number:
clc
adc XPOS
sta XPOS
lda NUMBER_LOW
;=====================
; number in A
draw_dni_number:
sta DRAW_NUMBER
; draw frame
lda #<frame_sprite
sta INL
lda #>frame_sprite
sta INH
jsr put_number_sprite
; adjust to be inside frame
inc YPOS
inc XPOS
inc XPOS
inc XPOS
; draw ones values
lda DRAW_NUMBER
bne regular_number
; lda LEADING_ZERO ; if 0 then regular
; beq regular_number
; if all zeros, then draw special zero char
lda #<zero_sprite
sta INL
lda #>zero_sprite
jmp finally_draw
regular_number:
and #$f
tax
lda ones_sprites_l,X
sta INL
lda ones_sprites_h,X
finally_draw:
sta INH
jsr put_number_sprite
lda DRAW_NUMBER
lsr
lsr
lsr
lsr
tax
lda fives_sprite_l,X
sta INL
lda fives_sprite_h,X
sta INH
jsr put_number_sprite
; restore
dec YPOS
dec XPOS
dec XPOS
dec XPOS
rts
;=====================
put_number_sprite:
ldy #0
lda (INL),Y
sta pns_xsize_smc+1
iny
lda (INL),Y
sta pns_ysize_smc+1
iny
lda #0
sta SPRITEY
pns_yloop:
lda SPRITEY
clc
adc YPOS
asl
tax
lda gr_offsets,X
; clc
adc XPOS
sta pns_out_smc+1
lda gr_offsets+1,X
; clc
adc DRAW_PAGE
sta pns_out_smc+2
lda #0
sta SPRITEX
pns_xloop:
ldx #8 ; rotate through 8 bits
lda (INL),Y
sta COLOR
pns_inner_loop:
asl COLOR
bcc pns_transparent
lda #$FF
pns_out_smc:
sta $400
pns_transparent:
inc pns_out_smc+1
dex
bne pns_inner_loop
iny
inc SPRITEX
lda SPRITEX
pns_xsize_smc:
cmp #3
bne pns_xloop
inc SPRITEY
pns_ysize_smc:
cpy #39
bcc pns_yloop ; blt
rts
ones_sprites_l:
.byte <empty_sprite,<one_sprite,<two_sprite,<three_sprite,<four_sprite
ones_sprites_h:
.byte >empty_sprite,>one_sprite,>two_sprite,>three_sprite,>four_sprite
fives_sprite_l:
.byte <empty_sprite,<five_sprite,<ten_sprite,<fifteen_sprite,<twenty_sprite
fives_sprite_h:
.byte >empty_sprite,>five_sprite,>ten_sprite,>fifteen_sprite,>twenty_sprite
.include "print_dni_numbers.s"
.include "number_sprites.inc"

21
demos/dni/page_flip.s Normal file
View File

@ -0,0 +1,21 @@
;==========
; flip page
;==========
flip_page:
lda DRAW_PAGE
beq draw_page2
draw_page1:
bit PAGE2
lda #0
beq done_flip
draw_page2:
bit PAGE1
lda #$4
done_flip:
sta DRAW_PAGE
rts

610
demos/dni/plasma.s Normal file
View File

@ -0,0 +1,610 @@
; Plasma D'ni Numbers
; by Vince `deater` Weaver / Dsr
; originally based on Plasmagoria (GPL3) code by French Touch
.include "hardware.inc"
.include "zp.inc"
lores_colors_fine=$8000
;tracker_song = peasant_song
;======================================
; start of code
;======================================
plasma_mask:
jsr HGR ; have table gen appear on hgr page1
;=================
; init music
PT3_LOC = song
PT3_ENABLE_APPLE_IIC = 1
lda #1
sta LOOP
lda #0
sta DONE_PLAYING
sta FRAMEL
sta WHICH_TRACK
.ifdef PT3_ENABLE_APPLE_IIC
jsr detect_appleii_model
.endif
;=======================
; Detect mockingboard
;========================
; jsr print_mockingboard_detect ; print message
jsr mockingboard_detect ; call detection routine
bcs mockingboard_found
; jsr print_mocking_notfound
; possibly can't detect on IIc so just try with slot#4 anyway
; even if not detected
jmp setup_interrupt
mockingboard_found:
; print found message
; modify message to print slot value
; lda MB_ADDR_H
; sec
; sbc #$10
; sta found_message+11
; jsr print_mocking_found
;==================================================
; patch the playing code with the proper slot value
;==================================================
jsr mockingboard_patch
setup_interrupt:
;=======================
; Set up 50Hz interrupt
;========================
jsr mockingboard_init
jsr mockingboard_setup_interrupt
;============================
; Init the Mockingboard
;============================
jsr reset_ay_both
jsr clear_ay_both
;==================
; init song
;==================
jsr pt3_init_song
;============================
; Enable 6502 interrupts
;============================
start_interrupts:
cli ; clear interrupt mask
; cli ; start music
bit LORES ; set lo-res
bit FULLGR
lda #0
sta DRAW_PAGE
lda #$00
sta NUMBER_HIGH
lda #$00
sta NUMBER_LOW
goopy:
lda #$4
clc
adc DRAW_PAGE
tax
lda #$0 ; black
jsr clear_1k
lda #$4
sta XPOS
lda #$5
sta YPOS
jsr draw_full_dni_number
jsr inc_base5
jsr flip_page
lda #200
jsr WAIT
lda NUMBER_HIGH
cmp #$02
beq next_scene
jmp goopy
next_scene:
lda #$0
sta DRAW_PAGE
bit PAGE1
ldx #$20
lda #$FF ; white
jsr clear_1k
; ============================================================================
; init lores colors (inline)
; ============================================================================
lda #<lores_colors_fine
sta INL
lda #>lores_colors_fine
sta INH
multiple_init_lores_colors:
init_lores_colors:
ldx #0
ldy #0
init_lores_colors_loop:
lcl_smc1:
lda lores_colors_lookup,X
sta (INL),Y
iny
sta (INL),Y
iny
sta (INL),Y
iny
sta (INL),Y
iny
beq done_init_lores_colors
inx
txa
and #$f
tax
jmp init_lores_colors_loop
done_init_lores_colors:
lda lcl_smc1+1
clc
adc #$10
sta lcl_smc1+1
inc INH
lda INH
cmp #$84
bne multiple_init_lores_colors
;====================================
; do plasma
;====================================
do_plasma:
; init
BP3:
;=============================
; adjust color palette
; lda WHICH_TRACK
; clc
; adc #$80
; sta display_lookup_smc+2
; ============================================================================
; Precalculate some values (inlined)
; ============================================================================
precalc:
lda PARAM1 ; self modify various parts
sta pc_off1+1
lda PARAM2
sta pc_off2+1
lda PARAM3
sta pc_off3+1
lda PARAM4
sta pc_off4+1
; Table1(X) = sin1(PARAM1+X)+sin2(PARAM1+X)
; Table2(X) = sin3(PARAM3+X)+sin1(PARAM4+X)
ldx #$28 ; 40
pc_b1:
pc_off1:
lda sin1
pc_off2:
adc sin2
sta Table1,X
pc_off3:
lda sin3
pc_off4:
adc sin1
sta Table2,X
inc pc_off1+1
inc pc_off2+1
inc pc_off3+1
inc pc_off4+1
dex
bpl pc_b1
inc PARAM1
inc PARAM1
dec PARAM2
inc PARAM3
dec PARAM4
; ============================================================================
; Display Routines
; ============================================================================
display_normal:
ldx #23 ; lines 0-23 lignes 0-23
display_line_loop:
txa
jsr GBASCALC
; set up pointer for mask
ldy WHICH_TRACK ; CURRENT_EFFECT
lda GBASL
sta INL
lda GBASH
clc
adc #$1c ; load from $2000
; adc graphics_loc,Y
sta INH
lda GBASH
clc
adc DRAW_PAGE
sta GBASH
ldy #39 ; col 0-39
lda Table2,X ; setup base sine value for row
sta display_row_sin_smc+1
display_col_loop:
lda Table1,Y ; load in column sine value
display_row_sin_smc:
adc #00 ; add in row value
; MASKING happens HERE
and (INL),Y
sta display_lookup_smc+1 ; patch in low byte of lookup
display_lookup_smc:
lda lores_colors_fine ; attention: must be aligned
sta (GBASL),Y
dey
bpl display_col_loop
dex
bpl display_line_loop
; ============================================================================
lda #4
sta XPOS
lda #5
sta YPOS
lda NUMBER_HIGH
and #$3
clc
adc #$80
sta display_lookup_smc+2
lda NUMBER_HIGH
and #$f
cmp #0
beq effect3
cmp #1
beq effect4
cmp #2
beq effect0
cmp #3
beq effect1
cmp #4
beq effect2
effect2:
ldx #$20
lda #$00 ; black
sta SIN_COUNT
jsr clear_1k
lda DRAW_PAGE
pha
lda #$1c
sta DRAW_PAGE
jsr draw_full_dni_number
pla
sta DRAW_PAGE
ldx #$20
jsr invert_1k
inc FRAMEL
lda FRAMEL
and #$3
bne no_inc_effect2
jsr inc_base5
no_inc_effect2:
jmp done_effect
effect0:
; full mask, so full plasma
ldx #$20
lda #$FF ; white
jsr clear_1k
; overlay with number
jsr draw_full_dni_number
; increment each 8th frame
inc FRAMEL
lda FRAMEL
and #$3
bne no_inc_effect0
jsr inc_base5
no_inc_effect0:
jmp done_effect
effect3:
ldx SIN_COUNT
lda sine_table,X
sta YPOS
effect4:
effect1:
ldx #$20
lda #$0 ; black
jsr clear_1k
lda DRAW_PAGE
pha
lda #$1c
sta DRAW_PAGE
jsr draw_full_dni_number
pla
sta DRAW_PAGE
inc SIN_COUNT
lda SIN_COUNT
cmp #25
bne sin_ok
lda #0
sta SIN_COUNT
sin_ok:
inc FRAMEL
lda FRAMEL
and #$3
bne no_inc_effect1
jsr inc_base5
no_inc_effect1:
done_effect:
jsr flip_page
inc COMPT1
beq zoop
; bne BP3
jmp BP3
zoop:
dec COMPT2
beq zoop2
; bne BP3
jmp BP3
zoop2:
; beq do_plasma ; bra
jmp do_plasma ; bra
.align $100
lores_colors_lookup:
; dark
.byte $00,$88,$55,$99,$ff,$bb,$33,$22,$66,$77,$44,$cc,$ee,$dd,$99,$11
; pink
.byte $00,$11,$33,$BB,$FF,$BB,$33,$11,$00,$11,$33,$BB,$FF,$BB,$33,$11
; blue
.byte $00,$22,$66,$77,$FF,$77,$66,$22,$00,$22,$66,$77,$FF,$77,$66,$22
; green
.byte $00,$44,$CC,$DD,$FF,$DD,$CC,$44,$00,$44,$CC,$DD,$FF,$DD,$CC,$44
;.include "make_tables.s"
;.include "interrupt_handler.s"
;.include "mockingboard_constants.s"
;graphics_loc:
; .byte >dsr_empty-4,>dsr_small-4,>dsr_big-4,>dsr_big2-4
.align $100
sin1:
.incbin "tables"
sin2=sin1+$100
sin3=sin1+$200
; graphics
;dsr_empty:
;.incbin "graphics/dsr_empty.gr"
;dsr_small:
;.incbin "graphics/dsr_small.gr"
;dsr_big:
;.incbin "graphics/dsr_big.gr"
;dsr_big2:
;.incbin "graphics/dsr_big2.gr"
; music
;.include "mA2E_2.s"
.include "print_dni_numbers.s"
.include "number_sprites.inc"
.include "gr_offsets.s"
.include "inc_base5.s"
.include "page_flip.s"
.ifdef PT3_ENABLE_APPLE_IIC
.include "pt3_lib_detect_model.s"
.endif
.include "pt3_lib_core.s"
.include "pt3_lib_init.s"
.include "pt3_lib_mockingboard_setup.s"
.include "interrupt_handler.s"
; if you're self patching, detect has to be after interrupt_handler.s
.include "pt3_lib_mockingboard_detect.s"
;======================
;
;======================
; X = page
; A = value
clear_1k:
stx OUTH
ldx #0
stx OUTL
ldx #4
; lda #0
ldy #0
inner_loop:
sta (OUTL),Y
iny
bne inner_loop
inc OUTH
dex
bne inner_loop
rts
;======================
;
;======================
; X = page
invert_1k:
stx OUTH
ldx #0
stx OUTL
ldx #4
ldy #0
invert_inner_loop:
lda (OUTL),Y
eor #$FF
sta (OUTL),Y
iny
bne invert_inner_loop
inc OUTH
dex
bne invert_inner_loop
rts
sine_table:
.byte 5,6,7,8,9
.byte 10,10,10,10,9
.byte 8,7,6,5,4
.byte 3,2,1,0,0
.byte 0,1,2,3,4
.align $100
song:
.incbin "mA2E_3.pt3"

View File

@ -0,0 +1,180 @@
;=====================
draw_full_dni_number:
lda NUMBER_HIGH
beq draw_only_low_dni_number
; drawing high number
jsr draw_dni_number
; adjust for right number
lda #14
bne draw_low_dni_number ; bra
draw_only_low_dni_number:
lda #7
draw_low_dni_number:
clc
adc XPOS
sta XPOS
lda NUMBER_LOW
;=====================
; number in A
draw_dni_number:
sta DRAW_NUMBER
; draw frame
lda #<frame_sprite
sta INL
lda #>frame_sprite
sta INH
jsr put_number_sprite
; adjust to be inside frame
inc YPOS
inc XPOS
inc XPOS
inc XPOS
; draw ones values
lda DRAW_NUMBER
bne regular_number
; lda LEADING_ZERO ; if 0 then regular
; beq regular_number
; if all zeros, then draw special zero char
lda #<zero_sprite
sta INL
lda #>zero_sprite
jmp finally_draw
regular_number:
and #$f
tax
lda ones_sprites_l,X
sta INL
lda ones_sprites_h,X
finally_draw:
sta INH
jsr put_number_sprite
lda DRAW_NUMBER
lsr
lsr
lsr
lsr
tax
lda fives_sprite_l,X
sta INL
lda fives_sprite_h,X
sta INH
jsr put_number_sprite
; restore
dec YPOS
dec XPOS
dec XPOS
dec XPOS
rts
;=====================
put_number_sprite:
ldy #0
lda (INL),Y
sta pns_xsize_smc+1
iny
lda (INL),Y
sta pns_ysize_smc+1
iny
lda #0
sta SPRITEY
pns_yloop:
lda SPRITEY
clc
adc YPOS
asl
tax
lda gr_offsets,X
; clc
adc XPOS
sta pns_out_smc+1
lda gr_offsets+1,X
; clc
adc DRAW_PAGE
sta pns_out_smc+2
lda #0
sta SPRITEX
pns_xloop:
ldx #8 ; rotate through 8 bits
lda (INL),Y
sta COLOR
pns_inner_loop:
asl COLOR
bcc pns_transparent
lda #$FF
pns_out_smc:
sta $400
pns_transparent:
inc pns_out_smc+1
dex
bne pns_inner_loop
iny
inc SPRITEX
lda SPRITEX
pns_xsize_smc:
cmp #3
bne pns_xloop
inc SPRITEY
pns_ysize_smc:
cpy #39
bcc pns_yloop ; blt
rts
ones_sprites_l:
.byte <empty_sprite,<one_sprite,<two_sprite,<three_sprite,<four_sprite
ones_sprites_h:
.byte >empty_sprite,>one_sprite,>two_sprite,>three_sprite,>four_sprite
fives_sprite_l:
.byte <empty_sprite,<five_sprite,<ten_sprite,<fifteen_sprite,<twenty_sprite
fives_sprite_h:
.byte >empty_sprite,>five_sprite,>ten_sprite,>fifteen_sprite,>twenty_sprite

2076
demos/dni/pt3_lib_core.s Normal file

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,98 @@
;===========================
; Check Apple II model
;===========================
; this is mostly for IIc and IIgs support
; as they do interrupts differently
; some of this info from the document:
; Apple II Family Identification Routines 2.2
;
; note the more obscure are not well tested
; Returns one of the following in A
; ' ' = Apple II
; '+' = Apple II+
; 'e' = Apple IIe
; 'c' = Apple IIc
; 'g' = Apple IIgs
; 'm' = mac L/C with board
; 'j' = jplus
; '3' = Apple III
detect_appleii_model:
lda #' '
ldx $FBB3
; II is $38
; J-plus is $C9
; II+ is $EA (so is III)
; IIe and newer is $06
cpx #$38 ; ii
beq done_apple_detect
; ii+ is EA FB1E=AD
; iii is EA FB1E=8A 00
cpx #$EA
bne not_ii_iii
ii_or_iii:
lda #'+' ; ii+/iii
ldx $FB1E
cpx #$AD
beq done_apple_detect ; ii+
lda #'3'
bne done_apple_detect ; bra iii
not_ii_iii:
lda #'j' ; jplus
cpx #$C9
beq done_apple_detect
cpx #$06
bne done_apple_detect
apple_iie_or_newer:
ldx $FBC0 ; $EA on a IIe
; $E0 on a IIe enhanced
; $00 on a IIc/IIc+
; $FE1F = $60, IIgs
beq apple_iic
lda #'e'
cpx #$EA
beq done_apple_detect
; cpx #$E0
; beq done_apple_detect
; should do something if not $E0
; GS and IIe enhanced are the same, need to check
sec ; set carry
jsr $FE1F
bcs done_apple_detect ;If carry then IIe enhanced
; get here we're a IIgs?
lda #'g'
bne done_apple_detect
apple_iic:
lda #'c'
done_apple_detect:
sta APPLEII_MODEL
rts

575
demos/dni/pt3_lib_init.s Normal file
View File

@ -0,0 +1,575 @@
; pt3_lib_init.s
; Initialize a song
; this is done before song starts playing so it is not
; as performance / timing critical
;====================================
; pt3_init_song
;====================================
;
pt3_init_song:
lda #$0
sta DONE_SONG ; 3
ldx #(end_vars-begin_vars)
zero_song_structs_loop:
dex
sta note_a,X
bne zero_song_structs_loop
sta pt3_noise_period_smc+1 ; 4
sta pt3_noise_add_smc+1 ; 4
sta pt3_envelope_period_l_smc+1 ; 4
sta pt3_envelope_period_h_smc+1 ; 4
sta pt3_envelope_slide_l_smc+1 ; 4
sta pt3_envelope_slide_h_smc+1 ; 4
sta pt3_envelope_slide_add_l_smc+1 ; 4
sta pt3_envelope_slide_add_h_smc+1 ; 4
sta pt3_envelope_add_smc+1 ; 4
sta pt3_envelope_type_smc+1 ; 4
sta pt3_envelope_type_old_smc+1 ; 4
sta pt3_envelope_delay_smc+1 ; 4
sta pt3_envelope_delay_orig_smc+1 ; 4
sta PT3_MIXER_VAL ; 3
sta current_pattern_smc+1 ; 4
sta current_line_smc+1 ; 4
sta current_subframe_smc+1 ; 4
lda #$f ; 2
sta note_a+NOTE_VOLUME ; 4
sta note_b+NOTE_VOLUME ; 4
sta note_c+NOTE_VOLUME ; 4
; default ornament/sample in A
; X is zero coming in here
;ldx #(NOTE_STRUCT_SIZE*0) ; 2
jsr load_ornament0_sample1 ; 6+93
; default ornament/sample in B
ldx #(NOTE_STRUCT_SIZE*1) ; 2
jsr load_ornament0_sample1 ; 6+93
; default ornament/sample in C
ldx #(NOTE_STRUCT_SIZE*2) ; 2
jsr load_ornament0_sample1 ; 6+93
;=======================
; load default speed
lda PT3_LOC+PT3_SPEED ; 4
sta pt3_speed_smc+1 ; 4
;=======================
; load loop
lda PT3_LOC+PT3_LOOP ; 4
sta pt3_loop_smc+1 ; 4
;========================
;========================
; set up note/freq table
; this saves some space and makes things marginally faster longrun
;========================
;========================
; note (heh) that there are separate tables if version 3.3
; but we are going to assume we are only going to be playing
; newer 3.4+ version files so only need the newer tables
ldx PT3_LOC+PT3_HEADER_FREQUENCY ; 4
beq use_freq_table_0
dex
beq use_freq_table_1
dex
beq use_freq_table_2
; fallthrough (freq table 3)
use_freq_table_3:
;=================================================
; Create Table #3, v4+, "PT3NoteTable_REAL_34_35"
;=================================================
ldy #11 ; !2
freq_table_3_copy_loop:
; note, high lookup almost same as 2v4, just need to adjust one value
lda base2_v4_high,Y ; !3
sta NoteTable_high,Y ; !3
lda base3_low,Y ; !3
sta NoteTable_low,Y ; !3
dey ; !1
bpl freq_table_3_copy_loop ; !2
dec NoteTable_high ; adjust to right value
jsr NoteTablePropogate ; !3
lda #<table3_v4_adjust
sta note_table_adjust_smc+1
lda #>table3_v4_adjust
sta note_table_adjust_smc+2
jsr NoteTableAdjust
jmp done_set_freq_table
use_freq_table_2:
;=================================================
; Create Table #2, v4+, "PT3NoteTable_ASM_34_35"
;=================================================
ldy #11
freq_table_2_copy_loop:
lda base2_v4_high,Y
sta NoteTable_high,Y
lda base2_v4_low,Y
sta NoteTable_low,Y
dey
bpl freq_table_2_copy_loop
jsr NoteTablePropogate ; !3
lda #<table2_v4_adjust
sta note_table_adjust_smc+1
lda #>table2_v4_adjust
sta note_table_adjust_smc+2
jsr NoteTableAdjust
jmp done_set_freq_table
use_freq_table_1:
;=================================================
; Create Table #1, "PT3NoteTable_ST"
;=================================================
ldy #11
freq_table_1_copy_loop:
lda base1_high,Y
sta NoteTable_high,Y
lda base1_low,Y
sta NoteTable_low,Y
dey
bpl freq_table_1_copy_loop
jsr NoteTablePropogate ; !3
; last adjustments
lda #$FD ; Tone[23]=$3FD
sta NoteTable_low+23
dec NoteTable_low+46 ; Tone[46]-=1;
jmp done_set_freq_table
use_freq_table_0:
;=================================================
; Create Table #0, "PT3NoteTable_PT_34_35"
;=================================================
ldy #11
freq_table_0_copy_loop:
lda base0_v4_high,Y
sta NoteTable_high,Y
lda base0_v4_low,Y
sta NoteTable_low,Y
dey
bpl freq_table_0_copy_loop
jsr NoteTablePropogate ; !3
lda #<table0_v4_adjust
sta note_table_adjust_smc+1
lda #>table0_v4_adjust
sta note_table_adjust_smc+2
jsr NoteTableAdjust
done_set_freq_table:
;======================
; calculate version
ldx #6 ; 2
lda PT3_LOC+PT3_VERSION ; 4
sec ; 2
sbc #'0' ; 2
cmp #9 ; 2
bcs not_ascii_number ; bge ; 2/3
tax ; 2
not_ascii_number:
; adjust version<6 SMC code in the slide code
; FIXME: I am sure there's a more clever way to do this
lda #$2C ; BIT ; 2
cpx #$6 ; 2
bcs version_greater_than_or_equal_6 ; bgt ; 3
; less than 6, jump
; also carry is known to be clear
adc #$20 ; BIT->JMP 2C->4C ; 2
version_greater_than_or_equal_6:
sta version_smc ; 4
pick_volume_table:
;=======================
; Pick which volume number, based on version
; if (PlParams.PT3.PT3_Version <= 4)
cpx #5 ; 2
; carry clear = 3.3/3.4 table
; carry set = 3.5 table
;==========================
; VolTableCreator
;==========================
; Creates the appropriate volume table
; based on z80 code by Ivan Roshin ZXAYHOBETA/VTII10bG.asm
;
; Called with carry==0 for 3.3/3.4 table
; Called with carry==1 for 3.5 table
; 177f-1932 = 435 bytes, not that much better than 512 of lookup
VolTableCreator:
; Init initial variables
lda #$0
sta z80_d_smc+1
ldy #$11
; Set up self modify
ldx #$2A ; ROL for self-modify
bcs vol_type_35
vol_type_33:
; For older table, we set initial conditions a bit
; different
dey
tya
ldx #$ea ; NOP for self modify
vol_type_35:
sty z80_l_smc+1 ; l=16 or 17
sta z80_e_smc+1 ; e=16 or 0
stx vol_smc ; set the self-modify code
ldy #16 ; skip first row, all zeros
ldx #16 ; c=16
vol_outer:
clc ; add HL,DE
z80_l_smc:
lda #$d1
z80_e_smc:
adc #$d1
sta z80_e_smc+1
lda #0
z80_d_smc:
adc #$d1
sta z80_d_smc+1 ; carry is important
; sbc hl,hl
lda #0
adc #$ff
eor #$ff
vol_write:
sta z80_h_smc+1
pha
vol_inner:
pla
pha
vol_smc:
nop ; nop or ROL depending
z80_h_smc:
lda #$d1
adc #$0 ; a=a+carry;
sta VolumeTable,Y
iny
pla ; add HL,DE
adc z80_e_smc+1
pha
lda z80_h_smc+1
adc z80_d_smc+1
sta z80_h_smc+1
inx ; inc C
txa ; a=c
and #$f
bne vol_inner
pla
lda z80_e_smc+1 ; a=e
cmp #$77
bne vol_m3
inc z80_e_smc+1
vol_m3:
txa ; a=c
bne vol_outer
vol_done:
rts
;=========================================
; copy note table seed to proper location
;=========================================
; faster inlined
;NoteTableCopy:
; ldy #11 ; !2
;note_table_copy_loop:
;ntc_smc1:
; lda base1_high,Y ; !3
; sta NoteTable_high,Y ; !3
;ntc_smc2:
; lda base1_low,Y ; !3
; sta NoteTable_low,Y ; !3
; dey ; !1
; bpl note_table_copy_loop ; !2
; rts ; !1
;==========================================
; propogate the freq down, dividing by two
;==========================================
NoteTablePropogate:
ldy #0
note_table_propogate_loop:
clc
lda NoteTable_high,Y
ror
sta NoteTable_high+12,Y
lda NoteTable_low,Y
ror
sta NoteTable_low+12,Y
iny
cpy #84
bne note_table_propogate_loop
rts
;================================================
; propogation isn't enough, various values
; are often off by one, so adjust using a bitmask
;================================================
NoteTableAdjust:
ldx #0
note_table_adjust_outer:
note_table_adjust_smc:
lda table0_v4_adjust,X
sta PT3_TEMP
; reset smc
lda #<NoteTable_low
sta ntl_smc+1
lda #>NoteTable_low
sta ntl_smc+2
ldy #7
note_table_adjust_inner:
ror PT3_TEMP
bcc note_table_skip_adjust
ntl_smc:
inc NoteTable_low,X
note_table_skip_adjust:
clc
lda #12
adc ntl_smc+1
sta ntl_smc+1
lda #0
adc ntl_smc+2 ; unnecessary if aligned
sta ntl_smc+2
skip_adjust_done:
dey
bpl note_table_adjust_inner
inx
cpx #12
bne note_table_adjust_outer
rts
;base0_v3_high:
;.byte $0C,$0B,$0A,$0A,$09,$09,$08,$08,$07,$07,$06,$06
;base0_v3_low:
;.byte $21,$73,$CE,$33,$A0,$16,$93,$18,$A4,$36,$CE,$6D
; note: same as base0_v3_high
base0_v4_high:
.byte $0C,$0B,$0A,$0A,$09,$09,$08,$08,$07,$07,$06,$06
base0_v4_low:
.byte $22,$73,$CF,$33,$A1,$17,$94,$19,$A4,$37,$CF,$6D
base1_high:
.byte $0E,$0E,$0D,$0C,$0B,$0B,$0A,$09,$09,$08,$08,$07
base1_low:
.byte $F8,$10,$60,$80,$D8,$28,$88,$F0,$60,$E0,$58,$E0
;base2_v3_high:
;.byte $0D,$0C,$0B,$0B,$0A,$09,$09,$08,$08,$07,$07,$07
;base2_v3_low:
;.byte $3E,$80,$CC,$22,$82,$EC,$5C,$D6,$58,$E0,$6E,$04
; note almost same as above
base2_v4_high:
.byte $0D,$0C,$0B,$0A,$0A,$09,$09,$08,$08,$07,$07,$06
base2_v4_low:
.byte $10,$55,$A4,$FC,$5F,$CA,$3D,$B8,$3B,$C5,$55,$EC
; note almost same as above
;base3_high:
;.byte $0C,$0C,$0B,$0A,$0A,$09,$09,$08,$08,$07,$07,$06
base3_low:
.byte $DA,$22,$73,$CF,$33,$A1,$17,$94,$19,$A4,$37,$CF
; Adjustment factors
table0_v4_adjust:
.byte $40,$e6,$9c,$66,$40,$2c,$20,$30,$48,$6c,$1c,$5a
table2_v4_adjust:
.byte $20,$a8,$40,$f8,$bc,$90,$78,$70,$74,$08,$2a,$50
table3_v4_adjust:
.byte $B4,$40,$e6,$9c,$66,$40,$2c,$20,$30,$48,$6c,$1c
; Table #1 of Pro Tracker 3.3x - 3.5x
;PT3NoteTable_ST_high:
;.byte $0E,$0E,$0D,$0C,$0B,$0B,$0A,$09
;.byte $09,$08,$08,$07,$07,$07,$06,$06
;.byte $05,$05,$05,$04,$04,$04,$04,$03
;.byte $03,$03,$03,$03,$02,$02,$02,$02
;.byte $02,$02,$02,$01,$01,$01,$01,$01
;.byte $01,$01,$01,$01,$01,$01,$01,$00
;.byte $00,$00,$00,$00,$00,$00,$00,$00
;.byte $00,$00,$00,$00,$00,$00,$00,$00
;.byte $00,$00,$00,$00,$00,$00,$00,$00
;.byte $00,$00,$00,$00,$00,$00,$00,$00
;.byte $00,$00,$00,$00,$00,$00,$00,$00
;.byte $00,$00,$00,$00,$00,$00,$00,$00
;PT3NoteTable_ST_low:
;.byte $F8,$10,$60,$80,$D8,$28,$88,$F0
;.byte $60,$E0,$58,$E0,$7C,$08,$B0,$40
;.byte $EC,$94,$44,$F8,$B0,$70,$2C,$FD
;.byte $BE,$84,$58,$20,$F6,$CA,$A2,$7C
;.byte $58,$38,$16,$F8,$DF,$C2,$AC,$90
;.byte $7B,$65,$51,$3E,$2C,$1C,$0A,$FC
;.byte $EF,$E1,$D6,$C8,$BD,$B2,$A8,$9F
;.byte $96,$8E,$85,$7E,$77,$70,$6B,$64
;.byte $5E,$59,$54,$4F,$4B,$47,$42,$3F
;.byte $3B,$38,$35,$32,$2F,$2C,$2A,$27
;.byte $25,$23,$21,$1F,$1D,$1C,$1A,$19
;.byte $17,$16,$15,$13,$12,$11,$10,$0F
; Table #2 of Pro Tracker 3.4x - 3.5x
;PT3NoteTable_ASM_34_35_high:
;.byte $0D,$0C,$0B,$0A,$0A,$09,$09,$08
;.byte $08,$07,$07,$06,$06,$06,$05,$05
;.byte $05,$04,$04,$04,$04,$03,$03,$03
;.byte $03,$03,$02,$02,$02,$02,$02,$02
;.byte $02,$01,$01,$01,$01,$01,$01,$01
;.byte $01,$01,$01,$01,$01,$00,$00,$00
;.byte $00,$00,$00,$00,$00,$00,$00,$00
;.byte $00,$00,$00,$00,$00,$00,$00,$00
;.byte $00,$00,$00,$00,$00,$00,$00,$00
;.byte $00,$00,$00,$00,$00,$00,$00,$00
;.byte $00,$00,$00,$00,$00,$00,$00,$00
;.byte $00,$00,$00,$00,$00,$00,$00,$00
;PT3NoteTable_ASM_34_35_low:
;.byte $10,$55,$A4,$FC,$5F,$CA,$3D,$B8
;.byte $3B,$C5,$55,$EC,$88,$2A,$D2,$7E
;.byte $2F,$E5,$9E,$5C,$1D,$E2,$AB,$76
;.byte $44,$15,$E9,$BF,$98,$72,$4F,$2E
;.byte $0F,$F1,$D5,$BB,$A2,$8B,$74,$60
;.byte $4C,$39,$28,$17,$07,$F9,$EB,$DD
;.byte $D1,$C5,$BA,$B0,$A6,$9D,$94,$8C
;.byte $84,$7C,$75,$6F,$69,$63,$5D,$58
;.byte $53,$4E,$4A,$46,$42,$3E,$3B,$37
;.byte $34,$31,$2F,$2C,$29,$27,$25,$23
;.byte $21,$1F,$1D,$1C,$1A,$19,$17,$16
;.byte $15,$14,$12,$11,$10,$0F,$0E,$0D
;PT3VolumeTable_33_34:
;.byte $0,$0,$0,$0,$0,$0,$0,$0,$0,$0,$0,$0,$0,$0,$0,$0
;.byte $0,$0,$0,$0,$0,$0,$0,$0,$1,$1,$1,$1,$1,$1,$1,$1
;.byte $0,$0,$0,$0,$0,$0,$1,$1,$1,$1,$1,$2,$2,$2,$2,$2
;.byte $0,$0,$0,$0,$1,$1,$1,$1,$2,$2,$2,$2,$3,$3,$3,$3
;.byte $0,$0,$0,$0,$1,$1,$1,$2,$2,$2,$3,$3,$3,$4,$4,$4
;.byte $0,$0,$0,$1,$1,$1,$2,$2,$3,$3,$3,$4,$4,$4,$5,$5
;.byte $0,$0,$0,$1,$1,$2,$2,$3,$3,$3,$4,$4,$5,$5,$6,$6
;.byte $0,$0,$1,$1,$2,$2,$3,$3,$4,$4,$5,$5,$6,$6,$7,$7
;.byte $0,$0,$1,$1,$2,$2,$3,$3,$4,$5,$5,$6,$6,$7,$7,$8
;.byte $0,$0,$1,$1,$2,$3,$3,$4,$5,$5,$6,$6,$7,$8,$8,$9
;.byte $0,$0,$1,$2,$2,$3,$4,$4,$5,$6,$6,$7,$8,$8,$9,$A
;.byte $0,$0,$1,$2,$3,$3,$4,$5,$6,$6,$7,$8,$9,$9,$A,$B
;.byte $0,$0,$1,$2,$3,$4,$4,$5,$6,$7,$8,$8,$9,$A,$B,$C
;.byte $0,$0,$1,$2,$3,$4,$5,$6,$7,$7,$8,$9,$A,$B,$C,$D
;.byte $0,$0,$1,$2,$3,$4,$5,$6,$7,$8,$9,$A,$B,$C,$D,$E
;.byte $0,$1,$2,$3,$4,$5,$6,$7,$8,$9,$A,$B,$C,$D,$E,$F
;PT3VolumeTable_35:
;.byte $0,$0,$0,$0,$0,$0,$0,$0,$0,$0,$0,$0,$0,$0,$0,$0
;.byte $0,$0,$0,$0,$0,$0,$0,$0,$1,$1,$1,$1,$1,$1,$1,$1
;.byte $0,$0,$0,$0,$1,$1,$1,$1,$1,$1,$1,$1,$2,$2,$2,$2
;.byte $0,$0,$0,$1,$1,$1,$1,$1,$2,$2,$2,$2,$2,$3,$3,$3
;.byte $0,$0,$1,$1,$1,$1,$2,$2,$2,$2,$3,$3,$3,$3,$4,$4
;.byte $0,$0,$1,$1,$1,$2,$2,$2,$3,$3,$3,$4,$4,$4,$5,$5
;.byte $0,$0,$1,$1,$2,$2,$2,$3,$3,$4,$4,$4,$5,$5,$6,$6
;.byte $0,$0,$1,$1,$2,$2,$3,$3,$4,$4,$5,$5,$6,$6,$7,$7
;.byte $0,$1,$1,$2,$2,$3,$3,$4,$4,$5,$5,$6,$6,$7,$7,$8
;.byte $0,$1,$1,$2,$2,$3,$4,$4,$5,$5,$6,$7,$7,$8,$8,$9
;.byte $0,$1,$1,$2,$3,$3,$4,$5,$5,$6,$7,$7,$8,$9,$9,$A
;.byte $0,$1,$1,$2,$3,$4,$4,$5,$6,$7,$7,$8,$9,$A,$A,$B
;.byte $0,$1,$2,$2,$3,$4,$5,$6,$6,$7,$8,$9,$A,$A,$B,$C
;.byte $0,$1,$2,$3,$3,$4,$5,$6,$7,$8,$9,$A,$A,$B,$C,$D
;.byte $0,$1,$2,$3,$4,$5,$6,$7,$7,$8,$9,$A,$B,$C,$D,$E
;.byte $0,$1,$2,$3,$4,$5,$6,$7,$8,$9,$A,$B,$C,$D,$E,$F

View File

@ -0,0 +1,117 @@
pt3_irq_handler:
pt3_irq_smc1:
bit MOCK_6522_T1CL ; clear 6522 interrupt by reading T1C-L ; 4
lda DONE_PLAYING ; 3
beq pt3_play_music ; if song done, don't play music ; 3/2nt
jmp done_pt3_irq_handler ; 3
;============
; 13
pt3_play_music:
; decode a frame of music
jsr pt3_make_frame
; handle song over condition
lda DONE_SONG
beq mb_write_frame ; if not done, continue
lda LOOP ; see if looping
beq move_to_next
pt3_loop_smc:
lda #$d1 ; looping, move to loop location
; non-zero to avoid the temptation
; to merge with following lda #$0
sta current_pattern_smc+1
lda #$0
sta current_line_smc+1
sta current_subframe_smc+1
sta DONE_SONG ; undo the next song
; beq done_pt3_irq_handler ; branch always
beq pt3_play_music ; branch always
move_to_next:
; same as "press right"
ldx #$20
jmp quiet_exit
;======================================
; Write frames to Mockingboard
;======================================
; for speed could merge this into
; the decode code
mb_write_frame:
tax ; set up reg count ; 2
;============
; 2
;==================================
; loop through the 14 registers
; reading the value, then write out
;==================================
mb_write_loop:
lda AY_REGISTERS,X ; load register value ; 4
; special case R13. If it is 0xff, then don't update
; otherwise might spuriously reset the envelope settings
cpx #13 ; 2
bne mb_not_13 ; 3/2nt
cmp #$ff ; 2
beq mb_skip_13 ; 3/2nt
;============
; typ 5
mb_not_13:
; address
pt3_irq_smc2:
stx MOCK_6522_ORA1 ; put address on PA1 ; 4
stx MOCK_6522_ORA2 ; put address on PA2 ; 4
ldy #MOCK_AY_LATCH_ADDR ; latch_address for PB1 ; 2
pt3_irq_smc3:
sty MOCK_6522_ORB1 ; latch_address on PB1 ; 4
sty MOCK_6522_ORB2 ; latch_address on PB2 ; 4
ldy #MOCK_AY_INACTIVE ; go inactive ; 2
pt3_irq_smc4:
sty MOCK_6522_ORB1 ; 4
sty MOCK_6522_ORB2 ; 4
; value
pt3_irq_smc5:
sta MOCK_6522_ORA1 ; put value on PA1 ; 4
sta MOCK_6522_ORA2 ; put value on PA2 ; 4
lda #MOCK_AY_WRITE ; ; 2
pt3_irq_smc6:
sta MOCK_6522_ORB1 ; write on PB1 ; 4
sty MOCK_6522_ORB1 ; 4
pt3_irq_smc7:
sta MOCK_6522_ORB2 ; write on PB2 ; 4
sty MOCK_6522_ORB2 ; 4
;===========
; 56
mb_no_write:
inx ; point to next register ; 2
cpx #14 ; if 14 we're done ; 2
bmi mb_write_loop ; otherwise, loop ; 3/2nt
;============
; 7
mb_skip_13:
;=================================
; Finally done with this interrupt
;=================================
done_pt3_irq_handler:

View File

@ -0,0 +1,340 @@
;===================================================================
; code to detect mockingboard
;===================================================================
; this isn't always easy
; my inclination is to just assume slot #4 but that isn't always realistic
; code below based on "hw.mockingboard.a" from "Total Replay"
;license:MIT
; By Andrew Roughan
; in the style of 4am for Total Replay
;
; Mockingboard support functions
;
;------------------------------------------------------------------------------
; HasMockingboard
; detect Mockingboard card by searching for 6522 timers across all slots
; access 6522 timers with deterministic cycle counts
;
; based on prior art in Mockingboard Developers Toolkit
; with optimisation from deater/french touch
; also takes into account FastChip //e clock difference
;
; in: none
; accelerators should be off
; out: C set if Mockingboard found in any slot
; if card was found, X = #$Cn where n is the slot number of the card
; C clear if no Mockingboard found
; other flags clobbered
; A/Y clobbered
;------------------------------------------------------------------------------
mockingboard_detect:
; activate Mockingboard IIc
; + the Mockingboard has to take over Slot#4 (IIc has no slots)
; in theory any write to the firmware area in $C400 will
; activate it, but that might not be fast enough when detecting
; so writing $FF to $C403/$C404 is official way to enable
; + Note this disables permanently the mouse firmware in $C400
; so "normal" interrupts are broken :( The hack to fix things
; is to switch in RAM for $F000 and just replace the IRQ
; vectors at $FFFE/$FFFF instead of $3FE/$3FF but that makes
; it difficult if you actually wanted to use any
; Applesoft/Monitor ROM routines
.ifdef PT3_ENABLE_APPLE_IIC
lda APPLEII_MODEL
cmp #'c'
bne not_iic
lda #$ff
; don't bother patching these, IIc mockingboard always slot 4
sta MOCK_6522_DDRA1 ; $C403
sta MOCK_6522_T1CL ; $C404
.endif
not_iic:
lda #$00
sta MB_ADDR_L
ldx #$C7 ; start at slot #7
mb_slot_loop:
stx MB_ADDR_H
ldy #$04 ; 6522 #1 $Cx04
jsr mb_timer_check
bne mb_next_slot
ldy #$84 ; 6522 #2 $Cx84
jsr mb_timer_check
bne mb_next_slot
mb_found:
sec ; found
rts
mb_next_slot:
dex
cpx #$C0
bne mb_slot_loop
clc ; not found
rts
mb_timer_check:
lda (MB_ADDR_L),Y ; read 6522 timer low byte
sta MB_VALUE
lda (MB_ADDR_L),Y ; second time
sec
sbc MB_VALUE
cmp #$F8 ; looking for (-)8 cycles between reads
beq mb_timer_check_done
cmp #$F7 ; FastChip //e clock is different
mb_timer_check_done:
rts
;===================================================================
; code to patch mockingboard if not in slot#4
;===================================================================
; this is the brute force version, we have to patch 39 locations
; see further below if you want to try a smaller, more dangerous, patch
.if 0
mockingboard_patch:
lda MB_ADDR_H
sta pt3_irq_smc1+2 ; 1
sta pt3_irq_smc2+2 ; 2
sta pt3_irq_smc2+5 ; 3
sta pt3_irq_smc3+2 ; 4
sta pt3_irq_smc3+5 ; 5
sta pt3_irq_smc4+2 ; 6
sta pt3_irq_smc4+5 ; 7
sta pt3_irq_smc5+2 ; 8
sta pt3_irq_smc5+5 ; 9
sta pt3_irq_smc6+2 ; 10
sta pt3_irq_smc6+5 ; 11
sta pt3_irq_smc7+2 ; 12
sta pt3_irq_smc7+5 ; 13
sta mock_init_smc1+2 ; 14
sta mock_init_smc1+5 ; 15
sta mock_init_smc2+2 ; 16
sta mock_init_smc2+5 ; 17
sta reset_ay_smc1+2 ; 18
sta reset_ay_smc2+2 ; 19
sta reset_ay_smc3+2 ; 20
sta reset_ay_smc4+2 ; 21
sta write_ay_smc1+2 ; 22
sta write_ay_smc1+5 ; 23
sta write_ay_smc2+2 ; 24
sta write_ay_smc2+5 ; 25
sta write_ay_smc3+2 ; 26
sta write_ay_smc3+5 ; 27
sta write_ay_smc4+2 ; 28
sta write_ay_smc4+5 ; 29
sta write_ay_smc5+2 ; 30
sta write_ay_smc5+5 ; 31
sta write_ay_smc6+2 ; 32
sta write_ay_smc6+5 ; 33
sta setup_irq_smc1+2 ; 34
sta setup_irq_smc2+2 ; 35
sta setup_irq_smc3+2 ; 36
sta setup_irq_smc4+2 ; 37
sta setup_irq_smc5+2 ; 38
sta setup_irq_smc6+2 ; 39
rts
.endif
;===================================================================
; dangerous code to patch mockingboard if not in slot#4
;===================================================================
; this code patches any $C4 value to the proper slot# if not slot4
; this can be dangerous, it might over-write other important values
; that should be $C4
; safer ways to do this:
; only do this if 2 bytes after a LDA/STA/LDX/STX
; count total and if not 39 then print error message
mockingboard_patch:
; from mockingboard_init $1BBF
; to done_pt3_irq_handler $1D85
ldx MB_ADDR_H
ldy #0
lda #<mockingboard_init
sta MB_ADDR_L
lda #>mockingboard_init
sta MB_ADDR_H
mb_patch_loop:
lda (MB_ADDR_L),Y
cmp #$C4
bne mb_patch_nomatch
txa
sta (MB_ADDR_L),Y
mb_patch_nomatch:
inc MB_ADDR_L
lda MB_ADDR_L
bne mb_patch_oflo
inc MB_ADDR_H
mb_patch_oflo:
lda MB_ADDR_H
cmp #>done_pt3_irq_handler
bne mb_patch_loop
lda MB_ADDR_L
cmp #<done_pt3_irq_handler
bne mb_patch_loop
mb_patch_done:
rts
.if 0
;=======================================
; Detect a Mockingboard card
;=======================================
; Based on code from the French Touch "Pure Noise" Demo
; Attempts to time an instruction sequence with a 6522
;
; If found, puts in bMB
; MB_ADDRL:MB_ADDRH has address of Mockingboard
; returns X=0 if not found, X=1 if found
mockingboard_detect:
lda #0
sta MB_ADDRL
mb_detect_loop: ; self-modifying
lda #$07 ; we start in slot 7 ($C7) and go down to 0 ($C0)
ora #$C0 ; make it start with C
sta MB_ADDRH
ldy #04 ; $CX04
ldx #02 ; 2 tries?
mb_check_cycle_loop:
lda (MB_ADDRL),Y ; timer 6522 (Low Order Counter)
; count down
sta PT3_TEMP ; 3 cycles
lda (MB_ADDRL),Y ; + 5 cycles = 8 cycles
; between the two accesses to the timer
sec
sbc PT3_TEMP ; subtract to see if we had 8 cycles
cmp #$f8 ; -8
bne mb_not_in_this_slot
dex ; decrement, try one more time
bne mb_check_cycle_loop ; loop detection
inx ; Mockingboard found (X=1)
done_mb_detect:
;stx bMB ; store result to bMB
rts ; return
mb_not_in_this_slot:
dec mb_detect_loop+1 ; decrement the "slot" (self_modify)
bne mb_detect_loop ; loop down to one
ldx #00
beq done_mb_detect
;alternative MB detection from Nox Archaist
; lda #$04
; sta MB_ADDRL
; ldx #$c7
;
;find_mb:
; stx MB_ADDRH
;
; ;detect sound I
;
; sec
; ldy #$00
; lda (MB_ADDRL), y
; sbc (MB_ADDRL), y
; cmp #$05
; beq found_mb
; dex
; cpx #$c0
; bne find_mb
; ldx #$00 ;no mockingboard found
; rts
;
;found_mb:
; ldx #$01 ;mockingboard found
; rts
;
; ;optionally detect sound II
;
; sec
; ldy #$80
; lda (MB_ADDRL), y
; sbc (MB_ADDRL), y
; cmp #$05
; beq found_mb
;=======================================
; Detect a Mockingboard card in Slot4
;=======================================
; Based on code from the French Touch "Pure Noise" Demo
; Attempts to time an instruction sequence with a 6522
;
; MB_ADDRL:MB_ADDRH has address of Mockingboard
; returns X=0 if not found, X=1 if found
mockingboard_detect_slot4:
lda #0
sta MB_ADDRL
mb4_detect_loop: ; self-modifying
lda #$04 ; we're only looking in Slot 4
ora #$C0 ; make it start with C
sta MB_ADDRH
ldy #04 ; $CX04
ldx #02 ; 2 tries?
mb4_check_cycle_loop:
lda (MB_ADDRL),Y ; timer 6522 (Low Order Counter)
; count down
sta PT3_TEMP ; 3 cycles
lda (MB_ADDRL),Y ; + 5 cycles = 8 cycles
; between the two accesses to the timer
sec
sbc PT3_TEMP ; subtract to see if we had 8 cycles
cmp #$f8 ; -8
bne mb4_not_in_this_slot
dex ; decrement, try one more time
bne mb4_check_cycle_loop ; loop detection
inx ; Mockingboard found (X=1)
done_mb4_detect:
rts ; return
mb4_not_in_this_slot:
ldx #00
beq done_mb4_detect
.endif

View File

@ -0,0 +1,323 @@
; Mockingboad programming:
; + Has two 6522 I/O chips connected to two AY-3-8910 chips
; + Optionally has some speech chips controlled via the outport on the AY
; + Often in slot 4. We autodetect and patch
; References used:
; http://macgui.com/usenet/?group=2&id=8366
; 6522 Data Sheet
; AY-3-8910 Data Sheet
;========================
; Mockingboard card
; Essentially two 6522s hooked to the Apple II bus
; Connected to AY-3-8910 chips
; PA0-PA7 on 6522 connected to DA0-DA7 on AY
; PB0 on 6522 connected to BC1
; PB1 on 6522 connected to BDIR
; PB2 on 6522 connected to RESET
; left speaker
MOCK_6522_ORB1 = $C400 ; 6522 #1 port b data
MOCK_6522_ORA1 = $C401 ; 6522 #1 port a data
MOCK_6522_DDRB1 = $C402 ; 6522 #1 data direction port B
MOCK_6522_DDRA1 = $C403 ; 6522 #1 data direction port A
MOCK_6522_T1CL = $C404 ; 6522 #1 t1 low order latches
MOCK_6522_T1CH = $C405 ; 6522 #1 t1 high order counter
MOCK_6522_T1LL = $C406 ; 6522 #1 t1 low order latches
MOCK_6522_T1LH = $C407 ; 6522 #1 t1 high order latches
MOCK_6522_T2CL = $C408 ; 6522 #1 t2 low order latches
MOCK_6522_T2CH = $C409 ; 6522 #1 t2 high order counters
MOCK_6522_SR = $C40A ; 6522 #1 shift register
MOCK_6522_ACR = $C40B ; 6522 #1 auxilliary control register
MOCK_6522_PCR = $C40C ; 6522 #1 peripheral control register
MOCK_6522_IFR = $C40D ; 6522 #1 interrupt flag register
MOCK_6522_IER = $C40E ; 6522 #1 interrupt enable register
MOCK_6522_ORANH = $C40F ; 6522 #1 port a data no handshake
; right speaker
MOCK_6522_ORB2 = $C480 ; 6522 #2 port b data
MOCK_6522_ORA2 = $C481 ; 6522 #2 port a data
MOCK_6522_DDRB2 = $C482 ; 6522 #2 data direction port B
MOCK_6522_DDRA2 = $C483 ; 6522 #2 data direction port A
; AY-3-8910 commands on port B
; RESET BDIR BC1
MOCK_AY_RESET = $0 ; 0 0 0
MOCK_AY_INACTIVE = $4 ; 1 0 0
MOCK_AY_READ = $5 ; 1 0 1
MOCK_AY_WRITE = $6 ; 1 1 0
MOCK_AY_LATCH_ADDR = $7 ; 1 1 1
;========================
; Mockingboard Init
;========================
; Initialize the 6522s
; set the data direction for all pins of PortA/PortB to be output
mockingboard_init:
lda #$ff ; all output (1)
mock_init_smc1:
sta MOCK_6522_DDRB1
sta MOCK_6522_DDRA1
mock_init_smc2:
sta MOCK_6522_DDRB2
sta MOCK_6522_DDRA2
rts
;===================================
;===================================
; Reset Both AY-3-8910s
;===================================
;===================================
;======================
; Reset Left AY-3-8910
;======================
reset_ay_both:
lda #MOCK_AY_RESET
reset_ay_smc1:
sta MOCK_6522_ORB1
lda #MOCK_AY_INACTIVE
reset_ay_smc2:
sta MOCK_6522_ORB1
;======================
; Reset Right AY-3-8910
;======================
;reset_ay_right:
;could be merged with both
lda #MOCK_AY_RESET
reset_ay_smc3:
sta MOCK_6522_ORB2
lda #MOCK_AY_INACTIVE
reset_ay_smc4:
sta MOCK_6522_ORB2
rts
; Write sequence
; Inactive -> Latch Address -> Inactive -> Write Data -> Inactive
;=========================================
; Write Right/Left to save value AY-3-8910
;=========================================
; register in X
; value in MB_VALUE
write_ay_both:
; address
write_ay_smc1:
stx MOCK_6522_ORA1 ; put address on PA1 ; 4
stx MOCK_6522_ORA2 ; put address on PA2 ; 4
lda #MOCK_AY_LATCH_ADDR ; latch_address on PB1 ; 2
write_ay_smc2:
sta MOCK_6522_ORB1 ; latch_address on PB1 ; 4
sta MOCK_6522_ORB2 ; latch_address on PB2 ; 4
ldy #MOCK_AY_INACTIVE ; go inactive ; 2
write_ay_smc3:
sty MOCK_6522_ORB1 ; 4
sty MOCK_6522_ORB2 ; 4
;===========
; 28
; value
lda MB_VALUE ; 3
write_ay_smc4:
sta MOCK_6522_ORA1 ; put value on PA1 ; 4
sta MOCK_6522_ORA2 ; put value on PA2 ; 4
lda #MOCK_AY_WRITE ; ; 2
write_ay_smc5:
sta MOCK_6522_ORB1 ; write on PB1 ; 4
sta MOCK_6522_ORB2 ; write on PB2 ; 4
write_ay_smc6:
sty MOCK_6522_ORB1 ; 4
sty MOCK_6522_ORB2 ; 4
;===========
; 29
rts ; 6
;===========
; 63
write_ay_both_end:
;.assert >write_ay_both = >write_ay_both_end, error, "write_ay_both crosses page"
;=======================================
; clear ay -- clear all 14 AY registers
; should silence the card
;=======================================
; 7+(74*14)+5=1048
clear_ay_both:
ldx #13 ; 2
lda #0 ; 2
sta MB_VALUE ; 3
clear_ay_left_loop:
jsr write_ay_both ; 6+63
dex ; 2
bpl clear_ay_left_loop ; 3
; -1
rts ; 6
;=======================================
; mute AY -- just turn off all 3 channels
; should silence the card
;
;=======================================
mute_ay_both:
ldx #7 ;
lda #$FF ;
sta MB_VALUE ;
mute_ay_left_loop:
jsr write_ay_both ;
rts
;=======================================
; unmute AY
; restore to value we had before muting
;=======================================
unmute_ay_both:
ldx #7 ;
lda ENABLE ;
sta MB_VALUE ;
unmute_ay_left_loop:
jsr write_ay_both ;
rts ;
clear_ay_end:
;.assert >clear_ay_both = >clear_ay_end, error, "clear_ay_both crosses page"
;=============================
; Setup
;=============================
mockingboard_setup_interrupt:
.ifdef PT3_ENABLE_APPLE_IIC
lda APPLEII_MODEL
cmp #'c'
bne done_iic_hack
;==================================================
; On IIc we use a hack and swap RAM into the langauge
; card and replace the interrupt vectors
; (should we do this on IIe too? probably faster)
; This does mean you can't use any ROM routines when
; playing music
;====================================================
; If we need the ROM routines we need to copy them
; first we have to copy the ROM to the language card
sei ; disable interrupts
lda $c08B ; read/write RAM1
lda $c08B ;
.ifdef PT3_ENABLE_IIC_COPY_ROM
copy_rom_loop:
lda $c089 ; read ROM, write RAM1
lda $c089
ldy #0
read_rom_loop:
lda $D000,Y
sta $400,Y ; note this uses text page as
; temporary data store
iny
bne read_rom_loop
lda $c08B ; read/write RAM1
lda $c08B ;
; should probably use $800 instead of $400
; as we over-write screen holes here
write_rom_loop:
lda $400,Y
sta $D000,Y
iny
bne write_rom_loop
inc read_rom_loop+2
inc write_rom_loop+5
bne copy_rom_loop
.endif
lda #<interrupt_handler
sta $fffe
lda #>interrupt_handler
sta $ffff
lda #$EA ; nop out the "lda $45" in the irq handler
; as it's not needed on IIc (and maybe others?)
sta interrupt_smc
sta interrupt_smc+1
.endif
done_iic_hack:
;=========================
; Setup Interrupt Handler
;=========================
; Vector address goes to 0x3fe/0x3ff
; FIXME: should chain any existing handler
lda #<interrupt_handler
sta $03fe
lda #>interrupt_handler
sta $03ff
;============================
; Enable 50Hz clock on 6522
;============================
; Note, on Apple II the clock isn't 1MHz but is actually closer to
; roughly 1.023MHz, and every 65th clock is stretched (it's complicated)
; 4fe7 / 1.023e6 = .020s, 50Hz
; 9c40 / 1.023e6 = .040s, 25Hz
; 411a / 1.023e6 = .016s, 60Hz
; French Touch uses
; 4e20 / 1.000e6 = .020s, 50Hz, which assumes 1MHz clock freq
sei ; disable interrupts just in case
lda #$40 ; Continuous interrupts, don't touch PB7
setup_irq_smc1:
sta MOCK_6522_ACR ; ACR register
lda #$7F ; clear all interrupt flags
setup_irq_smc2:
sta MOCK_6522_IER ; IER register (interrupt enable)
lda #$C0
setup_irq_smc3:
sta MOCK_6522_IFR ; IFR: 1100, enable interrupt on timer one oflow
setup_irq_smc4:
sta MOCK_6522_IER ; IER: 1100, enable timer one interrupt
lda #$E7
; lda #$20
setup_irq_smc5:
sta MOCK_6522_T1CL ; write into low-order latch
lda #$4f
; lda #$4E
setup_irq_smc6:
sta MOCK_6522_T1CH ; write into high-order latch,
; load both values into counter
; clear interrupt and start counting
rts

13
demos/dni/sin.c Normal file
View File

@ -0,0 +1,13 @@
#include <stdio.h>
#include <math.h>
int main(int argc, char **argv) {
double x;
for(x=0;x<25;x++) {
printf("%.2lf %.2lf\n",x,5.0+5.0*sin(x*6.28/25));
}
return 0;
}

BIN
demos/dni/tables Normal file

Binary file not shown.

View File

@ -40,12 +40,57 @@ MASK = $2E
COLOR_MASK = $2F
COLOR = $30
COMPT1 = $30
COMPT2 = $31
SEEDL = $4e
SEEDH = $4f
XMAX = $50
;XMAX = $50
PARAM1 = $50
PARAM2 = $51
PARAM3 = $52
PARAM4 = $53
WHICH_TRACK = $54
ORNAMENT_L = $60
ORNAMENT_H = $61
SAMPLE_L = $62
SAMPLE_H = $63
LOOP = $64
MB_ADDR_L = $65
MB_ADDR_H = $66
MB_VALUE = $67
DONE_PLAYING = $68
DONE_SONG = $69
PT3_TEMP = $6A
APPLEII_MODEL = $6B
AY_REGISTERS = $70
A_FINE_TONE = $70
A_COARSE_TONE = $71
B_FINE_TONE = $72
B_COARSE_TONE = $73
C_FINE_TONE = $74
C_COARSE_TONE = $75
NOISE = $76
ENABLE = $77
PT3_MIXER_VAL = $77
A_VOLUME = $78
B_VOLUME = $79
C_VOLUME = $7A
ENVELOPE_FINE = $7B
ENVELOPE_COARSE = $7C
ENVELOPE_SHAPE = $7D
PATTERN_L = $7E
PATTERN_H = $7F
; note 70-7f used by disk code (?) do we need to preserve?
; We have to save/restore the following values
; when loading/storing from disk
@ -101,14 +146,15 @@ IN_LEFT = $9A
IN_RIGHT = $9B
UPDATE_POINTER = $9C
APPLEII_MODEL = $9D
;APPLEII_MODEL = $9D
HGR_PAGE = $9E
WHICH_SLOT = $9F
MAGLEV_FLIP_DIRECTION = $A0
BEACH_ANIMALS_SEEN = $A1
Table1 = $A0 ; 40 bytes ($28) A0-C7
Table2 = $C8 ; 40 bytes ($28) C8-EF
LEADING_ZERO = $F2
SIN_COUNT = $F2
DRAW_NUMBER = $F3
NUMBER_HIGH = $F4
NUMBER_LOW = $F5