[comp.os.minix] Improved hard disk drivers

ast@cs.vu.nl (Andy Tanenbaum) (07/29/87)

This message contains the V1.2 xt_wini.c, at_wini.c, klib88.s and a program
dtest.c (see below) as a shar file (UNIX style).  The XT driver is more robust 
than the old one, and the AT driver is much faster than it was.

I believe that xt_wini.c should work with both standard IBM PC (Xebec) and
Western Digital Controllers.  It contains the Gary Oliver/Harry McGavran/
Mike Mitchell patches.  I would greatly appreciate a lot of people giving it
a test and then reporting back to me:
   1. Which CPU you tested it on (brand, model, clock rate)
   2. Which disk controller you tested it on (if you know)
   3. How you tested it, and how thoroughly

The program dtest.c can be used to test disks.  Compile it and then type:
   a.out /dev/hd0 n     (for some numeric value of n)
The second argument is an offset.  The test program reads and writes 25
blocks starting at that offset.  You can also use 0, but if something
should go wrong, its better not to wipe out the super block and the inodes.
If all goes well, this program will run until you hit del and should not
change any information on your disk.  It prints its results periodically.

You need to install the new klib88.s, which should also work on the Intel
386 CPU now, although I have not tested it.  If anyone has
a 386 (Compaq or other), I would be very interested in finding out if using
these drivers, the floppy driver I posted last week, and klib88.s MINIX works
on the 386.

Please reply by e-mail and I will summarize to the net later.

Thanks.

Andy Tanenbaum (ast@cs.vu.nl)
: This is a shar archive.  Extract with sh, not csh.
: This archive ends with exit, so do not worry about trailing junk.
: --------------------------- cut here --------------------------
PATH=/bin:/usr/bin
echo Extracting \k\l\i\b\8\8\.\s
sed 's/^X//' > \k\l\i\b\8\8\.\s << '+ END-OF-FILE '\k\l\i\b\8\8\.\s
X| This file contains a number of assembly code utility routines needed by the
X| kernel.  They are:
X|
X|   phys_copy:	copies data from anywhere to anywhere in memory
X|   cp_mess:	copies messages from source to destination
X|   port_out:	outputs data on an I/O port
X|   port_in:	inputs data from an I/O port
X|   lock:	disable interrupts
X|   unlock:	enable interrupts
X|   restore:	restore interrupts (enable/disabled) as they were before lock()
X|   build_sig:	build 4 word structure pushed onto stack for signals
X|   csv:	procedure prolog to save the registers
X|   cret:	procedure epilog to restore the registers
X|   get_chrome:	returns 0 is display is monochrome, 1 if it is color
X|   vid_copy:	copy data to video ram (on color display during retrace only)
X|   get_byte:	reads a byte from a user program and returns it as value
X|   reboot:	reboot for CTRL-ALT-DEL
X|   wreboot:	wait for character then reboot 
X|   dma_read:	transfer data between HD controller and memory
X|   dma_write:	transfer data between memory and HD controller
X
X| The following procedures are defined in this file and called from outside it.
X.globl _phys_copy, _cp_mess, _port_out, _port_in, _lock, _unlock, _restore
X.globl _build_sig, csv, cret, _get_chrome, _vid_copy, _get_byte, _reboot
X.globl _wreboot, _dma_read, _dma_write
X
X| The following external procedure is called in this file.
X.globl _panic
X
X| Variables and data structures
X.globl _color, _cur_proc, _proc_ptr, splimit, _vec_table, _vid_mask
X
X
X|*===========================================================================*
X|*				phys_copy				     *
X|*===========================================================================*
X| This routine copies a block of physical memory.  It is called by:
X|    phys_copy( (long) source, (long) destination, (long) bytecount)
X
X_phys_copy:
X	pushf			| save flags
X	cli			| disable interrupts
X	push bp			| save the registers
X	push ax			| save ax
X	push bx			| save bx
X	push cx			| save cx
X	push dx			| save dx
X	push si			| save si
X	push di			| save di
X	push ds			| save ds
X	push es			| save es
X	mov bp,sp		| set bp to point to saved es
X
X  L0:	mov ax,28(bp)		| ax = high-order word of 32-bit destination
X	mov di,26(bp)		| di = low-order word of 32-bit destination
X	mov cx,*4		| start extracting click number from dest
X  L1:	rcr ax,*1		| click number is destination address / 16
X	rcr di,*1		| it is used in segment register for copy
X	loop L1			| 4 bits of high-order word are used
X	mov es,di		| es = destination click
X
X	mov ax,24(bp)		| ax = high-order word of 32-bit source
X	mov si,22(bp)		| si = low-order word of 32-bit source
X	mov cx,*4		| start extracting click number from source
X  L2:	rcr ax,*1		| click number is source address / 16
X	rcr si,*1		| it is used in segment register for copy
X	loop L2			| 4 bits of high-order word are used
X	mov ds,si		| ds = source click
X
X	mov di,26(bp)		| di = low-order word of dest address
X	and di,*0x000F		| di = offset from paragraph # in es
X	mov si,22(bp)		| si = low-order word of source address
X	and si,*0x000F		| si = offset from paragraph # in ds
X
X	mov dx,32(bp)		| dx = high-order word of byte count
X	mov cx,30(bp)		| cx = low-order word of byte count
X
X	test cx,#0x8000		| if bytes >= 32768, only do 32768 
X	jnz L3			| per iteration
X	test dx,#0xFFFF		| check high-order 17 bits to see if bytes
X	jnz L3			| if bytes >= 32768 then go to L3
X	jmp L4			| if bytes < 32768 then go to L4
X  L3:	mov cx,#0x8000		| 0x8000 is unsigned 32768
X  L4:	mov ax,cx		| save actual count used in ax; needed later
X
X	test cx,*0x0001		| should we copy a byte or a word at a time?
X	jz L5			| jump if even
X	rep			| copy 1 byte at a time
X	movb			| byte copy
X	jmp L6			| check for more bytes
X
X  L5:	shr cx,*1		| word copy
X	rep			| copy 1 word at a time
X	movw			| word copy
X
X  L6:	mov dx,32(bp)		| decr count, incr src & dst, iterate if needed
X	mov cx,30(bp)		| dx || cx is 32-bit byte count
X	xor bx,bx		| bx || ax is 32-bit actual count used
X	sub cx,ax		| compute bytes - actual count
X	sbb dx,bx		| dx || cx is # bytes not yet processed
X	or cx,cx		| see if it is 0
X	jnz L7			| if more bytes then go to L7
X	or dx,dx		| keep testing
X	jnz L7			| if loop done, fall through
X
X	pop es			| restore all the saved registers
X	pop ds			| restore ds
X	pop di			| restore di
X	pop si			| restore si
X	pop dx			| restore dx
X	pop cx			| restore cx
X	pop bx			| restore bx
X	pop ax			| restore ax
X	pop bp			| restore bp
X	popf			| restore flags
X	ret			| return to caller
X
XL7:	mov 32(bp),dx		| store decremented byte count back in mem
X	mov 30(bp),cx		| as a long
X	add 26(bp),ax		| increment destination
X	adc 28(bp),bx		| carry from low-order word
X	add 22(bp),ax		| increment source
X	adc 24(bp),bx		| carry from low-order word
X	jmp L0			| start next iteration
X
X
X|*===========================================================================*
X|*				cp_mess					     *
X|*===========================================================================*
X| This routine is makes a fast copy of a message from anywhere in the address
X| space to anywhere else.  It also copies the source address provided as a
X| parameter to the call into the first word of the destination message.
X| It is called by:
X|    cp_mess(src, src_clicks, src_offset, dst_clicks, dst_offset)
X| where all 5 parameters are shorts (16-bits).
X|
X| Note that the message size, 'Msize' is in WORDS (not bytes) and must be set
X| correctly.  Changing the definition of message the type file and not changing
X| it here will lead to total disaster.
X| This routine destroys ax.  It preserves the other registers.
X
XMsize = 12			| size of a message in 16-bit words
X_cp_mess:
X	push bp			| save bp
X	push es			| save es
X	push ds			| save ds
X	mov bp,sp		| index off bp because machine can't use sp
X	pushf			| save flags
X	cli			| disable interrupts
X	push cx			| save cx
X	push si			| save si
X	push di			| save di
X
X	mov ax,8(bp)		| ax = process number of sender
X	mov di,16(bp)		| di = offset of destination buffer
X	mov es,14(bp)		| es = clicks of destination
X	mov si,12(bp)		| si = offset of source message
X	mov ds,10(bp)		| ds = clicks of source message
X	seg es			| segment override prefix
X  	mov (di),ax		| copy sender's process number to dest message
X	add si,*2		| don't copy first word
X	add di,*2		| don't copy first word
X	mov cx,*Msize-1		| remember, first word doesn't count
X	rep			| iterate cx times to copy 11 words
X	movw			| copy the message
X
X	pop di			| restore di
X	pop si			| restore si
X	pop cx			| restore cs
X	popf			| restore flags
X	pop ds			| restore ds
X	pop es			| restore es
X	pop bp			| restore bp
X	ret			| that's all folks!
X
X
X|*===========================================================================*
X|*				port_out				     *
X|*===========================================================================*
X| port_out(port, value) writes 'value' on the I/O port 'port'.
X
X_port_out:
X	push bx			| save bx
X	mov bx,sp		| index off bx
X	push ax			| save ax
X	push dx			| save dx
X	mov dx,4(bx)		| dx = port
X	mov ax,6(bx)		| ax = value
X	out			| output 1 byte
X	pop dx			| restore dx
X	pop ax			| restore ax
X	pop bx			| restore bx
X	ret			| return to caller
X
X
X|*===========================================================================*
X|*				port_in					     *
X|*===========================================================================*
X| port_in(port, &value) reads from port 'port' and puts the result in 'value'.
X_port_in:
X	push bx			| save bx
X	mov bx,sp		| index off bx
X	push ax			| save ax
X	push dx			| save dx
X	mov dx,4(bx)		| dx = port
X	in			| input 1 byte
X	xorb ah,ah		| clear ah
X	mov bx,6(bx)		| fetch address where byte is to go
X	mov (bx),ax		| return byte to caller in param
X	pop dx			| restore dx
X	pop ax			| restore ax
X	pop bx			| restore bx
X	ret			| return to caller
X
X
X|*===========================================================================*
X|*				lock					     *
X|*===========================================================================*
X| Disable CPU interrupts.
X_lock:  
X	pushf			| save flags on stack
X	cli			| disable interrupts
X	pop lockvar		| save flags for possible restoration later
X	ret			| return to caller
X
X
X|*===========================================================================*
X|*				unlock					     *
X|*===========================================================================*
X| Enable CPU interrupts.
X_unlock:
X	sti			| enable interrupts
X	ret			| return to caller
X
X
X|*===========================================================================*
X|*				restore					     *
X|*===========================================================================*
X| Restore enable/disable bit to the value it had before last lock.
X_restore:
X	push lockvar		| push flags as they were before previous lock
X	popf			| restore flags
X	ret			| return to caller
X
X
X|*===========================================================================*
X|*				build_sig				     *
X|*===========================================================================*
X|* Build a structure that is pushed onto the stack for signals.  It contains
X|* pc, psw, etc., and is machine dependent. The format is the same as generated
X|* by hardware interrupts, except that after the "interrupt", the signal number
X|* is also pushed.  The signal processing routine within the user space first
X|* pops the signal number, to see which function to call.  Then it calls the
X|* function.  Finally, when the function returns to the low-level signal
X|* handling routine, control is passed back to where it was prior to the signal
X|* by executing a return-from-interrupt instruction, hence the need for using
X|* the hardware generated interrupt format on the stack.  The call is:
X|*     build_sig(sig_stuff, rp, sig)
X
X| Offsets within proc table
XPC    = 24
Xcsreg = 18
XPSW   = 28
X
X_build_sig:
X	push bp			| save bp
X	mov bp,sp		| set bp to sp for accessing params
X	push bx			| save bx
X	push si			| save si
X	mov bx,4(bp)		| bx points to sig_stuff
X	mov si,6(bp)		| si points to proc table entry
X	mov ax,8(bp)		| ax = signal number
X	mov (bx),ax		| put signal number in sig_stuff
X	mov ax,PC(si)		| ax = signalled process' PC
X	mov 2(bx),ax		| put pc in sig_stuff
X	mov ax,csreg(si)	| ax = signalled process' cs
X	mov 4(bx),ax		| put cs in sig_stuff
X	mov ax,PSW(si)		| ax = signalled process' PSW
X	mov 6(bx),ax		| put psw in sig_stuff
X	pop si			| restore si
X	pop bx			| restore bx
X	pop bp			| restore bp
X	ret			| return to caller
X
X
X|*===========================================================================*
X|*				csv & cret				     *
X|*===========================================================================*
X| This version of csv replaces the standard one.  It checks for stack overflow
X| within the kernel in a simpler way than is usually done. cret is standard.
Xcsv:
X	pop bx			| bx = return address
X	push bp			| stack old frame pointer
X	mov bp,sp		| set new frame pointer to sp
X	push di			| save di
X	push si			| save si
X	sub sp,ax		| ax = # bytes of local variables
X	cmp sp,splimit		| has kernel stack grown too large
X	jbe csv.1		| if sp is too low, panic
X	jmp (bx)		| normal return: copy bx to program counter
X
Xcsv.1:
X	mov splimit,#0		| prevent call to panic from aborting in csv
X	mov bx,_proc_ptr	| update rp->p_splimit
X	mov 50(bx),#0		| rp->sp_limit = 0
X	push _cur_proc		| task number
X	mov ax,#stkoverrun	| stack overran the kernel stack area
X	push ax			| push first parameter
X	call _panic		| call is: panic(stkoverrun, cur_proc)
X	jmp csv.1		| this should not be necessary
X
X
Xcret:
X	lea	sp,*-4(bp)	| set sp to point to saved si
X	pop	si		| restore saved si
X	pop	di		| restore saved di
X	pop	bp		| restore bp
X	ret			| end of procedure
X
X|*===========================================================================*
X|*				get_chrome				     *
X|*===========================================================================*
X| This routine calls the BIOS to find out if the display is monochrome or 
X| color.  The drivers are different, as are the video ram addresses, so we
X| need to know.
X_get_chrome:
X	int 0x11		| call the BIOS to get equipment type
X	andb al,#0x30		| isolate color/mono field
X	cmpb al,*0x30		| 0x30 is monochrome
X	je getchr1		| if monochrome then go to getchr1
X	mov ax,#1		| color = 1
X	ret			| color return
Xgetchr1: xor ax,ax		| mono = 0
X	ret			| monochrome return
X
X|*===========================================================================*
X|*				dma_read				     *
X|*===========================================================================*
X_dma_read:
X	push	bp
X	mov	bp,sp
X	push	cx
X	push	dx
X	push	di
X	push	es
X	mov	cx,#256		| transfer 256 words
X	mov	dx,#0x1F0	| from/to port 1f0
X	cld
X	mov	es,4(bp)	| segment in es
X	mov	di,6(bp)	| offset in di
X	.byte	0xF3, 0x6D	| opcode for 'rep insw'
X	pop	es
X	pop	di
X	pop	dx
X	pop	dx
X	mov	sp,bp
X	pop	bp
X	ret
X
X|*===========================================================================*
X|*				dma_write				     *
X|*===========================================================================*
X_dma_write:
X	push	bp
X	mov	bp,sp
X	push	cx
X	push	dx
X	push	si
X	push	ds
X	mov	cx,#256		| transfer 256 words
X	mov	dx,#0x1F0	| from/to port 1f0
X	cld
X	mov	ds,4(bp)	| segment in ds
X	mov	si,6(bp)	| offset in si
X	.byte	0xF3, 0x6F	| opcode for 'rep outsw'
X	pop	ds
X	pop	si
X	pop	dx
X	pop	dx
X	mov	sp,bp
X	pop	bp
X	ret
X
X|*===========================================================================*
X|*				vid_copy				     *
X|*===========================================================================*
X| This routine takes a string of (character, attribute) pairs and writes them
X| onto the screen.  For a color display, the writing only takes places during
X| the vertical retrace interval, to avoid displaying garbage on the screen.
X| The call is:
X|     vid_copy(buffer, videobase, offset, words)
X| where
X|     'buffer'    is a pointer to the (character, attribute) pairs
X|     'videobase' is 0xB800 for color and 0xB000 for monochrome displays
X|     'offset'    tells where within video ram to copy the data
X|     'words'     tells how many words to copy
X| if buffer is zero, the fill char (BLANK) is used
X
XBLANK = 0x0700			| controls color of cursor on blank screen
X
X_vid_copy:
X	push bp			| we need bp to access the parameters
X	mov bp,sp		| set bp to sp for indexing
X	push si			| save the registers
X	push di			| save di
X	push bx			| save bx
X	push cx			| save cx
X	push dx			| save dx
X	push es			| save es
Xvid.0:	mov si,4(bp)		| si = pointer to data to be copied
X	mov di,8(bp)		| di = offset within video ram
X	and di,_vid_mask	| only 4K or 16K counts
X	mov cx,10(bp)		| cx = word count for copy loop
X	mov dx,#0x3DA		| prepare to see if color display is retracing
X
X	mov bx,di		| see if copy will run off end of video ram
X	add bx,cx		| compute where copy ends
X	add bx,cx		| bx = last character copied + 1
X	sub bx,_vid_mask	| bx = # characters beyond end of video ram
X	sub bx,#1		| note: dec bx doesn't set flags properly
X	jle vid.1		| jump if no overrun
X	sar bx,#1		| bx = # words that don't fit in video ram
X	sub cx,bx		| reduce count by overrun
X	mov tmp,cx		| save actual count used for later
X
Xvid.1:	test _color,*1		| skip vertical retrace test if display is mono
X	jz vid.4		| if monochrome then go to vid.2
X
X|vid.2:	in			| with a color display, you can only copy to
X|	test al,*010		| the video ram during vertical retrace, so
X|	jnz vid.2		| wait for start of retrace period.  Bit 3 of
Xvid.3:	in			| 0x3DA is set during retrace.  First wait
X	testb al,*010		| until it is off (no retrace), then wait
X	jz vid.3		| until it comes on (start of retrace)
X
Xvid.4:	pushf			| copying may now start; save flags
X	cli			| interrupts just get in the way: disable them
X	mov es,6(bp)		| load es now: int routines may ruin it
X
X	cmp si,#0		| si = 0 means blank the screen
X	je vid.7		| jump for blanking
X	lock			| this is a trick for the IBM PC simulator only
X	inc vidlock		| 'lock' indicates a video ram access
X	rep			| this is the copy loop
X	movw			| ditto
X
Xvid.5:	popf			| restore flags
X	cmp bx,#0		| if bx < 0, then no overrun and we are done
X	jle vid.6		| jump if everything fit
X	mov 10(bp),bx		| set up residual count
X	mov 8(bp),#0		| start copying at base of video ram
X	cmp 4(bp),#0		| NIL_PTR means store blanks
X	je vid.0		| go do it
X	mov si,tmp		| si = count of words copied
X	add si,si		| si = count of bytes copied
X	add 4(bp),si		| increment buffer pointer
X	jmp vid.0		| go copy some more
X
Xvid.6:	pop es			| restore registers
X	pop dx			| restore dx
X	pop cx			| restore cx
X	pop bx			| restore bx
X	pop di			| restore di
X	pop si			| restore si
X	pop bp			| restore bp
X	ret			| return to caller
X
Xvid.7:	mov ax,#BLANK		| ax = blanking character
X	rep			| copy loop
X	stow			| blank screen
X	jmp vid.5		| done
X
X|*===========================================================================*
X|*				get_byte				     *
X|*===========================================================================*
X| This routine is used to fetch a byte from anywhere in memory.
X| The call is:
X|     c = get_byte(seg, off)
X| where
X|     'seg' is the value to put in es
X|     'off' is the offset from the es value
X_get_byte:
X	push bp			| save bp
X	mov bp,sp		| we need to access parameters
X	push es			| save es
X	mov es,4(bp)		| load es with segment value
X	mov bx,6(bp)		| load bx with offset from segment
X	seg es			| go get the byte
X	movb al,(bx)		| al = byte
X	xorb ah,ah		| ax = byte
X	pop es			| restore es
X	pop bp			| restore bp
X	ret			| return to caller
X
X
X
X
X|*===========================================================================*
X|*				reboot & wreboot			     *
X|*===========================================================================*
X| This code reboots the PC
X
X_reboot:
X	cli			| disable interrupts
X	mov ax,#0x20		| re-enable interrupt controller
X	out 0x20
X	call resvec		| restore the vectors in low core
X	mov ax,#0x40
X	mov ds,ax
X	mov ax,#0x1234
X	mov 0x72,ax
X	mov ax,#0xFFFF
X	mov ds,ax
X	mov ax,3
X	push ax
X	mov ax,1
X	push ax
X	reti
X
X_wreboot:
X	cli			| disable interrupts
X	mov ax,#0x20		| re-enable interrupt controller
X	out 0x20
X	call resvec		| restore the vectors in low core
X	xor ax,ax		| wait for character before continuing
X	int 0x16		| get char
X	mov ax,#0x40
X	mov ds,ax
X	mov ax,#0x1234
X	mov 0x72,ax
X	mov ax,#0xFFFF
X	mov ds,ax
X	mov ax,3
X	push ax
X	mov ax,1
X	push ax
X	reti
X
X| Restore the interrupt vectors in low core.
Xresvec:	cld
X	mov cx,#2*71
X	mov si,#_vec_table
X	xor di,di
X	mov es,di
X	rep
X	movw
X	ret
X
X| Some library routines use exit, so this label is needed.
X| Actual calls to exit cannot occur in the kernel.
X.globl _exit
X_exit:	sti
X	jmp _exit
X
X.data
Xlockvar:	.word 0		| place to store flags for lock()/restore()
Xvidlock:	.word 0		| dummy variable for use with lock prefix
Xsplimit:	.word 0		| stack limit for current task (kernel only)
Xtmp:		.word 0		| count of bytes already copied
Xstkoverrun:	.asciz "Kernel stack overrun, task = "
X_vec_table:	.zerow 142	| storage for interrupt vectors
+ END-OF-FILE klib88.s
chmod 'u=rw,g=r,o=r' \k\l\i\b\8\8\.\s
set `sum \k\l\i\b\8\8\.\s`
sum=$1
case $sum in
11868)	:;;
*)	echo 'Bad sum in '\k\l\i\b\8\8\.\s >&2
esac
echo Extracting \a\t\_\w\i\n\i\.\c
sed 's/^X//' > \a\t\_\w\i\n\i\.\c << '+ END-OF-FILE '\a\t\_\w\i\n\i\.\c
X/* This file contains a driver for the IBM-AT winchester controller.
X * It was written by Adri Koppes.
X *
X * The driver supports two operations: read a block and
X * write a block.  It accepts two messages, one for reading and one for
X * writing, both using message format m2 and with the same parameters:
X *
X *    m_type      DEVICE    PROC_NR     COUNT    POSITION  ADRRESS
X * ----------------------------------------------------------------
X * |  DISK_READ | device  | proc nr |  bytes  |  offset | buf ptr |
X * |------------+---------+---------+---------+---------+---------|
X * | DISK_WRITE | device  | proc nr |  bytes  |  offset | buf ptr |
X * ----------------------------------------------------------------
X *
X * The file contains one entry point:
X *
X *   winchester_task:	main entry when system is brought up
X *
X */
X
X#include "../h/const.h"
X#include "../h/type.h"
X#include "../h/callnr.h"
X#include "../h/com.h"
X#include "../h/error.h"
X#include "const.h"
X#include "type.h"
X#include "proc.h"
X
X/* I/O Ports used by winchester disk controller. */
X
X#define WIN_REG1       0x1f0
X#define WIN_REG2       0x1f1
X#define WIN_REG3       0x1f2
X#define WIN_REG4       0x1f3
X#define WIN_REG5       0x1f4
X#define WIN_REG6       0x1f5
X#define WIN_REG7       0x1f6
X#define WIN_REG8       0x1f7
X#define WIN_REG9       0x3f6
X
X/* Winchester disk controller command bytes. */
X#define WIN_RECALIBRATE	0x10	/* command for the drive to recalibrate */
X#define WIN_READ        0x20	/* command for the drive to read */
X#define WIN_WRITE       0x30	/* command for the drive to write */
X#define WIN_SPECIFY     0x91	/* command for the controller to accept params */
X
X/* Parameters for the disk drive. */
X#define SECTOR_SIZE      512	/* physical sector size in bytes */
X
X/* Error codes */
X#define ERR		  -1	/* general error */
X
X/* Miscellaneous. */
X#define MAX_ERRORS         4	/* how often to try rd/wt before quitting */
X#define NR_DEVICES        10	/* maximum number of drives */
X#define MAX_WIN_RETRY  10000	/* max # times to try to output to WIN */
X#define PART_TABLE     0x1C6	/* IBM partition table starts here in sect 0 */
X#define DEV_PER_DRIVE      5	/* hd0 + hd1 + hd2 + hd3 + hd4 = 5 */
X
X/* Variables. */
XPRIVATE struct wini {		/* main drive struct, one entry per drive */
X  int wn_opcode;		/* DISK_READ or DISK_WRITE */
X  int wn_procnr;		/* which proc wanted this operation? */
X  int wn_drive;			/* drive number addressed */
X  int wn_cylinder;		/* cylinder number addressed */
X  int wn_sector;		/* sector addressed */
X  int wn_head;			/* head number addressed */
X  int wn_heads;			/* maximum number of heads */
X  int wn_maxsec;		/* maximum number of sectors per track */
X  int wn_ctlbyte;		/* control byte (steprate) */
X  int wn_precomp;		/* write precompensation cylinder / 4 */
X  long wn_low;			/* lowest cylinder of partition */
X  long wn_size;			/* size of partition in blocks */
X  int wn_count;			/* byte count */
X  vir_bytes wn_address;		/* user virtual address */
X} wini[NR_DEVICES];
X
XPRIVATE int w_need_reset = FALSE;	 /* set to 1 when controller must be reset */
XPRIVATE int nr_drives;		 /* Number of drives */
X
XPRIVATE message w_mess;		/* message buffer for in and out */
X
XPRIVATE int command[8];		/* Common command block */
X
XPRIVATE unsigned char buf[BLOCK_SIZE]; /* Buffer used by the startup routine */
X
X/*===========================================================================*
X *				winchester_task				     * 
X *===========================================================================*/
XPUBLIC winchester_task()
X{
X/* Main program of the winchester disk driver task. */
X
X  int r, caller, proc_nr;
X
X  /* First initialize the controller */
X  init_param();
X
X  /* Here is the main loop of the disk task.  It waits for a message, carries
X   * it out, and sends a reply.
X   */
X
X  while (TRUE) {
X	/* First wait for a request to read or write a disk block. */
X	receive(ANY, &w_mess);	/* get a request to do some work */
X	if (w_mess.m_source < 0) {
X		printf("winchester task got message from %d ", w_mess.m_source);
X		continue;
X	}
X	caller = w_mess.m_source;
X	proc_nr = w_mess.PROC_NR;
X
X	/* Now carry out the work. */
X	switch(w_mess.m_type) {
X	    case DISK_READ:
X	    case DISK_WRITE:	r = w_do_rdwt(&w_mess);	break;
X	    default:		r = EINVAL;		break;
X	}
X
X	/* Finally, prepare and send the reply message. */
X	w_mess.m_type = TASK_REPLY;	
X	w_mess.REP_PROC_NR = proc_nr;
X
X	w_mess.REP_STATUS = r;	/* # of bytes transferred or error code */
X	send(caller, &w_mess);	/* send reply to caller */
X  }
X}
X
X
X/*===========================================================================*
X *				w_do_rdwt					     * 
X *===========================================================================*/
XPRIVATE int w_do_rdwt(m_ptr)
Xmessage *m_ptr;			/* pointer to read or write w_message */
X{
X/* Carry out a read or write request from the disk. */
X  register struct wini *wn;
X  int r, device, errors = 0;
X  long sector;
X
X  /* Decode the w_message parameters. */
X  device = m_ptr->DEVICE;
X  if (device < 0 || device >= NR_DEVICES)
X	return(EIO);
X  if (m_ptr->COUNT != BLOCK_SIZE)
X	return(EINVAL);
X  wn = &wini[device];		/* 'wn' points to entry for this drive */
X  wn->wn_drive = device/DEV_PER_DRIVE;	/* save drive number */
X  if (wn->wn_drive >= nr_drives)
X	return(EIO);
X  wn->wn_opcode = m_ptr->m_type;	/* DISK_READ or DISK_WRITE */
X  if (m_ptr->POSITION % BLOCK_SIZE != 0)
X	return(EINVAL);
X  sector = m_ptr->POSITION/SECTOR_SIZE;
X  if ((sector+BLOCK_SIZE/SECTOR_SIZE) > wn->wn_size)
X	return(EOF);
X  sector += wn->wn_low;
X  wn->wn_cylinder = sector / (wn->wn_heads * wn->wn_maxsec);
X  wn->wn_sector =  (sector % wn->wn_maxsec) + 1;
X  wn->wn_head = (sector % (wn->wn_heads * wn->wn_maxsec) )/wn->wn_maxsec;
X  wn->wn_count = m_ptr->COUNT;
X  wn->wn_address = (vir_bytes) m_ptr->ADDRESS;
X  wn->wn_procnr = m_ptr->PROC_NR;
X
X  /* This loop allows a failed operation to be repeated. */
X  while (errors <= MAX_ERRORS) {
X	errors++;		/* increment count once per loop cycle */
X	if (errors > MAX_ERRORS)
X		return(EIO);
X
X	/* First check to see if a reset is needed. */
X	if (w_need_reset) w_reset();
X
X	/* Perform the transfer. */
X	r = w_transfer(wn);
X	if (r == OK) break;	/* if successful, exit loop */
X
X  }
X
X  return(r == OK ? BLOCK_SIZE : EIO);
X}
X
X/*===========================================================================*
X *				w_transfer				     * 
X *===========================================================================*/
XPRIVATE int w_transfer(wn)
Xregister struct wini *wn;	/* pointer to the drive struct */
X{
X  extern phys_bytes umap();
X  phys_bytes usr_buf = umap(proc_addr(wn->wn_procnr), D, wn->wn_address, BLOCK_SIZE);
X  register int i,j;
X  int r = 0;
X
X  /* The command is issued by outputing 7 bytes to the controller chip. */
X
X  if (usr_buf == (phys_bytes)0)
X	return(ERR);
X  command[0] = wn->wn_ctlbyte;
X  command[1] = wn->wn_precomp;
X  command[2] = BLOCK_SIZE/SECTOR_SIZE;
X  command[3] = wn->wn_sector;
X  command[4] = wn->wn_cylinder & 0xFF;
X  command[5] = ((wn->wn_cylinder & 0x0300) >> 8);
X  command[6] = (wn->wn_drive << 4) | wn->wn_head | 0xA0;
X  command[7] = (wn->wn_opcode == DISK_READ ? WIN_READ : WIN_WRITE);
X
X  if (com_out() != OK)
X	return(ERR);
X
X  /* Block, waiting for disk interrupt. */
X  if (wn->wn_opcode == DISK_READ) {
X	for (i=0; i<BLOCK_SIZE/SECTOR_SIZE; i++) {
X		receive(HARDWARE, &w_mess);
X		lock();
X		dma_read((unsigned)(usr_buf >> 4), (unsigned)(usr_buf & 0x0F));
X		unlock();
X		usr_buf += 0x200;
X		if (win_results() != OK) {
X			w_need_reset = TRUE;
X			return(ERR);
X		}
X	}
X	r = OK;
X  } else {
X	for (i=0; i<MAX_WIN_RETRY && (r&8) == 0; i++)
X		port_in(WIN_REG8, &r);
X	if ((r&8) == 0) {
X		w_need_reset = TRUE;
X		return(ERR);
X	}
X	for (i=0; i<BLOCK_SIZE/SECTOR_SIZE; i++) {
X		lock();
X		dma_write((unsigned)(usr_buf >> 4), (unsigned)(usr_buf & 0x0F));
X		unlock();
X		usr_buf += 0x200;
X		receive(HARDWARE, &w_mess);
X		if (win_results() != OK) {
X			w_need_reset = TRUE;
X			return(ERR);
X		}
X	}
X	r = OK;
X  }
X
X  if (r == ERR)
X	w_need_reset = TRUE;
X  return(r);
X}
X
X/*===========================================================================*
X *				w_reset					     * 
X *===========================================================================*/
XPRIVATE w_reset()
X{
X/* Issue a reset to the controller.  This is done after any catastrophe,
X * like the controller refusing to respond.
X */
X
X  int i, r;
X
X  /* Strobe reset bit low. */
X  lock();
X  port_out(WIN_REG9, 4);
X  for (i = 0; i < 10; i++)
X	 ;
X  port_out(WIN_REG9, wini[0].wn_ctlbyte & 0x0F);
X  unlock();
X  for (i = 0; i < MAX_WIN_RETRY && drive_busy(); i++)
X	;
X  if (drive_busy()) {
X	printf("Winchester wouldn't reset, drive busy\n");
X	return(ERR);
X  }
X  port_in(WIN_REG2, &r);
X  if (r != 1) {
X	printf("Winchester wouldn't reset, drive error\n");
X	return(ERR);
X  }
X
X  /* Reset succeeded.  Tell WIN drive parameters. */
X
X  w_need_reset = FALSE;
X  return(win_init());
X}
X
X/*===========================================================================*
X *				win_init				     * 
X *===========================================================================*/
XPRIVATE win_init()
X{
X/* Routine to initialize the drive parameters after boot or reset */
X
X  register int i;
X
X  command[0] = wini[0].wn_ctlbyte;
X  command[1] = wini[0].wn_precomp;
X  command[2] = wini[0].wn_maxsec;
X  command[4] = 0;
X  command[6] = (wini[0].wn_heads - 1) | 0xA0;
X  command[7] = WIN_SPECIFY;		/* Specify some parameters */
X
X  if (com_out() != OK)	/* Output command block */
X	return(ERR);
X
X  receive(HARDWARE, &w_mess);
X  if (win_results() != OK) {	/* See if controller accepted parameters */
X	w_need_reset = TRUE;
X	return(ERR);
X  }
X
X  if (nr_drives > 1) {
X	command[0] = wini[5].wn_ctlbyte;
X	command[1] = wini[5].wn_precomp;
X	command[2] = wini[5].wn_maxsec;
X	command[4] = 0;
X	command[6] = (wini[5].wn_heads - 1) | 0xB0;
X	command[7] = WIN_SPECIFY;		/* Specify some parameters */
X
X	if (com_out() != OK)			/* Output command block */
X		return(ERR);
X	receive(HARDWARE, &w_mess);
X	if (win_results() != OK) {  /* See if controller accepted parameters */
X		w_need_reset = TRUE;
X		return(ERR);
X	}
X  }
X  for (i=0; i<nr_drives; i++) {
X	command[0] = wini[i*5].wn_ctlbyte;
X	command[6] = i << 4 | 0xA0;
X	command[7] = WIN_RECALIBRATE;
X	if (com_out() != OK)
X		return(ERR);
X	receive(HARDWARE, &w_mess);
X	if (win_results() != OK) {
X		w_need_reset = TRUE;
X		return(ERR);
X	}
X  }
X  return(OK);
X}
X
X/*============================================================================*
X *				win_results				      *
X *============================================================================*/
XPRIVATE win_results()
X{
X/* Routine to check if controller has done the operation succesfully */
X  int r;
X
X  port_in(WIN_REG8, &r);
X  if ((r&0x80) != 0)
X	return(OK);
X  if ((r&0x40) == 0 || (r&0x20) != 0 || (r&0x10) == 0 || (r&1) != 0) {
X	if ((r&01) != 0)
X		port_in(WIN_REG2, &r);
X	return(ERR);
X  }
X  return(OK);
X}
X
X/*============================================================================*
X *				drive_busy				      *
X *============================================================================*/
XPRIVATE drive_busy()
X{
X/* Wait until the controller is ready to receive a command or send status */
X
X  register int i = 0;
X  int r;
X
X  for (i = 0, r = 255; i<MAX_WIN_RETRY && (r&0x80) != 0; i++)
X	port_in(WIN_REG8, &r);
X  if ((r&0x80) != 0 || (r&0x40) == 0 || (r&0x10) == 0) {
X	w_need_reset = TRUE;
X	return(ERR);
X  }
X  return(OK);
X}
X
X/*============================================================================*
X *				com_out					      *
X *============================================================================*/
XPRIVATE com_out()
X{
X/* Output the command block to the winchester controller and return status */
X
X	register int i;
X	int r;
X
X	if (drive_busy()) {
X		w_need_reset = TRUE;
X		return(ERR);
X	}
X	r = WIN_REG2;
X	lock();
X	port_out(WIN_REG9, command[0]);
X	for (i=1; i<8; i++, r++)
X		port_out(r, command[i]);
X	unlock();
X	return(OK);
X}
X
X/*============================================================================*
X *				init_params				      *
X *============================================================================*/
XPRIVATE init_params()
X{
X/* This routine is called at startup to initialize the partition table,
X * the number of drives and the controller
X*/
X  unsigned int i, segment, offset;
X  phys_bytes address;
X  extern phys_bytes umap();
X  extern int vec_table[];
X
X  /* Copy the parameter vector from the saved vector table */
X  offset = vec_table[2 * 0x41];
X  segment = vec_table[2 * 0x41 + 1];
X
X  /* Calculate the address off the parameters and copy them to buf */
X  address = ((long)segment << 4) + offset;
X  phys_copy(address, umap(proc_addr(WINCHESTER), D, buf, 16), 16L);
X
X  /* Copy the parameters to the structures */
X  copy_param(buf, &wini[0]);
X
X  /* Copy the parameter vector from the saved vector table */
X  offset = vec_table[2 * 0x46];
X  segment = vec_table[2 * 0x46 + 1];
X
X  /* Calculate the address off the parameters and copy them to buf */
X  address = ((long)segment << 4) + offset;
X  phys_copy(address, umap(proc_addr(WINCHESTER), D, buf, 16), 16L);
X
X  /* Copy the parameters to the structures */
X  copy_param(buf, &wini[5]);
X
X  /* Get the nummer of drives from the bios */
X  phys_copy(0x475L, umap(proc_addr(WINCHESTER), D, buf, 1), 1L);
X  nr_drives = (int) *buf;
X
X  /* Set the parameters in the drive structure */
X  wini[0].wn_low = wini[5].wn_low = 0L;
X
X  /* Initialize the controller */
X  if ((nr_drives > 0) && (win_init() != OK))
X		nr_drives = 0;
X
X  /* Read the partition table for each drive and save them */
X  for (i = 0; i < nr_drives; i++) {
X	w_mess.DEVICE = i * 5;
X	w_mess.POSITION = 0L;
X	w_mess.COUNT = BLOCK_SIZE;
X	w_mess.ADDRESS = (char *) buf;
X	w_mess.PROC_NR = WINCHESTER;
X	w_mess.m_type = DISK_READ;
X	if (w_do_rdwt(&w_mess) != BLOCK_SIZE)
X		panic("Can't read partition table of winchester ", i);
X	if (buf[510] != 0x55 || buf[511] != 0xAA) {
X		printf("Invalid partition table\n");
X		continue;
X	}
X	copy_prt(i*5);
X  }
X}
X
X/*============================================================================*
X *				copy_params				      *
X *============================================================================*/
XPRIVATE copy_params(src, dest)
Xregister unsigned char *src;
Xregister struct wini *dest;
X{
X/* This routine copies the parameters from src to dest
X * and sets the parameters for partition 0 and 5
X*/
X  register int i;
X  long cyl, heads, sectors;
X
X  for (i=0; i<5; i++) {
X	dest[i].wn_heads = (int)src[2];
X	dest[i].wn_precomp = *(int *)&src[5] >> 2;
X	dest[i].wn_ctlbyte = (int)src[8];
X	dest[i].wn_maxsec = (int)src[14];
X  }
X  cyl = (long)(*(int *)src);
X  heads = (long)dest[0].wn_heads;
X  sectors = (long)dest[0].wn_maxsec;
X  dest[0].wn_size = cyl * heads * sectors;
X}
X
X/*============================================================================*
X *				copy_prt				      *
X *============================================================================*/
XPRIVATE copy_prt(drive)
Xint drive;
X{
X/* This routine copies the partition table for the selected drive to
X * the variables wn_low and wn_size
X */
X
X  register int i, offset;
X  struct wini *wn;
X  long adjust;
X
X  for (i=0; i<4; i++) {
X	adjust = 0;
X	wn = &wini[i + drive + 1];
X	offset = PART_TABLE + i * 0x10;
X	wn->wn_low = *(long *)&buf[offset];
X	if ((wn->wn_low % (BLOCK_SIZE/SECTOR_SIZE)) != 0) {
X		adjust = wn->wn_low;
X		wn->wn_low = (wn->wn_low/(BLOCK_SIZE/SECTOR_SIZE)+1)*(BLOCK_SIZE/SECTOR_SIZE);
X		adjust = wn->wn_low - adjust;
X	}
X	wn->wn_size = *(long *)&buf[offset + sizeof(long)] - adjust;
X  }
X  sort(&wini[drive + 1]);
X}
X
Xsort(wn)
Xregister struct wini *wn;
X{
X  register int i,j;
X
X  for (i=0; i<4; i++)
X	for (j=0; j<3; j++)
X		if ((wn[j].wn_low == 0) && (wn[j+1].wn_low != 0))
X			swap(&wn[j], &wn[j+1]);
X		else if (wn[j].wn_low > wn[j+1].wn_low && wn[j+1].wn_low != 0)
X			swap(&wn[j], &wn[j+1]);
X}
X
Xswap(first, second)
Xregister struct wini *first, *second;
X{
X  register struct wini tmp;
X
X  tmp = *first;
X  *first = *second;
X  *second = tmp;
X}
+ END-OF-FILE at_wini.c
chmod 'u=rw,g=r,o=r' \a\t\_\w\i\n\i\.\c
set `sum \a\t\_\w\i\n\i\.\c`
sum=$1
case $sum in
11751)	:;;
*)	echo 'Bad sum in '\a\t\_\w\i\n\i\.\c >&2
esac
echo Extracting \x\t\_\w\i\n\i\.\c
sed 's/^X//' > \x\t\_\w\i\n\i\.\c << '+ END-OF-FILE '\x\t\_\w\i\n\i\.\c
X/* This file contains a driver for the WD winchester controller from 
X * Western Digital (WX-2 and related controllers).
X *
X * Original code written by Adri Koppes.
X * Patches from Gary Oliver for use with the Western Digital WX-2.
X * Patches from Harry McGavran for robust operation on turbo clones.
X * Patches from Mike Mitchell for WX-2 auto configure operation.
X *
X * The driver supports two operations: read a block and
X * write a block.  It accepts two messages, one for reading and one for
X * writing, both using message format m2 and with the same parameters:
X *
X *	m_type	  DEVICE   PROC_NR	COUNT	 POSITION  ADRRESS
X * ----------------------------------------------------------------
X * |  DISK_READ | device  | proc nr |  bytes  |	 offset | buf ptr |
X * |------------+---------+---------+---------+---------+---------|
X * | DISK_WRITE | device  | proc nr |  bytes  |	 offset | buf ptr |
X * ----------------------------------------------------------------
X *
X * The file contains one entry point:
X *
X *	 winchester_task:	main entry when system is brought up
X *
X */
X
X#include "../h/const.h"
X#include "../h/type.h"
X#include "../h/callnr.h"
X#include "../h/com.h"
X#include "../h/error.h"
X#include "const.h"
X#include "type.h"
X#include "proc.h"
X
X#define AU  TO_BIOS     TRUE	/* TRUE: use Western's autoconfig BIOS */
X#define DEBUG	       FALSE	/* TRUE: enable debug messages */
X#define MONITOR		TRUE	/* TRUE: monitor performance of busy loops */
X#define MAX_DRIVES         1
X
X/* I/O Ports used by winchester disk task. */
X#define WIN_DATA       0x320	/* winchester disk controller data register */
X#define WIN_STATUS     0x321	/* winchester disk controller status register */
X#define WST_REQ	       0x001	/* Request bit */
X#define WST_INPUT      0x002	/* Set if controller is writing to cpu */
X#define WST_BUS	       0x004	/* Command/status bit */
X#define WST_BUSY       0x008	/* Busy */
X#define WST_INTERRUPT  0x020	/* Interrupt generated ?? */
X#define WIN_SELECT     0x322	/* winchester disk controller select port */
X#define WIN_DMA	       0x323	/* winchester disk controller dma register */
X#define DMA_ADDR       0x006	/* port for low 16 bits of DMA address */
X#define DMA_TOP	       0x082	/* port for top 4 bits of 20-bit DMA addr */
X#define DMA_COUNT      0x007	/* port for DMA count (count =	bytes - 1) */
X#define DMA_M2	       0x00C	/* DMA status port */
X#define DMA_M1	       0x00B	/* DMA status port */
X#define DMA_INIT       0x00A	/* DMA init port */
X
X/* Winchester disk controller command bytes. */
X#define WIN_RECALIBRATE	0x01	/* command for the drive to recalibrate */
X#define WIN_SENSE	0x03	/* command for the controller to get its status */
X#define WIN_READ	0x08	/* command for the drive to read */
X#define WIN_WRITE	0x0a	/* command for the drive to write */
X#define WIN_SPECIFY	0x0C	/* command for the controller to accept params	*/
X#define WIN_ECC_READ	0x0D	/* command for the controller to read ecc length */
X
X#define DMA_INT		   3 /* Command with dma and interrupt */
X#define INT		   2	/* Command with interrupt, no dma */
X#define NO_DMA_INT	   0	/* Command without dma and interrupt */
X
X/* DMA channel commands. */
X#define DMA_READ	0x47	/* DMA read opcode */
X#define DMA_WRITE	0x4B	/* DMA write opcode */
X
X/* Parameters for the disk drive. */
X#define SECTOR_SIZE	 512	/* physical sector size in bytes */
X#define NR_SECTORS	0x11	/* number of sectors per track */
X
X/* Error codes */
X#define ERR		  -1	/* general error */
X
X/* Miscellaneous. */
X#define MAX_ERRORS	   4	/* how often to try rd/wt before quitting */
X#define MAX_RESULTS	   4	/* max number of bytes controller returns */
X#define NR_DEVICES	  10	/* maximum number of drives */
X#define MAX_WIN_RETRY  32000	/* max # times to try to output to WIN */
X#define PART_TABLE     0x1C6	/* IBM partition table starts here in sect 0 */
X#define DEV_PER_DRIVE	   5	/* hd0 + hd1 + hd2 + hd3 + hd4 = 5 */
X#if AUTO_BIOS
X#define AUTO_PARAM     0x1AD	/* drive parameter table starts here in sect 0	*/
X#define AUTO_ENABLE	0x10	/* auto bios enabled bit from status reg */
X/* some start up parameters in order to extract the drive parameter table */
X/* from the winchester. these should not need changed. */
X#define AUTO_CYLS	 306	/* default number of cylinders */
X#define AUTO_HEADS	   4	/* default number of heads */
X#define AUTO_RWC	 307	/* default reduced write cylinder */
X#define AUTO_WPC	 307	/* default write precomp cylinder */
X#define AUTO_ECC	  11	/* default ecc burst */
X#define AUTO_CTRL	   5	/* default winchester stepping speed byte */
X#endif
X
X/* Variables. */
XPRIVATE struct wini {		/* main drive struct, one entry per drive */
X  int wn_opcode;		/* DISK_READ or DISK_WRITE */
X  int wn_procnr;		/* which proc wanted this operation? */
X  int wn_drive;			/* drive number addressed (<< 5) */
X  int wn_cylinder;		/* cylinder number addressed */
X  int wn_sector;		/* sector addressed */
X  int wn_head;			/* head number addressed */
X  int wn_heads;			/* maximum number of heads */
X  int wn_ctrl_byte;		/* Control byte for COMMANDS (10-Apr-87 GO) */
X  long wn_low;			/* lowest cylinder of partition */
X  long wn_size;			/* size of partition in blocks */
X  int wn_count;			/* byte count */
X  vir_bytes wn_address;		/* user virtual address */
X  char wn_results[MAX_RESULTS];	/* the controller can give lots of output */
X} wini[NR_DEVICES];
X
XPRIVATE int w_need_reset = FALSE;	 /* set to 1 when controller must be reset	*/
XPRIVATE int nr_drives;		 /* Number of drives */
X
XPRIVATE message w_mess;		/* message buffer for in and out */
X
XPRIVATE int command[6];		/* Common command block */
X
XPRIVATE unsigned char buf[BLOCK_SIZE]; /* Buffer used by the startup routine */
X
XPRIVATE struct param {
X	int nr_cyl;		/* Number of cylinders */
X	int nr_heads;		/* Number of heads */
X	int reduced_wr;		/* First cylinder with reduced write current */
X	int wr_precomp;		/* First cylinder with write precompensation */
X	int max_ecc;		/* Maximum ECC burst length */
X	int ctrl_byte;		/* Copied control-byte from bios tables */
X} param0, param1;
X
X
X/*=========================================================================*
X *							winchester_task					 			   * 
X *=========================================================================*/
XPUBLIC winchester_task()
X{
X/* Main program of the winchester disk driver task. */
X
X  int r, caller, proc_nr;
X
X  /* First initialize the controller */
X  init_params();
X
X  /* Here is the main loop of the disk task.  It waits for a message, carries
X   * it out, and sends a reply.
X   */
X
X  while (TRUE) {
X	/* First wait for a request to read or write a disk block. */
X	receive(ANY, &w_mess);	/* get a request to do some work */
X	if (w_mess.m_source < 0) {
X		printf("winchester task got message from %d ", w_mess.m_source);
X		continue;
X	}
X	caller = w_mess.m_source;
X	proc_nr = w_mess.PROC_NR;
X
X	/* Now carry out the work. */
X	switch(w_mess.m_type) {
X		case DISK_READ:
X		case DISK_WRITE:	r = w_do_rdwt(&w_mess);	break;
X		default:		r = EINVAL;		break;
X	}
X
X	/* Finally, prepare and send the reply message. */
X	w_mess.m_type = TASK_REPLY;	
X	w_mess.REP_PROC_NR = proc_nr;
X
X	w_mess.REP_STATUS = r;	/* # of bytes transferred or error code */
X	send(caller, &w_mess);	/* send reply to caller */
X  }
X}
X
X
X/*==========================================================================*
X *								w_do_rdwt						 			* 
X *==========================================================================*/
XPRIVATE int w_do_rdwt(m_ptr)
Xmessage *m_ptr;			/* pointer to read or write w_message */
X{
X/* Carry out a read or write request from the disk. */
X  register struct wini *wn;
X  int r, device, errors = 0;
X  long sector;
X
X  /* Decode the w_message parameters. */
X  device = m_ptr->DEVICE;
X  if (device < 0 || device >= NR_DEVICES)
X	return(EIO);
X  if (m_ptr->COUNT != BLOCK_SIZE)
X	return(EINVAL);
X  wn = &wini[device];		/* 'wn' points to entry for this drive */
X
X  wn->wn_opcode = m_ptr->m_type;	/* DISK_READ or DISK_WRITE */
X  if (m_ptr->POSITION % BLOCK_SIZE != 0)
X	return(EINVAL);
X  sector = m_ptr->POSITION/SECTOR_SIZE;
X  if ((sector+BLOCK_SIZE/SECTOR_SIZE) > wn->wn_size)
X	return(EOF);
X  sector += wn->wn_low;
X  wn->wn_cylinder = sector / (wn->wn_heads * NR_SECTORS);
X  wn->wn_sector =  (sector % NR_SECTORS);
X  wn->wn_head = (sector % (wn->wn_heads * NR_SECTORS) )/NR_SECTORS;
X  wn->wn_count = m_ptr->COUNT;
X  wn->wn_address = (vir_bytes) m_ptr->ADDRESS;
X  wn->wn_procnr = m_ptr->PROC_NR;
X
X  /* This loop allows a failed operation to be repeated. */
X  while (errors <= MAX_ERRORS) {
X	errors++;		/* increment count once per loop cycle */
X	if (errors >= MAX_ERRORS)
X		return(EIO);
X
X	/* First check to see if a reset is needed. */
X	if (w_need_reset) w_reset();
X
X	/* Now set up the DMA chip. */
X	w_dma_setup(wn);
X
X	/* Perform the transfer. */
X	r = w_transfer(wn);
X	if (r == OK) break;	/* if successful, exit loop */
X
X  }
X
X  return(r == OK ? BLOCK_SIZE : EIO);
X}
X
X
X/*==========================================================================*
X *								w_dma_setup					 				* 
X *==========================================================================*/
XPRIVATE w_dma_setup(wn)
Xstruct wini *wn;		/* pointer to the drive struct */
X{
X/* The IBM PC can perform DMA operations by using the DMA chip.	 To use it,
X * the DMA (Direct Memory Access) chip is loaded with the 20-bit memory address
X * to by read from or written to, the byte count minus 1, and a read or write
X * opcode.	This routine sets up the DMA chip.	Note that the chip is not
X * capable of doing a DMA across a 64K boundary (e.g., you can't read a 
X * 512-byte block starting at physical address 65520).
X */
X
X  int mode, low_addr, high_addr, top_addr, low_ct, high_ct, top_end;
X  vir_bytes vir, ct;
X  phys_bytes user_phys;
X  extern phys_bytes umap();
X
X  mode = (wn->wn_opcode == DISK_READ ? DMA_READ : DMA_WRITE);
X  vir = (vir_bytes) wn->wn_address;
X  ct = (vir_bytes) wn->wn_count;
X  user_phys = umap(proc_addr(wn->wn_procnr), D, vir, ct);
X  low_addr	= (int) user_phys & BYTE;
X  high_addr = (int) (user_phys >>  8) & BYTE;
X  top_addr	= (int) (user_phys >> 16) & BYTE;
X  low_ct  = (int) (ct - 1) & BYTE;
X  high_ct = (int) ( (ct - 1) >> 8) & BYTE;
X
X  /* Check to see if the transfer will require the DMA address counter to
X   * go from one 64K segment to another.  If so, do not even start it, since
X   * the hardware does not carry from bit 15 to bit 16 of the DMA address.
X   * Also check for bad buffer address.	 These errors mean FS contains a bug.
X   */
X  if (user_phys == 0)
X	  panic("FS gave winchester disk driver bad addr", (int) vir);
X  top_end = (int) (((user_phys + ct - 1) >> 16) & BYTE);
X  if (top_end != top_addr) panic("Trying to DMA across 64K boundary", top_addr);
X
X  /* Now set up the DMA registers. */
X  lock();
X  port_out(DMA_M2, mode);	/* set the DMA mode */
X  port_out(DMA_M1, mode);	/* set it again */
X  port_out(DMA_ADDR, low_addr);	/* output low-order 8 bits */
X  port_out(DMA_ADDR, high_addr);/* output next 8 bits */
X  port_out(DMA_TOP, top_addr);	/* output highest 4 bits */
X  port_out(DMA_COUNT, low_ct);	/* output low 8 bits of count - 1 */
X  port_out(DMA_COUNT, high_ct);	/* output high 8 bits of count - 1 */
X  unlock();
X}
X
X/*=========================================================================*
X *								w_transfer								   *
X *=========================================================================*/
XPRIVATE int w_transfer(wn)
Xregister struct wini *wn;	/* pointer to the drive struct */
X{
X/* The drive is now on the proper cylinder.	 Read or write 1 block. */
X
X  /* The command is issued by outputing 6 bytes to the controller chip. */
X  command[0] = (wn->wn_opcode == DISK_READ ? WIN_READ : WIN_WRITE);
X  command[1] = wn->wn_head | wn->wn_drive;
X  command[2] = (((wn->wn_cylinder & 0x0300) >> 2) | wn->wn_sector);
X  command[3] = (wn->wn_cylinder & 0xFF);
X  command[4] = BLOCK_SIZE/SECTOR_SIZE;
X  command[5] = wn->wn_ctrl_byte;
X
X  if (com_out(DMA_INT) != OK)
X	return(ERR);
X
X  port_out(DMA_INIT, 3);	/* initialize DMA */
X  /* Block, waiting for disk interrupt. */
X  w_wait_int();
X
X  /* Get controller status and check for errors. */
X  if (win_results(wn) == OK)
X	return(OK);
X  if ((wn->wn_results[0] & 63) == 24)
X	read_ecc();
X  else
X	w_need_reset = TRUE;
X  return(ERR);
X}
X
X
X/*===========================================================================*
X *				win_results					 * 
X *===========================================================================*/
XPRIVATE int win_results(wn)
Xregister struct wini *wn;	/* pointer to the drive struct */
X{
X/* Extract results from the controller after an operation. */
X
X  register int i;
X  int status;
X
X  port_in(WIN_DATA, &status);
X  port_out(WIN_DMA, 0);
X  if (!(status & 2))		/* Test "error" bit */
X	return(OK);
X  command[0] = WIN_SENSE;
X  command[1] = wn->wn_drive;
X  if (com_out(NO_DMA_INT) != OK)
X	return(ERR);
X
X  /* Loop, extracting bytes from WIN */
X  for (i = 0; i < MAX_RESULTS; i++) {
X	if (hd_wait(WST_REQ) != OK)
X		return(ERR);
X	port_in(WIN_DATA, &status);
X	wn->wn_results[i] = status & BYTE;
X  }
X  if(hd_wait(WST_REQ) != OK)	/* Missing from			*/
X	 return (ERR);		/* Original.  11-Apr-87 G.O.	*/
X
X  port_in(WIN_DATA, &status);		 /* Read "error" flag */
X
X  if(((status & 2) != 0) || (wn->wn_results[0] & 0x3F)) {
X	return(ERR);
X  } else
X	return(OK);
X}
X
X
X/*===========================================================================*
X *				win_out						 * 
X *===========================================================================*/
XPRIVATE win_out(val)
Xint val;			/* write this byte to winchester disk controller */
X{
X/* Output a byte to the controller.	 This is not entirely trivial, since you
X * can only write to it when it is listening, and it decides when to listen.
X * If the controller refuses to listen, the WIN chip is given a hard reset.
X */
X  int r;
X
X  if (w_need_reset) return;	/* if controller is not listening, return */
X
X  do {
X	port_in(WIN_STATUS, &r);
X  } while((r & (WST_REQ | WST_BUSY)) == WST_BUSY);
X
X	port_out(WIN_DATA, val);
X}
X
X/*===========================================================================*
X *				w_reset						 * 
X *===========================================================================*/
XPRIVATE w_reset()
X{
X/* Issue a reset to the controller.	 This is done after any catastrophe,
X * like the controller refusing to respond.
X */
X
X  int r = 0, i;
X
X  /* Strobe reset bit low. */
X  port_out(WIN_STATUS, 0);
X
X  for(i = MAX_WIN_RETRY/10; i; --i)
X	;	/* Spin loop for a while */
X
X  port_out(WIN_SELECT, 0);	/* Issue select pulse */
X  for (i = 0; i < MAX_WIN_RETRY; i++) {
X	port_in(WIN_STATUS, &r);
X	if(r & 0x30)		/* What is 10? 20 = INTERRUPT */
X		return (ERR);
X
X	if((r & (WST_BUSY | WST_BUS | WST_REQ)) ==
X		(WST_BUSY | WST_BUS | WST_REQ))
X		break;
X  }
X
X  if (i == MAX_WIN_RETRY) {
X	printf("Hard disk won't reset, status = %x\n", r);
X	return(ERR);
X  }
X
X  /* Reset succeeded.  Tell WIN drive parameters. */
X  w_need_reset = FALSE;
X
X  if(win_specify(0, &param0) != OK)
X	return (ERR);
X
X
X  if ((nr_drives > 1) && (win_specify(1, &param1) != OK))
X	return(ERR);
X
X
X  for (i=0; i<nr_drives; i++) {
X	command[0] = WIN_RECALIBRATE;
X	command[1] = i << 5;
X	command[5] = wini[i * DEV_PER_DRIVE].wn_ctrl_byte;
X
X
X	if (com_out(INT) != OK)
X		return(ERR);
X
X	w_wait_int();
X
X	if (win_results(&wini[i * DEV_PER_DRIVE]) != OK) {
X		w_need_reset = TRUE;
X		return(ERR);
X	}
X	 }
X	 return(OK);
X}
X
X
X/*===========================================================================*
X *				w_wait_int					 *
X *===========================================================================*/
XPRIVATE w_wait_int()
X{
X   /*DEBUG: loop looking for 0x20 in status (I don't know what that is!!) */
X   /*		 10-Apr-87. G. Oliver					  */
X   int r, i; /* Some local storage */
X
X   receive(HARDWARE, &w_mess);
X
X   port_out(DMA_INIT, 0x07);	/* Disable int from DMA */
X
X   for(i=0; i<MAX_WIN_RETRY; ++i) {
X	port_in(WIN_STATUS, &r);
X	if(r & WST_INTERRUPT)
X		break;		/* Exit if end of int */
X  }
X
X#if	 MONITOR
X   if(i > 10) {		/* Some arbitrary limit below which we don't really care */
X	if(i == MAX_WIN_RETRY)
X		printf("wini: timeout waiting for INTERRUPT status\n");
X	else
X		printf("wini: %d loops waiting for INTERRUPT status\n", i);
X   }
X#endif	/* MONITOR */
X}
X
X
X/*============================================================================*
X *				win_specify					  *
X *============================================================================*/
XPRIVATE win_specify(drive, paramp)
Xint drive;
Xstruct param *paramp;
X{
X  command[0] = WIN_SPECIFY;		/* Specify some parameters */
X  command[1] = drive << 5;		/* Drive number */
X
X	if (com_out(NO_DMA_INT) != OK)		/* Output command block */
X		return(ERR);
X	lock();
X
X	/* No. of cylinders (high byte) */
X  win_out(paramp->nr_cyl >> 8);
X
X	/* No. of cylinders (low byte) */
X  win_out(paramp->nr_cyl);
X
X	/* No. of heads */
X  win_out(paramp->nr_heads);
X
X	/* Start reduced write (high byte) */
X  win_out(paramp->reduced_wr >> 8);
X
X	/* Start reduced write (low byte) */
X  win_out(paramp->reduced_wr);
X
X	/* Start write precompensation (high byte) */
X  win_out(paramp->wr_precomp >> 8);
X
X	/* Start write precompensation (low byte) */
X  win_out(paramp->wr_precomp);
X
X	/* Ecc burst length */
X  win_out(paramp->max_ecc);
X	unlock();
X
X	if (check_init() != OK) {  /* See if controller accepted parameters */
X		w_need_reset = TRUE;
X		return(ERR);
X	}
X  else
X  return(OK);
X}
X
X/*============================================================================*
X *				check_init					  *
X *============================================================================*/
XPRIVATE check_init()
X{
X/* Routine to check if controller accepted the parameters */
X  int r, s;
X
X  if (hd_wait(WST_REQ | WST_INPUT) == OK) {
X	  port_in(WIN_DATA, &r);
X
X	   do {
X		port_in(WIN_STATUS, &s);
X	   } while(s & WST_BUSY);		/* Loop while still busy */
X
X	   if (r & 2)		/* Test error bit */
X		{
X		return(ERR);
X		}
X	  else
X		return(OK);
X  } else
X	{
X	return (ERR);	/* Missing from original: 11-Apr-87 G.O. */
X  }
X}
X
X/*============================================================================*
X *				read_ecc					  *
X *============================================================================*/
XPRIVATE read_ecc()
X{
X/* Read the ecc burst-length and let the controller correct the data */
X
X  int r;
X
X  command[0] = WIN_ECC_READ;
X  if (com_out(NO_DMA_INT) == OK && hd_wait(WST_REQ) == OK) {
X	port_in(WIN_DATA, &r);
X	if (hd_wait(WST_REQ) == OK) {
X		port_in(WIN_DATA, &r);
X		if (r & 1)
X			w_need_reset = TRUE;
X	}
X  }
X  return(ERR);
X}
X
X/*============================================================================*
X *				hd_wait						  *
X *============================================================================*/
XPRIVATE hd_wait(bits)
Xregister int bits;
X{
X/* Wait until the controller is ready to receive a command or send status */
X
X  register int i = 0;
X  int r;
X
X  do {
X	port_in(WIN_STATUS, &r);
X	r &= bits;
X  } while ((i++ < MAX_WIN_RETRY) && r != bits);		/* Wait for ALL bits */
X
X  if (i >= MAX_WIN_RETRY) {
X	w_need_reset = TRUE;
X	return(ERR);
X  } else
X	return(OK);
X}
X
X/*============================================================================*
X *				com_out						  *
X *============================================================================*/
XPRIVATE com_out(mode)
Xint mode;
X{
X/* Output the command block to the winchester controller and return status */
X
X	register int i;
X	int r;
X
X	port_out(WIN_DMA, mode);
X	port_out(WIN_SELECT, mode);
X	for (i=0; i<MAX_WIN_RETRY; i++) {
X		port_in(WIN_STATUS, &r);
X		if (r & WST_BUSY)
X			break;
X	}
X
X	if (i == MAX_WIN_RETRY) {
X		w_need_reset = TRUE;
X		return(ERR);
X	}
X
X
X	lock();
X
X	for (i=0; i<6; i++) {
X		if(hd_wait(WST_REQ) != OK)
X			break;		/* No data request pending */
X
X		port_in(WIN_STATUS, &r);
X
X		if((r & (WST_BUSY | WST_BUS | WST_INPUT)) !=
X			(WST_BUSY | WST_BUS))
X			break;
X
X		port_out(WIN_DATA, command[i]);
X	}
X
X	unlock();
X
X	if(i != 6) {
X		return(ERR);
X	}
X	else
X		return(OK);
X}
X
X/*============================================================================*
X *				init_params					  *
X *============================================================================*/
XPRIVATE init_params()
X{
X/* This routine is called at startup to initialize the partition table,
X * the number of drives and the controller
X*/
X  unsigned int i, segment, offset;
X  int type_0, type_1;
X  phys_bytes address;
X  extern phys_bytes umap();
X  extern int vec_table[];
X
X  /* Get the number of drives from the bios */
X  phys_copy(0x475L, umap(proc_addr(WINCHESTER), D, buf, 1), 1L);
X  nr_drives = (int) *buf > MAX_DRIVES ? MAX_DRIVES : (int) *buf;
X
X  /* Read the switches from the controller */
X  port_in(WIN_SELECT, &i);
X
X#if AUTO_BIOS
X  /* Get the drive parameters from sector zero of the drive if the */
X  /* autoconfig mode of the controller has been selected */
X
X  if(i & AUTO_ENABLE) {
X
X	/* set up some phoney parameters so that we can read the first sector */
X	/* from the winchester. all drives will have one cylinder and one head */
X	/* but set up initially to the mini scribe drives from ibm */
X	param1.nr_cyl = param0.nr_cyl = AUTO_CYLS;
X	param1.nr_heads = param0.nr_heads = AUTO_HEADS;
X	param1.reduced_wr = param0.reduced_wr = AUTO_RWC;
X	param1.wr_precomp = param0.wr_precomp = AUTO_WPC;
X	param1.max_ecc = param0.max_ecc = AUTO_ECC;
X	param1.ctrl_byte = param0.ctrl_byte = AUTO_CTRL;
X	wini[DEV_PER_DRIVE].wn_heads = wini[0].wn_heads = param0.nr_heads;
X	wini[DEV_PER_DRIVE].wn_low = wini[0].wn_low = 0L;
X	wini[DEV_PER_DRIVE].wn_size = wini[0].wn_size = (long)AUTO_CYLS * (long)AUTO_HEADS * (long)NR_SECTORS;
X	if(w_reset() != OK)
X	  panic("cannot setup for reading winchester parameter tables",0);
X
X	if (nr_drives > 1) {
X	  
X	  /* generate the request to read the first sector from the winchester */
X	  w_mess.DEVICE = DEV_PER_DRIVE;
X	  w_mess.POSITION = 0L;
X	  w_mess.COUNT = BLOCK_SIZE;
X	  w_mess.ADDRESS = (char *) buf;
X	  w_mess.PROC_NR = WINCHESTER;
X	  w_mess.m_type = DISK_READ;
X	  if(w_do_rdwt(&w_mess) != BLOCK_SIZE)
X		panic("cannot read drive parameters from winchester",DEV_PER_DRIVE);
X
X	  /* copy the parameter tables into the structures for later use */
X	  copy_param(&buf[AUTO_PARAM], &param1);
X
X	}
X
X	/* generate the request to read the first sector from the winchester */
X	w_mess.DEVICE = 0;
X	w_mess.POSITION = 0L;
X	w_mess.COUNT = BLOCK_SIZE;
X	w_mess.ADDRESS = (char *) buf;
X	w_mess.PROC_NR = WINCHESTER;
X	w_mess.m_type = DISK_READ;
X	if(w_do_rdwt(&w_mess) != BLOCK_SIZE)
X	  panic("cannot read drive parameters from winchester", 0);
X
X	/* copy the parameter tables into the structures for later use */
X	copy_param(&buf[AUTO_PARAM], &param0);
X
X	   
X   /* whoever compiled the kernel wanted the auto bios code included. if it
X	* turns out that the tables should be read from the rom, then handle
X	* this case the regular way */
X  } else {
X#endif
X
X  /* Calculate the drive types */
X  type_0 = i & 3;
X  type_1 = (i >> 2) & 3;
X
X  /* Copy the parameter vector from the saved vector table */
X  offset = vec_table[2 * 0x41];
X  segment = vec_table[2 * 0x41 + 1];
X
X  /* Calculate the address off the parameters and copy them to buf */
X  address = ((phys_bytes)segment << 4) + offset;
X  phys_copy(address, umap(proc_addr(WINCHESTER), D, buf, 64), 64L);
X
X  /* Copy the parameters to the structures */
X  copy_param(&buf[type_0 * 16], &param0);
X  copy_param(&buf[type_1 * 16], &param1);
X
X#if AUTO_BIOS
X  /* close up the code to be executed when the controller has not been
X   * set up to for auto configuration */
X  }
X#endif
X
X  /* Set the parameters in the drive structure */
X  for (i = 0; i < DEV_PER_DRIVE; i++) {
X	wini[i].wn_heads = param0.nr_heads;
X	wini[i].wn_ctrl_byte = param0.ctrl_byte;
X	wini[i].wn_drive = 0 << 5;	/* Set drive number */
X  }
X
X  wini[0].wn_low = wini[DEV_PER_DRIVE].wn_low = 0L;
X  wini[0].wn_size = (long)((long)param0.nr_cyl * (long)param0.nr_heads * (long)NR_SECTORS);
X
X  for (i = DEV_PER_DRIVE; i < (2*DEV_PER_DRIVE); i++) {
X	wini[i].wn_heads = param1.nr_heads;
X	wini[i].wn_ctrl_byte = param1.ctrl_byte;
X	wini[i].wn_drive = 1 << 5;	/* Set drive number */
X  }
X  wini[DEV_PER_DRIVE].wn_size =
X	(long)((long)param1.nr_cyl * (long)param1.nr_heads * (long)NR_SECTORS);
X
X  /* Initialize the controller */
X  if ((nr_drives > 0) && (w_reset() != OK))
X		nr_drives = 0;
X
X  /* Read the partition table for each drive and save them */
X  for (i = 0; i < nr_drives; i++) {
X	w_mess.DEVICE = i * DEV_PER_DRIVE;
X	w_mess.POSITION = 0L;
X	w_mess.COUNT = BLOCK_SIZE;
X	w_mess.ADDRESS = (char *) buf;
X	w_mess.PROC_NR = WINCHESTER;
X	w_mess.m_type = DISK_READ;
X	if (w_do_rdwt(&w_mess) != BLOCK_SIZE)
X		panic("Can't read partition table of winchester ", i);
X	copy_prt(i * DEV_PER_DRIVE);
X  }
X}
X
X/*==========================================================================*
X *								copy_params					 				*
X *==========================================================================*/
XPRIVATE copy_params(src, dest)
Xregister unsigned char *src;
Xregister struct param *dest;
X{
X/* This routine copies the parameters from src to dest
X * and sets the parameters for partition 0 and DEV_PER_DRIVE
X*/
X
X  dest->nr_cyl = *(int *)src;
X  dest->nr_heads = (int)src[2];
X  dest->reduced_wr = *(int *)&src[3];
X  dest->wr_precomp = *(int *)&src[5];
X  dest->max_ecc = (int)src[7];
X  dest->ctrl_byte = (int)src[8];
X}
X
X/*==========================================================================*
X *								copy_prt									*
X *==========================================================================*/
XPRIVATE copy_prt(drive)
Xint drive;
X{
X/* This routine copies the partition table for the selected drive to
X * the variables wn_low and wn_size
X */
X
X  register int i, offset;
X  struct wini *wn;
X  long adjust;
X
X  for (i=0; i<4; i++) {
X	adjust = 0;
X	wn = &wini[i + drive + 1];
X	offset = PART_TABLE + i * 0x10;
X	wn->wn_low = *(long *)&buf[offset];
X	if ((wn->wn_low % (BLOCK_SIZE/SECTOR_SIZE)) != 0) {
X		adjust = wn->wn_low;
X		wn->wn_low = (wn->wn_low/(BLOCK_SIZE/SECTOR_SIZE)+1)*(BLOCK_SIZE/SECTOR_SIZE);
X		adjust = wn->wn_low - adjust;
X	}
X	wn->wn_size = *(long *)&buf[offset + sizeof(long)] - adjust;
X  }
X  sort(&wini[drive + 1]);
X}
X
Xsort(wn)
Xregister struct wini *wn;
X{
X  register int i,j;
X
X  for (i=0; i<4; i++)
X	for (j=0; j<3; j++)
X		if ((wn[j].wn_low == 0) && (wn[j+1].wn_low != 0))
X			swap(&wn[j], &wn[j+1]);
X		else if (wn[j].wn_low > wn[j+1].wn_low && wn[j+1].wn_low != 0)
X			swap(&wn[j], &wn[j+1]);
X}
X
Xswap(first, second)
Xregister struct wini *first, *second;
X{
X  register struct wini tmp;
X
X  tmp = *first;
X  *first = *second;
X  *second = tmp;
X}
X
+ END-OF-FILE xt_wini.c
chmod 'u=rw,g=r,o=r' \x\t\_\w\i\n\i\.\c
set `sum \x\t\_\w\i\n\i\.\c`
sum=$1
case $sum in
53356)	:;;
*)	echo 'Bad sum in '\x\t\_\w\i\n\i\.\c >&2
esac
echo Extracting \d\t\e\s\t\.\c
sed 's/^X//' > \d\t\e\s\t\.\c << '+ END-OF-FILE '\d\t\e\s\t\.\c
X#define N 25
Xchar buf1[N*1024];
Xchar buf2[N*1024];
X
Xmain(argc, argv)
Xint argc;
Xchar *argv[];
X{
X  int fd, i, j, k=0;
X  int off;
X
X  fd = open(argv[1], 2);
X  if (fd < 0) {printf("Bad file %s\n", argv[1]); exit(1);}
X  off = 1024 * atoi(argv[2]);
X  
X  lseek(fd, (long) off, 0);
X  if (read(fd, buf1, N*1024) != N * 1024) 
X	{printf("Bad initial read\n"); exit(1);}
X
X  i = 0;
X  while (1) {
X	lseek(fd, (long) off, 0);
X	if (read(fd, buf2, N*1024) != N * 1024) 
X		{printf("Bad read\n"); exit(1);}
X	
X	for (j= 0; j < N * 1024; j++)
X		if (buf1[j] != buf2[j]) {
X			k++;
X			printf("Compare error #%d\n",k);
X		}
X	lseek(fd, (long) off, 0);
X	if (write(fd, buf2, N*1024) != N * 1024) 
X		{printf("Bad write\n"); exit(1);}
X	if (++i % 10 == 0) printf("%d passes, %d errors\n",i,k);
X  }
X}
X
+ END-OF-FILE dtest.c
chmod 'u=rw,g=r,o=r' \d\t\e\s\t\.\c
set `sum \d\t\e\s\t\.\c`
sum=$1
case $sum in
15218)	:;;
*)	echo 'Bad sum in '\d\t\e\s\t\.\c >&2
esac
exit 0