home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Simtel MSDOS 1992 December
/
simtel1292_SIMTEL_1292_Walnut_Creek.iso
/
msdos
/
modem
/
async1.arc
/
ASYNC.ASM
next >
Wrap
Assembly Source File
|
1985-09-13
|
26KB
|
546 lines
Page 60,132
.Radix 16
Title Communications Interface Routine
Subttl Macros
Page
Save Macro R1,R2,R3,R4,R5,R6,R7,R8,R9,R10
Irp Rx,<R1,R2,R3,R4,R5,R6,R7,R8,R9,R10> ;Repeat for each parm
Ifnb <Rx> ;If this parm not blank
Push Rx ;Save the register
Endif ;End Ifnb
Endm ;End Irp
;; The Restore macro makes use of the fact that R1-R10 are still defined,
;; but, being a different macro, this will not expand when the Save macro
;; is used. Note that the Restore macro will restore whatever registers
;; were last Save'd in the assembly listing, not during execution.
;; Therefore, its use is restricted to restoring the previous sequential
;; Save macro's registers.
Restore Macro
Irp Rx,<R10,R9,R8,R7,R6,R5,R4,R3,R2,R1> ;Repeat for each parm
Ifnb <Rx> ;If this parm not blank
Pop Rx ;Pop the register
Endif ;End Ifnb
Endm ;End Irp
Endm ;End of Restore macro
Endm ;End of Save Macro
Setint Macro Vector,Routine ;Sets an interrupt vector
Lea DX,Routine ;Address the routine
Mov AX,25*100+Vector ;Set the vector
Int 21 ;Call DOS to do it
Endm
Incbuf Macro Buffer
Local Notend ;Not at end of buffer label
;; Macro to increment the buffer pointer. This macro is used
;; internally by other buffer processing macros. The pointer to
;; be incremented must be in BX. Results in BX.
Inc BX ;Point at next character
Cmp BX,Offset Buffer.Buff + Length Buff ;At end of buffer?
Jb Notend ;No - continue
Lea BX,Buffer.Buff ;Point back to start of buffer
Notend Label Near ;Not at end of buffer
Endm ;End of macro
Bufinit Macro Buffer ;Initialize the buffers
;; This macro must be called once for each buffer. It's purpose
;; is to ensure the pointers are set up correctly before the
;; buffers are used. Unless the buffers are initialized, the
;; results will be unpredictable.
Lea BX,Buffer.Buff ;Get address of buffer
Mov Buffer.Staptr,BX ;Set start of data address
Mov Buffer.Endptr,BX ;End of data too (buffer empty)
Endm ;End of macro
Putbuf Macro Buffer ;Insert a character in the buffer
Local Bufull
;; This macro puts a byte into BUFFER. Origin is AL, and it uses the
;; BX reg. The carry flag is set if the buffer is full and the routine
;; cannot place a bit in the buffer, and is cleared if the character is
;; inserted in the buffer and pointers updated.
;; The buffer must have been defined with the BUFFER structure.
Mov BX,Buffer.Endptr ;Get pointer to end of buffer
Incbuf Buffer ;Point at next character
Cmp BX,Buffer.Staptr ;Buffer full?
Je Bufull ;Yes - buffer overrun
Mov [BX],AL ;Store a byte
Mov Buffer.Endptr,BX ;Replace new pointer
Stc ;Inverse of carry flag returned
Bufull Label Near ;Get a character from the buffer
Cmc ;Invert carry bit for return code
Endm ;End of macro
Getbuf Macro Buffer ;Get a character from the buffer
Local Bufemp
;; This macro gets a character from BUFFER and returns it in AL. It
;; uses the BX reg. Carry flag is set if the buffer is empty, and
;; cleared if a character is returned in AL.
;; The buffer must have been defined with the BUFFER structure.
Mov BX,Buffer.Staptr ;Get buffer data start
Cmp BX,Buffer.Endptr ;Any data in buffer?
Je Bufemp ;Yes - go transmit it
Incbuf Buffer ;Point at next character
Mov AL,[BX] ;Get a byte
Mov Buffer.Staptr,BX ;Restore pointer
Stc ;Set complement of carry flag
Bufemp Label Near
Cmc ;Set true return flag
Endm
Flush Macro Buffer ;Flush the buffer
;; This macro will flush BUFFER by setting the start and end
;; pointers equal. It uses the BX reg.
Mov BX,Buffer.Staptr ;Get start of data
Mov Buffer.Endptr,BX ;Set end = start (empty)
Endm
; Structure used for buffer definition.
; Staptr = Endptr means buffer is full. Otherwise buffer has data
; in it.
Buffer Struc
Buff Db 256d Dup (0) ;Buffer size in decimal
Staptr Dw 0 ;Start of data pointer
Endptr Dw 0 ;End of data pointer
Buffer Ends
Inital Record Speed:3, Parity:2, Stop:1, Len:2 ;Init call parms in AL
Subttl Equates
Page
; Line status bits -- AH
Timeout Equ 80 ;Time out error
Tbufemp Equ 40 ;Transmit buffer empty
Tbufnfl Equ 20 ;Transmit buffer not full
Brkdet Equ 10 ;Break detect
Framerr Equ 08 ;Framing error
Parerr Equ 04 ;Parity error
Rcveovr Equ 02 ;Receive buffer overrun
Rdatrdy Equ 01 ;Receive buffer has data
; Modem status bits -- AL
Rlsd Equ 80 ;Received line signal detect
Ri Equ 40 ;Ring indicator
Dsr Equ 20 ;Data set ready
Cts Equ 10 ;Clear to send
Drlds Equ 08 ;Delta receive line signal detect
Teri Equ 04 ;Trailing edge ring indicator
Ddsr Equ 02 ;Delta data set ready
Dcts Equ 01 ;Delta clear to send
; Interrupt Enable reg bit definitions
Msint Equ 08 ;Modem status int bit
Rlsint Equ 04 ;Receive line status int bit
Thrint Equ 02 ;Transmit holding reg empty int bit
Daint Equ 01 ;Data availalbe interrupt
; Modem Control Port
Out2 Equ 08 ;Out2 bit
Out1 Equ 04 ;Out1 bit
Rts Equ 02 ;Request to Send
Dtr Equ 01 ;Data Terminal Ready
; Other equates and records
Asysmsk Equ 10 ;System interrupt (port 21) mask
Perror Equ -1 ;Paramater error
Baseadr Equ 3F8 ;Comm port 1 base address
Subttl Constants
Page +
Comm Segment Para Public 'Code'
Assume CS:Comm ,DS:Comm ,ES:nothing ,SS:Nothing
Org 100h ;Set starting point
Entry Label Near ;Initialization entry point
Jmp Start ;Go to initialization code
Db 'Asynchronous Communications Port Driver '
Db '(C) Copyright 1985 by Jerry D. Stuckle.'
Db 'Released to Public Domain for non-business use only.'
Divisor Label Word ;Table of divisor values
Dw 1047d ; 110 baud
Dw 768d ; 150 baud
Dw 384d ; 300 baud
Dw 192d ; 600 baud
Dw 96d ;1200 baud
Dw 48d ;2400 baud
Dw 24d ;4800 baud
Dw 12d ;9600 baud
Functbl Label Word ;Function request table of routines
Dw Copen ;AH = 0 Open communications port
Dw Csend ;AH = 1 Send a character
Dw Crcve ;AH = 2 Receive a character
Dw Cstat ;AH = 3 Get buffer status
Dw Cclos ;AH = 4 Close communications port
Funcnt Equ ($ - Functbl) / 2 ;Number of words in table
Subttl Data Areas
Page
; Transmit and receive buffer structures
Xmit Buffer <,,> ;No override for initial values
Rcve Buffer <,,> ;No override for initial values
Lstatus Db 0 ;Line status byte
Mstatus Db 0 ;Modem status byte
Subttl Interface Routines
Page
Int14 Proc Near ;Interrupt 14 input
Sti ;Other interrupts are OK here.
Save DS,DX,SI,DI,BX ;Save all required regs
Push CS ;Place CS on stack so...
Pop DS ;...we can set DS
Or DX,DX ;Is DX 0?
Jnz Parmerr ;No - error found - return
Cmp AH,Funcnt ;Check against number of entries in..
Ja Parmerr ;..the table and branch if too high.
Mov DX,Baseadr ;Get port base address
Xor BH,BH ;One byte index being used
Mov BL,AH ;Get function code
Shl BX,1 ;Multiply by 2
Call Functbl[BX] ;Call the correct routine
Jmp Short Intret ;Go return to caller
Parmerr Label Near ;Paramater error detected
Mov AH,Perror ;Move in error code
Intret Label Near ;Return to caller
Restore ;Put back all registers
Iret ;Interrupt return
Int14 Endp ;End of mainline code
Subttl Open the Comm port
Page
Copen Proc Near
Mov AH,AL ;Save parms in AH
Add DX,3 ;Point at line control reg
In AL,DX ;Get the reg in AL
Or AL,80 ;Turn on Divisor Latch Bit
Out DX,AL ;Enable the latch
Sub DX,3 ;Point back to base port
Xor BH,BH ;Insure BH is low values
Mov BL,AH ;Get all init parms in BL
And BL,Mask Speed ;Turn off excess bits
Mov CL,Speed ;Get the shift value
Shr BL,CL ;And move it over.
Shl BL,1 ;X2 for index into word table
Lea SI,Divisor[BX] ;Set pointer to correct divisor
Lodsb ;Get the low order of the divisor
Out DX,AL ;Set into the divisor latch
Lodsb ;Get the high order of the divisor
Inc DX ;Point to the high order port
Out DX,AL ;And set latch high order
Inc DX ;Now back to the...
Inc DX ;...DLAB bit
Mov AL,AH ;Get the original parms in AL
And AL,Mask Parity + Mask Stop + Mask Len ;Leave on only desired bits.
; Now magically, the rest of the bits in AL match exactly
; the Line Control Register bits (maybe it was planned?).
Out DX,AL ;And set the other parms in the LCR
; Now we have all the requested parms set, all that remains is to
; set DTR and RTS, and enable the interrupts on the async board
; and from the system (port 21). Note that this uses negative logic
; (a bit being '0' means this interrupt is active).
Push DX ;Save base address on stack
Mov DX,21 ;Address interrupt control reg
In AL,DX ;Get current interrupts
And AL,0FF-Asysmsk ;Allow Async interrupts from port 1
Out DX,AL ;Put it back out
Pop DX ;Restore base addr from stack
Inc DX ;Point to Modem Control Reg
Mov AL,Out2+Rts+Dtr ;RTS and DTR
Out DX,AL ;Set the Modem Control Reg
Sub DX,3 ;Back up to Interupt Enable Reg
In AL,DX ;Port might already be set.
Or AL,Msint+Rlsint+Daint ;Modem status+Line status+Data avail
Out DX,AL ;Set the reg
Nop ;Allow dummy machine cycle
; Disable all interrupts before flushing buffers and getting status.
Cli ;Disable again
Flush Xmit ;Flush the transmit buffer
Flush Rcve ;Flush the receive buffer
Add DX,4 ;Point to Line Status Reg
In AL,DX ;Get the status
In AL,DX ;Do it again to clear any errors
Mov Lstatus,AL ;Set the status byte
Inc DX ;Point to Modem Status Reg
In AL,DX ;Get the status
In AL,DX ;Again to clear any delta bits
Mov Mstatus,AL ;Set current modem status
Sti ;All done with buffers - enable ints
Call Cstat ;Allow Cstat to set status
Ret ;Return to caller
Copen Endp
Subttl Put character in AL into buffer
Page
Csend Proc Near ;Put the character in AX
Putbuf Xmit ;Put AL to the transmit buffer
Jc Csend2 ;If carry, return buffer full
Inc DX ;Point at Interrupt enable register
In AL,DX ;Get the port
Test AL,Thrint ;Is transmit already enabled?
Jnz Csend1 ;Yes - return
Or AL,Thrint ;Enable xmit hold reg interrupt
Out DX,AL ;And put it back out
Csend1 Label Near
Dec DX ;Point back to base address
Call Ahstat ;Get status in AH
And AH,0FF-Timeout ;Turn off timeout bit
Ret ;Return to caller
Csend2 Label Near
Call Ahstat ;Get status in AH
Or AH,Timeout ;Set timeout bit (can't send)
Ret ;Return to caller
Csend Endp
Subttl Receive a character from the buffer into AL
Page
Crcve Proc Near
Getbuf Rcve
Jc Crcve1 ;If buffer empty, return FF in AH
Call Ahstat ;Get status in AH
And AH,Timeout+Brkdet+Framerr+Parerr+Rcveovr ; Only error bits
Ret ;And return to caller
Crcve1 Label Near
Mov AH,-1 ;Indicate buffer empty
Ret ;And return to caller
Crcve Endp
Subttl Get port status
Page
Cstat Proc Near
Call Ahstat ;Get line status in AH
Mov AL,Mstatus ;Get modem status
Ret ;And return to caller
Ahstat Proc Near
Xor AH,AH ;New line status (0)
Xchg AH,Lstatus ;Get line status and reset it
; Set the Transmit buff
Mov BX,Xmit.Endptr ;Get start pointer
Cmp BX,Xmit.Staptr ;If Endptr = Staptr, Buffer empty
Jne Ahstat1 ;If not empty, check if full
Or AH,Tbufemp+Tbufnfl ;Turn on empty and not full
Jmp Short Ahstat2 ;Check receive buffer
Ahstat1 Label Near ;Transmit not empty, check if full
Incbuf Xmit ;Point at next character
Cmp BX,Xmit.Staptr ;Equal to start of buffer?
Je Ahstat2 ;Yes - buffer is full. Continue.
Or AH,Tbufnfl ;Not full, so set the bit.
Ahstat2 Label Near
Mov BX,Rcve.Staptr ;Get start pointer
Cmp BX,Rcve.Endptr ;If Start = End, buffer empty
Jne Ahstat3 ;If empty, continue
Ret ;Else all done, so return to caller
; Now we have all the bits in AH set, so lets return to the caller.
Ahstat3 Label Near
Or AH,Rdatrdy ;Set receive data ready
Ret ;Return to caller
Ahstat Endp
Cstat Endp
Subttl Close the Comm Port and flush the buffers
Page
Cclos Proc Near
Xor AL,AL ;No interrupts
Inc DX ;Point at IER
Out DX,AL ;Disable the interrupts
Push DX ;Save IER address on stack
Mov DX,21 ;System interrupt mask
In AL,DX ;Get the port
Or AL,Asysmsk ;Disable the interrupt
Out DX,AL ;And put it back to the port
Pop DX ;Restore origingal value of DX
Add DX,3 ;Point at Modem control reg
Out DX,AL ;Turn off all bits
Sub DX,3 ;Back to base address
Flush Xmit ;Clear the transmit buffer
Flush Rcve ;Clear the receive buffer
Ret ;And return to caller
Cclos Endp
Subttl Interrupt handlers
Page +
;**********************************************************************
;* *
;* ASYNC INTERRUPT HANDLERS *
;* *
;**********************************************************************
Int0C Proc Near
Sti ;Allow interrupts
Save AX,BX,DX,DS ;Save the regs
Mov DX,20 ;System interrupt controller
Mov AL,20 ;Reset interrupt pending
Out DX,AL ;Put back to system controller
Push CS ;Put CS into stack...
Pop DS ;And pop it back into DS
Mov DX,Baseadr ;Get address of async port
Inc DX ;Point at...
Inc DX ;...Interrupt ID reg
Intloop Label Near ;Handle interrupts loop
In AL,DX ;Get interrupt type
Test AL,1 ;Any interrupt pending?
Jnz Asynrtn ;No - return
Xor BH,BH ;Prepare for indexed call
Mov BL,AL ;Interrupt code to index reg
Push DX ;Save DX across call
Call Inttbl[BX] ;Call the correct routine
Pop DX ;Restore original DX
Jmp Intloop ;Loop until all interrupts handled.
Asynrtn Label Near
Restore
Iret ;Return from interrupt
Inttbl Label Word
Dw Modemst ;Modem status interrupt
Dw Xmithrg ;Transmit holding reg empty
Dw Rdatint ;Receive data available
Dw Rcvrlst ;Receiver line status
Subttl Get the modem status
Page
Modemst Proc Near ;Modem status
Add DX,4 ;Point at modem status reg
In AL,DX ;Read it
Mov Mstatus,AL ;Place in status byte
Ret ;Return to caller
Modemst Endp
Subttl Transmit a character from the buffer
Page
Xmithrg Proc Near ;Xmit hold reg empty
Dec DX ;Point at IER
Cli ;Disable while working with buffer
Getbuf Xmit ;Get a character from the buffer
Jc Xmithr1 ;No - disable transmit interrupts
Dec DX ;Point at transmit holding reg
Out DX,AL ;Put it out
Sti ;Enable interrupts
Ret ;Return to caller
Xmithr1 Label Near
In AL,DX ;Get the interrupt reg
And AL,0FF-Thrint ;Turn off xmit holing reg bit
Out DX,AL ;And send it back out
Sti ;Re-enable interrupts
Ret ;Return to caller
Xmithrg Endp
Subttl Receive a byte into the buffer
Page
Rdatint Proc Near
Dec DL ;Point to ...
Dec DX ;... data reg
Cli ;Disable interrupts
In AL,DX ;Get a byte
Test Lstatus,Parerr ;Parity error this byte?
Jz Rdatpok ;No, parity OK
Or AL,80h ;Bad parity, set high bit in AL
And Lstatus,0FFh-Parerr ;Turn off parity error
Rdatpok Label Near
Putbuf Rcve ;Put into receive buffer
Jc Rcve2 ;If full, set overrun bit
Sti
Ret ;Return to caller
Rcve2 Label Near
Sti ;Enable interrupts again
Or Lstatus,Rcveovr ;Set overrun
Ret ;And return to caller
Rdatint Endp
Subttl Receiver line status interrupt
Page
Rcvrlst Proc Near
Add DL,3 ;Point at line status reg
In AL,DX ;Go read it
And Lstatus,Rcveovr ;Turn off all but overrun bit
And AH,0FF-(Tbufemp+Tbufnfl+Rcveovr+Rdatrdy) ;Unwanted bits off
Or Lstatus,AL ;And turn on new status bits
Ret ;Return to caller
Rcvrlst Endp
Int0C Endp
Resend Equ $ ;Resident code ends here
Subttl Initialization routine
Page +
Start Proc Near ;Initialization code
; First of all, initialize the buffers
Bufinit Xmit
Bufinit Rcve
; Now let's set the interrupt handlers
Setint 0C,Int0C ;Port 1 Interrupt and routine
Setint 14,Int14 ;Program interface interrupt
; And finally, terminate but leave resident code
; Use the old Int 27 call for DOS 1.x compatability.
Lea DX,Resend ;Address end of resident section
Int 27 ;Use Int 27 for DOS 1.0 Compatability
Start Endp ;End of procedure
Comm Ends
End Entry