1
0
mirror of https://github.com/cc65/cc65.git synced 2025-01-19 02:33:19 +00:00

Cleanup coding style a bit

This commit is contained in:
Colin Leroy-Mira 2023-09-30 11:09:27 +02:00 committed by Oliver Schmidt
parent 4ff917816e
commit df4902157a

View File

@ -38,8 +38,8 @@
.endif .endif
; Driver signature ; Driver signature
.byte $73, $65, $72 ; "ser" .byte $73, $65, $72 ; "ser"
.byte SER_API_VERSION ; Serial API version number .byte SER_API_VERSION ; Serial API version number
; Library reference ; Library reference
.addr $0000 .addr $0000
@ -59,16 +59,16 @@
; I/O definitions ; I/O definitions
.if (.cpu .bitand CPU_ISET_65C02) .if (.cpu .bitand CPU_ISET_65C02)
ACIA = $C088 ACIA := $C088
.else .else
Offset = $8F ; Move 6502 false read out of I/O to page $BF Offset = $8F ; Move 6502 false read out of I/O to page $BF
ACIA = $C088-Offset ACIA := $C088-Offset
.endif .endif
ACIA_DATA = ACIA+0 ; Data register ACIA_DATA := ACIA+0 ; Data register
ACIA_STATUS = ACIA+1 ; Status register ACIA_STATUS := ACIA+1 ; Status register
ACIA_CMD = ACIA+2 ; Command register ACIA_CMD := ACIA+2 ; Command register
ACIA_CTRL = ACIA+3 ; Control register ACIA_CTRL := ACIA+3 ; Control register
;---------------------------------------------------------------------------- ;----------------------------------------------------------------------------
; Global variables ; Global variables
@ -77,16 +77,17 @@ ACIA_CTRL = ACIA+3 ; Control register
RecvHead: .res 1 ; Head of receive buffer RecvHead: .res 1 ; Head of receive buffer
RecvTail: .res 1 ; Tail of receive buffer RecvTail: .res 1 ; Tail of receive buffer
RecvFreeCnt: .res 1 ; Number of bytes in receive buffer RecvFreeCnt: .res 1 ; Number of free bytes in receive buffer
SendHead: .res 1 ; Head of send buffer SendHead: .res 1 ; Head of send buffer
SendTail: .res 1 ; Tail of send buffer SendTail: .res 1 ; Tail of send buffer
SendFreeCnt: .res 1 ; Number of bytes in send buffer SendFreeCnt: .res 1 ; Number of free bytes in send buffer
Stopped: .res 1 ; Flow-stopped flag Stopped: .res 1 ; Flow-stopped flag
RtsOff: .res 1 ; RtsOff: .res 1 ; Cached value of command register with
; flow stopped
RecvBuf: .res 256 ; Receive buffers: 256 bytes RecvBuf: .res 256 ; Receive buffer: 256 bytes
SendBuf: .res 256 ; Send buffers: 256 bytes SendBuf: .res 256 ; Send buffer: 256 bytes
Index: .res 1 ; I/O register index Index: .res 1 ; I/O register index
@ -96,8 +97,9 @@ Slot: .byte $02 ; Default to SSC in slot 2
.rodata .rodata
; Tables used to translate RS232 params into register values BaudTable: ; Table used to translate RS232 baudrate param
BaudTable: ; bit7 = 1 means setting is invalid ; into control register value
; bit7 = 1 means setting is invalid
.byte $FF ; SER_BAUD_45_5 .byte $FF ; SER_BAUD_45_5
.byte $01 ; SER_BAUD_50 .byte $01 ; SER_BAUD_50
.byte $02 ; SER_BAUD_75 .byte $02 ; SER_BAUD_75
@ -118,49 +120,55 @@ BaudTable: ; bit7 = 1 means setting is invalid
.byte $FF ; SER_BAUD_57600 .byte $FF ; SER_BAUD_57600
.byte $FF ; SER_BAUD_115200 .byte $FF ; SER_BAUD_115200
.byte $FF ; SER_BAUD_230400 .byte $FF ; SER_BAUD_230400
BitTable:
BitTable: ; Table used to translate RS232 databits param
; into control register value
.byte $60 ; SER_BITS_5 .byte $60 ; SER_BITS_5
.byte $40 ; SER_BITS_6 .byte $40 ; SER_BITS_6
.byte $20 ; SER_BITS_7 .byte $20 ; SER_BITS_7
.byte $00 ; SER_BITS_8 .byte $00 ; SER_BITS_8
StopTable:
StopTable: ; Table used to translate RS232 stopbits param
; into control register value
.byte $00 ; SER_STOP_1 .byte $00 ; SER_STOP_1
.byte $80 ; SER_STOP_2 .byte $80 ; SER_STOP_2
ParityTable:
ParityTable: ; Table used to translate RS232 parity param
; into command register value
.byte $00 ; SER_PAR_NONE .byte $00 ; SER_PAR_NONE
.byte $20 ; SER_PAR_ODD .byte $20 ; SER_PAR_ODD
.byte $60 ; SER_PAR_EVEN .byte $60 ; SER_PAR_EVEN
.byte $A0 ; SER_PAR_MARK .byte $A0 ; SER_PAR_MARK
.byte $E0 ; SER_PAR_SPACE .byte $E0 ; SER_PAR_SPACE
; Check five bytes at known positions on the IdOfsTable: ; Table of bytes positions, used to check five
; slot's firmware to make sure this is an SSC ; specific bytes on the slot's firmware to make
; (or Apple //c comm port) firmware that drives ; sure this is an SSC (or Apple //c comm port)
; an ACIA 6551 chip. ; firmware that drives an ACIA 6551 chip.
; ;
; The SSC firmware and the Apple //c(+) comm ; The SSC firmware and the Apple //c(+) comm
; port firmware all begin with a BIT instruction. ; port firmware all begin with a BIT instruction.
; The IIgs, on the other hand, has a ; The IIgs, on the other hand, has a
; Zilog Z8530 chip and its firmware starts with ; Zilog Z8530 chip and its firmware starts with
; a SEP instruction. We don't want to load this ; a SEP instruction. We don't want to load this
; driver on the IIgs' serial port. We'll ; driver on the IIgs' serial port. We'll
; differentiate the firmware on this byte. ; differentiate the firmware on this byte.
; ;
; The next four bytes we check are the Pascal ; The next four bytes we check are the Pascal
; Firmware Protocol Bytes that identify a ; Firmware Protocol Bytes that identify a
; serial card. Those are the same bytes for ; serial card. Those are the same bytes for
; SSC firmwares, Apple //c firmwares and IIgs ; SSC firmwares, Apple //c firmwares and IIgs
; Zilog Z8530 firmwares - which is the reason ; Zilog Z8530 firmwares - which is the reason
; we have to check for the firmware's first ; we have to check for the firmware's first
; instruction too. ; instruction too.
IdOfsTable:
.byte $00 ; First instruction .byte $00 ; First instruction
.byte $05 ; Pascal 1.0 ID byte .byte $05 ; Pascal 1.0 ID byte
.byte $07 ; Pascal 1.0 ID byte .byte $07 ; Pascal 1.0 ID byte
.byte $0B ; Pascal 1.1 generic signature byte .byte $0B ; Pascal 1.1 generic signature byte
.byte $0C ; Device signature byte .byte $0C ; Device signature byte
IdValTable:
IdValTable: ; Table of expected values for the five checked
; bytes
.byte $2C ; BIT .byte $2C ; BIT
.byte $38 ; ID Byte 0 (from Pascal 1.0), fixed .byte $38 ; ID Byte 0 (from Pascal 1.0), fixed
.byte $18 ; ID Byte 1 (from Pascal 1.0), fixed .byte $18 ; ID Byte 1 (from Pascal 1.0), fixed
@ -193,12 +201,10 @@ SER_CLOSE:
ldx Index ; Check for open port ldx Index ; Check for open port
beq :+ beq :+
; Deactivate DTR and disable 6551 interrupts lda #%00001010 ; Deactivate DTR and disable 6551 interrupts
lda #%00001010
sta ACIA_CMD,x sta ACIA_CMD,x
; Done, return an error code : lda #SER_ERR_OK ; Done, return an error code
: lda #SER_ERR_OK
.assert SER_ERR_OK = 0, error .assert SER_ERR_OK = 0, error
tax tax
stx Index ; Mark port as closed stx Index ; Mark port as closed
@ -215,98 +221,96 @@ SER_OPEN:
ora Slot ora Slot
sta ptr2+1 sta ptr2+1
; Check Pascal 1.1 Firmware Protocol ID bytes : ldy IdOfsTable,x ; Check Pascal 1.1 Firmware Protocol ID bytes
: ldy IdOfsTable,x
lda IdValTable,x lda IdValTable,x
cmp (ptr2),y cmp (ptr2),y
bne NoDevice bne NoDev
inx inx
cpx #IdTableLen cpx #IdTableLen
bcc :- bcc :-
; Convert slot to I/O register index lda Slot ; Convert slot to I/O register index
lda Slot
asl asl
asl asl
asl asl
asl asl
.if .not (.cpu .bitand CPU_ISET_65C02) .if .not (.cpu .bitand CPU_ISET_65C02)
adc #Offset ; Assume carry to be clear adc #Offset ; Assume carry to be clear
.endif .endif
tax tax
; Check if the handshake setting is valid ; Check if the handshake setting is valid
ldy #SER_PARAMS::HANDSHAKE ; Handshake ldy #SER_PARAMS::HANDSHAKE
lda (ptr1),y lda (ptr1),y
cmp #SER_HS_HW ; This is all we support cmp #SER_HS_HW ; This is all we support
bne InvParam bne InvParm
; Initialize buffers ldy #$00 ; Initialize buffers
ldy #$00
sty Stopped sty Stopped
sty RecvHead sty RecvHead
sty RecvTail sty RecvTail
sty SendHead sty SendHead
sty SendTail sty SendTail
dey ; Y = 255 dey ; Y = 255
sty RecvFreeCnt sty RecvFreeCnt
sty SendFreeCnt sty SendFreeCnt
; Set the value for the control register, which contains stop bits, ; Set the value for the control register, which contains stop bits,
; word length and the baud rate. ; word length and the baud rate.
ldy #SER_PARAMS::BAUDRATE ldy #SER_PARAMS::BAUDRATE
lda (ptr1),y ; Baudrate index lda (ptr1),y ; Baudrate index
tay tay
lda BaudTable,y ; Get 6551 value lda BaudTable,y ; Get 6551 value
bmi InvBaud ; Branch if rate not supported bmi InvBaud ; Branch if rate not supported
sta tmp1 sta tmp1
ldy #SER_PARAMS::DATABITS ; Databits ldy #SER_PARAMS::DATABITS
lda (ptr1),y lda (ptr1),y ; Databits index
tay tay
lda BitTable,y lda BitTable,y ; Get 6551 value
ora tmp1 ora tmp1
sta tmp1 sta tmp1
ldy #SER_PARAMS::STOPBITS ; Stopbits ldy #SER_PARAMS::STOPBITS
lda (ptr1),y lda (ptr1),y ; Stopbits index
tay tay
lda StopTable,y lda StopTable,y ; Get 6551 value
ora tmp1 ora tmp1
ora #%00010000 ; Receiver clock source = baudrate ora #%00010000 ; Set receiver clock source = baudrate
sta ACIA_CTRL,x sta ACIA_CTRL,x
; Set the value for the command register. We remember the base value ; Set the value for the command register. We remember the base value
; in RtsOff, since we will have to manipulate ACIA_CMD often. ; in RtsOff, since we will have to manipulate ACIA_CMD often.
ldy #SER_PARAMS::PARITY ; Parity ldy #SER_PARAMS::PARITY
lda (ptr1),y lda (ptr1),y ; Parity index
tay tay
lda ParityTable,y lda ParityTable,y ; Get 6551 value
ora #%00000001 ; DTR active
sta RtsOff ora #%00000001 ; Set DTR active
ora #%00001000 ; Enable receive interrupts sta RtsOff ; Store value to easily handle flow control later
ora #%00001000 ; Enable receive interrupts (RTS low)
sta ACIA_CMD,x sta ACIA_CMD,x
; Done ; Done
stx Index ; Mark port as open stx Index ; Mark port as open
lda #SER_ERR_OK lda #SER_ERR_OK
.assert SER_ERR_OK = 0, error .assert SER_ERR_OK = 0, error
tax tax
rts rts
; Device (hardware) not found ; Device (hardware) not found
NoDevice:lda #SER_ERR_NO_DEVICE NoDev: lda #SER_ERR_NO_DEVICE
ldx #0 ; return value is char ldx #$00 ; return value is char
rts rts
; Invalid parameter ; Invalid parameter
InvParam:lda #SER_ERR_INIT_FAILED InvParm:lda #SER_ERR_INIT_FAILED
ldx #0 ; return value is char ldx #$00 ; return value is char
rts rts
; Baud rate not available ; Baud rate not available
InvBaud:lda #SER_ERR_BAUD_UNAVAIL InvBaud:lda #SER_ERR_BAUD_UNAVAIL
ldx #0 ; return value is char ldx #$00 ; return value is char
rts rts
;---------------------------------------------------------------------------- ;----------------------------------------------------------------------------
@ -317,21 +321,19 @@ InvBaud:lda #SER_ERR_BAUD_UNAVAIL
SER_GET: SER_GET:
ldx Index ldx Index
; Check for buffer empty lda RecvFreeCnt ; Check for buffer empty
lda RecvFreeCnt ; (25)
cmp #$FF cmp #$FF
bne :+ bne :+
lda #SER_ERR_NO_DATA lda #SER_ERR_NO_DATA
ldx #0 ; return value is char ldx #$00 ; return value is char
rts rts
; Check for flow stopped & enough free: release flow control : ldy Stopped ; Check for flow stopped
: ldy Stopped ; (34)
beq :+ beq :+
cmp #63 cmp #63 ; Enough free?
bcc :+ bcc :+
.if (.cpu .bitand CPU_ISET_65C02) .if (.cpu .bitand CPU_ISET_65C02)
stz Stopped stz Stopped ; Release flow control
.else .else
lda #$00 lda #$00
sta Stopped sta Stopped
@ -340,14 +342,13 @@ SER_GET:
ora #%00001000 ora #%00001000
sta ACIA_CMD,x sta ACIA_CMD,x
; Get byte from buffer : ldy RecvHead ; Get byte from buffer
: ldy RecvHead ; (41)
lda RecvBuf,y lda RecvBuf,y
inc RecvHead inc RecvHead
inc RecvFreeCnt inc RecvFreeCnt
ldx #$00 ; (59) ldx #$00
.if (.cpu .bitand CPU_ISET_65C02) .if (.cpu .bitand CPU_ISET_65C02)
sta (ptr1) sta (ptr1) ; Store it for caller
.else .else
sta (ptr1,x) sta (ptr1,x)
.endif .endif
@ -361,29 +362,26 @@ SER_GET:
SER_PUT: SER_PUT:
ldx Index ldx Index
; Try to send ldy SendFreeCnt ; Anything to send first?
ldy SendFreeCnt cpy #$FF ; No
cpy #$FF ; Nothing to flush
beq :+ beq :+
pha pha
lda #$00 ; TryHard = false lda #$00 ; TryHard = false
jsr TryToSend jsr TryToSend ; Try to flush send buffer
pla pla
; Reload SendFreeCnt after TryToSend ldy SendFreeCnt ; Reload SendFreeCnt after TryToSend
ldy SendFreeCnt
bne :+ bne :+
lda #SER_ERR_OVERFLOW lda #SER_ERR_OVERFLOW
ldx #0 ; return value is char ldx #$00 ; return value is char
rts rts
; Put byte into send buffer & send : ldy SendTail ; Put byte into send buffer
: ldy SendTail
sta SendBuf,y sta SendBuf,y
inc SendTail inc SendTail
dec SendFreeCnt dec SendFreeCnt
lda #$FF ; TryHard = true lda #$FF ; TryHard = true
jsr TryToSend jsr TryToSend ; Flush send buffer
lda #SER_ERR_OK lda #SER_ERR_OK
.assert SER_ERR_OK = 0, error .assert SER_ERR_OK = 0, error
tax tax
@ -405,26 +403,25 @@ SER_STATUS:
;---------------------------------------------------------------------------- ;----------------------------------------------------------------------------
; SER_IOCTL: Driver defined entry point. The wrapper will pass a pointer to ioctl ; SER_IOCTL: Driver defined entry point. The wrapper will pass a pointer to ioctl
; specific data in ptr1, and the ioctl code in A. ; specific data in ptr1, and the ioctl code in A.
; The ioctl data is the slot number to open.
; Must return an SER_ERR_xx code in a/x. ; Must return an SER_ERR_xx code in a/x.
SER_IOCTL: SER_IOCTL:
; Check data msb and code to be 0 ora ptr1+1 ; Check data msb and code to be 0
ora ptr1+1
bne :+ bne :+
; Check data lsb to be [1..7] ldx ptr1 ; Check data lsb to be [1..7]
ldx ptr1
beq :+ beq :+
cpx #7+1 cpx #7+1
bcs :+ bcs :+
stx Slot stx Slot ; Store slot
.assert SER_ERR_OK = 0, error .assert SER_ERR_OK = 0, error
tax tax
rts rts
: lda #SER_ERR_INV_IOCTL : lda #SER_ERR_INV_IOCTL
ldx #0 ; return value is char ldx #$00 ; return value is char
rts rts
;---------------------------------------------------------------------------- ;----------------------------------------------------------------------------
@ -450,8 +447,7 @@ SER_IRQ:
bcc Flow ; Assert flow control if buffer space low bcc Flow ; Assert flow control if buffer space low
rts ; Interrupt handled (carry already set) rts ; Interrupt handled (carry already set)
; Assert flow control if buffer space too low Flow: ldx Index ; Assert flow control if buffer space too low
Flow: ldx Index
lda RtsOff lda RtsOff
sta ACIA_CMD,x sta ACIA_CMD,x
sta Stopped sta Stopped
@ -464,26 +460,23 @@ Done: rts
TryToSend: TryToSend:
sta tmp1 ; Remember tryHard flag sta tmp1 ; Remember tryHard flag
NextByte: NextByte:
lda SendFreeCnt lda SendFreeCnt ; Is there anything to send? This can happen if
cmp #$FF cmp #$FF ; we got interrupted by RX while sending, and
beq Quit ; Bail out beq Quit ; flow control was asserted.
; Check for flow stopped Again: lda Stopped ; Is flow stopped?
Again: lda Stopped bne Quit ; Yes, Bail out
bne Quit ; Bail out
; Check that ACIA is ready to send lda ACIA_STATUS,x ; Check that ACIA is ready to send
lda ACIA_STATUS,x
and #$10 and #$10
bne Send bne Send ; It is!
bit tmp1 ; Keep trying if must try hard bit tmp1 ; Keep trying if must try hard
bmi Again bmi Again
Quit: rts Quit: rts
; Send byte and try again Send: ldy SendHead ; Get first byte to send
Send: ldy SendHead
lda SendBuf,y lda SendBuf,y
sta ACIA_DATA,x sta ACIA_DATA,x ; Send it
inc SendHead inc SendHead
inc SendFreeCnt inc SendFreeCnt
jmp NextByte jmp NextByte ; And try next one