📄 comm.asm
字号:
TITLE COMM
PAGE 83,132
; $Id: comm.asm 1.7 1993/05/31 01:39:23 ahd Exp $
;
; $Log: comm.asm $
;; Revision 1.7 1993/05/31 01:39:23 ahd
;; Add return to spin loop (fix by Bill Plummer)
;; Drop FIFO size to 8
;;
;; Revision 1.4 1993/05/30 00:20:02 ahd
;; Insert minor delay to allow slow modems to catch up
;;
;; Revision 1.2 1992/12/18 12:08:25 ahd
;; Add Plummer's fix for bad TASM assemble of com_errors
;;
;
; 14-Jun-93 plummer Add RET to spinloop routine
; 14-Jun-93 plummer Set FIFO thresholds to 8 rather than 16 bytes
; 18-May-93 plummer Define IO$DELAY and use in UART type determination
; 16-May-93 plummer Debug code to printout UART type
; 22-Apr-93 plummer Make case consistent in "TBuff" so it links properly
; 2-Dec-92 plummer Fix com_errors() again. Change got lost.
; Fix com_errors() to avoid problems with tasm. Plummer, 11/16/92
; 8259 EOI issued after interrupts serviced. Plummer, 3/25/92
; Fix botch in Set_Baud. Plummer, 3/20/92
; Put in Gordon Lee's cure from dropped interrupts. Plummer, 3/19/92
; TEMPORARY ioctl_com(). Plummer, 3/9/92.
; Clear OUT2 bit in UART. Some machines use it so enable IRQ. Plummer, 3/9/92
; Release send buffer if we can't assign a recv buffer. Plummer, 3/9/92
; Move EQU's outside of SP_TAB struc definition. ahd, 3/8/92.
; ahd changes: short jmp's out of range in INST, OPEN ??? (ahd, 3/?/92)
; open_com() leaves DTR unchanged so Drew's autobaud works. Plummer, 3/2/92
; Missing DX load in close_com() -- FIFO mode not cleared. Plummer, 3/2/92
; C calling convention does not require saving AX, BX, CX, DX. Plummer 2/23/92
; Flush consideration of the PC Jr. Wm. W. Plummer, 2/15/92
; Cleanup PUSHF/POPF and CLI/STI useage. Wm. W. Plummer, 2/15/92
; Make SENDII have Giles Todd's change. Wm. W. Plummer, 2/15/92
; Changes to Giles Todd's code to support dynamic buffers. Plummer, 2/3/92
; 26 Jan 92 Giles Todd Prime THR for UARTs which do not give a Tx empty
; interrupt when Tx interrupts are enabled.
; S_SIZE & R_SIZE may be set with -D to MASM. Wm. W. Plummer, 1/19/92
; Assign buffers dynamically. Wm. W. Plummer, 1/19/92
; Unfix byte length -- I screwed up. Wm. W. Plummer, 1/15/92
; Fix byte length with specific PARITY select. Wm. W. Plummer, 1/13/92
; Buffers up to 4096 per AHD. Wm. W. Plummer, 1/1/92
; Always use FIFO length of 16 on send side. Wm. W. Plummer, 12/30/91.
; Init DSR and CTS previous state from current status. Wm. Plummer, 12/30/91.
; UUPC conditional to disable v.24. Wm. W. Plummer, 12/30/91.
; Buffer sizes up to 2048 per ahd. Wm. W. Plummer, 12/15/91.
; dtr_on() switches to D connection if CTS&DSR don't come up. WWP, 12/15/91.
; New dtr_on() logic. Wm. W. Plummer, 12/11/91
; Fix bad reg. per report from user. Wm. W. Plummer, 12/11/91
; Semicolon before control-L's for MASM 5.00 per ahd. Wm. W. Plummer, 12/8/91
; Use AHD's handling of COM ports. Wm. W. Plummer, 11/29/91
; Buffer sizes reduced and required to be 2**N. Wm. W. Plummer, 11/11/91
; Accomodate V.24 requirements on DTR flaps. Wm. W. Plummer 10/15/91
; Revised DTR_ON_COM to solve user problem. Wm. W. Plummer, 10/3/91
; Make time delays independent of CPU speed. Wm. W. Plummer, 9/16/91
; Use interrupts to trace CD, DSR, Wm. W. Plummer, 9/16/91
; Remove modem control from TXI. Wm. W. Plummer, 9/13/91
; Completely redo the XOFF/XON logic. Too many races before. Wm. W. Plummer
; Revise interrupt dispatch for speed & function. William W. Plummer, 9/12/91
; Merge in ahd's changes to flush control Q,S when received as flow control
; SEND buffer allows one byte for a SENDII call. Avoids flow control
; lockups. - William W. Plummer, 8/30/91
; Support for NS16550A chip with SILO - William W. Plummer, 8/30/91
; Add modem_status() routine - William W. Plummer, 7/2/91
; Put wrong code under AHD conditional - William W. Plummer, 7/2/91
; Change TITLE, repair bad instr after INST3 - William W. Plummer, 7/1/91
; Modified to use COM1 thru COM4 - William W. Plummer, 2/21/91
; Eliminate (incomplete) support for DOS1 - William W. Plummer, 11/13/90
; Changes may be copied and modified with no notice. Copyrights and copylefts
; are consider silly and do not apply. -- William W. Plummer
; modified to use MSC calling sequence. jrr 3/86
;****************************************************************************
; Communications Package for the IBM PC, XT, AT and strict compatibles.
; May be copied and used freely -- This is a public domain program
; Developed by Richard Gillmann, John Romkey, Jerry Saltzer,
; Craig Milo Rogers, Dave Mitton and Larry Afrin.
;
; We'd sure like to see any improvements you might make.
; Please send all comments and queries about this package
; to GILLMANN@USC-ISIB.ARPA
;
; o Supports both serial ports simultaneously
; o All speeds to 19200 baud
; o Compatible with PC, XT, AT
; o Built in XON/XOFF flow control option
; o C language calling conventions
; o Logs all comm errors
; o Direct connect or modem protocol
PAGE;
;
; Buffer sizes -- *** MUST be powers of 2 ****
IFDEF UUPC
R_SIZE EQU 4096
S_SIZE EQU 4096
ENDIF
; If not set above, maybe on assembler command line. But if not, ...
IFNDEF R_SIZE
R_SIZE EQU 512 ; Recv buffer size
ENDIF
IFNDEF S_SIZE
S_SIZE EQU 512 ; Send buffer size
ENDIF
; INTERRUPT NUMBERS
INT_COM1 EQU 0CH ; COM1: FROM 8259
INT_COM2 EQU 0BH ; COM2: FROM 8259
INT_COM3 EQU 0CH ; COM3: FROM 8259
INT_COM4 EQU 0BH ; COM4: FROM 8259
; 8259 PORTS
INTA00 EQU 20H ; 8259A PORT, A0 = 0
INTA01 EQU 21H ; 8259A PORT, A0 = 1
; COM1: & COM3: LEVEL 4
IRQ4 EQU 2*2*2*2 ; 8259A OCW1 MASK, M4=1, A0=0
NIRQ4 EQU NOT IRQ4 AND 0FFH ; COMPLEMENT OF ABOVE
EOI4 EQU 4 OR 01100000B ; 8259A OCW2 SPECIFIC IRQ4 EOI, A0=0
; COM2: & COM4: LEVEL 3
IRQ3 EQU 2*2*2 ; 8259A OCW1 MASK, M3=1, A0=0
NIRQ3 EQU NOT IRQ3 AND 0FFH ; COMPLEMENT OF ABOVE
EOI3 EQU 3 OR 01100000B ; 8259A OCW2 SPECIFIC IRQ3 EOI, A0=0
; FLOW CONTROL CHARACTERS
CONTROL_Q EQU 11H ; XON
CONTROL_S EQU 13H ; XOFF
; MISC.
DOS EQU 21H ; DOS FUNCTION CALLS
;
; ROM BIOS Data Area
;
RBDA SEGMENT AT 40H
RS232_BASE DW 4 DUP(?) ; ADDRESSES OF RS232 ADAPTERS
RBDA ENDS
PAGE;
;
; TABLE FOR EACH SERIAL PORT
;
SP_TAB STRUC
PORT DB ? ; 1 OR 2 OR 3 OR 4
; PARAMETERS FOR THIS INTERRUPT LEVEL
INT_COM DB ? ; INTERRUPT NUMBER
IRQ DB ? ; 8259A OCW1 MASK
NIRQ DB ? ; COMPLEMENT OF ABOVE
EOI DB ? ; 8259A OCW2 SPECIFIC END OF INTERRUPT
; INTERRUPT HANDLERS FOR THIS LEVEL
INT_HNDLR DW ? ; OFFSET TO INTERRUPT HANDLER
OLD_COM_OFF DW ? ; OLD HANDLER'S OFFSET
OLD_COM_SEG DW ? ; OLD HANDLER'S SEGMENT
; ATTRIBUTES
INSTALLED DB ? ; IS PORT INSTALLED ON THIS PC? (1=YES,0=NO)
BAUD_RATE DW ? ; 19200 MAX
CONNECTION DB ? ; M(ODEM), D(IRECT)
PARITY DB ? ; N(ONE), O(DD), E(VEN), S(PACE), M(ARK)
STOP_BITS DB ? ; 1, 2
XON_XOFF DB ? ; E(NABLED), D(ISABLED)
; FLOW CONTROL STATE
HOST_OFF DB ? ; HOST XOFF'ED (1=YES,0=NO)
PC_OFF DB ? ; PC XOFF'ED (1=YES,0=NO)
URGENT_SEND DB ? ; We MUST send one byte (XON/XOFF)
SEND_OK DB ? ; DSR and CTS are ON
; ERROR COUNTS
ERROR_BLOCK DW 8 DUP(?); EIGHT ERROR COUNTERS
; UART PORTS - DATREG thru MSR must be in order shown.
DATREG DW ? ; DATA REGISTER
IER DW ? ; INTERRUPT ENABLE REGISTER
IIR DW ? ; INTERRUPT IDENTIFICATION REGISTER (RO)
LCR DW ? ; LINE CONTROL REGISTER
MCR DW ? ; MODEM CONTROL REGISTER
LSR DW ? ; LINE STATUS REGISTER
MSR DW ? ; MODEM STATUS REGISTER
UART_SILO_LEN DB ? ; Size of a silo chunk (1 for 8250)
;
; BUFFER POINTERS
START_TDATA DW ? ; INDEX TO FIRST CHARACTER IN X-MIT BUFFER
END_TDATA DW ? ; INDEX TO FIRST FREE SPACE IN X-MIT BUFFER
START_RDATA DW ? ; INDEX TO FIRST CHARACTER IN REC. BUFFER
END_RDATA DW ? ; INDEX TO FIRST FREE SPACE IN REC. BUFFER
; BUFFER COUNTS
SIZE_TDATA DW ? ; NUMBER OF CHARACTERS IN X-MIT BUFFER
SIZE_RDATA DW ? ; NUMBER OF CHARACTERS IN REC. BUFFER
; BUFFERS
TBuff DD ? ; Pointer to transmit buffer
RBuff DD ? ; Pointer to receive buffer
SP_TAB ENDS
; SP_TAB EQUATES
; WE HAVE TO USE THESE BECAUSE OF PROBLEMS WITH STRUC
EOVFLOW EQU ERROR_BLOCK ; BUFFER OVERFLOWS
EOVRUN EQU ERROR_BLOCK+2 ; RECEIVE OVERRUNS
EBREAK EQU ERROR_BLOCK+4 ; BREAK CHARS
EFRAME EQU ERROR_BLOCK+6 ; FRAMING ERRORS
EPARITY EQU ERROR_BLOCK+8 ; PARITY ERRORS
EXMIT EQU ERROR_BLOCK+10 ; TRANSMISSION ERRORS
EDSR EQU ERROR_BLOCK+12 ; DATA SET READY ERRORS
ECTS EQU ERROR_BLOCK+14 ; CLEAR TO SEND ERRORS
DLL EQU DATREG ; LOW DIVISOR LATCH
DLH EQU IER ; HIGH DIVISOR LATCH
;
; Equates having to do with the FIFO
;
FCR EQU IIR ; FIFO Control Register (WO)
; Bits in FCR for NS16550A UART. Note that writes to FCR are ignored
; by other chips.
FIFO_ENABLE EQU 001H ; Enable FIFO mode
FIFO_CLR_RCV EQU 002H ; Clear receive FIFO
FIFO_CLR_XMT EQU 004H ; Clear transmit FIFO
FIFO_STR_DMA EQU 008H ; Start DMA Mode
; 10H and 20H bits are register bank select on some UARTs (not handled)
FIFO_SZ_4 EQU 040H ; Warning level is 4 before end
FIFO_SZ_8 EQU 080H ; Warning level is 8 before end
FIFO_SZ_14 EQU 0C0H ; Warning level is 14 before end
;
; Commands used in code to operate FIFO. Made up as combinations of above
;
FIFO_CLEAR EQU 0 ; Turn off FIFO
FIFO_SETUP EQU FIFO_SZ_8 OR FIFO_ENABLE
FIFO_INIT EQU FIFO_SETUP OR FIFO_CLR_RCV OR FIFO_CLR_XMT
;
; Miscellaneous FIFO-related stuff
;
FIFO_ENABLED EQU 0C0H ; 16550 makes these equal FIFO_ENABLE
FIFO_LEN EQU 8 ; Length of the transmit FIFO in a 16550A
PAGE;
; put the data in the DGROUP segment
; far calls enter with DS pointing to DGROUP
;
DGROUP GROUP _DATA
_DATA SEGMENT PUBLIC 'DATA'
;
DIV50 DW 2304 ; ACTUAL DIVISOR FOR 50 BAUD IN USE
CURRENT_AREA DW AREA1 ; CURRENTLY SELECTED AREA
; DATA AREAS FOR EACH PORT
AREA1 SP_TAB <1,INT_COM1,IRQ4,NIRQ4,EOI4> ; COM1 DATA AREA
AREA2 SP_TAB <2,INT_COM2,IRQ3,NIRQ3,EOI3> ; COM2 DATA AREA
AREA3 SP_TAB <3,INT_COM3,IRQ4,NIRQ4,EOI4> ; COM3 DATA AREA
AREA4 SP_TAB <4,INT_COM4,IRQ3,NIRQ3,EOI3> ; COM4 DATA AREA
IFDEF DEBUG
ST8250: DB "8250$"
ST16550: DB "16550$"
STUART: DB " UART detected", 0DH, 0AH, '$'
ENDIF
_DATA ENDS
COM_TEXT SEGMENT PARA PUBLIC 'CODE'
ASSUME CS:COM_TEXT,DS:DGROUP,ES:NOTHING
PUBLIC AREA1, AREA2, AREA3, AREA4
PUBLIC _select_port
PUBLIC _save_com
PUBLIC _install_com
PUBLIC _restore_com
PUBLIC _open_com
PUBLIC _ioctl_com
PUBLIC _close_com
PUBLIC _dtr_on
PUBLIC _dtr_off
PUBLIC _r_count
PUBLIC _s_count
PUBLIC _receive_com
PUBLIC _send_com
PUBLIC _sendi_com
IFNDEF UUPC
PUBLIC _send_local
ENDIF
PUBLIC _break_com
PUBLIC _com_errors
PUBLIC _modem_status
IFDEF DEBUG
PUBLIC INST2, INST4
PUBLIC OPEN1, OPEN2, OPENX
PUBLIC DTRON1, DTRON6, DTRONF, DTRONS, DTRONX
PUBLIC RECV1, RECV3, RECV4, RECVX
PUBLIC SEND1, SENDX
PUBLIC WaitN, WaitN1, WaitN2
PUBLIC SENDII, SENDII2, SENDII4, SENDIIX
PUBLIC SPINLOOP
PUBLIC CHROUT, CHROUX
PUBLIC BREAKX
PUBLIC INT_HNDLR1, INT_HNDLR2, INT_HNDLR3, INT_HNDLR4
PUBLIC INT_COMMON, REPOLL, INT_END
PUBLIC LSI
PUBLIC MSI
PUBLIC TXI, TXI1, TXI2, TXI3, TXI9
PUBLIC TX_CHR
PUBLIC RXI, RXI0, RXI1, RXI2, RXI6, RXIX
ENDIF
PAGE;
; Notes, thoughts and explainations by Bill Plummer. These are intended to
; help those of you who would like to make modifications.
; Here's the order of calls in UUPC. The routines in COMM.ASM are called
; from ulib.c.
; First (when a line in system has been read?), ulib&openline calls
; select_port() ; Sets up CURRENT_AREA
; then, save_com() ; Save INT vector
; then, install_com() ; Init area, hook INT
; then, open_com(&cmd, 'D', 'N', STOP*T, 'D') ; Init UART, clr bufs
; then, dtr_on().
; At that point the line is up and running. UUPC calls ulib&sread()
; which calls, receive_com();
; And UUPC calls ulib&swrite()
; which calls, send_com();
; To cause an error that the receiver will see, UUPC calls ulib&ssendbrk();
; which calls, break_com();
; When all done with the line, UUPC calls ulib&closeline()
; which calls, dtr_off();
; then, close_com();
; then, restore_com(); ; Unhook INT
; and, stat_errors();
; Note: On the PC COM1 and COM3 share IRQ4, while COM2 and COM4 share IRQ3.
; BUT, only one device on a given IRQ line can be active at a time. So it is
; sufficient for UUPC to hook whatever IRQ INT its modem is on as long as it
; unhooks it when it is done with that COM port. COMM cannot be an installed
; device driver since it must go away when UUPC is done so that other devices
; on the same INTs will come back to life. Also, it is OK to have a static
; CURRENT_AREA containing the current area that UUPC is using.
; Note about using the NS16550A UART chip's FIFOs. These are operated as
; silos. In other words when an interrupt happens because the receive(send)
; FIFO is nearly full(empty), as many bytes as possible are transferred and
; the interrupt dismissed. Thus, the interrupt load is lowered.
; Concerning the way the comm line is brought up.
; There are two basic cases, the Direct ('D') connection and the Modem ('M')
; connection. For either UUPC calls dtr_on_com() to bring up the line. This
; causes Data Terminal Ready (DTR) and Request To Send (RTS) to be set. Note
; this is OK for a simple 3-wire link but may be REQUIRED for a COM port
; connected to an external modem.
; The difference between a D connection and an M connection is
; whether or not the PC can expect any signals back from the modem. If
; there is a simple 3-wire link, Data Set Ready will be floating.
; (Actually, some wise people jumper Data Terminal Read back to Data
; Set Ready so the PC sees its own DTR appear as DSR.) UUPC should be
; able to handle the simplest cable as a design feature. So both D and
; M connections send out DTR and RTS, but only the M connection expects
; a modem to respond.
; Then, if it is full modem connection (M), we wait for a few
; seconds hoping that both Data Set Ready (DSR) and Clear To Send (CTS)
; will come up. If they don't, the associated counters are incremented
; for subsequent printing in the error log. Note that no error is
; reported from COMM to UUPC at this point, although this would be a
; good idea. COMMFIFO.ASM forces the connection to be a D type and lets
; UUPC storm ahead with its output trying to
; establish a link, but the output is never sent due to one of the
; control signals being false. UUPC could check the modem status using
; a call which has been installed just for this purpose.
; Note, if you are going to connect your PC running UUPC to,
; say, a mainframe and you need hardware flow control (i.e., RTS-CTS
; handshaking), use a Modem connection. Using a simple 3-wire cable
; forbids hardware flow control and UUPC must be instructed to use a
; Direct connection. Refer to comments in the SYSTEMS file on how to
; make this selection.
; References used in designing the revisions to COMM.ASM:
; 1. The UNIX fas.c Driver code.
; 2. SLIP8250.ASM from the Clarkson driver set.
; 3. NS16550A data sheet and AN-491 from National Semiconductor.
; 4. Bell System Data Communications, Technical Reference for
; Data Set 103A, Interface Specification, February, 1967
; 5. Network mail regarding V.24
; 6. Joe Doupnik
PAGE;
;
; void far select_port(int)
; Arg is 1..4 and specifies which COM port is referenced by
; all other calls in this package.
;
_select_port PROC FAR
push bp
mov bp,sp
mov AX,[bp+6] ; get aguement
CMP AL,1 ; Port 1?
JE SP1 ; Yes
CMP AL,2 ; Port 2?
JE SP2 ; Yes
CMP AL,3 ; Port 3?
JE SP3 ; Yes
CMP AL,4 ; Port 4?
JE SP4 ; Yes
INT 20H ; N.O.T.A. ????? Halt for debugging!
; Assume port 1 if continued
SP1: MOV AX,OFFSET DGROUP:AREA1 ; SELECT COM1 DATA AREA
JMP SHORT SPX ; CONTINUE
SP2: MOV AX,OFFSET DGROUP:AREA2 ; SELECT COM2 DATA AREA
JMP SHORT SPX ; CONTINUE
SP3: MOV AX,OFFSET DGROUP:AREA3 ; SELECT COM3 DATA AREA
JMP SHORT SPX ; CONTINUE
SP4: MOV AX,OFFSET DGROUP:AREA4 ; SELECT COM4 DATA AREA
;Fall into SPX
SPX: MOV CURRENT_AREA,AX ; SET SELECTION IN MEMORY
mov sp,bp
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -