xref: /csrg-svn/sys/tahoe/vba/hd.c (revision 33165)
1*33165Sbostic /*
2*33165Sbostic  *  Driver for HCX Disk Controller (HDC)
3*33165Sbostic  *
4*33165Sbostic  *	@(#)hd.c	7.1 (Berkeley) 12/28/87
5*33165Sbostic  */
6*33165Sbostic 
7*33165Sbostic #include <sys/types.h>
8*33165Sbostic #include <ctype.h>
9*33165Sbostic #include "../sys/param.h"
10*33165Sbostic #include "../sys/buf.h"
11*33165Sbostic #include "../sys/conf.h"
12*33165Sbostic #include "../sys/dir.h"
13*33165Sbostic #include "../sys/dk.h"
14*33165Sbostic #include "../ml/mtpr.h"
15*33165Sbostic #include "../sys/systm.h"
16*33165Sbostic #include "../sys/vbavar.h"
17*33165Sbostic #include "../sys/user.h"
18*33165Sbostic #include "../sys/vmmac.h"
19*33165Sbostic #include "../sys/uio.h"
20*33165Sbostic #include "../sys/elog.h"
21*33165Sbostic #include "../sys/iobuf.h"
22*33165Sbostic #include "../sys/kernel.h"
23*33165Sbostic #include "../sys/reboot.h"
24*33165Sbostic #include "../sys/ioctl.h"
25*33165Sbostic #define DSKGENDATA
26*33165Sbostic #include "../sys/dsk.h"
27*33165Sbostic #undef DSKGENDATA
28*33165Sbostic #include "../sys/dskio.h"
29*33165Sbostic #include "../sys/hdc.h"
30*33165Sbostic #include "../sys/proc.h"
31*33165Sbostic 
32*33165Sbostic /*
33*33165Sbostic  * External data.
34*33165Sbostic  */
35*33165Sbostic 
36*33165Sbostic extern unsigned int		blkacty;	/* for error logging      */
37*33165Sbostic extern hdc_ctlr_type		hdc_ctlrs[];	/* hdc controller info    */
38*33165Sbostic extern hdc_unit_type		hdc_units[];	/* hdc unit info          */
39*33165Sbostic extern struct vba_ctlr		*hdminfo[];	/* vba controller info    */
40*33165Sbostic extern struct vba_device	*vddinfo[];	/* vba device info        */
41*33165Sbostic extern struct iotime		vdstat[];	/* for disk activity info */
42*33165Sbostic extern struct iobuf		vdtab[];	/* for disk activity info */
43*33165Sbostic extern int			maxfree;	/* no. of blocks for dump */
44*33165Sbostic 
45*33165Sbostic /*
46*33165Sbostic  * Procedure forward references.
47*33165Sbostic  */
48*33165Sbostic 
49*33165Sbostic int  hdprobe();
50*33165Sbostic int  hdslave();
51*33165Sbostic int  hdstrategy();
52*33165Sbostic int  hdattach();
53*33165Sbostic 
54*33165Sbostic /*
55*33165Sbostic  * Driver structure.
56*33165Sbostic  */
57*33165Sbostic 
58*33165Sbostic struct  vba_driver hddriver = {
59*33165Sbostic 	hdprobe,		/* handler probe routine        */
60*33165Sbostic 	hdslave,		/* handler slave routine        */
61*33165Sbostic 	hdattach,		/* handler attach routine       */
62*33165Sbostic 	0,			/* handler go routine           */
63*33165Sbostic 	0,			/*                              */
64*33165Sbostic 	"dsk",			/* name of the device           */
65*33165Sbostic 	vddinfo,		/* table of unit info           */
66*33165Sbostic 	"HDC Controller #",	/* name of the controller       */
67*33165Sbostic 	hdminfo,		/* table of ctlr info           */
68*33165Sbostic 	HDC_MID,		/* controller's module id       */
69*33165Sbostic 	0			/* no exclusive use of bdp's    */
70*33165Sbostic };
71*33165Sbostic 
72*33165Sbostic #ifdef HDCLOG
73*33165Sbostic /*************************************************************************
74*33165Sbostic *  Procedure:	hdlog
75*33165Sbostic *
76*33165Sbostic *  Description: logs mcb's, master mcb's, etc.
77*33165Sbostic *
78*33165Sbostic *  Returns:
79*33165Sbostic **************************************************************************/
80*33165Sbostic 
81*33165Sbostic #define ENT_SIZE 16
82*33165Sbostic #define ENT_COUNT 256
83*33165Sbostic static int  hdclog_index = 0;
84*33165Sbostic static unsigned int  hdclog[ ENT_SIZE * ENT_COUNT ];
85*33165Sbostic 
86*33165Sbostic hdlog(ptr,id)
87*33165Sbostic register unsigned int   *ptr;
88*33165Sbostic register unsigned int   id;
89*33165Sbostic {
90*33165Sbostic 	int i;
91*33165Sbostic 
92*33165Sbostic 	hdclog[hdclog_index++] = id;
93*33165Sbostic 	hdclog[hdclog_index++] = time.tv_sec;
94*33165Sbostic 	hdclog[hdclog_index++] = time.tv_usec;
95*33165Sbostic 	for (i=3; i<ENT_SIZE; i++) {
96*33165Sbostic 		hdclog[hdclog_index++] = *ptr;
97*33165Sbostic 		ptr++;
98*33165Sbostic 	}
99*33165Sbostic 	if (hdclog_index >= ENT_SIZE * ENT_COUNT) hdclog_index=0;
100*33165Sbostic }
101*33165Sbostic #endif
102*33165Sbostic 
103*33165Sbostic /*************************************************************************
104*33165Sbostic *  Procedure:	hdattach
105*33165Sbostic *
106*33165Sbostic *  Description: "hdattach" does device-dependent initialization of
107*33165Sbostic * 		hdc drives. It is called during the configuration phase
108*33165Sbostic *               of a reboot for each disk device on an hdc controller.
109*33165Sbostic *               Note that most things get initialized in "hdslave",
110*33165Sbostic *               because "slave" initializes what it needs to determine
111*33165Sbostic *               whether the drive is ready (which turns out to be a lot).
112*33165Sbostic *
113*33165Sbostic *  Returns:
114*33165Sbostic **************************************************************************/
115*33165Sbostic 
116*33165Sbostic hdattach(vba_unit)
117*33165Sbostic 
118*33165Sbostic register struct vba_device *vba_unit;	/* Pointer to vba drive info
119*33165Sbostic 					 */
120*33165Sbostic {
121*33165Sbostic 	register hdc_unit_type	*hu;	/* hdc unit info
122*33165Sbostic 					 */
123*33165Sbostic 	register int		unit;	/* drive's unit# (0-31)
124*33165Sbostic 					 */
125*33165Sbostic 	unit = vba_unit->ui_unit;
126*33165Sbostic 	hu = &hdc_units[ unit ];
127*33165Sbostic 
128*33165Sbostic 	/*
129*33165Sbostic 	 * Initialize the hdc unit information structure.
130*33165Sbostic 	 * A lot of this is done in "hdslave".
131*33165Sbostic 	 */
132*33165Sbostic 
133*33165Sbostic 	hu->spc = hu->heads * hu->sectors;
134*33165Sbostic 
135*33165Sbostic 	/*
136*33165Sbostic 	 * bytes per second:
137*33165Sbostic 	 *      (number of sectors per track) * (bytes per sector) * rpm / 60
138*33165Sbostic  	 */
139*33165Sbostic 
140*33165Sbostic 	dk_bps[unit] = hu->sectors * BPS * hu->rpm / 60;
141*33165Sbostic }
142*33165Sbostic 
143*33165Sbostic /*************************************************************************
144*33165Sbostic *  Procedure:	hddump
145*33165Sbostic *
146*33165Sbostic *  Description: Dump system memory to disk. The hdc controller is reset.
147*33165Sbostic *               After this call, queued operations on this hdc are no
148*33165Sbostic *               longer possible until the next reboot.
149*33165Sbostic *
150*33165Sbostic *  Returns:     ENXIO    the dump was truncated for some reason.
151*33165Sbostic *               EIO      there were controller problems
152*33165Sbostic *               0        normal
153*33165Sbostic **************************************************************************/
154*33165Sbostic 
155*33165Sbostic int
156*33165Sbostic hddump(dev)
157*33165Sbostic 
158*33165Sbostic int	dev;		/* the major/minor device number.
159*33165Sbostic 			 */
160*33165Sbostic {
161*33165Sbostic 	register hdc_unit_type	*hu;		/* hdc unit info            */
162*33165Sbostic 	register hdc_ctlr_type	*hc;		/* hdc controller info      */
163*33165Sbostic 	register mcb_type	*mcb;		/* hdc controller info      */
164*33165Sbostic 	register int		current_block;	/* next disk block to write */
165*33165Sbostic 	register int		block_count;	/* #blocks to dump total    */
166*33165Sbostic 	register int		blocks;		/* #blocks to dump at a time*/
167*33165Sbostic 	register int		mem_addr;	/* memory address to dump   */
168*33165Sbostic 	int			sector;		/* sector to write to       */
169*33165Sbostic 	int			par;		/* disk partition number    */
170*33165Sbostic 	int			parlen;		/* disk partition # blocks  */
171*33165Sbostic 	int			dump_short;	/* TRUE= dump was truncated */
172*33165Sbostic 	int			chn;		/* temporary data chain no. */
173*33165Sbostic 	int			bc;		/* temporary byte count     */
174*33165Sbostic 
175*33165Sbostic 
176*33165Sbostic 	mem_addr = 0;
177*33165Sbostic 	dump_short = FALSE;
178*33165Sbostic 	par = HDC_PARTITION(dev);
179*33165Sbostic 	hu = &hdc_units[ HDC_UNIT(dev) ];
180*33165Sbostic 	hc = &hdc_ctlrs[hu->ctlr];
181*33165Sbostic 	mcb = &hu->phio_mcb;
182*33165Sbostic 	parlen = hu->partition[par].length;
183*33165Sbostic 	printf("\nhdc: resetting controller #%d.\n", hc->ctlr);
184*33165Sbostic 	HDC_REGISTER(soft_reset_reg) = 0;
185*33165Sbostic 	DELAY(1000000);
186*33165Sbostic 	mtpr(0,PADC);
187*33165Sbostic 
188*33165Sbostic 	/*
189*33165Sbostic 	 * If the drive has not been initialized yet, abort the dump.
190*33165Sbostic 	 * Set dump limits. The dump must fit in the partition.
191*33165Sbostic 	 */
192*33165Sbostic 
193*33165Sbostic 	if (hu->sectors <= 0 || hu->heads <= 0 || hu->cylinders <= 0 ) {
194*33165Sbostic 		printf("\nhdc: dump device is not initialized - no dump!\n");
195*33165Sbostic 		return EIO;
196*33165Sbostic 	}
197*33165Sbostic 	block_count = dumpsize;
198*33165Sbostic 	if ((dumplo + block_count) > parlen) {
199*33165Sbostic 		block_count = parlen - dumplo;
200*33165Sbostic 		dumpsize = block_count;  /* let savecore know */
201*33165Sbostic 		printf("\nhdc: only dumping first %dmb of memory!\n",
202*33165Sbostic 		    block_count/1024);
203*33165Sbostic 		dump_short = TRUE;
204*33165Sbostic 	}
205*33165Sbostic 	current_block = hu->partition[par].start + dumplo;
206*33165Sbostic 
207*33165Sbostic 	/*
208*33165Sbostic 	 * Dump memory to disk. For each disk transfer, fill in the
209*33165Sbostic 	 * mcb with information describing the transfer, then send
210*33165Sbostic 	 * the mcb to the hdc controller.
211*33165Sbostic 	 */
212*33165Sbostic 
213*33165Sbostic 	while (block_count > 0) {
214*33165Sbostic 		blocks = MIN(block_count, HDC_DUMPSIZE);
215*33165Sbostic 		sector = HDC_SPB * current_block;
216*33165Sbostic 		mcb->command   = HCMD_WRITE;
217*33165Sbostic 		mcb->cyl = sector/hu->spc;
218*33165Sbostic 		mcb->head = (sector/hu->sectors) % hu->heads;
219*33165Sbostic 		mcb->sector = sector % hu->sectors;
220*33165Sbostic 	        chn = 0;
221*33165Sbostic 	        bc = blocks * DEV_BSIZE;
222*33165Sbostic 	        while (bc > 0) {
223*33165Sbostic 	        	mcb->chain[chn].ta  = mem_addr;
224*33165Sbostic 	        	mcb->chain[chn].lwc = (bc > HDC_MAXBC) ?
225*33165Sbostic         			(LWC_DATA_CHAIN | (HDC_MAXBC/4)) : bc/4;
226*33165Sbostic 	        	mem_addr += ((bc > HDC_MAXBC) ? HDC_MAXBC : bc);
227*33165Sbostic 	        	chn++;
228*33165Sbostic 	        	bc -= HDC_MAXBC;
229*33165Sbostic 		}
230*33165Sbostic 		if (!hdimcb(hu,mcb))
231*33165Sbostic 			return EIO;
232*33165Sbostic 		block_count -= blocks;
233*33165Sbostic 		current_block += blocks;
234*33165Sbostic 	}
235*33165Sbostic 	return (dump_short ? ENXIO : 0);
236*33165Sbostic }
237*33165Sbostic 
238*33165Sbostic /*************************************************************************
239*33165Sbostic *  Procedure:	hddumpmcb
240*33165Sbostic *
241*33165Sbostic *  Description: Dumps a single mcb to the console - up to the last
242*33165Sbostic *               active data chain lword.
243*33165Sbostic *
244*33165Sbostic *  Returns:
245*33165Sbostic **************************************************************************/
246*33165Sbostic 
247*33165Sbostic hddumpmcb(mcb)
248*33165Sbostic 
249*33165Sbostic register mcb_type *mcb; /* the mcb pointer
250*33165Sbostic 			 */
251*33165Sbostic {
252*33165Sbostic 	unsigned int *ptr,i;
253*33165Sbostic 
254*33165Sbostic 	printf("mcb: ");
255*33165Sbostic 	ptr = (unsigned int *) &mcb->forw_phaddr;
256*33165Sbostic 	for (i=0; i<6; i++)
257*33165Sbostic 		printf(" %x",ptr[i]);
258*33165Sbostic 	for (i=6; i<72; i+=2) {
259*33165Sbostic 		printf("  %x %x", ptr[i], ptr[i+1]);
260*33165Sbostic 		if ( !(ptr[i] & 0x80000000)) break;
261*33165Sbostic 	}
262*33165Sbostic 	printf("\n");
263*33165Sbostic }
264*33165Sbostic 
265*33165Sbostic /*************************************************************************
266*33165Sbostic *  Procedure:	hddumpmmcb
267*33165Sbostic *
268*33165Sbostic *  Description: dumps the master mcb on the console up to the
269*33165Sbostic *               last non-zero byte of the extended status.
270*33165Sbostic *
271*33165Sbostic *  Returns:
272*33165Sbostic **************************************************************************/
273*33165Sbostic 
274*33165Sbostic hddumpmmcb(master)
275*33165Sbostic 
276*33165Sbostic register master_mcb_type *master; /* the master mcb pointer
277*33165Sbostic 				   */
278*33165Sbostic {
279*33165Sbostic 	unsigned int *ptr,i,end;
280*33165Sbostic 
281*33165Sbostic 	printf("mmcb:  ");
282*33165Sbostic 	ptr = (unsigned int *) master;
283*33165Sbostic 	for (i=0;i<8;i++)
284*33165Sbostic 		printf("%x ",ptr[i]);
285*33165Sbostic 	for (i=7+HDC_XSTAT_SIZE; i>7; i--) {
286*33165Sbostic 		end = i;
287*33165Sbostic 		if (ptr[i] != 0) break;
288*33165Sbostic 	}
289*33165Sbostic 	for (i=8;i<=end;i++)
290*33165Sbostic 		printf(" %x",ptr[i]);
291*33165Sbostic 	printf("\n");
292*33165Sbostic };
293*33165Sbostic 
294*33165Sbostic /*************************************************************************
295*33165Sbostic *  Procedure:	hdimcb
296*33165Sbostic *
297*33165Sbostic *  Description: "hdc immediate mcb" sends an mcb to the hdc and returns
298*33165Sbostic *               when the hdc has completed the operation (polled io).
299*33165Sbostic *               "hdimcb" is called during system configuration or
300*33165Sbostic *               when the system is being dumped after a fatal error.
301*33165Sbostic *
302*33165Sbostic *  Entry:       o  There is no active process.
303*33165Sbostic *
304*33165Sbostic *               o  "hdimcb" cannot be called from interrupt level.
305*33165Sbostic *
306*33165Sbostic *               o  There can be no queued operations pending; i.e.
307*33165Sbostic *                  this routine assumes exclusive use of the hdc.
308*33165Sbostic *                  Note: a soft reset will terminate queued operations.
309*33165Sbostic *
310*33165Sbostic *  Returns:     Returns FALSE if a controller error occurred.
311*33165Sbostic **************************************************************************/
312*33165Sbostic 
313*33165Sbostic int
314*33165Sbostic hdimcb(hu,mcb)
315*33165Sbostic 
316*33165Sbostic register hdc_unit_type	*hu;		/* unit information
317*33165Sbostic 					 */
318*33165Sbostic register mcb_type	*mcb;		/* mcb to send to the hdc
319*33165Sbostic 					 */
320*33165Sbostic {
321*33165Sbostic 	register hdc_ctlr_type	 *hc;		/* controller information   */
322*33165Sbostic 	register master_mcb_type *master;	/* the hdc's master mcb     */
323*33165Sbostic 	register int		 timeout;	/* used to timeout the mcb  */
324*33165Sbostic 	register int		 ctlr;		/* controller number        */
325*33165Sbostic 	int	 i,ok;
326*33165Sbostic 	unsigned int *ptr;
327*33165Sbostic 
328*33165Sbostic 
329*33165Sbostic 	ok = TRUE;
330*33165Sbostic 	ctlr = hu->ctlr;
331*33165Sbostic 	hc = &hdc_ctlrs[ctlr];
332*33165Sbostic 	master = &hc->master_mcb;
333*33165Sbostic 
334*33165Sbostic 	/*
335*33165Sbostic 	 * Complete the setup of the mcb and master mcb.
336*33165Sbostic 	 */
337*33165Sbostic 
338*33165Sbostic 	mcb->priority   = 0;
339*33165Sbostic 	mcb->interrupt  = FALSE;
340*33165Sbostic 	mcb->drive      = hu->slave;
341*33165Sbostic 	mcb->forw_phaddr= 0;
342*33165Sbostic 	mcb->context	= 0;
343*33165Sbostic 	mcb->reserved[0]= 0;
344*33165Sbostic 	mcb->reserved[1]= 0;
345*33165Sbostic 	master->forw_phaddr = (long) vtoph(0,&mcb->forw_phaddr);
346*33165Sbostic 	master->mcs = 0;
347*33165Sbostic 	master->reserve1 = 0;
348*33165Sbostic 	master->reserve2 = 0;
349*33165Sbostic 	master->context = 0;
350*33165Sbostic 	master->cmcb_phaddr = 0;
351*33165Sbostic 	master->mcl = MCL_IMMEDIATE;
352*33165Sbostic 	bzero( (caddr_t)&master->xstatus[0], HDC_XSTAT_SIZE );
353*33165Sbostic 
354*33165Sbostic 	/*
355*33165Sbostic 	 * Tell hdc to xqt the mcb; wait for completion.
356*33165Sbostic 	 * If a controller error or timeout occurs, print
357*33165Sbostic 	 * out the mcb and master mcb on the console.
358*33165Sbostic 	 */
359*33165Sbostic 
360*33165Sbostic 	HDC_REGISTER(master_mcb_reg) = hc->master_phaddr;
361*33165Sbostic 	timeout = 15000;
362*33165Sbostic 	while (TRUE) {
363*33165Sbostic 		DELAY(1000);
364*33165Sbostic 		mtpr(0,PADC);
365*33165Sbostic 		if ( (master->mcs & MCS_DONE) &&
366*33165Sbostic 		    !(master->mcs & MCS_FATALERROR ) ) break;
367*33165Sbostic 		timeout--;
368*33165Sbostic 		if ( timeout > 0   &&
369*33165Sbostic 			!(master->mcs & MCS_FATALERROR) ) continue;
370*33165Sbostic 		if ( master->mcs & MCS_FATALERROR )
371*33165Sbostic 			printf("hdc: controller %d fatal error\n",ctlr);
372*33165Sbostic 		else
373*33165Sbostic 			printf("hdc: controller %d timed out\n",ctlr);
374*33165Sbostic 	        hddumpmcb(mcb);
375*33165Sbostic 	        hddumpmmcb(master);
376*33165Sbostic 		ok = FALSE;
377*33165Sbostic 		break;
378*33165Sbostic 	}
379*33165Sbostic 	master->mcl = MCL_QUEUED;
380*33165Sbostic 	return(ok);
381*33165Sbostic }
382*33165Sbostic 
383*33165Sbostic /*************************************************************************
384*33165Sbostic *  Procedure:	hdintr
385*33165Sbostic *
386*33165Sbostic *  Description: The hdc interrupt routine.
387*33165Sbostic *
388*33165Sbostic *  Returns:
389*33165Sbostic **************************************************************************/
390*33165Sbostic 
391*33165Sbostic hdintr(ctlr)
392*33165Sbostic 
393*33165Sbostic int	ctlr;		/* the hdc controller number.
394*33165Sbostic 			 */
395*33165Sbostic {
396*33165Sbostic 	register master_mcb_type *master;	/* master mcb for this hdc  */
397*33165Sbostic 	register mcb_type	 *mcb;		/* the mcb just completed   */
398*33165Sbostic 	register struct buf	 *bp;		/* buf for the completed mcb*/
399*33165Sbostic 	register hdc_ctlr_type   *hc;		/* info for this controller */
400*33165Sbostic 	register struct iobuf    *iobp;		/* iobuf for this unit      */
401*33165Sbostic 	register int		 unit;		/* unit# of the hdc drive   */
402*33165Sbostic 	register int		 i;		/* temporary                */
403*33165Sbostic 
404*33165Sbostic 
405*33165Sbostic 	hc = &hdc_ctlrs[ctlr];
406*33165Sbostic 	master = &hc->master_mcb;
407*33165Sbostic 	uncache( &master->mcs );
408*33165Sbostic 	uncache( &master->context );
409*33165Sbostic #ifdef HDCLOG
410*33165Sbostic 	hdlog(master,1 + 16*hc->ctlr);
411*33165Sbostic #endif
412*33165Sbostic 	if ( !(master->mcs & MCS_DONE) ) {
413*33165Sbostic 	        printf("\nhdc: spurious interrupt from controller #%d\n",ctlr);
414*33165Sbostic 	        return;
415*33165Sbostic 	}
416*33165Sbostic 	mcb = (mcb_type *) master->context;
417*33165Sbostic 	bp = mcb->buf_ptr;
418*33165Sbostic 	unit = HDC_UNIT(bp->b_dev);
419*33165Sbostic 	iobp = &vdtab[unit];
420*33165Sbostic 
421*33165Sbostic 	/*
422*33165Sbostic 	 * Error log and system activity.
423*33165Sbostic 	 *
424*33165Sbostic 	 * Turn off the activity bit for this device.
425*33165Sbostic 	 * Record the time required to process the buf.
426*33165Sbostic 	 * If there is no more activity on this unit, record the
427*33165Sbostic 	 * amount of time that the unit was active.
428*33165Sbostic 	 * Update dkprf and lastcyl for "sadp".
429*33165Sbostic 	 */
430*33165Sbostic 
431*33165Sbostic 	blkacty &= ~(1 << major(bp->b_dev));
432*33165Sbostic 	if (iobp->b_active) {
433*33165Sbostic 		vdstat[unit].io_resp += (time.tv_sec - bp->b_start);
434*33165Sbostic 		if (--iobp->b_active == 0)
435*33165Sbostic 			vdstat[unit].io_act += (time.tv_sec - iobp->io_start);
436*33165Sbostic 	}
437*33165Sbostic 	i = mcb->cyl;
438*33165Sbostic 	dkprf[unit][i >> 3]++;
439*33165Sbostic 	i -= lastcyl[unit];
440*33165Sbostic 	if (i < 0) i = -i;
441*33165Sbostic 	skprf[unit][i >> 3]++;
442*33165Sbostic 	lastcyl[unit] = mcb->cyl;
443*33165Sbostic 	dk_busy &= ~(1 << unit);
444*33165Sbostic 	dk_seek[unit]++;
445*33165Sbostic 	dk_xfer[unit]++;
446*33165Sbostic 
447*33165Sbostic 	/*
448*33165Sbostic 	 * If there are no free mcb's, wake up anyone that might
449*33165Sbostic 	 * be waiting for one.  Remove the completed mcb from the
450*33165Sbostic 	 * queue of active mcb's and add it to the free-mcb queue.
451*33165Sbostic 	 */
452*33165Sbostic 
453*33165Sbostic 	if (hc->forw_free == (mcb_type *)&hc->forw_free)
454*33165Sbostic 		wakeup(hc);
455*33165Sbostic 	remque(mcb);
456*33165Sbostic 	insque(mcb,&hc->forw_free);
457*33165Sbostic 
458*33165Sbostic 	/*
459*33165Sbostic 	 * If there was a fatal error, dump the mcb and master mcb on the
460*33165Sbostic 	 * console, then halt if the system was booted with the debug option.
461*33165Sbostic 	 *
462*33165Sbostic 	 * Record fatal and soft errors in the error log.
463*33165Sbostic 	 */
464*33165Sbostic 
465*33165Sbostic 	bp->b_resid = 0;
466*33165Sbostic 	if (master->mcs & (MCS_SOFTERROR | MCS_FATALERROR) ) {
467*33165Sbostic 		mtpr( (caddr_t) master, P1DC );
468*33165Sbostic 		mtpr( (caddr_t) &master->xstatus[HDC_XSTAT_SIZE]-1, P1DC );
469*33165Sbostic 		if (master->mcs & MCS_FATALERROR) {
470*33165Sbostic 			bp->b_flags |= B_ERROR;
471*33165Sbostic 			bp->b_error = EIO;
472*33165Sbostic 			harderr(bp,"hdc");
473*33165Sbostic 			printf("\nhdc:  fatal error on controller #%d\n",ctlr);
474*33165Sbostic 			hddumpmmcb(master);
475*33165Sbostic 			hddumpmcb(mcb);
476*33165Sbostic 			if (boothowto & RB_DEBUG) asm("halt");
477*33165Sbostic 		};
478*33165Sbostic 		vdstat[unit].ios.io_misc++ ;
479*33165Sbostic 		iobp->io_erec = 0;
480*33165Sbostic 		iobp->io_addr = (caddr_t) hc->registers;
481*33165Sbostic 		iobp->io_stp  = &vdstat[unit].ios;
482*33165Sbostic 		iobp->io_nreg = HDC_XSTAT_SIZE;
483*33165Sbostic 		for (i=HDC_XSTAT_SIZE-1; i>0; i--) {
484*33165Sbostic 			if (master->xstatus[i] != 0) break;
485*33165Sbostic 			iobp->io_nreg--;
486*33165Sbostic 		}
487*33165Sbostic 		iobp->b_actf  = bp;
488*33165Sbostic 		iobp->b_dev   = bp->b_dev;
489*33165Sbostic 		fmtberr( iobp, mcb->cyl, &master->xstatus[0] );
490*33165Sbostic 		logberr(iobp, master->mcs & MCS_FATALERROR);
491*33165Sbostic 		bzero( (caddr_t)&master->xstatus[0], HDC_XSTAT_SIZE );
492*33165Sbostic 	}
493*33165Sbostic 
494*33165Sbostic 	/*
495*33165Sbostic 	 * If there are any waiting mcb's, move them to the active queue.
496*33165Sbostic 	 * Physically link the new mcb's from the master mcb.
497*33165Sbostic 	 */
498*33165Sbostic 
499*33165Sbostic 	master->forw_phaddr = 0;
500*33165Sbostic next:   mcb = hc->forw_wait;
501*33165Sbostic 	remque(mcb);
502*33165Sbostic 	asm(" bvs done");
503*33165Sbostic 	insque(mcb,&hc->forw_active);
504*33165Sbostic 	mcb->forw_phaddr = master->forw_phaddr;
505*33165Sbostic #ifdef HDCLOG
506*33165Sbostic 	hdlog(mcb,2 + 16*hc->ctlr);
507*33165Sbostic #endif
508*33165Sbostic 	master->forw_phaddr = mcb->mcb_phaddr;
509*33165Sbostic 	goto next;
510*33165Sbostic done:   asm("done:");
511*33165Sbostic 
512*33165Sbostic 	/*
513*33165Sbostic 	 * If there are any mcb's active, initialize the master mcb
514*33165Sbostic 	 * and tell the hdc to continue queued operation.
515*33165Sbostic 	 * New mcb's (if any) are linked off of "forw_phaddr".
516*33165Sbostic 	 */
517*33165Sbostic 
518*33165Sbostic 	if (hc->forw_active != (mcb_type *) &hc->forw_active) {
519*33165Sbostic 		master->mcs = 0;
520*33165Sbostic #ifdef HDCLOG
521*33165Sbostic 		hdlog(master,3 + 16*hc->ctlr);
522*33165Sbostic #endif
523*33165Sbostic 		HDC_REGISTER(master_mcb_reg)= hc->master_phaddr;
524*33165Sbostic 	}
525*33165Sbostic 
526*33165Sbostic 	/*
527*33165Sbostic 	 * Return the buf for the completed operation.
528*33165Sbostic 	 */
529*33165Sbostic 
530*33165Sbostic 	iodone(bp);
531*33165Sbostic 	return;
532*33165Sbostic }
533*33165Sbostic 
534*33165Sbostic /*************************************************************************
535*33165Sbostic *  Procedure:	hdioctl
536*33165Sbostic *
537*33165Sbostic *  Description: Character device ioctl routine.
538*33165Sbostic *
539*33165Sbostic *  Returns:     EACCES    formatting is active on the drive
540*33165Sbostic *                         (or) function is valid only for the format program
541*33165Sbostic *                         (or) formatting ioctl's must be done on partition 7
542*33165Sbostic *               EIO       controller error occurred
543*33165Sbostic *               ENXIO     invalid parameter value
544*33165Sbostic *               0         normal
545*33165Sbostic **************************************************************************/
546*33165Sbostic 
547*33165Sbostic int
548*33165Sbostic hdioctl(dev, command, arg, flag)
549*33165Sbostic 
550*33165Sbostic dev_t		dev ; 		/* Device type. Major/minor dev#.
551*33165Sbostic 				 */
552*33165Sbostic int		command ;	/* The ioctl commmand.
553*33165Sbostic 				 */
554*33165Sbostic int		*arg ; 		/* Data. Format depends on ioctl.
555*33165Sbostic 				 */
556*33165Sbostic int		flag ;		/* Not used.
557*33165Sbostic 				 */
558*33165Sbostic {
559*33165Sbostic 	register hdc_unit_type	*hu;		/* unit information        */
560*33165Sbostic 	int			formatok;	/* TRUE= it's ok to format */
561*33165Sbostic 	register int		i;
562*33165Sbostic 
563*33165Sbostic 	hu = &hdc_units[ HDC_UNIT(dev) ];
564*33165Sbostic 	formatok = ( HDC_PARTITION(dev)==7  &&  hu->format );
565*33165Sbostic 	switch (command) {
566*33165Sbostic 
567*33165Sbostic 	case DSKIOCFORMAT: {
568*33165Sbostic 
569*33165Sbostic 		/*
570*33165Sbostic 		 * Format a disk track. The received argument is a pointer
571*33165Sbostic 		 * to a "formatop" structure describing the track to format.
572*33165Sbostic 		 *
573*33165Sbostic 		 * Set up a buffer with each longword corresponding to a
574*33165Sbostic 		 * sector on the track; a 1 means no flaw, a 0 means a flaw.
575*33165Sbostic 		 * Call hdphysio to send the data from the phio_data buffer
576*33165Sbostic 		 * to the hdc to format the track.
577*33165Sbostic 		 */
578*33165Sbostic 
579*33165Sbostic 		register struct formatop *track;
580*33165Sbostic 
581*33165Sbostic 		if (!formatok) return EACCES;
582*33165Sbostic 		track = (struct formatop *) arg;
583*33165Sbostic 		for (i=0; i<hu->phys_sectors; i++)
584*33165Sbostic 			hu->phio_data[i] = 1;
585*33165Sbostic 		for (i=0; i<track->flaw_count; i++)
586*33165Sbostic 			hu->phio_data[track->flaw[i]] = 0;
587*33165Sbostic 		if (!hdphysio(
588*33165Sbostic 			dev,
589*33165Sbostic 			HCMD_FORMAT,
590*33165Sbostic 			track->cylinder,
591*33165Sbostic 			track->head,
592*33165Sbostic 			0,
593*33165Sbostic 			hu->phio_data,
594*33165Sbostic 			hu->phys_sectors * 4) )
595*33165Sbostic 			   return EIO;
596*33165Sbostic 		break;
597*33165Sbostic 	}
598*33165Sbostic 
599*33165Sbostic 	case DSKIOCCERTIFY: {
600*33165Sbostic 
601*33165Sbostic 		/*
602*33165Sbostic 		 * Certify a disk track. The received argument is a pointer
603*33165Sbostic 		 * to a "formatop" structure describing the track to certify.
604*33165Sbostic 		 *
605*33165Sbostic 		 * Call hdphysio to read data into the phio_data buffer.
606*33165Sbostic 		 * The controller returns data in which each longword
607*33165Sbostic 		 * corresponds to a sector on the track; a 1 means no flaw,
608*33165Sbostic 		 * a 0 means a flaw.
609*33165Sbostic 		 */
610*33165Sbostic 
611*33165Sbostic 		register struct formatop *track;
612*33165Sbostic 
613*33165Sbostic 		if (!formatok) return EACCES;
614*33165Sbostic 		track = (struct formatop *) arg;
615*33165Sbostic 		if (!hdphysio(
616*33165Sbostic 			dev,
617*33165Sbostic 			HCMD_CERTIFY,
618*33165Sbostic 			track->cylinder,
619*33165Sbostic 			track->head,
620*33165Sbostic 			0,
621*33165Sbostic 			hu->phio_data,
622*33165Sbostic 			hu->phys_sectors * 4) )
623*33165Sbostic 			   return EIO;
624*33165Sbostic 		track->flaw_count = 0;
625*33165Sbostic 		for (i=0; i<hu->phys_sectors; i++) {
626*33165Sbostic 			if (track->flaw_count >= MAXVFLAW) break;
627*33165Sbostic 			if (hu->phio_data[i]==0) {
628*33165Sbostic 				track->flaw[track->flaw_count] = i;
629*33165Sbostic 				track->flaw_count++;
630*33165Sbostic 			}
631*33165Sbostic 		}
632*33165Sbostic 		break;
633*33165Sbostic 	}
634*33165Sbostic 
635*33165Sbostic 	case DSKIOCVERIFY: {
636*33165Sbostic 
637*33165Sbostic 		/*
638*33165Sbostic 		 * Verify a disk track. The received argument is a pointer
639*33165Sbostic 		 * to a "formatop" structure describing the track to verify.
640*33165Sbostic 		 */
641*33165Sbostic 
642*33165Sbostic 		register struct formatop *track;
643*33165Sbostic 
644*33165Sbostic 		if (!formatok) return EACCES;
645*33165Sbostic 		track = (struct formatop *) arg;
646*33165Sbostic 		if (!hdphysio(
647*33165Sbostic 			dev,
648*33165Sbostic 			HCMD_VERIFY,
649*33165Sbostic 			track->cylinder,
650*33165Sbostic 			track->head,
651*33165Sbostic 			0,
652*33165Sbostic 			0,
653*33165Sbostic 			0) )
654*33165Sbostic 				return EIO;
655*33165Sbostic 		break;
656*33165Sbostic 	}
657*33165Sbostic 
658*33165Sbostic 	case DSKIOCFORMATCTL: {
659*33165Sbostic 
660*33165Sbostic 		/*
661*33165Sbostic 		 * This ioctl provides special format control.
662*33165Sbostic 		 *
663*33165Sbostic 		 * Currently the valid arguments are:
664*33165Sbostic 		 * arg= 0  disable formatting;
665*33165Sbostic 		 * arg= 1  enable formatting (allow privileged access);
666*33165Sbostic 		 *
667*33165Sbostic 		 * Partition must be the disk definition tracks of
668*33165Sbostic 		 * the raw device.
669*33165Sbostic 		 */
670*33165Sbostic 
671*33165Sbostic 	        if (HDC_PARTITION(dev) != HDC_DEFPART )
672*33165Sbostic 	                return EACCES;
673*33165Sbostic 		switch (*arg) {
674*33165Sbostic 
675*33165Sbostic 	        case 0: hu->format = FALSE;
676*33165Sbostic 	                break;
677*33165Sbostic 
678*33165Sbostic 	        case 1: if (hu->format)
679*33165Sbostic 				return EACCES;
680*33165Sbostic 	        	hu->format = TRUE;
681*33165Sbostic 	                break;
682*33165Sbostic 
683*33165Sbostic 	        default: return ENXIO;
684*33165Sbostic 		}
685*33165Sbostic 		break;
686*33165Sbostic 	}
687*33165Sbostic 
688*33165Sbostic 	case DSKIOCGEOMETRY: {
689*33165Sbostic 
690*33165Sbostic 		/*
691*33165Sbostic 		 * Return info about disk geometry (partitions).
692*33165Sbostic 		 * Caller's parameter is a pointer to a geometry
693*33165Sbostic 		 * status structure.
694*33165Sbostic 		 */
695*33165Sbostic 
696*33165Sbostic 		register geometry_status *geo_status;
697*33165Sbostic 
698*33165Sbostic 		geo_status = (geometry_status *) arg;
699*33165Sbostic 		for (i=0; i<GB_MAXPART; i++) {
700*33165Sbostic 			geo_status->partition[i].start = hu->partition[i].start;
701*33165Sbostic 			geo_status->partition[i].length=hu->partition[i].length;
702*33165Sbostic 		}
703*33165Sbostic 		break;
704*33165Sbostic 	}
705*33165Sbostic 
706*33165Sbostic 	case DSKIOCSETGEOMETRY: {
707*33165Sbostic 
708*33165Sbostic 		/*
709*33165Sbostic 		 * Set new geometry - new partition sizes.
710*33165Sbostic 		 * Caller must have formatting privilege.
711*33165Sbostic 		 * Caller's parameter is a pointer to a geometry
712*33165Sbostic 		 * status structure containing the new geometries.
713*33165Sbostic 		 * The disk definition partition cannot be changed.
714*33165Sbostic 		 */
715*33165Sbostic 
716*33165Sbostic 		register geometry_status *geo_status;
717*33165Sbostic 
718*33165Sbostic 		if (!formatok) return EACCES;
719*33165Sbostic 		geo_status = (geometry_status *) arg;
720*33165Sbostic 		for (i=0; i<GB_MAXPART; i++) {
721*33165Sbostic 			if (i==HDC_DEFPART) continue;
722*33165Sbostic 			hu->partition[i].start = geo_status->partition[i].start;
723*33165Sbostic 			hu->partition[i].length=geo_status->partition[i].length;
724*33165Sbostic 		}
725*33165Sbostic 		break;
726*33165Sbostic 	}
727*33165Sbostic 
728*33165Sbostic 	case DSKIOCSTATUS: {
729*33165Sbostic 
730*33165Sbostic 		/*
731*33165Sbostic 		 * Return info about the disk. Caller's parameter is a
732*33165Sbostic 		 * pointer to a dsk_status structure.
733*33165Sbostic 		 */
734*33165Sbostic 
735*33165Sbostic 		register dsk_status *status;
736*33165Sbostic 
737*33165Sbostic 		status = (dsk_status *) arg;
738*33165Sbostic 		status->id =		hu->id;
739*33165Sbostic 		status->rpm =		hu->rpm;
740*33165Sbostic 		status->bytes_per_sec=	hu->bytes_per_sec;
741*33165Sbostic 		status->cylinders =	hu->cylinders;
742*33165Sbostic 		status->heads =		hu->heads;
743*33165Sbostic 		status->sectors =	hu->sectors;
744*33165Sbostic 		status->phys_cylinders=	hu->phys_cylinders;
745*33165Sbostic 		status->phys_heads =	hu->phys_heads;
746*33165Sbostic 		status->phys_sectors =	hu->phys_sectors;
747*33165Sbostic 		status->diag_cyl =	hu->diag_cyl;
748*33165Sbostic 		status->diag_cylinders=	hu->diag_cyl_count;
749*33165Sbostic 		status->def_cyl =	hu->def_cyl;
750*33165Sbostic 		status->def_cylinders =	hu->def_cyl_count;
751*33165Sbostic 		break;
752*33165Sbostic 	}
753*33165Sbostic 
754*33165Sbostic 	case DSKIOCVENDORFLAW: {
755*33165Sbostic 
756*33165Sbostic 		/*
757*33165Sbostic 		 * Return vendor flaw info.
758*33165Sbostic 		 *
759*33165Sbostic 		 * Read in the vendor data from relative sector 0 of
760*33165Sbostic 		 * the track to the phio_data buffer; then copy the
761*33165Sbostic 		 * vendor flaw data to the caller's buffer.
762*33165Sbostic 		 */
763*33165Sbostic 
764*33165Sbostic 		register vflaw_type *vflaw;
765*33165Sbostic 		register struct flaw *vendor;
766*33165Sbostic 
767*33165Sbostic 		if (!formatok) return EACCES;
768*33165Sbostic 		vflaw = (vflaw_type *) arg;
769*33165Sbostic 		if (!hdphysio(
770*33165Sbostic 			dev,
771*33165Sbostic 			HCMD_VENDOR,
772*33165Sbostic 			vflaw->cylinder,
773*33165Sbostic 			vflaw->head,
774*33165Sbostic 			0,
775*33165Sbostic 			hu->phio_buf,
776*33165Sbostic 			HDC_VDATA_SIZE << 2 ))
777*33165Sbostic  				return EIO;
778*33165Sbostic 		vendor = (struct flaw *) &hu->phio_data[0];
779*33165Sbostic 		for (i=0; i<MAXVFLAW; i++) {
780*33165Sbostic 			vflaw->flaw[i].offset = vendor[i].offset;
781*33165Sbostic 			vflaw->flaw[i].length = vendor[i].length;
782*33165Sbostic 		}
783*33165Sbostic 		break;
784*33165Sbostic 	}
785*33165Sbostic 
786*33165Sbostic 	default: return ENXIO;
787*33165Sbostic 
788*33165Sbostic 	}
789*33165Sbostic 	return 0;
790*33165Sbostic }
791*33165Sbostic 
792*33165Sbostic /*************************************************************************
793*33165Sbostic *  Procedure:	hdopen
794*33165Sbostic *
795*33165Sbostic *  Description: The character device and block device open routine.
796*33165Sbostic *
797*33165Sbostic *  Returns:     ENXIO     the partition or device isn't defined
798*33165Sbostic *               EACCES    Formatting is active on this drive
799*33165Sbostic *               0         normal
800*33165Sbostic **************************************************************************/
801*33165Sbostic 
802*33165Sbostic int
803*33165Sbostic hdopen(dev, flag)
804*33165Sbostic 
805*33165Sbostic dev_t		dev ; 		/* Device type. Major/minor dev#.
806*33165Sbostic 				 */
807*33165Sbostic int		flag ;		/* Not used.
808*33165Sbostic 				 */
809*33165Sbostic {
810*33165Sbostic 	register int			unit;		/* hdc unit#  (0-31)*/
811*33165Sbostic 	register int			par;		/* partition# (0-7) */
812*33165Sbostic 	register struct vba_device	*vba_unit;	/* vba unit info    */
813*33165Sbostic 	register hdc_unit_type		*hu;		/* hdc unit info    */
814*33165Sbostic 
815*33165Sbostic 
816*33165Sbostic 	unit = HDC_UNIT(dev);
817*33165Sbostic 	par = HDC_PARTITION(dev);
818*33165Sbostic 	vba_unit = vddinfo[unit];
819*33165Sbostic 	hu = &hdc_units[unit];
820*33165Sbostic 	if ( !vba_unit->ui_alive || hu->partition[par].length == 0)
821*33165Sbostic 	      return ENXIO;
822*33165Sbostic 	if (hu->format)
823*33165Sbostic 	      return EACCES;
824*33165Sbostic 	vdtab[unit].io_stp  = &vdstat[unit].ios;
825*33165Sbostic 	return 0;
826*33165Sbostic }
827*33165Sbostic 
828*33165Sbostic /*************************************************************************
829*33165Sbostic *  Procedure:	hdphysio
830*33165Sbostic *
831*33165Sbostic *  Description: "hdphysio" does the physical i/o initiated by this
832*33165Sbostic *               handler. It does the things which "physio" does for
833*33165Sbostic *               raw read/writes; i.e. it provides an interface to the
834*33165Sbostic *               hdstrategy routine.
835*33165Sbostic *
836*33165Sbostic *               hdphysio assumes that it has exclusive access to the
837*33165Sbostic *               drive; it uses the drive's phio buf.
838*33165Sbostic *
839*33165Sbostic *  Returns:     FALSE     an i/o error occurred.
840*33165Sbostic *               0         normal; data is in phio_data if read was done
841*33165Sbostic **************************************************************************/
842*33165Sbostic 
843*33165Sbostic int
844*33165Sbostic hdphysio(dev,command,cylinder,head,sector,ta,bc)
845*33165Sbostic 
846*33165Sbostic dev_t	dev;			/*  major/minor device number
847*33165Sbostic 				 */
848*33165Sbostic int	command;		/*  the hdc command to execute
849*33165Sbostic 				 */
850*33165Sbostic int	cylinder;		/*  disk cylinder address
851*33165Sbostic 				 */
852*33165Sbostic int	head;			/*  disk head address
853*33165Sbostic 				 */
854*33165Sbostic int	sector;			/*  disk sector address
855*33165Sbostic 				 */
856*33165Sbostic int	ta;			/*  memory transfer address
857*33165Sbostic 				 */
858*33165Sbostic int	bc;			/*  byte count
859*33165Sbostic 				 */
860*33165Sbostic {
861*33165Sbostic 	register struct buf	*bp;	/* buf structure built here */
862*33165Sbostic 	hdc_unit_type		*hu;	/* hdc device unit info     */
863*33165Sbostic 	int			s;	/* processor level save     */
864*33165Sbostic 
865*33165Sbostic 	hu = &hdc_units[ HDC_UNIT(dev) ];
866*33165Sbostic 	bp = (struct buf *) &hu->phio_buf;
867*33165Sbostic 	bp->b_error = 0;
868*33165Sbostic 	bp->b_proc = u.u_procp;
869*33165Sbostic 	bp->b_un.b_addr = (caddr_t) ta;
870*33165Sbostic 	bp->b_flags = B_BUSY | B_PHYS | B_READ | B_LOCALIO;
871*33165Sbostic 	bp->b_dev = dev;
872*33165Sbostic 	bp->b_blkno = 0;
873*33165Sbostic 	bp->b_hdccommand = command;
874*33165Sbostic 	bp->b_cyl = cylinder;
875*33165Sbostic 	bp->b_head = head;
876*33165Sbostic 	bp->b_sector = sector;
877*33165Sbostic 	bp->b_bcount = bc;
878*33165Sbostic 	hdstrategy(bp);
879*33165Sbostic 	s = spl8();
880*33165Sbostic 	while ((bp->b_flags & B_DONE) == 0)
881*33165Sbostic 		slumber((caddr_t)bp, 0, iocomboost);
882*33165Sbostic 	splx(s);
883*33165Sbostic 	bp->b_flags &= ~(B_BUSY | B_PHYS | B_WANTED | B_LOCALIO);
884*33165Sbostic 	if (bp->b_error != 0)
885*33165Sbostic 		return FALSE;
886*33165Sbostic 	return TRUE;
887*33165Sbostic }
888*33165Sbostic 
889*33165Sbostic /*************************************************************************
890*33165Sbostic *  Procedure:	hdprobe
891*33165Sbostic *
892*33165Sbostic *  Description: "hdprobe" verifies that an hdc controller is really
893*33165Sbostic *               there and then initializes the controller. It is called
894*33165Sbostic *		during the configuration phase of a reboot for each
895*33165Sbostic *		hdc controller in the configuration.
896*33165Sbostic *
897*33165Sbostic *  Returns:	TRUE means the controller is ready.
898*33165Sbostic **************************************************************************/
899*33165Sbostic 
900*33165Sbostic int
901*33165Sbostic hdprobe(vba_ctlr)
902*33165Sbostic 
903*33165Sbostic register struct vba_ctlr	*vba_ctlr;	/* vba controller information
904*33165Sbostic 						 */
905*33165Sbostic {
906*33165Sbostic 	register hdc_ctlr_type	*hc;		/* hdc controller info      */
907*33165Sbostic 	register hdc_mid_type	*id;		/* returned module id word  */
908*33165Sbostic 	register int		ctlr;		/* the controller number    */
909*33165Sbostic 	register int		i;		/* temporary                */
910*33165Sbostic 	mcb_type		*mcb;		/* temporary mcb pointer    */
911*33165Sbostic 	extern	int		Xhdintr0, Xhdintr1, Xhdintr2, Xhdintr3,
912*33165Sbostic 				Xhdintr4, Xhdintr5, Xhdintr6, Xhdintr7 ;
913*33165Sbostic 	static  int		hd_proc[] = {
914*33165Sbostic 					(int)& Xhdintr0, (int)& Xhdintr1,
915*33165Sbostic 					(int)& Xhdintr2, (int)& Xhdintr3,
916*33165Sbostic 					(int)& Xhdintr4, (int)& Xhdintr5,
917*33165Sbostic 					(int)& Xhdintr6, (int)& Xhdintr7
918*33165Sbostic 	} ;
919*33165Sbostic 
920*33165Sbostic 
921*33165Sbostic 	ctlr = vba_ctlr->um_ctlr;
922*33165Sbostic 	hc = &hdc_ctlrs[ctlr];
923*33165Sbostic 	/*
924*33165Sbostic 	 * Initialize the hdc controller structure.
925*33165Sbostic 	 * Initially all mcb's are in the free-mcb list.
926*33165Sbostic 	 * The interrupt acknowledge word is the vector offset
927*33165Sbostic 	 * for this controller's interrupts.
928*33165Sbostic 	 */
929*33165Sbostic 
930*33165Sbostic 	hc->ctlr = ctlr;
931*33165Sbostic 	hc->registers = (hdc_regs_type *) vba_ctlr->um_addr;
932*33165Sbostic 	id = &hc->mid;
933*33165Sbostic 	if (badaddr(&hc->registers->module_id_reg,4,vtoph(0,id)))
934*33165Sbostic                 return FALSE;
935*33165Sbostic 	hc->forw_active = (mcb_type *) &hc->forw_active;
936*33165Sbostic 	hc->back_active = (mcb_type *) &hc->forw_active;
937*33165Sbostic 	hc->forw_wait   = (mcb_type *) &hc->forw_wait;
938*33165Sbostic 	hc->back_wait   = (mcb_type *) &hc->forw_wait;
939*33165Sbostic 	hc->forw_free   = (mcb_type *) &hc->forw_free;
940*33165Sbostic 	hc->back_free   = (mcb_type *) &hc->forw_free;
941*33165Sbostic 	for (i=HDC_MAXMCBS-1; i>=0; i--) {
942*33165Sbostic 		mcb = &hc->mcbs[i];
943*33165Sbostic 		mcb->mcb_phaddr = vtoph( 0, &mcb->forw_phaddr);
944*33165Sbostic 		insque( mcb, &hc->forw_free);
945*33165Sbostic 	}
946*33165Sbostic 	vba_ctlr -> um_ivct = get_ivct( 0, 1 ) ;
947*33165Sbostic 	if ( vba_ctlr -> um_ivct == (-1) )
948*33165Sbostic 		return FALSE ;
949*33165Sbostic 	init_ivct( vba_ctlr -> um_ivct, hd_proc[ vba_ctlr -> um_ctlr ] ) ;
950*33165Sbostic 	hc->master_mcb.interrupt = vba_ctlr -> um_ivct ;
951*33165Sbostic 	hc->master_phaddr = (u_long) vtoph( 0, &hc->master_mcb) ;
952*33165Sbostic 
953*33165Sbostic 	/*
954*33165Sbostic 	 * Read in the hdc module id word.
955*33165Sbostic 	 */
956*33165Sbostic 
957*33165Sbostic 	HDC_REGISTER(module_id_reg) = (unsigned long) vtoph(0,id);
958*33165Sbostic 	DELAY(10000);
959*33165Sbostic 	mtpr(0,PADC);
960*33165Sbostic 
961*33165Sbostic 	/*
962*33165Sbostic 	 * hdc's are reset and downloaded by the console processor.
963*33165Sbostic 	 * Check the module id; the controller is bad if:
964*33165Sbostic 	 * 1) it is not an hdc;
965*33165Sbostic 	 * 2) the hdc's writeable control store is not loaded;
966*33165Sbostic 	 * 3) the hdc failed the functional integrity test;
967*33165Sbostic 	 */
968*33165Sbostic 
969*33165Sbostic 	printf("hdc controller %d module id is %x\n", ctlr, *id);
970*33165Sbostic 	if (id->module_id != (unsigned char) HDC_MID) {
971*33165Sbostic 		printf("hdc:  controller #%d bad module id.\n",ctlr);
972*33165Sbostic 		return FALSE;
973*33165Sbostic 	}
974*33165Sbostic 	if (id->code_rev == (unsigned char) 0xFF ) {
975*33165Sbostic 		printf("hdc:  controller #%d micro-code not loaded.\n",ctlr);
976*33165Sbostic 		return FALSE;
977*33165Sbostic 	}
978*33165Sbostic 	if (id->fit != (unsigned char) 0xFF ) {
979*33165Sbostic 		printf("hdc:  controller #%d FIT test failed.\n",ctlr);
980*33165Sbostic 		return FALSE;
981*33165Sbostic 	}
982*33165Sbostic 	/*
983*33165Sbostic 	 * Reset the hdc in case it still has queued mcb's.
984*33165Sbostic 	 */
985*33165Sbostic 
986*33165Sbostic 	HDC_REGISTER(soft_reset_reg) = 0;
987*33165Sbostic 	DELAY(1000000);
988*33165Sbostic 	return TRUE;
989*33165Sbostic }
990*33165Sbostic 
991*33165Sbostic /*************************************************************************
992*33165Sbostic *  Procedure:	hdread
993*33165Sbostic *
994*33165Sbostic *  Description: Character read routine. This procedure is called by the
995*33165Sbostic *               inode read/write routine 'ino_rw'.
996*33165Sbostic *
997*33165Sbostic *  Returns:     Error status returned by 'physio'.
998*33165Sbostic **************************************************************************/
999*33165Sbostic 
1000*33165Sbostic int
1001*33165Sbostic hdread(dev, uio)
1002*33165Sbostic 
1003*33165Sbostic dev_t		dev;	/* Device type. Major/minor dev#.
1004*33165Sbostic 			 */
1005*33165Sbostic int		*uio;	/* Pointer to a uio structure describing
1006*33165Sbostic 			 * a read request: buffer address;
1007*33165Sbostic 			 * sector offset; no. of sectors; etc.
1008*33165Sbostic 			 */
1009*33165Sbostic {
1010*33165Sbostic 	hdc_unit_type	*hu;	/* hdc unit information   */
1011*33165Sbostic 
1012*33165Sbostic 	hu = &hdc_units[ HDC_UNIT(dev) ];
1013*33165Sbostic 
1014*33165Sbostic 	/*
1015*33165Sbostic 	 * 'physio' builds the buf structure, locks the user pages, calls
1016*33165Sbostic 	 * 'hdstrategy' to do the read, waits until i/o is complete (iodone),
1017*33165Sbostic 	 * then deallocates the buf structure and unlocks the pages.
1018*33165Sbostic 	 */
1019*33165Sbostic 
1020*33165Sbostic 	return physio(
1021*33165Sbostic 		hdstrategy,	/* hdc's strategy routine	    */
1022*33165Sbostic 		&hu->raw_buf,	/* physio builds a buf struct here  */
1023*33165Sbostic 		dev,		/* major/minor device number	    */
1024*33165Sbostic 		B_READ,		/* read the buffer 		    */
1025*33165Sbostic 		minphys,	/* routine to set max transfer size */
1026*33165Sbostic 		uio);		/* describes the transfer request   */
1027*33165Sbostic }
1028*33165Sbostic 
1029*33165Sbostic /*************************************************************************
1030*33165Sbostic *  Procedure:	hdsize
1031*33165Sbostic *
1032*33165Sbostic *  Description: Return the partition size for a specified partition.
1033*33165Sbostic *
1034*33165Sbostic *  Returns:     Partition size in blocks.
1035*33165Sbostic *               -1 means the device isn't there
1036*33165Sbostic **************************************************************************/
1037*33165Sbostic 
1038*33165Sbostic int
1039*33165Sbostic hdsize(dev)
1040*33165Sbostic 
1041*33165Sbostic register dev_t	dev ; 		/* Major/minor dev#.
1042*33165Sbostic 				 */
1043*33165Sbostic {
1044*33165Sbostic 	int			unit;		/* hdc unit#  (0-31)  */
1045*33165Sbostic 	int			par;		/* partition# (0-7)   */
1046*33165Sbostic 	struct vba_device	*vba_unit;	/* vba unit info      */
1047*33165Sbostic 	hdc_unit_type		*hu;		/* hdc unit info      */
1048*33165Sbostic 
1049*33165Sbostic 	unit = HDC_UNIT(dev);
1050*33165Sbostic 	par = HDC_PARTITION(dev);
1051*33165Sbostic 	vba_unit = vddinfo[unit];
1052*33165Sbostic 	hu = &hdc_units[unit];
1053*33165Sbostic 	if (vba_unit==0 || !vba_unit->ui_alive) return -1;
1054*33165Sbostic 	return (hu->partition[par].length);
1055*33165Sbostic }
1056*33165Sbostic 
1057*33165Sbostic /*************************************************************************
1058*33165Sbostic *  Procedure:	hdslave
1059*33165Sbostic *
1060*33165Sbostic *  Description: "hdslave" verifies that an hdc drive is really there.
1061*33165Sbostic *               It is called during the configuration phase of a reboot
1062*33165Sbostic *               for each drive on an hdc.
1063*33165Sbostic *
1064*33165Sbostic *               Note: a lot of device initialization is done here, which
1065*33165Sbostic *               should normally be done in hdattach; however, it is
1066*33165Sbostic *               done here since it is info needed to determine whether
1067*33165Sbostic *               the drive is really there and is functional.
1068*33165Sbostic *
1069*33165Sbostic *  Returns:	TRUE means the drive is there.
1070*33165Sbostic **************************************************************************/
1071*33165Sbostic 
1072*33165Sbostic int
1073*33165Sbostic hdslave(vba_unit,regs)
1074*33165Sbostic 
1075*33165Sbostic struct vba_device	*vba_unit;		/* vba drive info
1076*33165Sbostic 						 */
1077*33165Sbostic hdc_regs_type		*regs;			/* hdc io address (not used)
1078*33165Sbostic 						 */
1079*33165Sbostic {
1080*33165Sbostic 	register hdc_ctlr_type	*hc;		/* hdc ctlr info            */
1081*33165Sbostic 	register hdc_unit_type	*hu;		/* hdc unit info            */
1082*33165Sbostic 	register mcb_type	*mcb;		/* mcb to send to the hdc   */
1083*33165Sbostic 	register int		unit;		/* hdc unit# (0-31)         */
1084*33165Sbostic 	register int		ctlr;		/* hdc ctlr# (0-15)         */
1085*33165Sbostic 	register int		i;		/* temp                     */
1086*33165Sbostic 	geometry_block		*geo;		/* ptr to the geometry block*/
1087*33165Sbostic 	drive_stat_type		*drive_status;	/* status returned by hdc   */
1088*33165Sbostic 
1089*33165Sbostic 	ctlr = vba_unit->ui_ctlr;
1090*33165Sbostic 	hc = &hdc_ctlrs[ctlr];
1091*33165Sbostic 	unit = vba_unit->ui_unit;
1092*33165Sbostic 	hu = &hdc_units[unit];
1093*33165Sbostic 	mcb = (mcb_type *) &hu->phio_mcb;
1094*33165Sbostic 
1095*33165Sbostic 	/*
1096*33165Sbostic 	 * Initialize things in the hdc unit structure which are used
1097*33165Sbostic 	 * by this routine. The rest is initialized by hdattach.
1098*33165Sbostic 	 */
1099*33165Sbostic 
1100*33165Sbostic 	hu->ctlr = ctlr;
1101*33165Sbostic 	hu->unit = unit;
1102*33165Sbostic 	hu->slave = vba_unit->ui_slave;
1103*33165Sbostic 
1104*33165Sbostic 	/*
1105*33165Sbostic 	 * Read the drive status and keep a permanent copy of the
1106*33165Sbostic 	 * info in the hdc unit structure.
1107*33165Sbostic 	 */
1108*33165Sbostic 
1109*33165Sbostic 	drive_status = (drive_stat_type *) hu->phio_data;
1110*33165Sbostic 	mcb->command = HCMD_STATUS;
1111*33165Sbostic 	mcb->chain[0].lwc = sizeof(drive_stat_type) / 4;
1112*33165Sbostic 	mcb->chain[0].ta  = (u_long) vtoph(0,drive_status);
1113*33165Sbostic 	if (!hdimcb(hu,mcb))
1114*33165Sbostic 		return FALSE;
1115*33165Sbostic 	hu->id =		drive_status->id;
1116*33165Sbostic 	hu->cylinders =		drive_status->max_cyl+1;
1117*33165Sbostic 	hu->heads =		drive_status->max_head+1;
1118*33165Sbostic 	hu->sectors =		drive_status->max_sector+1;
1119*33165Sbostic 	hu->phys_cylinders =	drive_status->max_phys_cyl+1;
1120*33165Sbostic 	hu->phys_heads =	drive_status->max_phys_head+1;
1121*33165Sbostic 	hu->phys_sectors =	drive_status->max_phys_sector+1;
1122*33165Sbostic 	hu->def_cyl =		drive_status->def_cyl;
1123*33165Sbostic 	hu->def_cyl_count =	drive_status->def_cyl_count;
1124*33165Sbostic 	hu->diag_cyl =		drive_status->diag_cyl;
1125*33165Sbostic 	hu->diag_cyl_count =	drive_status->diag_cyl_count;
1126*33165Sbostic 	hu->bytes_per_sec =	drive_status->bytes_per_sec;
1127*33165Sbostic 	hu->rpm =		drive_status->rpm;
1128*33165Sbostic 	hu->partition[HDC_DEFPART].start  =
1129*33165Sbostic 		hu->def_cyl * hu->sectors * hu->heads / HDC_SPB;
1130*33165Sbostic 	hu->partition[HDC_DEFPART].length =
1131*33165Sbostic 		hu->def_cyl_count * hu->sectors * hu->heads / HDC_SPB;
1132*33165Sbostic 
1133*33165Sbostic 	/*
1134*33165Sbostic 	 * Report the drive down if anything in the drive status
1135*33165Sbostic 	 * looks bad.  If the drive is offline and it is not on
1136*33165Sbostic 	 * cylinder, then the drive is not there.
1137*33165Sbostic 	 * If there is a fault condition, the hdc will try to clear
1138*33165Sbostic 	 * it when we read the geometry block.
1139*33165Sbostic 	 */
1140*33165Sbostic 
1141*33165Sbostic 	if (drive_status->drs & DRS_FAULT)
1142*33165Sbostic 		printf("hdc: clearing fault on unit #%d.\n",unit);
1143*33165Sbostic 	if ( !(drive_status->drs  &  DRS_ONLINE)) {
1144*33165Sbostic 		if ( drive_status->drs  &  DRS_ON_CYLINDER )
1145*33165Sbostic 			printf("hdc: unit #%d is not online.\n",unit);
1146*33165Sbostic 	        return FALSE;
1147*33165Sbostic 	}
1148*33165Sbostic 
1149*33165Sbostic 	/*
1150*33165Sbostic 	 * Read the geometry block from the start of the drive
1151*33165Sbostic 	 * definition cylinder, validate it (must have the correct
1152*33165Sbostic 	 * header and checksum), and set partition starts and sizes
1153*33165Sbostic 	 * (definition partition has already been set above).
1154*33165Sbostic 	 */
1155*33165Sbostic 
1156*33165Sbostic  	geo = (geometry_block *) hu->phio_data;
1157*33165Sbostic 	mcb->command      = HCMD_READ;
1158*33165Sbostic 	mcb->cyl          = hu->def_cyl;
1159*33165Sbostic 	mcb->head         = 0;
1160*33165Sbostic 	mcb->sector       = 0;
1161*33165Sbostic 	mcb->chain[0].lwc = sizeof(geometry_sector) / 4;
1162*33165Sbostic 	mcb->chain[0].ta  = (unsigned long) vtoph(0,geo);
1163*33165Sbostic 	if (!hdimcb(hu,mcb))
1164*33165Sbostic 		goto badgeo;
1165*33165Sbostic  	if ( geo->version > 64000  ||  geo->version < 0 ) {
1166*33165Sbostic  		printf("hdc: bad geometry block version# on unit #%d\n",unit);
1167*33165Sbostic 		goto badgeo;
1168*33165Sbostic 	}
1169*33165Sbostic 	if (strcmp(&geo->id[0],GB_ID) != 0) {
1170*33165Sbostic 		printf("hdc: bad geometry block header on unit #%d\n",unit);
1171*33165Sbostic 		goto badgeo;
1172*33165Sbostic 	}
1173*33165Sbostic  	GB_CHECKSUM( geo, i );
1174*33165Sbostic  	if ( ((geometry_sector *)geo)->checksum != i) {
1175*33165Sbostic  		printf("hdc: bad geometry block checksum on unit #%d\n",unit);
1176*33165Sbostic  		goto badgeo;
1177*33165Sbostic 	}
1178*33165Sbostic 	for (i=0; i<GB_MAXPART; i++) {
1179*33165Sbostic 		if (i==HDC_DEFPART) continue;
1180*33165Sbostic 		hu->partition[i].start  = geo->partition[i].start;
1181*33165Sbostic 		hu->partition[i].length = geo->partition[i].length;
1182*33165Sbostic 	}
1183*33165Sbostic 	return TRUE;
1184*33165Sbostic 
1185*33165Sbostic 	/*
1186*33165Sbostic 	 * If the geometry block is bad, return ok status so that
1187*33165Sbostic 	 * the disk can be formatted etc, but zero the partitions
1188*33165Sbostic 	 * so that no one except "format" can read/write the disk.
1189*33165Sbostic 	 */
1190*33165Sbostic 
1191*33165Sbostic badgeo: for (i=0; i<GB_MAXPART; i++) {
1192*33165Sbostic 		if (i==HDC_DEFPART) continue;
1193*33165Sbostic 		hu->partition[i].start  = 0;
1194*33165Sbostic 		hu->partition[i].length = 0;
1195*33165Sbostic 	}
1196*33165Sbostic 	return TRUE;
1197*33165Sbostic }
1198*33165Sbostic 
1199*33165Sbostic /*************************************************************************
1200*33165Sbostic *  Procedure:	hdstrategy
1201*33165Sbostic *
1202*33165Sbostic *  Description: The hdc strategy routine. It is called by the kernel
1203*33165Sbostic *               to do a disk operation  ('physio' if raw i/o, the block
1204*33165Sbostic *               i/o routines if block i/o); i.e. this is the point where
1205*33165Sbostic *               raw i/o and block i/o merge. This routine is also called
1206*33165Sbostic *               internally by this handler to do misc disk operations.
1207*33165Sbostic *
1208*33165Sbostic *  Returns:
1209*33165Sbostic **************************************************************************/
1210*33165Sbostic 
1211*33165Sbostic hdstrategy(bp)
1212*33165Sbostic 
1213*33165Sbostic register struct buf *bp;	/* This buf structure contains info
1214*33165Sbostic        				 * describing the requested disk xfer.
1215*33165Sbostic 				 */
1216*33165Sbostic {
1217*33165Sbostic 	register hdc_unit_type	 *hu;	   /* hdc device unit info     */
1218*33165Sbostic 	register mcb_type	 *mcb;	   /* the mcb built here       */
1219*33165Sbostic 	register int		 vaddr;    /* virtual address of data  */
1220*33165Sbostic 	hdc_ctlr_type		 *hc;	   /* hdc controller info      */
1221*33165Sbostic 	int			 sector;   /* absolute sector number   */
1222*33165Sbostic 	int			 unit;	   /* minor device unit#       */
1223*33165Sbostic 	int			 par;	   /* disk partition number    */
1224*33165Sbostic 	int			 blocks;   /* number of blocks to xfer */
1225*33165Sbostic 	int			 priority; /* processor level save     */
1226*33165Sbostic 	int			 bytes;	   /* bytecount requested      */
1227*33165Sbostic 	int			 i;	   /* temporary                */
1228*33165Sbostic 
1229*33165Sbostic 	/*
1230*33165Sbostic 	 * Initialize pointers and data.
1231*33165Sbostic 	 */
1232*33165Sbostic 
1233*33165Sbostic 	unit = HDC_UNIT(bp->b_dev);
1234*33165Sbostic 	par = HDC_PARTITION(bp->b_dev);
1235*33165Sbostic 	hu = &hdc_units[unit];
1236*33165Sbostic 	hc = &hdc_ctlrs[hu->ctlr];
1237*33165Sbostic 	bytes = bp->b_bcount;
1238*33165Sbostic 	vaddr = (int) bp->b_un.b_addr;
1239*33165Sbostic 
1240*33165Sbostic 	/*
1241*33165Sbostic 	 * Make some preliminary checks of the i/o request.
1242*33165Sbostic 	 * Terminate the i/o immediately if: the request is for zero
1243*33165Sbostic 	 * bytes or more than 32k bytes; the xfer does not start or
1244*33165Sbostic 	 * end on a longword boundary.
1245*33165Sbostic 	 * "format" sometimes requires bytes=0; e.g. for verify and
1246*33165Sbostic 	 * format ioctls.
1247*33165Sbostic 	 */
1248*33165Sbostic 
1249*33165Sbostic 	if (bytes==0 || bytes>32*1024)
1250*33165Sbostic 		if (!hu->format) goto enxio;
1251*33165Sbostic 	if ( (bytes&3) || (vaddr&3) )
1252*33165Sbostic 		goto efault;
1253*33165Sbostic 
1254*33165Sbostic 	/*
1255*33165Sbostic 	 * Round up requested byte count to a multiple of the block size.
1256*33165Sbostic 	 * If the transfer would exceed the end of the partition,
1257*33165Sbostic 	 * truncate the byte count at the partition boundary (except that
1258*33165Sbostic 	 * the format program is allowed to access the entire disk).
1259*33165Sbostic 	 * Determine absolute sector number of the start of the transfer
1260*33165Sbostic 	 * (requested start plus the start of the partition).
1261*33165Sbostic 	 */
1262*33165Sbostic 
1263*33165Sbostic 	{
1264*33165Sbostic 		register int par_start;  /* partition start blk */
1265*33165Sbostic 		register int par_length; /* partition blk count */
1266*33165Sbostic 
1267*33165Sbostic 		par_start = hu->partition[par].start;
1268*33165Sbostic 		par_length= hu->partition[par].length;
1269*33165Sbostic 		blocks = (bytes + DEV_BSIZE - 1) >> DEV_BSHIFT;
1270*33165Sbostic 		if ( par_length < (bp->b_blkno + blocks) )
1271*33165Sbostic 			if ( !hu->format) {
1272*33165Sbostic 				blocks = par_length - bp->b_blkno;
1273*33165Sbostic 				if(blocks <= 0) goto enxio;
1274*33165Sbostic 				bytes = blocks * DEV_BSIZE;
1275*33165Sbostic 			}
1276*33165Sbostic 		sector = HDC_SPB * (bp->b_blkno + par_start);
1277*33165Sbostic 	}
1278*33165Sbostic 
1279*33165Sbostic 	/*
1280*33165Sbostic 	 * Insure that nobody except the format program writes to
1281*33165Sbostic 	 * the drive definition tracks in partition 7.
1282*33165Sbostic 	 * Note: they may access other tracks in partition 7
1283*33165Sbostic 	 * (i.e. diagnostic tracks).
1284*33165Sbostic 	 */
1285*33165Sbostic 
1286*33165Sbostic 	if (par==HDC_DEFPART)
1287*33165Sbostic 		if (!hu->format && !(bp->b_flags & B_READ))
1288*33165Sbostic 		{
1289*33165Sbostic 			register int defs;  /* definition cyl start */
1290*33165Sbostic 			register int defe;  /* (def cylinder end)+1 */
1291*33165Sbostic 
1292*33165Sbostic 			defs = hu->def_cyl * hu->spc;
1293*33165Sbostic 			defe = defs + hu->def_cyl_count * hu->spc;
1294*33165Sbostic 	        	if (sector < defe && (sector + blocks * HDC_SPB) > defs)
1295*33165Sbostic 				goto eacces;
1296*33165Sbostic 		}
1297*33165Sbostic 
1298*33165Sbostic 	/*
1299*33165Sbostic 	 * Get a free mcb. Wait if no mcb's are available
1300*33165Sbostic 	 */
1301*33165Sbostic 
1302*33165Sbostic 	priority = spl7();
1303*33165Sbostic get:	mcb = hc->forw_free;
1304*33165Sbostic 	remque(mcb);
1305*33165Sbostic 	asm(" bvc got");
1306*33165Sbostic 	slumber(hc, 0, iocomboost);
1307*33165Sbostic 	goto get;
1308*33165Sbostic got:    asm("got:");
1309*33165Sbostic 	splx(priority);
1310*33165Sbostic 
1311*33165Sbostic 	/*
1312*33165Sbostic 	 * Fill in the mcb with information about the xfer.
1313*33165Sbostic 	 *
1314*33165Sbostic 	 * Currently everything is given equal priority.
1315*33165Sbostic 	 * Keep a pointer to the buf associated with the mcb.
1316*33165Sbostic 	 * Add virtual address of this mcb to the software context
1317*33165Sbostic 	 * word of the mcb; the hdc firmware copies this word to
1318*33165Sbostic 	 * the master mcb when the mcb is complete.
1319*33165Sbostic 	 *
1320*33165Sbostic 	 * If the buf was sent locally by this handler (via 'hdphysio')
1321*33165Sbostic 	 * then there may be commands other than just read or write.
1322*33165Sbostic 	 * 'hdphysio' also provides a cylinder/head/sector address.
1323*33165Sbostic 	 */
1324*33165Sbostic 
1325*33165Sbostic 	{
1326*33165Sbostic 		/*
1327*33165Sbostic 		 * The following priority calculation is based on the
1328*33165Sbostic 		 * real time functional specification.
1329*33165Sbostic 		 */
1330*33165Sbostic 		register struct  proc *p = u.u_procp;
1331*33165Sbostic 		mcb->priority = 0;
1332*33165Sbostic 		if ((p->p_ppid) &&	/* not a system process */
1333*33165Sbostic 		    ((p->p_nice < MIN_NON_RT_NICE_VAL) ||
1334*33165Sbostic                      (rt_disk_scheduling))) {
1335*33165Sbostic 			mcb->priority = 32 - p->p_basepri;
1336*33165Sbostic 		}
1337*33165Sbostic 	}
1338*33165Sbostic 
1339*33165Sbostic 	mcb->interrupt = TRUE;
1340*33165Sbostic 	mcb->drive     = hu->slave;
1341*33165Sbostic 	mcb->buf_ptr   = bp;
1342*33165Sbostic 	mcb->context   = (unsigned long) mcb;
1343*33165Sbostic 	if (bp->b_flags & B_LOCALIO) {
1344*33165Sbostic  		mcb->command = bp->b_hdccommand;
1345*33165Sbostic 		mcb->cyl     = bp->b_cyl;
1346*33165Sbostic 		mcb->head    = bp->b_head;
1347*33165Sbostic 		mcb->sector  = bp->b_sector;
1348*33165Sbostic 	}
1349*33165Sbostic 	else {
1350*33165Sbostic 		mcb->command = (bp->b_flags & B_READ) ? HCMD_READ:HCMD_WRITE;
1351*33165Sbostic 		mcb->cyl     = sector/hu->spc;
1352*33165Sbostic 		mcb->head    = (sector/hu->sectors) % hu->heads;
1353*33165Sbostic 		mcb->sector  = sector % hu->sectors;
1354*33165Sbostic 	}
1355*33165Sbostic 
1356*33165Sbostic 	/*
1357*33165Sbostic 	 * Build the data chain - address/count pairs for each page.
1358*33165Sbostic 	 * The first transfer might not start on a page boundary.
1359*33165Sbostic 	 * Purge the data cache for pages to be dma'd into.
1360*33165Sbostic 	 *
1361*33165Sbostic 	 * There is no attempt to combine physically contiguous
1362*33165Sbostic 	 * pages into the same data chain, since it is faster
1363*33165Sbostic 	 * to just dma the extra data chain into the controller
1364*33165Sbostic 	 * than it is to combine the pages;
1365*33165Sbostic 	 */
1366*33165Sbostic 
1367*33165Sbostic 	{
1368*33165Sbostic 		register struct  proc *procp;	 /* process structure   */
1369*33165Sbostic 		register int	 bc;		 /* bytecount this page */
1370*33165Sbostic 		register int	 bcremain=bytes; /* bytecount remaining */
1371*33165Sbostic 
1372*33165Sbostic 		if ( bp->b_flags & B_DIRTY )
1373*33165Sbostic 			procp = (struct proc *) &proc[2] ;
1374*33165Sbostic 		else
1375*33165Sbostic 			procp = bp->b_proc;
1376*33165Sbostic 		if (bp->b_flags & B_READ) mtpr(vaddr,P1DC);
1377*33165Sbostic 		bc = min( bcremain, (NBPG-(vaddr&(NBPG-1))) );
1378*33165Sbostic 		mcb->chain[0].ta = vtoph(procp,vaddr);
1379*33165Sbostic 		mcb->chain[0].lwc = bc/4;
1380*33165Sbostic 		bcremain -= bc;
1381*33165Sbostic 		i = 0;
1382*33165Sbostic 		while (bcremain>0) {
1383*33165Sbostic 	        	vaddr += bc;
1384*33165Sbostic 			if (bp->b_flags & B_READ) mtpr(vaddr,P1DC);
1385*33165Sbostic 			bc = min(bcremain,NBPG);
1386*33165Sbostic 			mcb->chain[i].lwc |= LWC_DATA_CHAIN;
1387*33165Sbostic 			i++;
1388*33165Sbostic 			mcb->chain[i].ta = vtoph(procp,vaddr);
1389*33165Sbostic 			mcb->chain[i].lwc= bc/4;
1390*33165Sbostic 	        	bcremain -= bc;
1391*33165Sbostic 		}
1392*33165Sbostic 	}
1393*33165Sbostic 
1394*33165Sbostic 	/*
1395*33165Sbostic 	 * Set up information for error logging and system activity
1396*33165Sbostic 	 * for programs such as iostat, sadp, sadc, sar, sag.
1397*33165Sbostic 	 * Time-stamp the buf (and the unit if it is just becoming busy).
1398*33165Sbostic 	 * Record the total number of transfer operations and the total
1399*33165Sbostic 	 * no. of 512-byte blocks xferred.
1400*33165Sbostic 	 * Turn on the activity bit for this device - for error logging.
1401*33165Sbostic 	 */
1402*33165Sbostic 
1403*33165Sbostic 	bp->b_start = time.tv_sec;
1404*33165Sbostic 	if (vdtab[unit].b_active++ == 1)
1405*33165Sbostic 		vdtab[unit].io_start = time.tv_sec;
1406*33165Sbostic 	vdstat[unit].io_cnt++;
1407*33165Sbostic 	vdstat[unit].io_bcnt += blocks * HDC_SPB;
1408*33165Sbostic 	blkacty |= (1 << major(bp->b_dev));
1409*33165Sbostic 	dk_wds[unit] += bytes/32;
1410*33165Sbostic   	dk_busy |= 1 << unit;
1411*33165Sbostic 
1412*33165Sbostic 	/*
1413*33165Sbostic 	 * If the controller has active mcb's:
1414*33165Sbostic 	 *    don't send this mcb until the next interrupt occurs.
1415*33165Sbostic 	 *
1416*33165Sbostic 	 * Otherwise:
1417*33165Sbostic 	 *    1) add the mcb to the active queue;
1418*33165Sbostic 	 *    2) physically link the mcb from the master mcb;
1419*33165Sbostic 	 *    3) fill in the master mcb;
1420*33165Sbostic 	 *    4) tell the hdc to scan the new mcb.
1421*33165Sbostic 	 */
1422*33165Sbostic 
1423*33165Sbostic 	{
1424*33165Sbostic 		register master_mcb_type *master; /* hdc's master mcb */
1425*33165Sbostic 
1426*33165Sbostic 		master= &hc->master_mcb;
1427*33165Sbostic 		priority = spl7();
1428*33165Sbostic 		if ( hc->forw_active != (mcb_type *) &hc->forw_active ) {
1429*33165Sbostic 	        	insque(mcb, &hc->forw_wait);
1430*33165Sbostic #ifdef HDCLOG
1431*33165Sbostic 			hdlog(mcb,4 + 16*hc->ctlr);
1432*33165Sbostic #endif
1433*33165Sbostic 		}
1434*33165Sbostic 		else
1435*33165Sbostic 		{
1436*33165Sbostic 			insque(mcb, &hc->forw_active);
1437*33165Sbostic 			master->forw_phaddr = mcb->mcb_phaddr;
1438*33165Sbostic 			mcb->forw_phaddr = 0;
1439*33165Sbostic 			master->mcs = 0;
1440*33165Sbostic #ifdef HDCLOG
1441*33165Sbostic 			hdlog(mcb,5 + 16*hc->ctlr);
1442*33165Sbostic #endif
1443*33165Sbostic 			HDC_REGISTER(master_mcb_reg) = hc->master_phaddr;
1444*33165Sbostic 		}
1445*33165Sbostic 		splx(priority);
1446*33165Sbostic 	}
1447*33165Sbostic 
1448*33165Sbostic 	/*
1449*33165Sbostic 	 * Returns.
1450*33165Sbostic 	 */
1451*33165Sbostic 
1452*33165Sbostic 	return;
1453*33165Sbostic eacces:	bp->b_error = EACCES;
1454*33165Sbostic 	goto errcom;
1455*33165Sbostic efault:	bp->b_error = EFAULT;
1456*33165Sbostic 	goto errcom;
1457*33165Sbostic enxio:	bp->b_error = ENXIO;
1458*33165Sbostic errcom:	bp->b_flags |= B_ERROR;
1459*33165Sbostic 	bp->b_resid = bytes;
1460*33165Sbostic 	iodone(bp);
1461*33165Sbostic }
1462*33165Sbostic 
1463*33165Sbostic /*************************************************************************
1464*33165Sbostic *  Procedure:	hdwrite
1465*33165Sbostic *
1466*33165Sbostic *  Description:	Character device write routine. It is called by the
1467*33165Sbostic *               inode read/write routine 'ino_rw'.
1468*33165Sbostic *
1469*33165Sbostic *  Returns:     The error status returned by 'physio'.
1470*33165Sbostic **************************************************************************/
1471*33165Sbostic 
1472*33165Sbostic int
1473*33165Sbostic hdwrite(dev, uio)
1474*33165Sbostic 
1475*33165Sbostic 
1476*33165Sbostic dev_t		dev;	/* Device type. Major/minor dev#.
1477*33165Sbostic 			 */
1478*33165Sbostic int		*uio;	/* Pointer to a uio structure describing
1479*33165Sbostic 			 * a write request: buffer address;
1480*33165Sbostic 			 * sector offset; no. of sectors; etc.
1481*33165Sbostic 			 */
1482*33165Sbostic {
1483*33165Sbostic 	hdc_unit_type	*hu;	/* hdc unit information   */
1484*33165Sbostic 
1485*33165Sbostic 	hu = &hdc_units[ HDC_UNIT(dev) ];
1486*33165Sbostic 
1487*33165Sbostic 	/*
1488*33165Sbostic 	 * 'physio' builds the buf structure, locks the user pages, calls
1489*33165Sbostic 	 * 'hdstrategy' to do the write, waits until i/o is complete
1490*33165Sbostic 	 * (iodone), deallocates the buf structure, and unlocks the pages.
1491*33165Sbostic 	 */
1492*33165Sbostic 
1493*33165Sbostic 	return physio(
1494*33165Sbostic 		hdstrategy,	/* hdc's strategy routine	    */
1495*33165Sbostic 		&hu->raw_buf,	/* physio builds a buf struct here  */
1496*33165Sbostic 		dev,		/* major/minor device number	    */
1497*33165Sbostic 		B_WRITE,	/* write the buffer		    */
1498*33165Sbostic 		minphys,	/* routine to set max transfer size */
1499*33165Sbostic 		uio);		/* describes the transfer request   */
1500*33165Sbostic }
1501