'Apple ]['에 해당되는 글 3건

  1. 2023.04.07 MockingBoard Test
  2. 2023.04.04 AY-3-8910
  3. 2023.04.03 6522
Apple ][2023. 4. 7. 13:51
procedure:
 interrupt test -> sound test -> bgm test (interrupt + sound)

 

65C02 codes with Merlin32, tested on AppleWin

(It can be easily converted to 6502 codes.)

 

1. 6522 Interrupt test

 

- mainThread : increases value at testMem[0] and displays values

- intrThread: increases value at testMem[1] and displays values

*-----------------------------------------------
; Init.s : interrupt test
*-----------------------------------------------
               
            ;use Def.s
           
            org $300
BANK2_RDROM_WRRAM   = $c081
BANK2_RDRAM_WRRAM   = $c083
BANK1_RDROM_WRRAM   = $c089
BANK1_RDRAM_WRRAM   = $c08b            
           
__RUN       ENT
        LDA BANK2_RDROM_WRRAM ; Double read: Read ROM, write RAM
        LDA BANK2_RDROM_WRRAM ; $D000-FFFF, use bank 1 $D000-DFFF
       
        LDY #$00  ; ------
        LDA #$00  ; Use Monitor MemCopy to copy
        STA $3C   ; the Monitor ROM $F800-FFFF
        STA $42   ; to RAM at $F800-FFFF in
        LDA #$FF  ; preparation to read/write
        STA $3E   ; $D000-FFFF without it.
        STA $3F   ;
        LDA #$F8  ;
        STA $3D   ;
        STA $43   ;
        JSR $FE2C ;-------
       
        LDA BANK2_RDRAM_WRRAM ; Double read: Read/Write RAM
        LDA BANK2_RDRAM_WRRAM ; $D000-$FFFF, use bank 2 $D000-DFFF

        ; sets timer 6522
setTimer
        ;sei
        lda #%01000000
        sta $C40B       ; acr = continuous
        lda $00
        sta $C40D       ; ifr
        lda #%11000000
        ;sta $C40D       ; ifr
        sta $C40E       ; ier

        lda #$36
        sta $C404       ; T1C-L
        lda #$4F
        sta $C405       ; T1C-H
        lda #<intrThread
        sta $FFFE
        lda #>intrThread
        sta $FFFF
        ;cli

mainThread
        ldy testMem
        iny
        sty testMem
        ldx testMem+1
        jsr printMem
        ;jsr $F940       ; prints Y and X
        ;lda KEY_RETURN
        ;jsr $FDED
        jmp mainThread

intrThread  ; interrupt thread
        php
        pha
        phx
        phy

        lda #$7f
        sta $C40D       ; clears ifr
       
        ; thread do here
        ldx testMem+1
        inx
        stx testMem+1
        jsr printMem
        ;ldy testMem
        ;jsr $F940
        ;lda KEY_RETURN
        ;jsr $FDED
        ;

        ply
        plx
        pla
        plp
        rti

printMem
        lda testMem
        and #$0f
        tax
        lda char, x
        sta $401
        lda testMem
        lsr
        lsr
        lsr
        lsr
        tax
        lda char, X
        sta $400

        lda testMem+1
        and #$0f
        tax
        lda char, x
        sta $404
        lda testMem+1
        lsr
        lsr
        lsr
        lsr
        tax
        lda char, X
        sta $403

        rts
       

testMem     db 00, 00            
char        asc "0123456789ABCDEF"

 

 

2. AY-3-8910 sound test

 

- generates C3 tone through channel A

*-----------------------------------------------
; MB.s  : MockingBoard tone test
*-----------------------------------------------
               
           
        org $C00

ORB1    = $C400
ORA1    = $C401
DDRB1   = $C402
DDRA1   = $C403

ORB2    = $C480
ORA2    = $C481
DDRB2   = $C482
DDRA2   = $C483

/WriteReg MAC   ; reg#, data
        lda ]1
        sta ORA1
        jsr latch
        lda ]2
        sta ORA1
        jsr write
        <<<



run
        jsr init6522

        ; volume
        /WriteReg #8; #$0f
        ; enable
        /WriteReg #7; #%11111110
       
        ; tone A
        /WriteReg #0; #$A3
        /WriteReg #1; #$00
       
        rts


init6522
        lda #$FF
        sta DDRA1
        sta DDRA2
        ;lda #$07
        sta DDRB1
        sta DDRB2

        lda #$FF
        sta DDRA1
        sta DDRA2
        ;lda #$07
        sta DDRB1
        sta DDRB2

        jmp reset

latch
        lda #$07
        sta ORB1
        lda #$04
        sta ORB1
        rts

write
        lda #$06
        sta ORB1
        lda #$04
        sta ORB1
        rts        

reset
        lda #$00
        sta ORB1
        lda #$04
        sta ORB1
        rts

 

3. BGM test

 

- mainThread : increases value at testMem and displays it

- intrThread: swaps tone between C3 and C4.

 

*-----------------------------------------------
; BGM.s : BGM test
*-----------------------------------------------

        ;use Def.s

        org $D00

BANK2_RDROM_WRRAM   = $c081
BANK2_RDRAM_WRRAM   = $c083
BANK1_RDROM_WRRAM   = $c089
BANK1_RDRAM_WRRAM   = $c08b        

*-----------------------------------------------
;
; assumed that MockingBoard is in slot 4
;
*--------------------------------------
; 6522 registers
*--------------------------------------
; for 6522 #1

; data ports
ORB1    = $C400     ; port B
ORA1    = $C401     ; port A
DDRB1   = $C402     ; data direction mask for port B
DDRA1   = $C403     ; data direction mask for port A

; interrupt controls
ACR     = $C40B     ; auxiliary control register
IFR     = $C40D     ; interrupt flag register, clears interrupts by clearing bit7
IER     = $C40E     ; interrupt enable register

; timer1 registers
T1CL    = $C404     ; timer1 counter low
T1CH    = $C405     ; timer1 counter high

; for 6522 #2
ORB2    = $C480
ORA2    = $C481
DDRB2   = $C482
DDRA2   = $C483

*--------------------------------------
; ay-3-8910 registers
*--------------------------------------
ATonePeriodL    = $00       ; channel A tone period, low byte
ATonePeriodH    = $01       ; channel A tone period, high 4bits
MixerControl    = $07       ; channel enable/disable
AVolume         = $08       ; channel A amplitude control

*--------------------------------------
; ay-3-8910 commands
*--------------------------------------
CMD_Latch       = $07       ; selects a register (=latch)
CMD_Write       = $06       ; writes to a register
CMD_Inactivate  = $04       ; inactivates data port
CMD_Reset       = $00       ; clears all register and reset ay-3-8910

StartBGMTest    ENT
        ;
        ; this moves monitor rom to high ram
        ;
        LDA BANK2_RDROM_WRRAM ; Double read: Read ROM, write RAM
        LDA BANK2_RDROM_WRRAM ; $D000-FFFF, use bank 1 $D000-DFFF
       
        LDY #$00  ; ------
        LDA #$00  ; Use Monitor MemCopy to copy
        STA $3C   ; the Monitor ROM $F800-FFFF
        STA $42   ; to RAM at $F800-FFFF in
        LDA #$FF  ; preparation to read/write
        STA $3E   ; $D000-FFFF without it.
        STA $3F   ;
        LDA #$F8  ;
        STA $3D   ;
        STA $43   ;
        JSR $FE2C ;-------
       
        LDA BANK2_RDRAM_WRRAM ; Double read: Read/Write RAM
        LDA BANK2_RDRAM_WRRAM ; $D000-$FFFF, use bank 2 $D000-DFFF      

init6522
        ;
        ; initializes 6522 data ports
        ; we will only use a 6522 #1
        ;
        lda #$FF
        sta DDRA1       ; port A to output 8bits
        lda #$07
        sta DDRB1       ; port B to output low 3bits

init8910
        ;
        ; initializes 8910        
        ; we will only use channel A tone
        ; /Write macro is defined below
        ;

        ; sets channel A vol. to max (=15)
        /Write #AVolume; #$0f

        ; enables channel A with tone usage
        /Write #MixerControl; #%11_111_110

        ; initial tone to C3 (=$01_E8)
        /Write #ATonePeriodL; #$E8
        /Write #ATonePeriodH; #$01

setTimer
        ; sets timer1 interrupt to continuous mode
        lda #%01000000  
        sta ACR
       
        ; clears all intterupt flag
        lda #$00
        sta IFR

        ; enable intterupt for timer1
        ; bit7 = mask for all, bit6 = timer1 enable
        ;  -> timer1.enable= bit7 & bit6
        lda #%11000000  
        sta IER

        ; sets timer1 counter to 60Hz
        ; 1022730 / 60 = 17030 cycles
        ;  -> timer1 = 17030 - 2(?) = $4284
        lda #$84
        sta T1CL
        lda #$42
        sta T1CH

        ; sets IRQ vector to intrThread
        lda #<intrThread
        sta $FFFE           ; IRQ vector low
        lda #>intrThread
        sta $FFFF           ; IRQ vector high

       
mainThread
        *--------------------------------------
        ; main thread
        ;
        ; increases value in testMem
        ; and displays it
        *--------------------------------------
        inc testMem
        jsr displayMem
        jmp mainThread      ; continue this

intrThread
        *--------------------------------------
        ; intterupt thread
        ;
        ; generates BGM ( or sound )
        ; tone C3 <--> C4
        *--------------------------------------
        ; pushes registers, php is not required (done by irq)
        pha
        phx ; for 6502, use: txa, pha
        phy

        ; clears 6522 interrupt flag
        lda #$7f
        sta IFR

        ;
        lda intrFrame
        inc
        sta intrFrame
        and #$0f        ; changes per 16 frames
        bne :exit
        lda #$10
        bit intrFrame
        beq :toneC3
        ;
        ; intrFrame++
        ; if ((intrFrame&0xf)==0) { // per 16 frames
        ;     // changes tone 
        ;     tone = intrFrame&0x10==0? C3 : C4
        ; }
        ;
 

:toneC4 ; C4 = $00_F4
        /Write #ATonePeriodL; #$F4
        /Write #ATonePeriodH; #$00
        bra :exit

:toneC3 ; C3 = $01_E8
        /Write #ATonePeriodL; #$E8
        /Write #ATonePeriodH; #$01

:exit
        ; pulls registers
        ply
        plx
        pla
        rti

               
*--------------------------------------
; 8910 command routines
;  sequence: Command -> Inactivate
*--------------------------------------
aySelectReg ; input: A = register index
        sta ORA1        ; sends register index to portA (= 8910 data port)
        lda #CMD_Latch
        sta ORB1        ; sends latch command to portB (= 8910 command port)
        ; selects a register whose index is in ORA
       
        lda #CMD_Inactivate
        sta ORB1        ; sends inactivate command
        rts

ayWriteToReg ; input: A = data to write
        sta ORA1        ; sends data
        lda #CMD_Write
        sta ORB1        ; sends write command
        ; writes a data in ORA to currently selected resgister

        lda #CMD_Inactivate
        sta ORB1        ; sends inactivate command
        rts

ayReset ; resets 8910
        lda #CMD_Reset
        sta ORB1
        lda #CMD_Inactivate
        sta ORB1        ; sends inactivate command
        rts

;
; writing macro for 8910 register
;
/Write  MAC     ; /Write regIndex; data
        lda ]1
        jsr aySelectReg
        lda ]2
        jsr ayWriteToReg
        <<<



*--------------------------------------
; simple display routine
*--------------------------------------
displayMem
        lda testMem
        and #$0f
        tax
        lda char, x
        sta $401
        lda testMem
        lsr
        lsr
        lsr
        lsr
        tax
        lda char, X
        sta $400
        rts

intrFrame   db 00
testMem     db 00            
char        asc "0123456789ABCDEF"

 

 

 

 

Posted by GNUPart
Apple ][2023. 4. 4. 16:28

 

 

Latch Address: This signal indiates that the bus contains a resister address which should be latched in the PSG. DA7~DA0 are in the input mode.

 

from 6522, ORB[0] = BC1, ORB[1] = BDIR, ORB[2] = ~RESET

 

ORB = 7 (111): Latch Address, sets register address

ORB = 6 (110): Write To PSG register

ORB = 4 (100): Inactive

ORB = 0~3 (0xx): Reset  : clears all registers

 

procedure: Command -> Inactive

 

* sets PSG register to N (0~15)

lda #N

sta ora  ; connected to psg data bus

lda #7   ; loads 'latch address' command

sta orb  ; sends the command. connected to bus controls (BDIR, BC1)

lda #4   ; loads inactive command

sta orb  ; sends the command

 

* writes data to PSG's current register

lda data

sta ora

lda #6    ; 'write to psg' command

sta orb

lda #4

sta orb

 

* reset

stz orb

lda #4

sta orb

 

==> PSG, R[2] = 2

set PSG register to 2 -> writes 2 to PSG

 

Register \ bit B7 B6 B5 B4 B3 B2 B1 B0
R0 Channel A Tone Period 8-Bit Fine Tune A
R1   4-Bit Coarse Tune A
R2 Channel B Tone Period 8-Bit Fine Tune B
R3   4-Bit Coarse Tune B
R4 Channel C Tone Period 8-Bit Fine Tune C
R5   4-Bit Coarse Tune C
R6 Noise period   5-Bit Period control
R7 Enable ( bit 0 = on, 1 = off ) IN/OUT Noise Tone
IOB IOA C B A C B A
R8 Channel A Envelope on/off, Volume   Env volume
R9 Channel B Envelope on/off, Volume   Env volume
R10 Channel C Envelope on/off, Volume   Env volume
R11 Envelope Period 8-Bit Fine Tune Envelope
R12   4-Bit Coarse Tune Envelope
R13 Envelope Shape/Cycle   CONT ATT ALT HOLD
R14 I/O Port A Data Store 8-Bit Parallel I/O on Port A
R15 I/O Port B Data Store 8-Bit Parallel I/O on Port B

* Enable output Channel A (R7 = 0011 1110)

 

 

 

Posted by GNUPart
Apple ][2023. 4. 3. 17:26

* datasheet

https://eater.net/datasheets/w65c22.pdf

 

 

* code exam.

https://github.com/fenarinarsa/Latecomer/blob/master/tools.a#L174

 

-sets timer

config_timer
    ; interruption - TIMER 1 6522
    LDA #%01000000      ; continuous interrupt / PB7 disabled
    ldy #$0B
    STA (MB_OUT),y      ; $Cx0B Auxiliary Control Register

    LDA #%11000000      ;
    ldy #$0D
    STA (MB_OUT),y      ; $Cx0D interrupt flag register (Time Out of Timer 1/Int)
    ldy #$0E
    STA (MB_OUT),y      ; $Cx0E interrupt Enable register (Timer 1 + Set)
   
    ; The 6522 timer to play at 50Hz is different on a PAL or NTSC Apple II
    ; Main Apple II clock is (composite frequency):
    ; PAL = 1.016 MHz
    ; NTSC = 1.0205 MHz
    ;
    ; For future reference the 6522 counter for a complete frame size should be set to
    ; PAL = $4F36 (50.08Hz) = 20280-2 cycles
    ; NTSC = $4284 (~59.94Hz) = 17030-2 cycles
    ;
    ; Of course on PAL Apple IIc the VSYNC interrupt may be used, it already has a frequency of 50.08Hz
    ;
    ; Because of the clock differences,
    ; to get a frequency 50.08Hz on an NTSC Apple II the 6522 counter should actually be set at $4F88
    ; but the difference is not big enough to be heard and I'm lazy
    ;
    ; We're using T1 (first timer) on MB's first 6522 (there is two timers/6522 and two 6522 on a MB)
    ; T1 is set in free run mode so the counter needs to be set up only once
    ; the timer will start and loop once the counter high byte is written

    LDA #$36
    ldy #$04
    STA (MB_OUT),y      ; $Cx04 T1C-Lower
    LDA #$4F
    ldy #$05
    STA (MB_OUT),y      ; $Cx05 T1C-High

    lda MB_OUT+1    ; modifies the BIT instruction in VBLI
    sta vbli_mod1+2
    +set_ptr VBLI_compatible,$FFFE  ; setting up the 50Hz interrupt handler

    rts

 

- interrupt routine

VBLI_compatible
    ; Interrupt handler for IIe/IIc, using a 50Hz mockingboard interrupt
    ; on PAL should activate roughly at the start of VBLANK
    ; on NTSC will activate quite anywhere => tearing :)

    php             ; save flags
    sta save_a
    stx save_x
    sty save_y

    lda #$7f
vbli_mod1   sta $C40D ; clear IFR
    ;bit $C404       ; Clears interrupt (T1CL)  / modified instruction

    ; change VBL flag
    ldx #0
    stx vblflag     ; clear hibit
   
    ;----- HGR double buffering
    lda vbl_swaphgr
    beq .noswap
    stx vbl_swaphgr
    jsr swap_page
.noswap +inc16 vbl_count
   
    ; play music
    lda music_on
    beq .no_music
    jsr player_mb
.no_music

    ldy save_y
    ldx save_x
    lda save_a
    plp
    rti

 

 

 

 

 

 

Posted by GNUPart