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

📄 comm.asm

📁 由3926个源代码
💻 ASM
📖 第 1 页 / 共 4 页
字号:
;
_ioctl_com PROC FAR
	PUSH BP
	MOV BP,SP
	PUSHF				; Save interrupt context
	PUSH SI
	MOV SI,CURRENT_AREA		; Pointer to COMi private area
	CLI				; Prevent surprises
	TEST INSTALLED[SI],1
	 JE IOCTLX			; No good.  Just return.
	MOV AX,[BP+6]			; Flags
	; Check bits here...
	MOV AX,[BP+8]			; Line speed
	MOV BAUD_RATE[SI],AX		; Save in parameter block
	CALL Set_Baud			; Set the baud rate in UART
IOCTLX: POP SI
	POPF				; Restore interrupt state
	MOV SP,BP
	POP BP
	RET
_ioctl_com	ENDP
	PAGE;
; ioctl-called routines (internal) ...

; SI:	COMi private block
;	CALL Set_Baud
; Returns: (nothing)
; Clobber: AX, BX, DX

Set_Baud PROC NEAR
	MOV AX,50
	MUL DIV50			; Could be different on a PCJr!
	DIV BAUD_RATE[SI]		; Get right number for the UART
	MOV BX,AX			; Save it
	MOV DX,LCR[SI]			; Line Control Register
	IN AL,DX			; Get current size, stops, parity,...
	PUSH AX
	OR AL,80H			; DLAB bit
	OUT DX,AL			; Talk to the baud rate regs now
	MOV DX,WORD PTR DLL[SI] 	; Least significant byte
	MOV AL,BL			; New value
	OUT DX,AL			; To UART
	MOV DX,WORD PTR DLH[SI] 	; Most signifiant byte
	MOV AL,BH			; New value
	OUT DX,AL
	MOV DX,LCR[SI]			; Line Control Register
	POP AX
	OUT DX,AL			; Turn off DLAB, keep saved settings
	RET
Set_Baud ENDP
	PAGE;
;
; void far close_com(void)
;	Turn off interrupts from the COM port
;
_close_com PROC FAR
	push bp
	mov bp,sp
	PUSHF
	PUSH SI
	MOV	SI,CURRENT_AREA 	; SI POINTS TO DATA AREA
	TEST	INSTALLED[SI],1 	; PORT INSTALLED?
	 JZ	CCX			; ABORT IF NOT

; TURN OFF UART and clear FIFOs in NS16550A
	CLI
	MOV DX,IER[SI]
	MOV AL,0
	OUT DX,AL			; No interrupts right now, please
	MOV DX,FCR[SI]			; FIFO Control Register
	MOV AL,FIFO_CLEAR		; Disable FIFOs
	OUT DX,AL
	MOV DX,MCR[SI]			; Modem control register
	XOR AL,AL			; OUT2 is IRQ enable on some machines,
	OUT DX,AL			; So, clear RTS, OUT1, OUT2, LOOPBACK

; TURN OFF 8259
	MOV	DX,INTA01
	IN	AL,DX
	OR	AL,IRQ[SI]
	JMP	$+2			; DELAY FOR AT
	JMP	$+2			; DELAY FOR AT
	JMP	$+2			; DELAY FOR AT
	OUT	DX,AL

CCX:	POP SI
	POPF				; Restore interrupt state
	mov sp,bp
	pop bp
	RET
_close_com ENDP
	PAGE;
;
; void far dtr_off(void)
;	Tells modem we are done.  Remote end should hang up also.
;
_dtr_off PROC FAR
	push bp
	mov bp,sp
	PUSH SI
	MOV	SI,CURRENT_AREA 	; SI POINTS TO DATA AREA
	TEST	INSTALLED[SI],1 	; PORT INSTALLED?
	 JZ	DFX			; ABORT IF NOT

	MOV DX,MCR[SI]			; Modem Control Register
	IN AL,DX			; Get current state
	PUSH AX 			; Save MCR
	MOV AL,08H			; DTR off, RTS off, OUT2 on
	OUT DX,AL
	POP AX				; Get previous state
	AND AL,1			; Just look at the DTR bit
	 JE DFX 			; Not on.  Don't clr.  Don't wait.
	MOV AX,50			; 50/100 of second
IFNDEF UUPC
	CALL WaitN			; V.24 says it must be low >1/2 sec
ENDIF
DFX:	POP SI
	mov sp,bp
	pop bp
	RET
_dtr_off	ENDP
	PAGE;
;
; void far dtr_on(void) 	Tell modem we can take traffic
;
_dtr_on PROC FAR
	push bp
	mov bp,sp
	PUSH SI
	MOV	SI,CURRENT_AREA 	; SI POINTS TO DATA AREA
	TEST	INSTALLED[SI],1 	; PORT INSTALLED?
	 JZ DTRONF			; Suppress output if not

; Tell modem we are ready and want to send with line idle

	MOV DX,MCR[SI]			; Modem Control Register
	MOV AL,00001011B		; OUT 2, RTS, DTR
	OUT DX,AL
	CMP CONNECTION[SI],'D'          ; Direct connection (no DSR,CTS)?
	 JNE DTRON0			; Go wait for DSR, CTS
	MOV SEND_OK[SI],1		; Set output enable flag
	JMP SHORT DTRONS		; Give success return

; Wait for awhile to give the modem time to respond

DTRON0: MOV AH,2CH			; Get time (H:M:S:H to CH:CL:DH:DL)
	INT 21H
	MOV BX,DX			; Save seconds&hundreths
	ADD BH,06			; Allow a few seconds
	CMP BH,60			; Wrap around check
	 JL DTRON1			; No wrap
	SUB BH,60
DTRON1: CMP SEND_OK[SI],1		; Did the modem come up?
	 JE DTRONS			; Yes.	Both DSR and CTS are true.
	INT 21H 			; Get the time again
	CMP DX,BX			; Current time is passed the deadline?
	 JB DTRON1			; No, keep checking 'til time runs out

	; Modem failed to come up.  Bump counts that tell why.
	MOV	DX,MSR[SI]		; MODEM STATUS REGISTER
	IN	AL,DX			; GET MODEM STATUS
	TEST	AL,20H			; DATA SET READY?
	 JNZ DTRON6			; Yup.
	INC	WORD PTR EDSR[SI]	; BUMP ERROR COUNT
DTRON6: TEST	AL,10H			; Clear To Send?
	 JNZ DTRONF			; That's OK.
	INC	WORD PTR ECTS[SI]	; BUMP ERROR COUNT - WE TIMED OUT
	; Fall into DTRONF
	PAGE;
; Failure return

DTRONF: MOV SEND_OK[SI],1		; Make believe DSR & CTS are up!!!
	MOV CONNECTION[SI],'D'          ; Switch to DIR connection (MSTATINT)
	JMP SHORT DTRONX


; Successful return

DTRONS: ; SEND_OK is on.  Setting it again could confuse interrupt level
	; Fall into DTRONX

DTRONX: MOV AX,200H			; 2 Seconds
IFNDEF UUPC
	CALL WaitN			; V.24 says 2 sec hi before data
ENDIF
	POP SI
	mov sp,bp
	pop bp
	RET
_dtr_on ENDP
	PAGE;
;
; Wait for specified time using the 18.2 ticks/second clock
;
; Call: 	AX has seconds,hundreths
;		CALL WaitN
; Return:	At least the requested time has passed
;

WaitN	PROC NEAR
	PUSH BP
	MOV BP,SP
	PUSH AX
	PUSH BX
	PUSH CX
	PUSH DX
	PUSH AX 			; Save a copy of the arg
	MOV AH,2CH			; Get time (H:M:S:H to CH:CL:DH:DL)
	INT DOS
	POP BX				; Recover S:H arg
	ADD BX,DX			; Determine deadline
	CMP BL,100			; Wrap around?
	 JL WaitN1			; No
	SUB BL,100			; Yes.	Subtract 100 hundreths
	INC BH				; And add a second
WaitN1: CMP BH,60			; Wrap around check
	 JL WaitN2			; No wrap
	SUB BH,60			; Forget about Days and Hours
WaitN2: INT DOS 			; Get the time again
	CMP DX,BX			; Is current time after the deadline?
	 JB WaitN2			; No, keep checking 'til time runs out
	POP DX
	POP CX
	POP BX
	POP CX
	MOV SP,BP
	POP BP
	RET
WaitN	ENDP
	PAGE;
;
; unsigned long r_count(void)
;	Value is really two uints:  Buffer size in high half, count in low.
;	Count returned is <= number of chars waiting to be read.
;		(More may come in after you asked.)
;
_r_count PROC FAR
	push bp
	mov bp,sp
	PUSH SI
	MOV	SI,CURRENT_AREA 	; SI POINTS TO DATA AREA
	XOR AX,AX			; Say nothing available if not inst'd
	MOV DX,R_SIZE			; Size of entire receive buffer
	TEST	INSTALLED[SI],1 	; PORT INSTALLED?
	 JZ	RCX			; ABORT IF NOT
	MOV	AX,SIZE_RDATA[SI]	; GET NUMBER OF BYTES USED
RCX:	POP SI
	mov sp,bp
	pop bp
	RET
_r_count ENDP
	PAGE;
;
; char far receive_com(void)
;	Returns AX: -1 if port not installed or no characters available
;		or AX: the next character with parity stipped if not in P mode
;
_receive_com PROC FAR
	push bp
	mov bp,sp
	PUSHF				; Save interrupt state
	PUSH SI
	PUSH ES
	MOV	SI,CURRENT_AREA 	; SI POINTS TO DATA AREA
	mov	ax,-1			; -1 if bad call
	TEST	INSTALLED[SI],1 	; PORT INSTALLED?
	 JZ	RECVX			; ABORT IF NOT
	CLI
	CMP	SIZE_RDATA[SI],0	; ANY CHARACTERS?
	 JE RECVX			; Return -1 in AX

	mov ah,0			; good call
	LES	BX,RBuff[SI]		; Location of receive buffer
	ADD	BX,START_RDATA[SI]	; GET POINTER TO OLDEST CHAR
	MOV AL,ES:[BX]			; Get character from buffer
	CMP	PARITY[SI],'N'          ; ARE WE RUNNING WITH NO PARITY? LBA
	 JE	RECV1			; IF SO, DON'T STRIP HIGH BIT    LBA
	AND	AL,7FH			; STRIP PARITY BIT
RECV1:	MOV BX,START_RDATA[SI]		; Get the start index again
	INC	BX			; BUMP START_RDATA
	AND BX,R_SIZE-1 		; Ring the pointer
	MOV	START_RDATA[SI],BX	; SAVE THE NEW START_RDATA VALUE
	DEC	SIZE_RDATA[SI]		; ONE LESS CHARACTER
	CMP	XON_XOFF[SI],'E'        ; FLOW CONTROL ENABLED?
	 JNE	RECVX			; DO NOTHING IF DISABLED
	CMP	HOST_OFF[SI],1		; HOST TURNED OFF?
	 JNE	RECVX			; JUMP IF NOT
	CMP	SIZE_RDATA[SI],R_SIZE/16; RECEIVE BUFFER NEARLY EMPTY?
	 JGE	RECVX			; DONE IF NOT
	MOV	HOST_OFF[SI],0		; TURN ON HOST IF SO

	PUSH	AX			; SAVE RECEIVED CHAR
	MOV	AL,CONTROL_Q		; TELL HIM TO TALK
RECV3:	CLI				; TURN OFF INTERRUPTS
	CMP URGENT_SEND[SI],1		; Previous send still in progress?
	 JNE RECV4			; No.  There is space now.
	STI				; Yes.	Wait for interrupt to take it.
	JMP SHORT RECV3 		; Loop 'til it's gone
RECV4:	CALL	SENDII			; SEND IMMEDIATELY INTERNAL
	POP	AX			; RESTORE RECEIVED CHAR

RECVX:	POP ES
	POP SI
	POPF				; Restore interrupt state
	mov sp,bp
	pop bp
	RET
_receive_com ENDP
	PAGE;
;
; unsigned long s_count(void)
;    Value is really two uints: Buffer size in high half (returned in DX).
;				Free space count in low (returned in AX).
;    Count returned is <= number of chars which can be sent without blocking.
;		(More may become available after you asked.)
;
; N.B. The free space might be negative (-1) if the buffer was full and then
; the program called SENDI or RXI required sending a control-S to squelch
; the remote sender.  Return 0 in this case.
;
_s_count PROC FAR
	push bp
	mov bp,sp
	PUSH SI
	MOV	SI,CURRENT_AREA 	; SI POINTS TO DATA AREA
	MOV	AX,0			; NO SPACE LEFT IF NOT INSTALLED
	mov dx,S_SIZE-1 		; Leave 1 byte for a SENDII call
	TEST	INSTALLED[SI],1 	; PORT INSTALLED?
	 JZ	SCX			; ABORT IF NOT
	MOV AX,S_SIZE-1 		; Size, keeping one aside for SENDII
	SUB AX,SIZE_TDATA[SI]		; Minus number in use right now
	 JGE SCX			; Avoid returning negative number
	XOR AX,AX			; Return 0
SCX:	POP SI
	mov sp,bp
	pop bp
	RET
_s_count ENDP
	PAGE;
;
; void far send_com(char)
;	Send a character to the selected port
;
_send_com PROC FAR
	push bp
	mov bp,sp
	PUSHF				; Save interrupt state
	PUSH SI
	PUSH ES
	MOV	SI,CURRENT_AREA 	; SI POINTS TO DATA AREA
	TEST	INSTALLED[SI],1 	; PORT INSTALLED?
	 JZ	SENDX			; ABORT IF NOT

SEND1:	CMP	SIZE_TDATA[SI],S_SIZE-1 ; BUFFER FULL? (Leave room for SENDII)
	 JGE SEND1			; Wait for interrupts to empty buffer
	CLI
	LES BX,TBuff[SI]		; Pointer to buffer
	ADD BX,END_TDATA[SI]		; ES:BX points to free space
	MOV AL,[BP+6]			; Character to send
	MOV ES:[BX],AL			; Move character to buffer
	MOV BX,END_TDATA[SI]		; Get index of end
	INC	BX			; INCREMENT END_TDATA
	AND BX,S_SIZE-1 		; Ring the pointer
	MOV	END_TDATA[SI],BX	; SAVE NEW END_TDATA
	INC	SIZE_TDATA[SI]		; ONE MORE CHARACTER IN X-MIT BUFFER

	TEST PC_OFF[SI],1		; Were we stopped by a ^S from host?
	 JNZ SENDX			; Yes.	Don't enable interrupts yet.
	CALL CHROUT			; Put a character out to the UART
SENDX:	POP ES
	POP SI
	POPF				; Restore interrupt state
	mov sp,bp
	pop bp
	RET
_send_com ENDP
	PAGE;
;
; void far sendi_com(char)
;	Send a character immediately by placing it at the head of the queue
;
_sendi_com PROC FAR
	push bp
	mov bp,sp
	PUSHF				; Save interrupt state
	PUSH SI
	mov al,[bp+6]
	MOV	SI,CURRENT_AREA 	; SI POINTS TO DATA AREA
	TEST	INSTALLED[SI],1 	; PORT INSTALLED?
	 JZ SENDIX			; Return if not

SENDI3: CLI				; TURN OFF INTERRUPTS
	CMP URGENT_SEND[SI],1		; Previous send still in progress?
	 JNE SENDI4			; No.  There is space now.
	STI				; Yes.	Wait for interrupt to take it.
	JMP SHORT SENDI3		; Loop 'til it's gone

SENDI4: CALL	SENDII			; CALL INTERNAL SEND IMMEDIATE

SENDIX: POP SI
	POPF				; Restore interrupt state
	mov sp,bp
	pop bp
	RET
_sendi_com ENDP
	PAGE;
; SENDII(AL, SI)  [internal routine]
;	Put char at head of output queue so it will go out next
;	Called from process level and (receive) interrupt level
;	DEPENDS ON CALLER TO KEEP INTERRUPTS CLEARED AND SET SI
;
SENDII	PROC NEAR
	PUSH BX
	PUSH DX
	PUSH ES
	LES BX,TBuff[SI]		; Location of transmit buffer

⌨️ 快捷键说明

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