Subversion Repositories MB01 Project

Rev

Blame | Last modification | View Log | Download | RSS feed

;;
;; Copyright (c) 2016 Marco Granati <mg@unet.bz>
;;
;; Permission to use, copy, modify, and distribute this software for any
;; purpose with or without fee is hereby granted, provided that the above
;; copyright notice and this permission notice appear in all copies.
;;
;; THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES
;; WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF
;; MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR
;; ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES
;; WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN
;; ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF
;; OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
;;

;; name: sp.asm 
;; rev.: 2016/07/28
;; bios C816 version v1.0

;; serial port handler

_ACIA_INC_      .SET    1

        .INCLUDE INC\GLOBAL.INC
        .INCLUDE INC\DIRP00.INC

.LIST   on

; page 0 local var's (declared in bios temp. work area)
_P0BTMP:        .SECTION page0, ref_only, offset bwrktmp        ; DP Tmp. BIOS

crc16           .DW
bycnt           .DW             ; data packet lenght
byndx           .DW             ; data buffer index
pkttyp          .DB             ; expected packet type
pktnum          .DB             ; current packet number
expect          .DB             ; expected packet number
tmpx            .DB

        .ENDS

        .CODEF8
        
        .LONGA  off
        .LONGI  off

; X=serial port
_spget0:
        txa
        bne     _spget1
        
        SPGETB  0
        
_spget1:
        SPGETB  1

; X=serial port
        .PUBLIC _spput0
_spput0:
        txy
        bne     _spput1
        
        SPPUTB  0
        
_spput1:
        SPPUTB  1
        
; A=mode, X=serial #
spset:
        txy
        beq     ?sr0            ; serial #0
        ldx     #4              ; serial #1
?sr0:   sei                     ; disable interrupt
        sta     spmode,x
        tay
        lda     #$7F            ; disable all interrupts
        sta     .ABS.ACIAIER,x
        lda     .ABS.ACIARDR,x  ; discard any pending received data
        lda     .ABS.ACIAISR,x  ; read current interrupt status
        lda     .ABS.ACIACSR,x  ; save current control status
        sta     spcsr,x
        tya                     ; mode
        and     #00001100B      ; mask on bits 3 & 2 (parity mode)
        ora     #11100000B      ; 8 data bits, RTS=DTR=low
        sta     spfr,x          ; value of format register
        ;ora    #00000011B
        sta     .ABS.ACIAFR,x   ; set format register: RTS=DTR=1
        tya     
        ldy     #01001110B      ; access to ACR, one stop bit, 38400
        bit     #00010000B
        bne     ?br             ; select baud rate=38400
        ldy     #01001101B      ; access to ACR, one stop bit, 19200
?br:    tya
        sta     .ABS.ACIACR,x   ; set control register
        stz     .ABS.ACIAACR,x  ; set aux. control reg. (normal tx, parity)
        lda     #$80
        tsb     VIA1+VIAPRANH   ; enble RS232
        lda     #00000010B      ; check RS485
        bit     spmode,x
        beq     ?cnt            ; interface type: RS232
        lda     spmode,x
        and     #10111111B      ; software handshake only for RS485
        sta     spmode,x
        lda     #$80
        trb     VIA1+VIAPRANH   ; enble RS485 interface
        lda     #$40
        trb     VIA0+VIAPRANH   ; disable 120 ohm termination
        lda     #00000001B      ; check termination status
        bit     spmode,x
        beq     ?cnt            ; termination off
        lda     #$40
        tsb     VIA0+VIAPRANH   ; enable 120 ohm termination
?cnt:   stz     sppause,x       ; init work area
        stz     spout,x
        stz     spstat,x
        bit     spmode,x
        CPU16                   ; init buffer's pointer's
        bvs     ?hw             ; hardware handshake
        lda     #NGUARD1
        ldy     #NFREE1
        bra     ?do
?hw:    lda     #NGUARD2
        ldy     #NFREE2
?do:    sta     icntmax,x
        sty     icntmin,x
        sec
        lda     #SIBUFSIZ
        sbc     icntmax,x
        sta     icntmax,x
        stz     ibuftail,x
        stz     ibufhead,x
        stz     ibufcnt,x
        stz     obuftail,x
        stz     obufhead,x
        stz     obufcnt,x
        CPU08
        lda     .ABS.ACIARDR,x  ; discard any pending received data
        lda     .ABS.ACIAISR,x  ; read current interrupt status
        lda     .ABS.ACIACSR,x  ; save current control status
        sta     spcsr,x
        and     #00111011B      ; mask lines level
        bit     #00001000B      ; check DSR line level
        beq     ?sav            ; DSR is low
        ora     #01000000B      ; DSR is high
?sav:   asl     a               ; 7:DSR, 6:CTS, 5:DCD, 2:DTR, 1:RTS
        sta     splin,x         ; save lines level
        lda     #$F9            ; enable interrupts
        sta     .ABS.ACIAIER,x
        cli
        rts

; X=serial #
spres:
        txy
        beq     ?sr0            ; serial #0
        ldx     #4              ; serial #1
?sr0:   sei                     ; disable interrupt
        lda     #$7F            ; disable all interrupts
        sta     .ABS.ACIAIER,x
        lda     spfr,x
        ora     #00000011B      ; set RTS=DTR=1
        sta     .ABS.ACIAFR,x
        lda     .ABS.ACIARDR,x  ; discard any pending received data
        lda     .ABS.ACIAISR,x  ; read current interrupt status
        lda     .ABS.ACIACSR,x  ; save current control status
        sta     spcsr,x
        cli
        rts

;---- TRANSFER

; X=port (0 or 4)
; get byte with timeout
sptget:
        lda     #$20            ; set T2 count PB6 pulse (1ms)
        tsb     .ABS.VIA0+VIAACR        
        stz     .ABS.VIA0+VIAT2CL
        lda     #4              ; set 1024ms timeout
        sta     .ABS.VIA0+VIAT2CH
?lp:    jsr     _spget0         ; get byte within timeout
        bcc     ?exit           ; ok, data available
        tay                     ; CF=1 here
        bne     ?exit           ; some rx error(s) 
        lda     #T2IFRB
        bit     .ABS.VIA0+VIAIFR
        beq     ?lp             ; no timeout: loop
        lda     #$08            ; set timeout error - CF=1 here
?exit:  rts

sndnack:
        ;ldy    #NACK
        bra     sndack2
        
sndack:
        ldy     #ACK
        
sndack2:
        sty     tmpx
        lda     #SYN
        jsr     sptput
        bcs     exit1
        lda     tmpx
        jsr     sptput
        bcs     exit1
        lda     pktnum

spxput:
        cmp     #SYN
        beq     ?esc
        cmp     #SPXON
        beq     ?esc
        cmp     #SPXOFF
        beq     ?esc
        cmp     #DLE
        bne     sptput
?esc:   eor     #$20
        sta     tmpx
        lda     #DLE
        jsr     sptput
        bcs     exit1
        lda     tmpx

; X=port (0 or 4)
; put byte with timeout
sptput:
        tay                     ; Y=data
        lda     #$20            ; set T2 count PB6 pulse (1ms)
        tsb     .ABS.VIA0+VIAACR        
        stz     .ABS.VIA0+VIAT2CL
        lda     #4              ; set 1024ms timeout
        sta     .ABS.VIA0+VIAT2CH
?lp:    tya                     ; byte to send  
        jsr     _spput0         ; put byte within timeout
        bcc     exit1           ; ok
        iny                     ; Y=$FF if remote disconnession
        beq     ?err            ; remote terminal disconnected
        tay                     ; Y=data
        lda     #T2IFRB
        bit     .ABS.VIA0+VIAIFR
        beq     ?lp             ; no timeout: loop
        tya                     ; restore data
?err:   ldy     #$80            ; timeout or remote disconnession
exit1:  rts

; frame alignment
; A=expected packet type (SOH or STX)
; X=0 (serial port 0)
; exit with CF=0 if no error (ZF=0 if STX/SOH, ZF=1 if EOT)
fndsyn:
        sta     pkttyp  
        jsr     sptget
        bcs     ?done           ; error
        cmp     #SYN
        bne     fndsyn          ; skip bytes until find start of trame
?lp:    jsr     sptget          ; next byte
        bcs     ?done           ; error
        cmp     #SYN            ; discard further consecutive sync's
        beq     ?lp
        cmp     pkttyp          ; expected SOH, STX or EOT
        bne     ?eot
        lda     #$FF            ; initialize crc computation
        sta     crc16
        sta     crc16+1         ; if received STX or SOH exit with ZF=0 
?ok:    clc                     ; no error
        rts
?eot:   ldy     pkttyp          ; when expect STX, an EOT is legal
        cpy     #STX
        bne     ?err            ; unexpected packet type
        cmp     #EOT            ; received an EOT?
        beq     ?ok             ; exit with ZF=1 (EOT)
?err:   lda     #$10            ; unexpected packet type error  
        sec
?done:  rts

; get escaped byte
; X=serial port
spxget:
        jsr     sptget
        bcs     ?done
        cmp     #SYN            ; here a SYN is an error
        beq     ?done           ; exit 
        cmp     #DLE
        bne     ?ok
        jsr     sptget
        bcs     ?done
        eor     #$20
?ok:    clc
?done:  rts

updcrc:
        tay
        eor     crc16+1         ; quick CRC computation with lookup tables
        tax                     ; index for lookup table
        lda     crc16
        eor     >crchi,x
        sta     crc16+1
        lda     >crclo,x
        sta     crc16
        tya
        rts

; X=serial port (0 or 4)
getdat:
        ACC16
        lda     #$200
        ldy     pkttyp
        cpy     #STX
        beq     ?st
        lda     #$10
?st:    sta     bycnt
        stz     byndx
        ACC08
?lp:    jsr     spxget
        bcs     ?err
        jsr     updcrc
        INDEX16
        ldx     byndx
        sta     >SPBUF,x
        inx
        stx     byndx
        cpx     bycnt
        INDEX08
        ldx     #0
        bcc     ?lp
        jsr     spxget
        bcs     ?err
        cmp     crc16
        bne     ?err
        jsr     spxget
        bcs     ?err
        cmp     crc16+1
        bne     ?err
        clc
        rts
?err:   sec
        rts
        
; X=serial port (0 or 4)
getpkt:
        lda     #STX
        jsr     fndsyn
        bcs     ?done
        jsr     spxget
        bcs     ?done
        sta     pktnum
        jsr     spxget
        bcs     ?done
        eor     #$FF
        cmp     pktnum
        bne     ?err
        cmp     expect
        bne     ?err
        jsr     getdat
        bcs     ?err    

        ; send positive ACK
        jmp     sndack  
        
?err:
?done:  rts

        
;------------------

lspget:
        .PUBLIC lspget
        phd                     ; save DP
        phb                     ; save DBR
        pea     #0              ; set DP = $0000
        pld
        ldy     #0              ; set DBR = $00
        phy
        plb
        jsr     _spget0
        plb
        pld
        rtl
        
lspput:
        .PUBLIC lspput
        phd                     ; save DP
        phb                     ; save DBR
        pea     #0              ; set DP = $0000
        pld
        ldy     #0              ; set DBR = $00
        phy
        plb
        jsr     _spput0
        plb
        pld
        rtl

lspset:
        .PUBLIC lspset
        phd                     ; save DP
        phb                     ; save DBR
        pea     #0              ; set DP = $0000
        pld
        ldy     #0              ; set DBR = $00
        phy
        plb
        jsr     spset
        plb
        pld
        rtl

lspres:
        .PUBLIC lspres
        phd                     ; save DP
        phb                     ; save DBR
        pea     #0              ; set DP = $0000
        pld
        ldy     #0              ; set DBR = $00
        phy
        plb
        jsr     spres
        plb
        pld
        rtl

crc16a:
        xba
        lda     #0
        ldx     #8
        ACC16
        eor     crc16
?lp:    asl     a
        bcc     ?skp
        eor     #$1021
?skp:   dex
        bne     ?lp
        sta     crc16
        ACC08
        rts

crc16b:
        ldx     #8
?lp:    tay
        eor     crc16
        lsr     a
        ACC16
        php
        lda     crc16
        lsr     a
        plp
        bcc     ?nxt
        eor     #$8408
?nxt:   sta     crc16
        ACC08
        tya
        lsr     a
        dex
        bne     ?lp
        rts
        
crccalc:
        phd
        pea     #0
        pld
        stx     $ff

        lda     #$FF
        sta     crc16
        sta     crc16+1
        jsr     crctb
        ACC16
        lda     crc16
        sta     $f0
        ACC08
        lda     #$00
        sta     crc16
        lda     #$00
        sta     crc16+1 
        jsr     crctb
        ACC16
        lda     crc16
        sta     $f2
        ACC08
        lda     #$0F
        sta     crc16
        lda     #$1D
        sta     crc16+1 
        jsr     crctb
        ACC16
        lda     crc16
        sta     $f4
        ACC08   
        pld
        rtl


crctb:
        stz     $fe
?lp:
        ldx     $fe
        cpx     $ff
        bcs     ?end
        lda     >$100000,x
        inx
        stx     $fe

        eor     crc16+1                 ; Quick CRC computation with lookup tables
        tax                     ; updates the two bytes at crc & crc+1
        lda     crc16           ; with the byte send in the "A" register
        eor     >crchi,x
        sta     crc16+1
        lda     >crclo,x
        sta     crc16
        
        bra     ?lp
?end:           
        rts                     ; y=82 on exit

crclo
 .byte $00,$21,$42,$63,$84,$A5,$C6,$E7,$08,$29,$4A,$6B,$8C,$AD,$CE,$EF
 .byte $31,$10,$73,$52,$B5,$94,$F7,$D6,$39,$18,$7B,$5A,$BD,$9C,$FF,$DE
 .byte $62,$43,$20,$01,$E6,$C7,$A4,$85,$6A,$4B,$28,$09,$EE,$CF,$AC,$8D
 .byte $53,$72,$11,$30,$D7,$F6,$95,$B4,$5B,$7A,$19,$38,$DF,$FE,$9D,$BC
 .byte $C4,$E5,$86,$A7,$40,$61,$02,$23,$CC,$ED,$8E,$AF,$48,$69,$0A,$2B
 .byte $F5,$D4,$B7,$96,$71,$50,$33,$12,$FD,$DC,$BF,$9E,$79,$58,$3B,$1A
 .byte $A6,$87,$E4,$C5,$22,$03,$60,$41,$AE,$8F,$EC,$CD,$2A,$0B,$68,$49
 .byte $97,$B6,$D5,$F4,$13,$32,$51,$70,$9F,$BE,$DD,$FC,$1B,$3A,$59,$78
 .byte $88,$A9,$CA,$EB,$0C,$2D,$4E,$6F,$80,$A1,$C2,$E3,$04,$25,$46,$67
 .byte $B9,$98,$FB,$DA,$3D,$1C,$7F,$5E,$B1,$90,$F3,$D2,$35,$14,$77,$56
 .byte $EA,$CB,$A8,$89,$6E,$4F,$2C,$0D,$E2,$C3,$A0,$81,$66,$47,$24,$05
 .byte $DB,$FA,$99,$B8,$5F,$7E,$1D,$3C,$D3,$F2,$91,$B0,$57,$76,$15,$34
 .byte $4C,$6D,$0E,$2F,$C8,$E9,$8A,$AB,$44,$65,$06,$27,$C0,$E1,$82,$A3
 .byte $7D,$5C,$3F,$1E,$F9,$D8,$BB,$9A,$75,$54,$37,$16,$F1,$D0,$B3,$92
 .byte $2E,$0F,$6C,$4D,$AA,$8B,$E8,$C9,$26,$07,$64,$45,$A2,$83,$E0,$C1
 .byte $1F,$3E,$5D,$7C,$9B,$BA,$D9,$F8,$17,$36,$55,$74,$93,$B2,$D1,$F0 

; hi byte CRC lookup table (should be page aligned)
crchi
 .byte $00,$10,$20,$30,$40,$50,$60,$70,$81,$91,$A1,$B1,$C1,$D1,$E1,$F1
 .byte $12,$02,$32,$22,$52,$42,$72,$62,$93,$83,$B3,$A3,$D3,$C3,$F3,$E3
 .byte $24,$34,$04,$14,$64,$74,$44,$54,$A5,$B5,$85,$95,$E5,$F5,$C5,$D5
 .byte $36,$26,$16,$06,$76,$66,$56,$46,$B7,$A7,$97,$87,$F7,$E7,$D7,$C7
 .byte $48,$58,$68,$78,$08,$18,$28,$38,$C9,$D9,$E9,$F9,$89,$99,$A9,$B9
 .byte $5A,$4A,$7A,$6A,$1A,$0A,$3A,$2A,$DB,$CB,$FB,$EB,$9B,$8B,$BB,$AB
 .byte $6C,$7C,$4C,$5C,$2C,$3C,$0C,$1C,$ED,$FD,$CD,$DD,$AD,$BD,$8D,$9D
 .byte $7E,$6E,$5E,$4E,$3E,$2E,$1E,$0E,$FF,$EF,$DF,$CF,$BF,$AF,$9F,$8F
 .byte $91,$81,$B1,$A1,$D1,$C1,$F1,$E1,$10,$00,$30,$20,$50,$40,$70,$60
 .byte $83,$93,$A3,$B3,$C3,$D3,$E3,$F3,$02,$12,$22,$32,$42,$52,$62,$72
 .byte $B5,$A5,$95,$85,$F5,$E5,$D5,$C5,$34,$24,$14,$04,$74,$64,$54,$44
 .byte $A7,$B7,$87,$97,$E7,$F7,$C7,$D7,$26,$36,$06,$16,$66,$76,$46,$56
 .byte $D9,$C9,$F9,$E9,$99,$89,$B9,$A9,$58,$48,$78,$68,$18,$08,$38,$28
 .byte $CB,$DB,$EB,$FB,$8B,$9B,$AB,$BB,$4A,$5A,$6A,$7A,$0A,$1A,$2A,$3A
 .byte $FD,$ED,$DD,$CD,$BD,$AD,$9D,$8D,$7C,$6C,$5C,$4C,$3C,$2C,$1C,$0C
 .byte $EF,$FF,$CF,$DF,$AF,$BF,$8F,$9F,$6E,$7E,$4E,$5E,$2E,$3E,$0E,$1E