Browse Source

Update dmamon.asm

pull/326/head
b1ackmai1er 3 years ago
parent
commit
a7ef76b9c4
  1. 349
      Source/Apps/Test/DMAmon/dmamon.asm

349
Source/Apps/Test/DMAmon/dmamon.asm

@ -39,12 +39,36 @@ INTENABLE .EQU TRUE ; ENABLE INT TESTING
INTIDX .EQU 1 ; INT VECTOR INDEX INTIDX .EQU 1 ; INT VECTOR INDEX
; ;
;================================================================================================== ;==================================================================================================
; DMA MODE BYTES
; DMA MODE BYTES - I/O ROUTINES CLEAR b3 AND ONLY PROGRAM LOW ADDRESS
;================================================================================================== ;==================================================================================================
; ;
DMA_CONTINUOUS .equ %10111101 ; + Pulse
DMA_BYTE .equ %10011101 ; + Pulse
DMA_BURST .equ %11011101 ; + Pulse
DMA_BYTE .equ %10011101 ; b7b1b0 = Register = 1xxxxx01 = Program R4
; b6b5 = Transfer Mode = x00xxxxx = Byte transfer mode
; b2 = start address (low) = xxxxx1xx = low address follows (1 byte)
; b3 = start address (high) = xxxx1xxx = high address follows (1 byte)
; b4 = int control byte = xxx1xxxx = interrupt, pulse or vector byte follow
;
DMA_CONTINUOUS .equ %10111101 ; b7b1b0 = Register = 1xxxxx01 = Program R4
; b6b5 = Transfer Mode = x01xxxxx = Continuous transfer mode (default)
; b2 = start address (low) = xxxxx1xx = low address follows (1 byte)
; b3 = start address (high) = xxxx1xxx = high address follows (1 byte)
; b4 = int control byte = xxx1xxxx = interrupt, pulse or vector byte follow
;
DMA_BURST .equ %11011101 ; b7b1b0 = Register = 1xxxxx01 = Program R4
; b6b5 = Transfer Mode = x10xxxxx = Burst transfer mode
; b2 = start address (low) = xxxxx1xx = low address follows (1 byte)
; b3 = start address (high) = xxxx1xxx = high address follows (1 byte)
; b4 = int control byte = xxx1xxxx = interrupt, pulse or vector byte follow
;
DMA_ICBYTE .equ %00001100 ; b7 = Interrupt Cont. Byte = 0xxxxxxx = Interrupt Control Byte identifier
; b6 = Interrupt on RDY = x0xxxxxx = Do not interrupt on RDY
; b5 = Status affects vector= xx0xxxxx = Status does not affect vector
; b4 = Interrupt vector byte= xxx0xxxx = No interrupt vector byte will follow
; b3 = Pulse control byte = xxxx1xxx = A pulse control byte will follow
; b2 = Pulse generation = xxxxx100 = A pulse will be generated
; b1 = Interrupt @ block end= xxxxxx0x = No interrupt at block end
; b0 = Interrupt on match = xxxxxxx0 = No interrupt on match
;
DMA_LOAD .equ $cf ; %11001111 DMA_LOAD .equ $cf ; %11001111
DMA_ENABLE .equ $87 ; %10000111 DMA_ENABLE .equ $87 ; %10000111
DMA_FORCE_READY .equ $b3 DMA_FORCE_READY .equ $b3
@ -64,6 +88,7 @@ DMA_REINIT_STATUS_BYTE .equ $8b
; ;
DMA_RDY .EQU %00001000 DMA_RDY .EQU %00001000
DMA_FORCE .EQU 0 DMA_FORCE .EQU 0
DMA_XMODE .equ 1 ; Byte = 0, Continuous = 1, Burst = 2
; ;
;================================================================================================== ;==================================================================================================
; ROMWBW HBIOS DEFINITIONS ; ROMWBW HBIOS DEFINITIONS
@ -116,6 +141,8 @@ MENULP: CALL DISPM ; DISPLAY MENU
; ;
MENULP1: MENULP1:
CALL NEWLINE CALL NEWLINE
CP 'C'
JP Z,DMACFG_C ; CONFIGURE XFER MODE
CP 'D' CP 'D'
JP Z,DMATST_D ; DUMP REGISTERS JP Z,DMATST_D ; DUMP REGISTERS
CP 'I' CP 'I'
@ -141,12 +168,33 @@ MENULP1:
JP Z,DMATST_Y ; TOGGLE READY JP Z,DMATST_Y ; TOGGLE READY
#ENDIF #ENDIF
cp 'S' cp 'S'
call z,DMACFG_S ; SET PORT
jp z,DMACFG_S ; SET PORT
cp 'V'
jp z,DMACFG_V ; TOGGLE VERBOSE
CP 'X' CP 'X'
JP Z,DMABYE ; EXIT JP Z,DMABYE ; EXIT
; ;
JR MENULP JR MENULP
; ;
DMABYE:
#IF (INTENABLE)
; Deinstall interrupt vector
ld hl,(orgvec) ; original vector
ld b,bf_sysint
ld c,bf_sysintset ; set new vector
ld e,INTIDX ; vector idx
di
rst 08 ; do it
ei ; interrupts back on
#ENDIF
;
LD SP,(SAVSTK) ; RESTORE CP/M STACK
RET
;
;==================================================================================================
; CONFIGURE PORT
;==================================================================================================
;
DMACFG_S: DMACFG_S:
call PRTSTRD call PRTSTRD
.db "\n\rSet port address\n\rPort:$" .db "\n\rSet port address\n\rPort:$"
@ -158,21 +206,6 @@ DMACFG_S:
ld (hl),a ld (hl),a
jp MENULP jp MENULP
; ;
DMABYE:
#IF (INTENABLE)
; Deinstall interrupt vector
ld hl,(orgvec) ; original vector
ld b,bf_sysint
ld c,bf_sysintset ; set new vector
ld e,INTIDX ; vector idx
di
rst 08 ; do it
ei ; interrupts back on
#ENDIF
;
LD SP,(SAVSTK) ; RESTORE CP/M STACK
RET
;
DMATST_I: DMATST_I:
call PRTSTRD call PRTSTRD
.db "\n\rStart Initialization\n\r$" .db "\n\rStart Initialization\n\r$"
@ -230,6 +263,16 @@ DMATST_R:
.db "\n\rPerforming Reset\n\r$" .db "\n\rPerforming Reset\n\r$"
; CALL ; CALL
JP MENULP JP MENULP
DMACFG_C:
CALL DMA_XferM
call PRTSTRD
.db "\n\rTransfer mode change to: $"
LD a,(dmaxfer)
LD DE,DMA_XFRMODE
CALL PRTIDXDEA
CALL NEWLINE
JP MENULP
; ;
;================================================================================================== ;==================================================================================================
; DISPLAY MENU ; DISPLAY MENU
@ -274,7 +317,6 @@ DISPM_INT:
#ENDIF #ENDIF
call PRTSTRD ; DISPLAY SPEED call PRTSTRD ; DISPLAY SPEED
.db "\n\rCPU at $" .db "\n\rCPU at $"
LD B,bf_sysget LD B,bf_sysget
LD C,bf_sysgetcpuspd ; GET CURRENT LD C,bf_sysgetcpuspd ; GET CURRENT
RST 08 ; SPEED SETTING RST 08 ; SPEED SETTING
@ -282,9 +324,14 @@ DISPM_INT:
LD A,L LD A,L
JR Z,SPDDISP JR Z,SPDDISP
LD A,3 LD A,3
;
SPDDISP:LD DE,DMA_SPD_STR SPDDISP:LD DE,DMA_SPD_STR
CALL PRTIDXDEA CALL PRTIDXDEA
;
call PRTSTRD
.db "\n\rTransfer Mode: $" ; DIPLAY TRANSFER
LD a,(dmaxfer) ; MODE
LD DE,DMA_XFRMODE
CALL PRTIDXDEA
CALL NEWLINE CALL NEWLINE
; ;
LD HL,MENU_OPT ; DISPLAY LD HL,MENU_OPT ; DISPLAY
@ -309,13 +356,16 @@ DMA_INIT:
LD A,DMA_FORCE LD A,DMA_FORCE
out (c),a ; force ready off out (c),a ; force ready off
#ENDIF #ENDIF
;
; ;
call DMAProbe ; do we have a dma? call DMAProbe ; do we have a dma?
jr nz,DMA_NOTFOUND jr nz,DMA_NOTFOUND
; ;
call PRTSTRD call PRTSTRD
.db " DMA Found\n\r$" .db " DMA Found\n\r$"
;
ld hl,DMAInitMode ; setup the
call SETXFER ; transfer mode
set 3,(hl) ; upper and lower address
; ;
ld hl,DMACode ; program the ld hl,DMACode ; program the
ld b,DMACode_Len ; dma command ld b,DMACode_Len ; dma command
@ -339,6 +389,27 @@ DMA_NOTFOUND:
DMA_FAIL_FLAG: DMA_FAIL_FLAG:
.db 0 .db 0
; ;
DMACode ;.db DMA_DISABLE ; R6-Command Disable DMA
.db %01111101 ; R0-Transfer mode, A -> B, start address, block length follow
.dw 0 ; R0-Port A, Start address
.dw 0 ; R0-Block length
.db %00010100 ; R1-No timing bytes follow, address increments, is memory
.db %00010000 ; R2-No timing bytes follow, address increments, is memory
.db %10000000 ; R3-DMA, interrupt, stop on match disabled
DMAInitMode: .db DMA_CONTINUOUS ; R4-Transfer mode, destination address, interrupt and control byte follow
.dw 0 ; R4-Port B, Destination address
.db DMA_ICBYTE ; R4-Pulse byte follows, Pulse generated
.db 0 ; R4-Pulse offset
.db %10010010+DMA_RDY; R5-Stop on end of block, ce/wait multiplexed, READY active config
.db DMA_LOAD ; R6-Command Load
; .db DMA_FORCE_READY ; R6-Command Force ready
; .db DMA_ENABLE ; R6-Command Enable DMA
DMACode_Len .equ $-DMACode
;
;==================================================================================================
; STRINGS
;==================================================================================================
;
DMA_DEV_STR: DMA_DEV_STR:
.TEXT "NONE$" .TEXT "NONE$"
.TEXT "ECB$" .TEXT "ECB$"
@ -354,8 +425,14 @@ DMA_SPD_STR:
.TEXT "double speed.$" .TEXT "double speed.$"
.TEXT "unknown speed.$" .TEXT "unknown speed.$"
; ;
DMA_XFRMODE:
.TEXT "Byte.$"
.TEXT "Continuous.$"
.TEXT "Burst.$"
;
MENU_OPT: MENU_OPT:
.TEXT "\n\r" .TEXT "\n\r"
.TEXT "C) Change transfer mode\n\r"
.TEXT "D) Dump DMA registers\n\r" .TEXT "D) Dump DMA registers\n\r"
.TEXT "I) Initialize DMA\n\r" .TEXT "I) Initialize DMA\n\r"
.TEXT "T) Toggle Interrupt Usage\n\r" .TEXT "T) Toggle Interrupt Usage\n\r"
@ -368,11 +445,36 @@ MENU_OPT:
.TEXT "Y) Test Ready Bit\n\r" .TEXT "Y) Test Ready Bit\n\r"
#ENDIF #ENDIF
.TEXT "S) Set DMA port\n\r" .TEXT "S) Set DMA port\n\r"
.TEXT "L) Set Latch port\n\r"
.TEXT "V) Verbose status toggle\n\r"
.TEXT "X) Exit\n\r" .TEXT "X) Exit\n\r"
.TEXT ">$" .TEXT ">$"
; ;
;================================================================================================== ;==================================================================================================
; TOGGLE TRANSFER MODE
;==================================================================================================
;
DMA_XferM: ; Set next transfer mode
ld a,(dmaxfer)
inc a
cp 3
jr nz,NextX
ld a,0
NextX: ld (dmaxfer),a
ret
;
;==================================================================================================
; TOGGLE VERBOSE MODE
;==================================================================================================
;
DMACFG_V:
ld a,(dmavbs)
cpl
ld (dmavbs),a
jp MENULP
;
;==================================================================================================
; OUTPUT A BUFFER OF TEXT TO AN IOPORT ; OUTPUT A BUFFER OF TEXT TO AN IOPORT
;================================================================================================== ;==================================================================================================
; ;
@ -393,19 +495,14 @@ IOLoop: push bc
ld bc,16 ld bc,16
; ;
call DMAOTIR call DMAOTIR
;
call PRTSTRD
.db " Return Status: $"
call PRTHEXBYTE
; ;
pop bc pop bc
djnz IOLoop djnz IOLoop
call NEWLINE call NEWLINE
ret ret
; ;
;================================================================================================== ;==================================================================================================
; PULSE PORT (COMMON ROUTINE WITH A CONTAINING ASCII PORT OFFSET)
; PULSE PORT (COMMON ROUTINE WHERE A CONTAINS THE ASCII PORT OFFSET)
;================================================================================================== ;==================================================================================================
; ;
DMA_Port01: DMA_Port01:
@ -480,7 +577,6 @@ portlp2:push bc
;================================================================================================== ;==================================================================================================
; ;
DMAMemMove: DMAMemMove:
;
LD HL,$8000 ; PREFILL DESTINATION WITH $55 LD HL,$8000 ; PREFILL DESTINATION WITH $55
LD A,$55 LD A,$55
LD (HL),A LD (HL),A
@ -513,10 +609,6 @@ DMAMemMove2:
; LD A,$00 ; BAD ; LD A,$00 ; BAD
; LD (HL),A ; SEED ; LD (HL),A ; SEED
; ;
call PRTSTRD
.db "Return Status: $"
call PRTHEXBYTE
LD A,$AA ; CHECK COPY SUCCESSFULL LD A,$AA ; CHECK COPY SUCCESSFULL
LD HL,$8000 LD HL,$8000
LD BC,4096 LD BC,4096
@ -616,23 +708,6 @@ DMAProbe:
cpl cpl
ret ret
; ;
DMACode ;.db DMA_DISABLE ; R6-Command Disable DMA
.db %01111101 ; R0-Transfer mode, A -> B, start address, block length follow
.dw 0 ; R0-Port A, Start address
.dw 0 ; R0-Block length
.db %00010100 ; R1-No timing bytes follow, address increments, is memory
.db %00010000 ; R2-No timing bytes follow, address increments, is memory
.db %10000000 ; R3-DMA, interrupt, stop on match disabled
.db DMA_CONTINUOUS ; R4-Continuous mode, destination address, interrupt and control byte follow
.dw 0 ; R4-Port B, Destination address
.db %00001100 ; R4-Pulse byte follows, Pulse generated
.db 0 ; R4-Pulse offset
.db %10010010+DMA_RDY; R5-Stop on end of block, ce/wait multiplexed, READY active config
.db DMA_LOAD ; R6-Command Load
; .db DMA_FORCE_READY ; R6-Command Force ready
; .db DMA_ENABLE ; R6-Command Enable DMA
DMACode_Len .equ $-DMACode
;
;================================================================================================== ;==================================================================================================
; DMA COPY BLOCK CODE - ASSUMES DMA PREINITIALIZED ; DMA COPY BLOCK CODE - ASSUMES DMA PREINITIALIZED
;================================================================================================== ;==================================================================================================
@ -641,6 +716,10 @@ DMALDIR:
ld (DMASource),hl ; populate the dma ld (DMASource),hl ; populate the dma
ld (DMADest),de ; register template ld (DMADest),de ; register template
ld (DMALength),bc ld (DMALength),bc
;
ld hl,DMACopyMode
call SETXFER
set 3,(hl) ; upper and lower address
; ;
ld hl,DMACopy ; program the ld hl,DMACopy ; program the
ld b,DMACopy_Len ; dma command ld b,DMACopy_Len ; dma command
@ -651,11 +730,7 @@ DMALDIR:
otir ; load and execute dma otir ; load and execute dma
ei ei
; ;
ld a,DMA_READ_STATUS_BYTE ; check status
out (c),a ; of transfer
in a,(c) ; set non-zero
; and %00111011 ; if failed
; sub %00011011
call DMASTATUS
ret ret
; ;
DMACopy ;.db DMA_DISABLE ; R6-Command Disable DMA DMACopy ;.db DMA_DISABLE ; R6-Command Disable DMA
@ -665,9 +740,9 @@ DMALength .dw 0 ; R0-Block length
.db %00010100 ; R1-No timing bytes follow, address increments, is memory .db %00010100 ; R1-No timing bytes follow, address increments, is memory
.db %00010000 ; R2-No timing bytes follow, address increments, is memory .db %00010000 ; R2-No timing bytes follow, address increments, is memory
.db %10000000 ; R3-DMA, interrupt, stop on match disabled .db %10000000 ; R3-DMA, interrupt, stop on match disabled
.db DMA_CONTINUOUS ; R4-Continuous mode, destination address, interrupt and control byte follow
DMACopyMode: .db DMA_CONTINUOUS ; R4-Transfer mode. Destination address, interrupt and control byte follow
DMADest .dw 0 ; R4-Port B, Destination address DMADest .dw 0 ; R4-Port B, Destination address
.db %00001100 ; R4-Pulse byte follows, Pulse generated
.db DMA_ICBYTE ; R4-Pulse byte follows, Pulse generated
.db 0 ; R4-Pulse offset .db 0 ; R4-Pulse offset
; .db %10010010+DMA_RDY;R5-Stop on end of block, ce/wait multiplexed, READY active config ; .db %10010010+DMA_RDY;R5-Stop on end of block, ce/wait multiplexed, READY active config
.db DMA_LOAD ; R6-Command Load .db DMA_LOAD ; R6-Command Load
@ -687,6 +762,10 @@ DMALDIRINT:
ld (DMASourceInt),hl ; populate the dma ld (DMASourceInt),hl ; populate the dma
ld (DMADestInt),de ; register template ld (DMADestInt),de ; register template
ld (DMALengthInt),bc ld (DMALengthInt),bc
;
ld hl,DMAICopyMode
call SETXFER
set 3,(hl) ; upper and lower address
; ;
ld hl,DMACopyInt ; program the ld hl,DMACopyInt ; program the
ld b,DMACopyInt_Len ; dma command ld b,DMACopyInt_Len ; dma command
@ -697,17 +776,7 @@ DMALDIRINT:
otir ; load and execute dma otir ; load and execute dma
ei ei
; ;
ld a,DMA_READ_STATUS_BYTE ; check status
out (c),a ; of transfer
in a,(c)
call PRTSTRD
.db "Return Status: $"
call PRTHEXBYTE
; and %00111011 ; set non-zero
; sub %00011011 ; if failed
;
call DMASTATUS
#ENDIF #ENDIF
; ;
ret ret
@ -721,7 +790,7 @@ DMALengthInt .dw 0 ; R0-Block length
.db %00010100 ; R1-No timing bytes follow, address increments, is memory .db %00010100 ; R1-No timing bytes follow, address increments, is memory
.db %00010000 ; R2-No timing bytes follow, address increments, is memory .db %00010000 ; R2-No timing bytes follow, address increments, is memory
.db %10100000 ; R3-DMA, interrupt, stop on match disabled .db %10100000 ; R3-DMA, interrupt, stop on match disabled
.db DMA_CONTINUOUS ; R4-Continuous mode, destination address, interrupt and control byte follow
DMAICopyMode: .db DMA_CONTINUOUS ; R4-Transfer mode, destination address, interrupt and control byte follow
DMADestInt .dw 0 ; R4-Port B, Destination address DMADestInt .dw 0 ; R4-Port B, Destination address
.db %00011110 ; R4-Interrupt control byte: Pulse byte follows, Pulse generated .db %00011110 ; R4-Interrupt control byte: Pulse byte follows, Pulse generated
.db 0 ; R4-Pulse control byte .db 0 ; R4-Pulse control byte
@ -743,6 +812,10 @@ DMAOTIR:
ld (DMAOutSource),hl ; populate the dma ld (DMAOutSource),hl ; populate the dma
ld (DMAOutDest),a ; register template ld (DMAOutDest),a ; register template
ld (DMAOutLength),bc ld (DMAOutLength),bc
;
ld hl,DMAOutMode
call SETXFER
res 3,(hl) ; no upper address
; ;
ld hl,DMAOutCode ; program the ld hl,DMAOutCode ; program the
ld b,DMAOut_Len ; dma command ld b,DMAOut_Len ; dma command
@ -753,14 +826,7 @@ DMAOTIR:
otir ; load and execute dma otir ; load and execute dma
ei ei
; ;
ld a,DMA_READ_STATUS_BYTE ; check status
out (c),a ; of transfer
in a,(c) ; set non-zero
; and %00111011 ; if failed
; sub %00011011
;
call DMASTATUS
ret ret
; ;
DMAOutCode ;.db DMA_DISABLE ; R6-Command Disable DMA DMAOutCode ;.db DMA_DISABLE ; R6-Command Disable DMA
@ -772,10 +838,10 @@ DMAOutLength .dw 0 ; R0-Block length
.db %00101000 ; R2-No timing bytes follow, address static, is i/o .db %00101000 ; R2-No timing bytes follow, address static, is i/o
.db %10000000 ; R3-DMA, interrupt, stop on match disabled .db %10000000 ; R3-DMA, interrupt, stop on match disabled
.db %10100101 ; R4-Continuous mode, destination port, interrupt and control byte follow
DMAOutMode: .db DMA_CONTINUOUS ; R4-Transfer Mode, destination port, interrupt and control byte follow
DMAOutDest .db 0 ; R4-Port B, Destination port DMAOutDest .db 0 ; R4-Port B, Destination port
; .db %00001100 ; R4-Pulse byte follows, Pulse generated
; .db 0 ; R4-Pulse offset
.db DMA_ICBYTE ; R4-Pulse byte follows, Pulse generated
.db 0 ; R4-Pulse offset
.db %10010010+DMA_RDY;R5-Stop on end of block, ce/wait multiplexed, READY active config .db %10010010+DMA_RDY;R5-Stop on end of block, ce/wait multiplexed, READY active config
.db DMA_LOAD ; R6-Command Load .db DMA_LOAD ; R6-Command Load
@ -794,6 +860,10 @@ DMAINIR:
ld (DMAInSource),a ; register template ld (DMAInSource),a ; register template
ld (DMAInLength),bc ld (DMAInLength),bc
; ;
ld hl,DMAOutMode
call SETXFER
res 3,(hl) ; no upper address
ld hl,DMAInCode ; program the ld hl,DMAInCode ; program the
ld b,DMAIn_Len ; dma command ld b,DMAIn_Len ; dma command
ld a,(dmaport) ; block ld a,(dmaport) ; block
@ -803,13 +873,7 @@ DMAINIR:
otir ; load and execute dma otir ; load and execute dma
ei ei
; ;
ld a,DMA_READ_STATUS_BYTE ; check status
out (c),a ; of transfer
in a,(c) ; set non-zero
; and %00111011 ; if failed
; sub %00011011
;
call DMASTATUS
ret ret
; ;
DMAInCode ;.db DMA_DISABLE ; R6-Command Disable DMA DMAInCode ;.db DMA_DISABLE ; R6-Command Disable DMA
@ -819,10 +883,10 @@ DMAInLength .dw 0 ; R0-Block length
.db %00010100 ; R1-No timing bytes follow, address increments, is memory .db %00010100 ; R1-No timing bytes follow, address increments, is memory
.db %00111000 ; R2-No timing bytes follow, address static, is i/o .db %00111000 ; R2-No timing bytes follow, address static, is i/o
.db %10000000 ; R3-DMA, interrupt, stop on match disabled .db %10000000 ; R3-DMA, interrupt, stop on match disabled
.db %10100101 ; R4-Continuous mode, destination port, no interrupt, control byte.
DMAInMode: .db DMA_CONTINUOUS ; R4-Transfer mode, destination port, no interrupt, control byte.
DMAInSource .db 0 ; R4-Port B, Destination port DMAInSource .db 0 ; R4-Port B, Destination port
; .db %00001100 ; R4-Pulse byte follows, Pulse generated
; .db 0 ; R4-Pulse offset
.db DMA_ICBYTE ; R4-Pulse byte follows, Pulse generated
.db 0 ; R4-Pulse offset
.db %10010010+DMA_RDY;R5-Stop on end of block, ce/wait multiplexed, READY active config .db %10010010+DMA_RDY;R5-Stop on end of block, ce/wait multiplexed, READY active config
.db DMA_LOAD ; R6-Command Load .db DMA_LOAD ; R6-Command Load
.db DMA_FORCE_READY ; R6-Command Force ready .db DMA_FORCE_READY ; R6-Command Force ready
@ -831,6 +895,99 @@ DMAInSource .db 0 ; R4-Port B, Destination port
DMAIn_Len .equ $-DMAInCode DMAIn_Len .equ $-DMAInCode
; ;
;================================================================================================== ;==================================================================================================
; SET TRANSFER MODE
;==================================================================================================
;
SETXFER:
ld a,(dmaxfer) ; setup the
cp 0 ; transfer mode
jr nz,DMAX1
ld a,DMA_BYTE
jr DMAX3
DMAX1: cp 1
jr nz,DMAX2
ld a,DMA_CONTINUOUS
jr DMAX3
DMAX2: cp 2
ret nz
ld a,DMA_BURST
DMAX3: ld (hl),a
ret
;
;==================================================================================================
; GET STATUS
;==================================================================================================
;
DMASTATUS:
ld a,(dmaxfer) ; if byte mode
cp 0 ; give some time to finish
jr nz,DMASTS1
; ld b,1
;DMASTS2:call delay
; djnz DMASTS2
;
DMASTS1:ld a,DMA_READ_STATUS_BYTE ; check status
out (c),a ; of transfer
in a,(c)
and %00111011
;
; push af
; ld a,DMA_REINIT_STATUS_BYTE
; out (c),a
; pop af
;
call PRTSTRD
.db "\n\rReturn Status: $"
call PRTHEXBYTE
call NEWLINE
;
ld c,a
ld a,(dmavbs)
or a
jr z,DMSSTS2
ld a,c
;
ld a,%00000001
ld de,DMASTSBIT0
call PRTIDXMSK
;
ld a,%00000010
ld de,DMASTSBIT1
call PRTIDXMSK
;
ld a,%00001000
ld de,DMASTSBIT3
call PRTIDXMSK
;
ld a,%00010000
ld de,DMASTSBIT4
call PRTIDXMSK
;
ld a,%00100000
ld de,DMASTSBIT5
call PRTIDXMSK
;
DMSSTS2:ld a,c
ret
DMASTSBIT0:
.TEXT "DMA Bus request did not occur after LOAD command\n\r$"
.TEXT "DMA Bus request occurred after the LOAD command\n\r$"
DMASTSBIT1:
.TEXT "Ready line inactive\n\r$"
.TEXT "Ready line active\n\r$"
DMASTSBIT3:
.TEXT "Interrupt pending\n\r$"
.TEXT "No interrupt pending\n\r$"
DMASTSBIT4:
.TEXT "Match found\n\r$"
.TEXT "No match found\n\r$"
DMASTSBIT5:
.TEXT "End of block reached\n\r$"
.TEXT "End of block not reached\n\r$"
;
;==================================================================================================
; DEBUG - READ START, DESTINATION AND COUNT REGISTERS ; DEBUG - READ START, DESTINATION AND COUNT REGISTERS
;================================================================================================== ;==================================================================================================
; ;
@ -1010,7 +1167,11 @@ CST:
RET RET
; ;
USEINT .DB FALSE ; USE INTERRUPTS FLAG USEINT .DB FALSE ; USE INTERRUPTS FLAG
;
counter .dw 0
dmaport .db DMABASE
dmautil .db DMABASE+1
dmaxfer .db DMA_XMODE
dmavbs .db 0
SAVSTK: .DW 2 SAVSTK: .DW 2
.FILL 64 .FILL 64
STACK: .EQU $ STACK: .EQU $
@ -1050,10 +1211,6 @@ int:
or $ff ; signal int handled or $ff ; signal int handled
ret ret
; ;
counter .dw 0
dmaport .db DMABASE
dmautil .db DMABASE+1
;
hsiz .equ $ - $A000 ; size of handler to relocate hsiz .equ $ - $A000 ; size of handler to relocate
; ;
.org reladr + hsiz .org reladr + hsiz

Loading…
Cancel
Save