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