[comp.os.minix] NYUMINIX:KERNEL\KLIB88.ASM

jai@lab.ultra.nyu.edu (Benchiao Jai) (02/24/91)

; This file contains a number of assembly code utility routines needed by the
; kernel.  They are:
;
;   phys_copy:	copies data from anywhere to anywhere in memory
;   cp_mess:	copies messages from source to destination
;   lock:	disable interrupts
;   restore:	restore interrupts (enable/disabled) as they were before lock()
;   build_sig:	build 4 word structure pushed onto stack for signals
;   csv:	procedure prolog to save the registers
;   cret:	procedure epilog to restore the registers
;   get_chrome: returns 0 if display is monochrome, 1 if it is color
;   get_ega:	returns 1 if display is EGA, 0 otherwise
;   vid_copy:	copy data to video ram (on color display during retrace only)
;   scr_up:	scroll screen a line up (in software, by copying)
;   scr_down:	scroll screen a line down (in software, by copying)
;   get_byte:	reads a byte from a user program and returns it as value
;   put_byte:	reads a byte from a user program and returns it as value
;   wait_retrace: waits for retrace interval, and returns int disabled
;   ack_char:	acknowledge character from keyboard
;   port_out:	output byte to port
;   port_in:	input byte from port
;   em_xfer:	expanded memory transfer

; The following procedures are defined in this file and called from outside it.
public _phys_copy, _cp_mess, _lock, _restore
public _build_sig, csv, cret, _get_chrome, _vid_copy, _get_byte, _put_byte
public _scr_up, _scr_down
public _ack_char, _get_ega, _wait_retrace
public _port_out, _port_in, _em_xfer

public splimit

; The following external procedures are called in this file.
extrn _panic:near

; Variables and data structures
extrn _color:word, _ega:word, _blank_color:word, _cur_proc:word, _proc_ptr:word
extrn _vid_mask:word, _vid_port:word

DGROUP	GROUP	_TEXT, _DATA

;*===========================================================================*
;*				phys_copy				     *
;*===========================================================================*
; This routine copies a block of physical memory.  It is called by:
;    phys_copy( (long) source, (long) destination, (long) bytecount)
_TEXT	segment byte	public	'CODE'
	assume	cs:_TEXT, ds:DGROUP
_phys_copy:
	pushf
	cld
	push bp
	push ax
	push bx
	push cx
	push dx
	push si
	push di
	push ds
	push es
	mov bp,sp

  L0:	mov ax,28[bp]		; ax = high-order word of 32-bit destination
	mov di,26[bp]		; di = low-order word of 32-bit destination
	mov cx, 4		; start extracting click number from dest
  L1:	rcr ax, 1		; click number is destination address / 16
	rcr di, 1		; it is used in segment register for copy
	loop L1 		; 4 bits of high-order word are used
	mov es,di		; es = destination click

	mov ax,24[bp]		; ax = high-order word of 32-bit source
	mov si,22[bp]		; si = low-order word of 32-bit source
	mov cx, 4		; start extracting click number from source
  L2:	rcr ax, 1		; click number is source address / 16
	rcr si, 1		; it is used in segment register for copy
	loop L2 		; 4 bits of high-order word are used
	mov ds,si		; ds = source click

	mov di,26[bp]		; di = low-order word of dest address
	and di,   000Fh 	; di = offset from paragraph # in es
	mov si,22[bp]		; si = low-order word of source address
	and si,   000Fh 	; si = offset from paragraph # in ds

	mov dx,32[bp]		; dx = high-order word of byte count
	mov cx,30[bp]		; cx = low-order word of byte count

	test cx,   8000h	; if bytes >= 32768, only do 32768
	jnz L3			; per iteration
	test dx,  0FFFFh	; check high-order 17 bits to see if bytes
	jnz L3			; if bytes >= 32768 then go to L3
	jmp short L4		; if bytes < 32768 then go to L4
  L3:	mov cx,   8000h 	; 0x8000 is unsigned 32768
  L4:	mov ax,cx		; save actual count used in ax; needed later

	test cx,   0001h	; should we copy a byte or a word at a time?
	jz L5			; jump if even
	rep movsb		; copy 1 byte at a time
	jmp short L6		; check for more bytes

  L5:	shr cx, 1		; word copy
	rep movsw		; copy 1 word at a time

  L6:	mov dx,32[bp]		; decr count, incr src & dst, iterate if needed
	mov cx,30[bp]		; dx .. cx is 32-bit byte count
	xor bx,bx		; bx .. ax is 32-bit actual count used
	sub cx,ax		; compute bytes - actual count
	sbb dx,bx		; dx .. cx is # bytes not yet processed
	or cx,cx		; see if it is 0
	jnz L7			; if more bytes then go to L7
	or dx,dx		; keep testing
	jnz L7			; if loop done, fall through

	pop es
	pop ds
	pop di
	pop si
	pop dx
	pop cx
	pop bx
	pop ax
	pop bp
	popf
	ret

L7:	mov 32[bp],dx		; store decremented byte count back in mem
	mov 30[bp],cx		; as a long
	add 26[bp],ax		; increment destination
	adc 28[bp],bx		; carry from low-order word
	add 22[bp],ax		; increment source
	adc 24[bp],bx		; carry from low-order word
	jmp L0			; start next iteration


;*===========================================================================*
;*				cp_mess 				     *
;*===========================================================================*
; This routine is makes a fast copy of a message from anywhere in the address
; space to anywhere else.  It also copies the source address provided as a
; parameter to the call into the first word of the destination message.
; It is called by:
;    cp_mess(src, src_clicks, src_offset, dst_clicks, dst_offset)
; where all 5 parameters are shorts (16-bits).
;
; Note that the message size, 'Msize' is in WORDS (not bytes) and must be set
; correctly.  Changing the definition of message the type file and not changing
; it here will lead to total disaster.
;
; This routine only preserves the registers the 'C' compiler
; expects to be preserved (es, ds, si, di, sp, bp).

Msize = 12			; size of a message in 16-bit words
_cp_mess:
	push es
	push ds
	mov bx,sp
	pushf
	cli
	push si
	push di
	mov di,14[bx]		; di = offset of destination buffer
	les si,10[bx]		; use 32 bit load(ds is our base)
				; si = offset of source message
				; es = clicks of destination
	lds ax,6[bx]		; use 32 bit load ....
				; ax = process number of sender
				; ds = clicks of source message
	mov es:[di],ax		; copy sender's process number to dest message
	add si, 2		; don't copy first word
	add di, 2		; don't copy first word
	mov cx, Msize-1 	; remember, first word doesn't count
	cld			; clear direction flag
	rep movsw		; iterate cx times to copy 11 words
	pop di
	pop si
	popf
	pop ds
	pop es
	ret


;*===========================================================================*
;*				lock					     *
;*===========================================================================*
; Disable CPU interrupts.  Return old psw as function value.
_lock:
	pushf
	cli
	pop ax
	ret


;*===========================================================================*
;*				restore 				     *
;*===========================================================================*
; restore enable/disable bit to the value it had before last lock.
_restore:
	push bp
	mov bp,sp
	push 4[bp]
	popf
	pop bp
	ret


;*===========================================================================*
;*				build_sig				     *
;*===========================================================================*
;* Build a structure that is pushed onto the stack for signals.  It contains
;* pc, psw, etc., and is machine dependent. The format is the same as generated
;* by hardware interrupts, except that after the "interrupt", the signal number
;* is also pushed.  The signal processing routine within the user space first
;* pops the signal number, to see which function to call.  Then it calls the
;* function.  Finally, when the function returns to the low-level signal
;* handling routine, control is passed back to where it was prior to the signal
;* by executing a return-from-interrupt instruction, hence the need for using
;* the hardware generated interrupt format on the stack.  The call is:
;*     build_sig(sig_stuff, rp, sig)

; Offsets within proc table
PC    = 24
csreg = 18
PSW   = 28

_build_sig:
	push bp
	mov bp,sp
	push bx
	push si
	mov bx,4[bp]		; bx points to sig_stuff
	mov si,6[bp]		; si points to proc table entry
	mov ax,8[bp]		; ax = signal number
	mov [bx],ax		; put signal number in sig_stuff
	mov ax,PC[si]		; ax = signalled process' PC
	mov 2[bx],ax		; put pc in sig_stuff
	mov ax,csreg[si]	; ax = signalled process' cs
	mov 4[bx],ax		; put cs in sig_stuff
	mov ax,PSW[si]		; ax = signalled process' PSW
	mov 6[bx],ax		; put psw in sig_stuff
	pop si
	pop bx
	pop bp
	ret


;*===========================================================================*
;*				csv & cret				     *
;*===========================================================================*
; This version of csv replaces the standard one.  It checks for stack overflow
; within the kernel in a simpler way than is usually done. cret is standard.
csv:
	pop bx			; bx = return address
	push bp 		; stack old frame pointer
	mov bp,sp		; set new frame pointer to sp
	push di 		; save di
	push si 		; save si
	sub sp,ax		; ax = # bytes of local variables
	cmp sp,splimit		; has kernel stack grown too large
	jbe csv1		; if sp is too low, panic
	jmp  bx 		; normal return: copy bx to program counter

csv1:
	mov splimit, 0		; prevent call to panic from aborting in csv
	mov bx,_proc_ptr	; update rp->p_splimit
	mov word ptr 50[bx], 0	; rp->sp_limit = 0
	push _cur_proc		; task number
	mov ax,offset DGROUP:stkoverrun ; stack overran the kernel stack area
	push ax 		; push first parameter
	call _panic		; call is: panic(stkoverrun, cur_proc)
	jmp csv1		; this should not be necessary

cret:
	lea	sp, -4[bp]	; set sp to point to saved si
	pop	si
	pop	di
	pop	bp
	ret

;*===========================================================================*
;*				get_chrome				     *
;*===========================================================================*
; This routine calls the BIOS to find out if the display is monochrome or
; color.  The drivers are different, as are the video ram addresses, so we
; need to know.
_get_chrome:
	int 11h 		; call the BIOS to get equipment type
	and al,30h		; isolate color/mono field
	cmp al,30h		; 0x30 is monochrome
	je getchr1		; if monochrome then go to getchr1
	mov ax,1		; color = 1
	ret
getchr1: xor ax,ax		; mono = 0
	ret

;*===========================================================================*
;*				get_ega 				     *
;*===========================================================================*
; This routine calls the BIOS to find out if the display is ega.  This
; is needed because scrolling is different.
_get_ega:
	mov bl,10h
	mov ah,12h
	int 10h 		; call the BIOS to get equipment type
	cmp bl,10h		; if reg is unchanged, it failed
	je notega
	mov ax,1		; color = 1
	ret			; color return
notega: xor ax,ax		; mono = 0
	ret

;*===========================================================================*
;*				vid_copy				     *
;*===========================================================================*
; This routine takes a string of (character, attribute) pairs and writes them
; onto the screen.  For a color display, the writing only takes places during
; the vertical retrace interval, to avoid displaying garbage on the screen.
; The call is:
;     vid_copy(buffer, videobase, offset, words)
; where
;     'buffer'    is a pointer to the (character, attribute) pairs
;     'videobase' is 0xB800 for color and 0xB000 for monochrome displays
;     'offset'    tells where within video ram to copy the data
;     'words'     tells how many words to copy
; if buffer is zero, the fill char (blank_color) is used

_vid_copy:
	push bp
	mov bp,sp
	push si
	push di
	push bx
	push cx
	push dx
	push es
vid0:	mov si,4[bp]		; si = pointer to data to be copied
	mov di,8[bp]		; di = offset within video ram
	and di,_vid_mask	; only 4K or 16K counts
	mov cx,10[bp]		; cx = word count for copy loop
	mov dx,3DAh		; prepare to see if color display is retracing
	mov bx,di		; see if copy will run off end of video ram
	add bx,cx		; compute where copy ends
	add bx,cx		; bx = last character copied + 1
	sub bx,_vid_mask	; bx = # characters beyond end of video ram
	sub bx, 1		; note: dec bx doesn't set flags properly
	jle vid1		; jump if no overrun
	sar bx, 1		; bx = # words that don't fit in video ram
	sub cx,bx		; reduce count by overrun
	mov tmp,cx		; save actual count used for later
vid1:	test _color,1		; skip vertical retrace test if display is mono
	jz vid4 		; if monochrome then go to vid.2
	test _ega,1		; if ega also don't need to wait
	jnz vid4
vid3:	in al,dx		; 0x3DA is set during retrace.	First wait
	test al,1000b		; until it is off (no retrace), then wait
	jz vid3 		; until it comes on (start of retrace)
vid4:	pushf
	cld
	mov es,6[bp]		; load es now: int routines may ruin it
	cmp si,0		; si = 0 means blank the screen
	je vid7
	rep movsw
vid5:	popf
	cmp bx,0		; if bx < 0, then no overrun and we are done
	jle vid6
	mov 10[bp],bx		; set up residual count
	mov word ptr 8[bp],0	; start copying at base of video ram
	cmp word ptr 4[bp],0	; NIL_PTR means store blanks
	je vid0
	mov si,tmp		; si = count of words copied
	add si,si		; si = count of bytes copied
	add 4[bp],si		; increment buffer pointer
	jmp vid0
vid6:	pop es
	pop dx
	pop cx
	pop bx
	pop di
	pop si
	pop bp
	ret
vid7:	mov ax,_blank_color	; ax = blanking character
	rep stosw
	jmp vid5

;*===========================================================================*
;*			      wait_retrace				     *
;*===========================================================================*
; Wait until we're in the retrace interval.  Return locked (ints off).
; But enable them during the wait.

_wait_retrace: push dx
	pushf
	mov dx,_vid_port
	or dx,000Ah
wtre3:	sti
	nop
	nop
	cli
	in al,dx		; 0x3DA bit 3 is set during retrace.
	test al,1000b		; Wait until it is on.
	jz wtre3
	pop ax
	pop dx
	ret

_scr_up:
	push bp
	mov bp,sp
	push si
	push di
	push cx
	push es
	push ds
	mov si,6[bp]
	mov di,8[bp]
	mov cx,10[bp]
	pushf
	cld
	mov ax,4[bp]
	mov es,ax
	mov ds,ax
	rep movsw
	popf
	pop ds
	pop es
	pop cx
	pop di
	pop si
	pop bp
	ret

_scr_down:
	push bp
	mov bp,sp
	push si
	push di
	push cx
	push es
	push ds
	mov si,6[bp]
	mov di,8[bp]
	mov cx,10[bp]
	pushf
	mov ax,4[bp]
	mov es,ax
	mov ds,ax
	std
	rep movsw
	popf
	pop ds
	pop es
	pop cx
	pop di
	pop si
	pop bp
	ret

_get_byte:
	push bp
	mov bp,sp
	push es
	mov es,4[bp]
	mov bx,6[bp]
	mov al,es:[bx]
	xor ah,ah
	pop es
	pop bp
	ret

_put_byte:
	push bp
	mov bp,sp
	push es
	mov es,4[bp]
	mov bx,6[bp]
	mov ax,8[bp]
	mov es:[bx],al
	pop es
	pop bp
	ret

;*===========================================================================
;*				ack_char
;*===========================================================================
; Acknowledge character from keyboard for PS/2

_ack_char:
	push dx
	mov dx,69h
	in al,dx
	xor ax,10h
	out dx,al
	xor ax,10h
	out dx,al
	mov dx,66h
	mov ah,10h
	in al,dx
	not ah
	and al,ah
	out dx,al
	jmp frw1
frw1:	not ah
	or al,ah
	out dx,al
	jmp frw2
frw2:	not ah
	and al,ah
	out dx,al
	pop dx
	ret

_port_out:
	push bx
	mov bx,sp
	push ax
	push dx
	mov dx,4[bx]
	mov ax,6[bx]
	out dx,al
	pop dx
	pop ax
	pop bx
	ret

_port_in:
	push bx
	mov bx,sp
	push ax
	push dx
	mov dx,4[bx]
	in al,dx
	xor ah,ah
	mov bx,6[bx]
	mov [bx],ax
	pop dx
	pop ax
	pop bx
	ret

;===========================================================================
;				em_xfer
;===========================================================================
;
;  This particular BIOS routine runs with interrupts off since the 80286
;  must be placed in protected mode to access the memory above 1 Mbyte.
;  So there should be no problems using the BIOS call.
;
gdt:				; Begin global descriptor table
					; Dummy descriptor
	dw    0 	; segment length (limit)
	dw    0 	; bits 15-0 of physical address
	db    0 	; bits 23-16 of physical address
	db    0 	; access rights byte
	dw    0 	; reserved
					; descriptor for GDT itself
	dw    0 	; segment length (limit)
	dw    0 	; bits 15-0 of physical address
	db    0 	; bits 23-16 of physical address
	db    0 	; access rights byte
	dw    0 	; reserved
src:					; source descriptor
srcsz	dw    0 	; segment length (limit)
srcl	dw    0 	; bits 15-0 of physical address
srch	db    0 	; bits 23-16 of physical address
	db    93h	; access rights byte
	dw    0 	; reserved
tgt:					; target descriptor
tgtsz	dw    0 	; segment length (limit)
tgtl	dw    0 	; bits 15-0 of physical address
tgth	db    0 	; bits 23-16 of physical address
	db    93h	; access rights byte
	dw    0 	; reserved
					; BIOS CS descriptor
	dw    0 	; segment length (limit)
	dw    0 	; bits 15-0 of physical address
	db    0 	; bits 23-16 of physical address
	db    0 	; access rights byte
	dw    0 	; reserved
					; stack segment descriptor
	dw    0 	; segment length (limit)
	dw    0 	; bits 15-0 of physical address
	db    0 	; bits 23-16 of physical address
	db    0 	; access rights byte
	dw    0 	; reserved

;
;
;  Execute a transfer between user memory and extended memory.
;
;  status = em_xfer(source, dest, count);
;
;    Where:
;	status => return code (0 => OK)
;	source => Physical source address (32-bit)
;	dest   => Physical destination address (32-bit)
;	count  => Number of words to transfer
;
;
;
_em_xfer:

	push	bp		; Save registers
	mov	bp,sp
	push	si
	push	es
	push	cx
;
;  Pick up source and destination addresses and update descriptor tables
;
	mov ax,4[bp]
	mov cs:srcl,ax
	mov ax,6[bp]
	mov cs:srch,al
	mov ax,8[bp]
	mov cs:tgtl,ax
	mov ax,10[bp]
	mov cs:tgth,al
;
;  Update descriptor table segment limits
;
	mov cx,12[bp]
	mov ax,cx
	add ax,ax
	mov cs:tgtsz,ax
	mov cs:srcsz,ax
;
;  Now do actual DOS call
;
	push cs
	pop es
	mov si,offset gdt
	mov ah,87h
	pushf
	int 15h 		; Do a far call to BIOS routine
;
;  All done, return to caller.
;

	pop	cx		; restore registers
	pop	es
	pop	si
	mov	sp,bp
	pop	bp
	ret

; Some library routines use exit, so this label is needed.
; Actual calls to exit cannot occur in the kernel.
public _exit
_exit:	sti
	jmp _exit
_TEXT	ends

_DATA	segment word	public	'DATA'
splimit    dw 0 ; stack limit for current task (kernel only)
tmp	   dw 0
stkoverrun db "Kernel stack overrun, task = ",0
_DATA	ends
	end