⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 comm.asm

📁 由3926个源代码
💻 ASM
📖 第 1 页 / 共 4 页
字号:
	pop bp
	RET
_select_port ENDP
	PAGE;
;
; void far save_com(void)
;	Save the interrupt vector of the selected COM port.
;	N.B. save_com() and restore_com() call MUST be properly nested
;
_save_com PROC FAR
	push bp
	mov bp,sp
	PUSH SI
	PUSH	ES			; SAVE EXTRA SEGMENT
	MOV	SI,CURRENT_AREA 	; SI POINTS TO DATA AREA
	MOV	AREA1.INT_HNDLR,OFFSET INT_HNDLR1
	MOV	AREA2.INT_HNDLR,OFFSET INT_HNDLR2
	MOV	AREA3.INT_HNDLR,OFFSET INT_HNDLR3
	MOV	AREA4.INT_HNDLR,OFFSET INT_HNDLR4

; Save old interrupt vector
	MOV	AH,35H			; FETCH INTERRUPT VECTOR CONTENTS
	MOV	AL,INT_COM[SI]		; INTERRUPT NUMBER
	INT	DOS			; DOS 2 FUNCTION
	MOV	OLD_COM_OFF[SI],BX	; SAVE
	MOV	BX,ES			; ES:BX
	MOV	OLD_COM_SEG[SI],BX	; FOR LATER RESTORATION
	POP	ES			; RESTORE ES
	POP SI
	mov sp,bp
	pop bp
	RET				; DONE
_save_com ENDP
	PAGE;
;
; int far install_com(void)
;
;	Install the selected COM port.
;	Returns:	0: Failure
;			1: Success
;
; SET UART PORTS FROM RS-232 BASE IN ROM BIOS DATA AREA
; INITIALIZE PORT CONSTANTS AND ERROR COUNTS
;
; Assign blocks of memory for transmit and receive buffers
;
_install_com PROC FAR
	push bp
	mov bp,sp
	PUSHF				; Save caller's interrupt state
	PUSH SI
	PUSH DI
	PUSH ES
	MOV	SI,CURRENT_AREA 	; SI POINTS TO DATA AREA
	CMP	INSTALLED[SI],1 	; Is port installed on this machine?
	 JNE	INST1			; NO, CONTINUE
	JMP	INST9			; ELSE JUMP IF ALREADY INSTALLED

; Assign memory for transmit and receive buffers

INST1:	MOV BX,S_SIZE			; Send buffer size
	ADD BX,0FH			; Round up
	SHR BX,1			; Must run on an XT
	SHR BX,1
	SHR BX,1
	SHR BX,1			; Now have number of paragraphs
	MOV AX,4800H			; Allocate memory
	INT DOS
	 JC INSTFAIL			; Give fail return
	MOV WORD PTR TBuff[SI],0	; Save in private block for this port
	MOV WORD PTR TBuff[SI+2],AX

	MOV BX,R_SIZE			; Receive buffer size
	ADD BX,0FH			; Round up
	SHR BX,1			; Must run on an XT
	SHR BX,1
	SHR BX,1
	SHR BX,1			; Now have number of paragraphs
	MOV AX,4800H			; Allocate memory
	INT DOS
	 JNC INSTSUCC			; Success --> Continue

	; Unhand the send buffer assigned above

	MOV AX,WORD PTR TBuff+2[SI]	; Transmit buffer paragraph
	MOV ES,AX			; Honest.  That's where the arg goes.
	MOV AX,4900H			; Release memory
	INT DOS
	; Ignore error
	; Fall into INSTFAIL

INSTFAIL:
	 JMP INST666			; Failure --> Give failed response

INSTSUCC:
	MOV WORD PTR RBuff[SI],0	; Save in private block for this port
	MOV WORD PTR RBuff[SI+2],AX

IFDEF DEBUG
	PUSH DI
	CLD				; Go up in memory
	XOR AX,AX			; A zero to store
	LES DI,TBuff[SI]		; Transmit buffer location
	MOV CX,S_SIZE			; Size of buffer
	REP STOSB			; Clear entire buffer
	LES DI,RBuff[SI]		; Receive buffer location
	MOV CX,R_SIZE			; Size of buffer
	REP STOSB			; Clear entire buffer
	POP DI
ENDIF
	PAGE;

; CLEAR ERROR COUNTS
	CLI				; Stray interrupts cause havoc
	MOV	WORD PTR EOVFLOW[SI],0	; BUFFER OVERFLOWS
	MOV	WORD PTR EOVRUN[SI],0	; RECEIVE OVERRUNS
	MOV	WORD PTR EBREAK[SI],0	; BREAK CHARS
	MOV	WORD PTR EFRAME[SI],0	; FRAMING ERRORS
	MOV	WORD PTR EPARITY[SI],0	; PARITY ERRORS
	MOV	WORD PTR EXMIT[SI],0	; TRANSMISSION ERRORS
	MOV	WORD PTR EDSR[SI],0	; DATA SET READY ERRORS
	MOV	WORD PTR ECTS[SI],0	; CLEAR TO SEND ERRORS

	MOV	BX,RBDA 		; ROM BIOS DATA AREA
	MOV	ES,BX			; TO ES
	ASSUME	ES:RBDA

; Map port number (COMx) into IO Address using the RS232_Base[x] table in
; the BIOS data area.  If any of the ports is missing there should be a
; zero in the table for this COM port.	BIOS startup routines pack the table
; so that if you have a COM4 but no COM3, 2E8 will be found in 40:4 and 0
; will be in 40:6.

; N.B. The exact IO address in 40:x is irrelevant and may well be something
; other than the "standard" values if specially designed hardware is used.
; To minimize flack, we will use the standard value if the slot in the table
; is 0.  The bad side effect of this is that (in the standard losing case of
; a COM4 but no COM3) both COM3 and COM4 will reference the hardware at 2E8.

	CMP	PORT[SI],1		; PORT 1?
	 JE	INST3F8 		; Yes
	CMP	PORT[SI],2		; PORT 2?
	 JE	INST2F8 		; Yes
	CMP	PORT[SI],3		; PORT 3?
	 JE	INST3E8 		; Yes
	CMP	PORT[SI],4		; PORT 4?
	 JE	INST2E8 		; Yes
	INT	20H			; NOTA. (Caller is screwed up badly)

INST3F8:MOV AX,3F8H			; Standard COM1 location
	CMP	RS232_BASE+0,0000H	; We have information?
	 JE	INST2			; No --> Use default
	MOV	AX,RS232_BASE+0 	; Yes --> Use provided info
	JMP	SHORT INST2		; CONTINUE

INST2F8:MOV AX,2F8H			; Standard COM2 location
	CMP	RS232_BASE+2,0000H	; We have information?
	 JE	INST2			; No --> Use default
	MOV	AX,RS232_BASE+2 	; Yes --> Use provided info
	JMP	SHORT INST2		; CONTINUE

INST3E8:MOV AX,3E8H			; Standard COM3 location
	CMP	RS232_BASE+4,0000H	; We have information?
	 JE	INST2			; No --> Use default
	MOV	AX,RS232_BASE+4 	; Yes --> Use provided info
	JMP	SHORT INST2		; CONTINUE

INST2E8:MOV AX,2E8H			; Standard COM4 location
	CMP	RS232_BASE+6,0000H	; We have information?
	 JE	INST2			; No --> Use default
	MOV	AX,RS232_BASE+6 	; Yes --> Use provided info
	; Fall into INST2


; Now we have an IO address for the COMx that we want to use.  If it is
; anywhere in RS232_Base, we know that it has been check and is OK to use.
; So, even if my 2E8 (COM4) appears in 40:6 (normally for COM3), I can use
; it.

INST2:	CMP	AX,RS232_BASE		; INSTALLED?
	 JE	INST2A			; JUMP IF SO
	CMP	AX,RS232_BASE+2 	; INSTALLED?
	 JE	INST2A			; JUMP IF SO
	CMP	AX,RS232_BASE+4 	; INSTALLED?
	 JE	INST2A			; JUMP IF SO
	CMP	AX,RS232_BASE+6 	; INSTALLED?
	 JNE	INST666 		; JUMP IF NOT
	; Fall into INST2A

INST2A: MOV	BX,DATREG		; OFFSET OF TABLE OF PORTS
	MOV	CX,7			; LOOP SIX TIMES
INST3:	MOV	WORD PTR [SI][BX],AX	; SET PORT ADDRESS
	INC	AX			; NEXT PORT
	ADD	BX,2			; NEXT WORD ADDRESS
	 LOOP	INST3			; RS232 BASE LOOP
	MOV DX,FCR[SI]			; Get FIFO Control Register
	MOV AL,FIFO_INIT
	OUT DX,AL			; Try to initialize the FIFO
	CALL SPINLOOP			; Permit I/O bus to settle
	MOV DX,IIR[SI]			; Get interrupt ID register
	IN AL,DX			; See how the UART responded
	AND AL,FIFO_ENABLED		; Keep only these bits
	MOV CX,1			; Assume chunk size of 1 for 8250 case
	CMP AL,FIFO_ENABLED		; See if 16550A
	 JNE INST4			; Jump if not
	MOV CX,FIFO_LEN
INST4:	MOV UART_SILO_LEN[SI],CL	; Save chunk size for XMIT side only
	MOV AL,FIFO_CLEAR
	OUT DX,AL

	MOV	AH,25H			; SET INTERRUPT VECTOR CONTENTS
	MOV	AL,INT_COM[SI]		; INTERRUPT NUMBER
	MOV	DX,INT_HNDLR[SI]	; OUR INTERRUPT HANDLER [WWP]
	PUSH	DS			; SAVE DATA SEGMENT
	PUSH	CS			; COPY CS
	POP	DS			; TO DS
	INT	DOS			; DOS FUNCTION
	POP	DS			; RECOVER DATA SEGMENT

; PORT INSTALLED
INST9:	MOV AX,1
	JMP SHORT INSTX

; PORT NOT INSTALLED
INST666:MOV AX,0
	;Fall into INSTX

; Common exit
INSTX:	MOV INSTALLED[SI],AL		; Indicate whether installed or not
IFDEF DEBUG
	MOV DX,ST8250
	CMP UART_SILO_LEN[SI],1
	 JE INSTXX
	MOV DX,ST16550
INSTXX: MOV AH,9
	INT DOS 			; Announce UART type
	MOV DX,STUART
	INT DOS
ENDIF
	POP ES
	POP DI
	POP SI
	POPF				; Restore caller's interrupt state
	mov sp,bp
	pop bp
	RET
_install_com ENDP
	PAGE;
;
; void far restore_com(void)
;	Restore original interrupt vector and release storage
;
_restore_com PROC FAR
	push bp
	mov bp,sp
	PUSHF
	PUSH SI
	PUSH ES
	MOV	SI,CURRENT_AREA 	; SI POINTS TO DATA AREA
	CLI
	MOV	INSTALLED[SI],0 	; PORT IS NO LONGER INSTALLED
	MOV	AH,25H			; SET INTERRUPT VECTOR FUNCTION
	MOV	AL,INT_COM[SI]		; INTERRUPT NUMBER
	MOV	DX,OLD_COM_OFF[SI]	; OLD OFFSET TO DX
	MOV	BX,OLD_COM_SEG[SI]	; OLD SEG
	PUSH	DS			; SAVE DS
	MOV	DS,BX			; TO DS
	INT	DOS			; DOS FUNCTION
	POP DS				; Recover our data segment

	MOV AX,WORD PTR TBuff+2[SI]	; Transmit buffer paragraph
	MOV ES,AX			; Honest.  That's where the arg goes.
	MOV AX,4900H			; Release memory
	INT DOS
	 ; Ignore error
	MOV AX,WORD PTR RBuff+2[SI]	; Receive buffer paragraph
	MOV ES,AX
	MOV AX,4900H
	INT DOS
	 ; Ignore error
	POP ES
	POP SI
	POPF
	mov sp,bp
	pop bp
	RET
_restore_com ENDP
	PAGE;
;
; void far open_com(int Baud, char Conn, char Parity, char Stops, char Flow);
;
; CLEAR BUFFERS
; RE-INITIALIZE THE UART
; ENABLE INTERRUPTS ON THE 8259 INTERRUPT CONTROL CHIP
;
; [bp+6] = BAUD RATE
; [bp+8] = CONNECTION: M(ODEM), D(IRECT)
; [bp+10] = PARITY:	N(ONE), O(DD), E(VEN), S(PACE), M(ARK)
; [bp+12] = STOP BITS:	1, 2
; [bp+14] = XON/XOFF:	E(NABLED), D(ISABLED)
;
_open_com PROC FAR
	push bp
	mov bp,sp
	PUSHF
	PUSH SI
	MOV	SI,CURRENT_AREA 	; SI POINTS TO DATA AREA
	CLI				; INTERRUPTS OFF
	TEST INSTALLED[SI],1		; Port installed?
	 JNZ OPEN1			; Yes --> Proceed
	 JMP OPENX			; No  --> Get out

OPEN1:	mov ax,[bp+6]
	MOV	BAUD_RATE[SI],AX	; SET
	mov bh,[bp+8]
	MOV	CONNECTION[SI],BH	; ARGS
	mov bl,[bp+10]
	MOV	PARITY[SI],BL		; IN
	mov ch,[bp+12]
	MOV	STOP_BITS[SI],CH	; MEMORY
	mov cl,[bp+14]
	MOV	XON_XOFF[SI],CL

; RESET FLOW CONTROL
	MOV	HOST_OFF[SI],0		; HOST FLOWING
	MOV	PC_OFF[SI],0		; PC FLOWING
	MOV URGENT_SEND[SI],0		; No (high priority) flow ctl
	MOV SEND_OK[SI],0		; DTR&CTS are not on yet

; RESET BUFFER COUNTS AND POINTERS
	MOV	START_TDATA[SI],0
	MOV	END_TDATA[SI],0
	MOV	START_RDATA[SI],0
	MOV	END_RDATA[SI],0
	MOV	SIZE_TDATA[SI],0
	MOV	SIZE_RDATA[SI],0

;
; RESET THE UART
	MOV DX,MCR[SI]			; Modem Control Register
	IN AL,DX			; Get current settings
	AND AL,0FEH			; Clr RTS, OUT1, OUT2 & LOOPBACK, but
	OUT DX,AL			; Not DTR (No hangup during autobaud)
	MOV DX,MSR[SI]			; Modem Status Register
	IN AL,DX			; Get current DSR and CTS states.
	AND AL,30H			; Init PREVIOUS STATE FLOPS to current
	OUT DX,AL			;  state and clear Loopback, etc.
	IN AL,DX			; Re-read to get delta bits & clr int
	AND AL,30H			; Leave the two critical bits
	CMP AL,30H			; Both on?
	 JNE OPEN2			; No.  Leave SEND_OK zero.
	MOV SEND_OK[SI],1		; Allow TXI to send out data
OPEN2:	MOV DX,FCR[SI]			; I/O Address of FIFO control register
	MOV AL,FIFO_CLEAR		; Disable FIFOs
	OUT DX,AL			; Non-16550A chips will ignore this
	MOV	DX,LSR[SI]		; RESET LINE STATUS CONDITION
	IN	AL,DX
	MOV	DX,DATREG[SI]		; RESET RECEIVE DATA CONDITION
	IN	AL,DX
	MOV	DX,MSR[SI]		; RESET MODEM DELTAS AND CONDITIONS
	IN	AL,DX

	CALL Set_Baud			; Set the baud rate from arg
	PAGE;
; SET PARITY AND NUMBER OF STOP BITS
	MOV	AL,03H			; Default: NO PARITY + 8 bits data

	CMP	PARITY[SI],'O'          ; ODD PARITY REQUESTED?
	 JNE	P1			; JUMP IF NOT
	MOV	AL,0AH			; SELECT ODD PARITY + 7 bits data
	JMP	SHORT P4		; CONTINUE
;
P1:	CMP	PARITY[SI],'E'          ; EVEN PARITY REQUESTED?
	 JNE	P2			; JUMP IF NOT
	MOV	AL,1AH			; SELECT EVEN PARITY + 7 bits data
	JMP	SHORT P4		; CONTINUE
;
P2:	CMP	PARITY[SI],'M'          ; MARK PARITY REQUESTED?
	 JNE	P3			; JUMP IF NOT
	MOV	AL,2AH			; SELECT MARK PARITY + 7 bits data
	JMP SHORT P4

P3:	CMP PARITY[SI],'S'              ; SPACE parity requested?
	 JNE P4 			; No.  Must be 'N' (NONE)
	MOV AL,3AH			; Select SPACE PARITY + 7 bits data

P4:	TEST	STOP_BITS[SI],2 	; 2 STOP BITS REQUESTED?
	 JZ	STOP1			; NO
	OR	AL,4			; YES
STOP1:	MOV	DX,LCR[SI]		; LINE CONTROL REGISTER
	OUT	DX,AL			; SET UART PARITY MODE AND DLAB=0

; Initialize the FIFOs
	MOV	DX,FCR[SI]		; I/O Address of FIFO control register
	MOV	AL,FIFO_INIT		; Clear FIFOs, set size, enable FIFOs
	OUT	DX,AL			; Non-16550A chips will ignore this

; ENABLE INTERRUPTS ON 8259 AND UART
	IN	AL,INTA01		; SET ENABLE BIT ON 8259
	AND	AL,NIRQ[SI]
	OUT	INTA01,AL
	MOV DX,IER[SI]			; Interrupt enable register
	MOV AL,0DH			; Line & Modem status, recv [GT]
	OUT DX,AL			; Enable those interrupts

OPENX:	POP SI
	POPF				; Restore interrupt state
	mov sp,bp
	pop bp
	RET				; DONE
_open_com ENDP
	PAGE;
;
; void far ioctl_com(int Flags, int Arg1, ...)
;	Flags have bits saying what to do or change (IGNORED TODAY)
;	Arg1, ...  are the new values

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -