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

📄 slib.asm

📁 The EZ320 utility demonstrates the communication program between host PC and the MR320.
💻 ASM
字号:
;;*****************************************************************************
; FILE : SLIB.OBJ
;	 Supports COM1, COM2, COM3, COM4
;
;		  IRQ	     Address
;	 COM1	  4	     03F8
;	 COM2	  3	     02F8
;	 COM3	  4	     03E8
;	 COM4	  3	     02E8
;
;*****************************************************************************

	BUFSIZE=8000 ;size of buffer to use for receive
_BSS	SEGMENT WORD	PUBLIC	'BSS'
_BSS	ENDS
_TEXT	SEGMENT BYTE	PUBLIC	'CODE'
_TEXT	ENDS
;---------------------------------------------
DGROUP	GROUP	_BSS ;global variable are in this group
_BSS	SEGMENT
intsav	dw	8 dup(?);storage for saved interrupt vectors
bufin	dw	4 dup(?);buffer input pointers
bufout	dw	4 dup(?);buffer output pointers
buff0	db	BUFSIZE dup(?);the com1 circular buffer
buff1	db	BUFSIZE dup(?);the com2 circular buffer
buff2	db	BUFSIZE dup(?);the com3 circular buffer
buff3	db	BUFSIZE dup(?);the com4 circular buffer
_BSS	ENDS
;---------------------------------------------
_DATA	 SEGMENT  PARA PUBLIC 'DATA'
baud	 db	 17h,04      ; 110
	 db	 00,03h      ; 150
	 db	 80h,01      ; 300
	 db	 0c0h,0h     ; 600
	 db	 60h,0h      ; 1200
	 db	 30h,0h      ; 2400
	 db	 18h,0h      ; 4800
	 db	 0ch,0h      ; 9600
	 db	 6h,0h	     ; 19200
	 db	 03h,0h      ; 38400
	 db	 02h,0h      ; 57600
	 db	 01h,0h      ; 115200
a_table  db	 '0123456789ABCDEF'
_DATA	  ENDS
_TEXT	SEGMENT
	ASSUME	CS:_TEXT,DS:DGROUP
;
;------------------------------------------------------------------------------
;Function:Initialize and configure serial port (0/1/2/3  for COM1/2/3/4).
;
;Algorithm:Call the ROM BIOS to configure and initialize the port.Then
;	   save the existing interrupt vector and replace it with our own.
;	   Enable interrupts at the port,and return.
;
;void serinit(int port,int baud)
;------------------------------------------------------------------------------
	public	_serinit
	port=6
	config=8
bufaddr dw	offset DGROUP:buff0,offset DGROUP:buff1
	dw	offset DGROUP:buff2,offset DGROUP:buff3
buflim	dw	offset DGROUP:buff0+BUFSIZE,offset DGROUP:buff1+BUFSIZE
	dw	offset DGROUP:buff2+BUFSIZE,offset DGROUP:buff3+BUFSIZE
_serinit	proc	far
	push	bp
	mov	bp,sp
	push	di
	push	si
	mov	dx,[bp+port]	  ;DX=port number
	mov	al,[bp+config]	  ;AL=port configuration
	mov	ah,0
	call	new_init
	cli			  ;Disable interrupts
	push	es
	xor	ax,ax
	mov	es,ax
	mov	si,[bp+port]
	shl	si,1
	mov	ax,cs:[si+bufaddr]   ;set the buffer empty:
	mov	[si+bufin],ax	     ;bufin=bufout=start of buffer
	mov	[si+bufout],ax
	mov	bx,es:[si+400h]      ;BX=base port address of serial port
	mov	si,1		     ;SI=(1-port#)*4(offset to vector)
     mov     ax,[bp+port]
     and     ax,1
     sub     si,ax
;;	sub	si,[bp+port]
	shl	si,1
	shl	si,1
	mov	ax,es:[si+2ch]	     ;Save the old vector in intsav
	mov	[si+intsav],ax
	mov	ax,es:[si+2ch+2]
	mov	[si+intsav+2],ax
	mov	ax,offset intserv    ;replace the vector with intserv
	mov	es:[si+2ch],ax
	mov	ax,_TEXT
	mov	es:[si+2ch+2],ax
	mov	dx,bx		     ;read the serial port to clear it
	in	al,dx
	add	dx,4		     ;get modem control register address
	in	al,dx		     ;get contents of modem control registers
        or      al,0bh               ;set the out2 bit, set DTR, set RTS
	out	dx,al		     ;output it

	sub	dx,3		     ;get interrupt enable register address
	mov	al,1		     ;enable receive interrupts only
	out	dx,al		     ;set it

	in	al,21h		     ;get enable register from the 8259
	mov	ah,0efh 	     ;get mask
	mov	cl,[bp+port]	     ;rotate it according to port number
	and	cl,1
	ror	ah,cl
	and	al,ah
	out	21h,al		     ;output it to enable interrupts
	sti
	pop	es
	pop	si
	pop	di
	pop	bp
	ret
_serinit   endp

	public	_serctl
	port=6
	config=8
_serctl proc	far
	push	bp
	mov	bp,sp
	push	di
	push	si
	push	es
	mov	si,[bp+port]	      ;DX=port number
	mov	al,[bp+config]	      ;AL=port configuration
	shl	si,1

	mov	bx,0
	push	bx
	pop	es
	mov	dx,es:[si+400h]       ;DX=I/O port base address
	add	dx,4		      ;DX=address of line status register

	out	dx,al

	pop	es
	pop	si
	pop	di
	pop	bp
	ret
_serctl endp

;------------------------------------------------------------------------------
;Function:serial receives interrupt service routine.
;
;Algorithm:Save registers.Figure out which port the interrupt is from.
;	   Figure out what kind of interrupt it is,and process it accordingly.
;	   Acknowledge the intrrupt at the 8259.Then restore registers and
;	   return.
;
intserv    proc    near
	push	ax
	push	bx
	push	cx
	push	dx
	push	si
	push	ds
	push	es
	mov	ax,DGROUP
	mov	ds,ax
	xor	ax,ax
	mov	es,ax
;find which port the interrupt is from:
	xor	si,si		;SI=0 (assume COM1)
	mov	dx,es:400h	;DX=base port address for COM1
	add	dx,2		;Get IIR address
	in	al,dx		;Get IIR contents
	mov	ah,al		;Make a copy of the input
	and	ah,1		;Any interrupt here?
	jnz	c_com2		;If there is an interrupt,go process it.
	jmp	loop1

c_com2: mov	si,2		;SI=2 (assume COM2)
	mov	dx,es:402h	;DX=base port address for COM2
	add	dx,2		;Get IIR address
	in	al,dx		;Get IIR contents
	mov	ah,al		;Make a copy of the input
	and	ah,1		;Any interrupt here?
	jnz	c_com3		;If there is an interrupt,go process it.
	jmp	loop1

c_com3: mov	si,4		;SI=4 (assume COM3)
	mov	dx,es:404h	;DX=base port address for COM3
	add	dx,2		;Get IIR address
	in	al,dx		;Get IIR contents
	mov	ah,al		;Make a copy of the input
	and	ah,1		;Any interrupt here?
	jnz	c_com4		;If there is an interrupt,go process it.
	jmp	loop1

c_com4: mov	si,6		;If yes,increment SI for use with COM4
	mov	dx,es:406h	;Otherwise,DX=base port address for COM4
	add	dx,2		;Get IIR address for COM4
	in	al,dx		;Get IIR contents
	mov	ah,al		;Make a copy of it
	and	ah,1		;Are there interrupts?
	jnz	loop2		;If not,forget this interrupt

;
;find out which type of interrupt it is,and handle it:
;
loop1:	cmp	al,0		;Is it a modem status change?
	jne	loop3		;If not,try the next interrupt type
	add	dx,4		;If it is,read the modem status to clear it.
	in	al,dx
	jmp	end_it		;And exit
loop3:	cmp	al,2		;Is it a transmit register empty interrupt?
	jne	loop4		;If not,try other types
	jmp	end_it		;If it is,exit.
loop4:	cmp	al,4		;Is it a receiver register full interrupt?
	jne	loop5		;If not,try other types
	sub	dx,2		;If yes,read in the received character
	in	al,dx
	call	putb		;Put it in the buffer
	jmp	end_it		;And exit
loop5:	cmp	al,6		;Is it a receive line status interrupt?
	jne	end_it		;If not,it's no known type--ignore it
	add	dx,3		;If yes,read the status to clear it
	in	al,dx
end_it: mov	al,20h		;send enable of interrupt
	out	20h,al
loop2:	pop	es
	pop	ds
	pop	si
	pop	dx
	pop	cx
	pop	bx
	pop	ax
	iret
intserv endp

;------------------------------------------------------------------------------
;void serclose(int port)
;     port: 0/1/2/3 for COM1/2/3/4
;Function:close the port;restore it to the state it was in before serinit
;	  was called.
;
;Algorithm:Turn off interrupts and restore the interrupt vector to its original
;	   state.
;
	public	_serclose
		port=6
_serclose proc	far
	push	bp
	mov	bp,sp
	push	di
	push	si
	push	es
	xor	ax,ax
	mov	es,ax
	cli			      ;Disable interrupts
	mov	si,[bp+port]	      ;SI=2*port#
	shl	si,1
	mov	bx,es:[si+400h]       ;BX=I/O port base address
	mov	si,1		      ;SI=4*(1-port#)
     mov     ax,[bp+port]
     and     ax,1
     sub     si,ax
;;	sub	si,[bp+port]
	shl	si,1
	shl	si,1
	mov	ax,[si+intsav]	      ;Restore the interrupt from intSav
	mov	es:[si+2ch],ax
	mov	ax,[si+intsav+2]
	mov	es:[si+2ch+2],ax
	mov	dx,bx		      ;Get modem control register address
	add	dx,4
	in	al,dx		      ;Get current value

	and	al,0f7h 	      ;turn off out2 bit
	out	dx,al		      ;Set it

	sub	dx,3		      ;Get inteerrupt enable register address
	xor	al,al		      ;Clear all interrupt enable bits
	out	dx,al		      ;Set them

	in	al,21h		      ;Get 8259 enable byte
	mov	ah,10h		      ;Get a mask for the enable for this port
	mov	cl,[bp+port]
	and	cl,1
	ror	ah,cl
	or	al,ah		      ;Turn off the enable bit for this port
	out	21h,al		      ;Set it
	mov	al,20h		      ;Write an EOI just in case
	out	20h,al
	sti			      ;Re-enable interrupts at the processor
	pop	es
	pop	si
	pop	di
	pop	bp
	ret
_serclose    endp

;------------------------------------------------------------------------------
;_sersend(int port,int char)
;
;Function:send the character char out over serial port.
;
;Algorithm:Wait for the transmit holding register to be empty,and then output
;	   the character to be sent to that register.
;
	public	_sersend
		port=6
		char=8
_sersend  proc	far
	push	bp
	mov	bp,sp
	push	di
	push	si
	push	es
	mov	dx,[bp+port]	      ;DX=port#
	xor	ax,ax		      ;ES=0(for access to low memory)
	mov	es,ax
	mov	si,[bp+port]	      ;SI=2*port#
	shl	si,1
	mov	dx,es:[si+400h]       ;DX=I/O port base address
	add	dx,5		      ;DX=address of line status register
sendwt: in	al,dx		      ;Get line status
	and	al,20h		      ;transmit holding register empty
	jz	sendwt		      ;If not,keep asking....

	sub	dx,5		      ;if yes,DX=address of transmit holding
				      ;reg.
	mov	al,[bp+char]	      ;send character
	out	dx,al
	pop	es
	pop	si
	pop	di
	pop	bp
	ret
_sersend   endp


;-----------------------------------------------------------------------------
;int _serrecv(int port)
;
;Function:If a character is available from serial port,return it.otherwise,
;	  return -1 ( 0xFFFF ).
;
;Algorithm:Get the port number,turn off interrupts,and call getb to get a
;	   character out of the input buffer.
;
	public	_serrecv
	port=6
_serrecv  proc	far
	push	bp
	mov	bp,sp
	push	di
	push	si
	mov	si,[bp+port]	    ;SI=2*port#
	shl	si,1
	cli			    ;Disable interrupts
	call	getb		    ;get a character from the buffer
	sti			    ;Enable interrupts
	pop	si
	pop	di
	pop	bp
	ret
_serrecv   endp

;-----------------------------------------------------------------------------
;int _serstat(int port)
;
;Function:return the status of the serial port specified
;
;Algorithm:Call the ROm BIOS serial status function.
;
	public	_serstat
	    port=6
_serstat  proc	far
	push	bp
	mov	bp,sp
	push	di
	push	si
	mov	dx,[bp+port]
	mov	ah,3
	int	14h
	pop	si
	pop	di
	pop	bp
	ret
_serstat  endp

;-----------------------------------------------------------------------------
;Function:put a byte into a circular buffer.
;	  AL=byte,SI=offset
;	  0 for com1 buffer,2 for com2 buffer
;
;Algorithm:Get the bufin pointer.compute what the new bufin will be.
;	   If it equals bufout,the buffer is full.Otherwise,the character can
;	   be stored and bufin updated.
putb	proc	near
	mov	ah,-1			;Assume the buffer'll be full
	mov	bx,[si+bufin]		;BX=bufin
	mov	cx,bx			;CX=(BX+1) modulo buffer
	inc	cx
	cmp	cx,cs:[si+buflim]	;Is it past the end of the buffer?
	jne	putb2			;If not,continue
	mov	cx,cs:[si+bufaddr]	;If yes,reset it to the beginning
putb2:	cmp	cx,[si+bufout]		;Is the buffer full?
	je	putb3			;If it is,don't store this byte
	mov	[bx],al 		;Otherwise,store the byte
	xor	ah,ah			;Set AH to indicate success
	mov	[si+bufin],cx		;Update bufin
putb3:	ret				;return
putb	endp				;End of subroutine
;
;Function:get character from the circular buffer
;
;Algorithm:get the bufout pointer.If it equals bufin,the buffer is full.Other-
;	   wise,get a byte and in crement bufout.
;
getb	proc	near
	mov	ax,-1
	mov	bx,[si+bufout]
	cmp	bx,[si+bufin]		;bufout==bufin
	je	getb2			;If yes,go exit
	mov	al,[bx] 		;Otherwise,get byte from buffer
	xor	ah,ah			;Clear top byte of AX
	inc	bx			;Increment bufout
	cmp	bx,cs:[si+buflim]	;past end of buffer
	jne	getb3			;If not,continue
	mov	bx,cs:[si+bufaddr]	;If yes,reset to the beginning
getb3:	mov	[si+bufout],bx		;Update bufout
getb2:	ret
getb	endp
;
;    DX:0 COM1	 DX:1 COM2
;    AL:Parameter
;	bit  7 - 4   0000      110
;		     0001      150
;		     0010      300
;		     0011      600
;		     0100      1200
;		     0101      2400
;		     0110      4800
;		     0111      9600
;		     1000      19200
;		     1001      38400
;		     1010      57600
;		     1011      115200
;	bit  3 - 2   00        none parity
;		     01        odd  parity
;		     11        even parity
;	bit  1	     0	       one stop bit
;		     1	       two stop bit
;	bit  0	     0	       7 data bits
;		     1	       8 data bits
io_port  dw	 2f8h
new_init proc
	 push	 ds
	 push	 ax
	 push	 bx
	 push	 cx
	 push	 dx

	 push	 ax
	 push	 es
	 push	 si
	 xor	 ax,ax
	 mov	 es,ax
	 mov	 si,dx
	 shl	 si,1
	 mov	 bx,es:[si+400h]
	 mov	 io_port,bx
	 pop	 si
	 pop	 es
	 pop	 ax

	 mov	 ah,al			;; ah = al = config
	 and	 ah,0fh 		;; ah = (al & 0x0f) << 1 + 0x81
	 shl	 ah,1			;;
	 add	 ah,129 		;;
;;;
	 mov	 bl,al			;;
	 and	 bl,1
	 and	 ah,0fch		 ;;
	 or	 ah,bl
	 or	 ah,2
;;;
	 push	 ax			;;
	 push	 ax			;;
	 mov	 dx,io_port		;; dx = 2f8 or 2f8 = io_port
	 add	 dx,3			;; io_port = io_port + 3
	 mov	 al,ah			;;
	 out	 dx,al			;; outport(io_port,ah)

	 pop	 ax
	 mov	 cl,4
	 shr	 al,cl
	 and	 al,0fh
	 shl	 al,1
	 mov	 ah,0
	 mov	 dx,seg _DATA
	 mov	 ds,dx
	 mov	 bx,offset baud
	 add	 bx,ax
	 mov	 al,byte ptr [bx]
	 inc	 bx
	 mov	 ah,byte ptr [bx]
	 mov	 dx,io_port
	 out	 dx,al
	 mov	 al,ah
	 mov	 dx,io_port
	 add	 dx,1
	 out	 dx,al

	 pop	 ax
	 sub	 ah,128
	 mov	 al,ah
	 mov	 dx,io_port
	 add	 dx,3
	 out	 dx,al
	 pop	 dx
	 pop	 cx
	 pop	 bx
	 pop	 ax
	 pop	 ds
	 ret

new_init endp

hexput	 proc
	 push	ds
	 push	bx
	 push	cx
	 push	dx
	 push	ax
	 mov	dx,seg _DATA
	 mov	ds,dx
	 mov	bx,offset a_table
	 mov	cl,4
	 shr	al,cl
	 xlatb
	 mov	dl,al
	 mov	ah,02
	 int	21h
	 pop	ax
	 push	ax
	 and	al,00001111b
	 xlatb
	 mov	dl,al
	 mov	ah,02
	 int	21h

	 pop	ax
	 pop	dx
	 pop	cx
	 pop	bx
	 pop	ds
	 ret
hexput	 endp
_TEXT	ENDS
	END

⌨️ 快捷键说明

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