xref: /csrg-svn/sys/tahoe/vba/hd.c (revision 37097)
1 /*
2  * Copyright (c) 1988 The Regents of the University of California.
3  * All rights reserved.
4  *
5  * This code is derived from software contributed to Berkeley by
6  * Harris Corp.
7  *
8  * Redistribution and use in source and binary forms are permitted
9  * provided that the above copyright notice and this paragraph are
10  * duplicated in all such forms and that any documentation,
11  * advertising materials, and other materials related to such
12  * distribution and use acknowledge that the software was developed
13  * by the University of California, Berkeley.  The name of the
14  * University may not be used to endorse or promote products derived
15  * from this software without specific prior written permission.
16  * THIS SOFTWARE IS PROVIDED ``AS IS'' AND WITHOUT ANY EXPRESS OR
17  * IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED
18  * WARRANTIES OF MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE.
19  *
20  *	@(#)hd.c	7.3 (Berkeley) 03/07/89
21  */
22 
23 #include "hd.h"
24 
25 #if NHD > 0
26 #include "param.h"
27 #include "buf.h"
28 #include "conf.h"
29 #include "dir.h"
30 #include "dkstat.h"
31 #include "disklabel.h"
32 #include "file.h"
33 #include "systm.h"
34 #include "vmmac.h"
35 #include "time.h"
36 #include "proc.h"
37 #include "uio.h"
38 #include "syslog.h"
39 #include "kernel.h"
40 #include "ioctl.h"
41 #include "stat.h"
42 #include "errno.h"
43 
44 #include "../tahoe/cpu.h"
45 #include "../tahoe/mtpr.h"
46 
47 #include "../tahoevba/vbavar.h"
48 #include "../tahoevba/hdreg.h"
49 
50 #define	b_cylin	b_resid
51 
52 #define	hdunit(dev)		(minor(dev)>>3)
53 #define	hdpart(dev)		(minor(dev)&0x07)
54 #define	hdminor(unit, part)	(((unit)<<3)|(part))
55 
56 struct vba_ctlr *hdcminfo[NHDC];
57 struct vba_device *hddinfo[NHD];
58 int hdcprobe(), hdslave(), hdattach(), hddgo(), hdstrategy();
59 struct vba_driver hdcdriver =
60     { hdcprobe, hdslave, hdattach, hddgo, 0L, "hd", hddinfo, "hdc", hdcminfo };
61 
62 /*
63  * Per-controller state.
64  */
65 struct hdcsoftc {
66 	u_short	hdc_flags;
67 #define	HDC_INIT	0x01	/* controller initialized */
68 #define	HDC_STARTED	0x02	/* start command issued */
69 #define	HDC_LOCKED	0x04	/* locked for direct controller access */
70 #define	HDC_WAIT	0x08	/* someone needs direct controller access */
71 	u_short	hdc_wticks;		/* timeout */
72 	struct master_mcb *hdc_mcbp;	/* address of controller mcb */
73 	struct registers *hdc_reg;	/* base address of i/o regs */
74 	struct vb_buf hdc_rbuf;		/* vba resources */
75 	struct master_mcb hdc_mcb;	/* controller mcb */
76 } hdcsoftc[NHDC];
77 
78 #define	HDCMAXTIME	20		/* max time for operation, sec. */
79 #define	HDCINTERRUPT	0xf0		/* interrupt vector */
80 
81 /*
82  * Per-drive state; probably everything should be "hd_", not "dk_",
83  * but it's not worth it, and dk is a better mnemonic for disk anyway.
84  */
85 struct dksoftc {
86 #ifdef COMPAT_42
87 	u_short	dk_def_cyl;	/* definition track cylinder address */
88 #endif
89 	int	dk_state;	/* open fsm */
90 	u_short	dk_bshift;	/* shift for * (DEV_BSIZE / sectorsize) XXX */
91 	int	dk_wlabel;	/* if label sector is writeable */
92 	u_long	dk_copenpart;	/* character units open on this drive */
93 	u_long	dk_bopenpart;	/* block units open on this drive */
94 	u_long	dk_openpart;	/* all units open on this drive */
95 	int	dk_unit;	/* unit# */
96 	int	dk_ctlr;	/* controller# */
97 	int	dk_format;	/* if format program is using disk */
98 	struct buf dk_utab;		/* i/o queue header */
99 	struct disklabel dk_label;	/* disklabel for this disk */
100 	struct mcb dk_mcb;		/* disk mcb */
101 } dksoftc[NHD];
102 
103 /*
104  * Drive states.  Used during steps of open/initialization.
105  * States < OPEN (> 0) are transient, during an open operation.
106  * OPENRAW is used for unlabeled disks, to allow format operations.
107  */
108 #define	CLOSED		0		/* disk is closed */
109 #define	WANTOPEN	1		/* open requested, not started */
110 #define	WANTOPENRAW	2		/* open requested, no label */
111 #define	RDLABEL		3		/* reading pack label */
112 #define	OPEN		4		/* intialized and ready */
113 #define	OPENRAW		5		/* open, no label */
114 
115 int hdcwstart, hdcwatch();
116 
117 /* see if the controller is really there, if so, init it. */
118 /* ARGSUSED */
119 hdcprobe(reg, vm)
120 	caddr_t reg;
121 	/* register */ struct vba_ctlr *vm;
122 {
123 	register int br, cvec;		/* must be r12, r11 */
124 	register struct hdcsoftc *hdc;
125 	static struct module_id id;
126 	struct pte *dummypte;
127 	caddr_t putl;
128 
129 	/* initialize the hdc controller structure. */
130 	hdc = &hdcsoftc[vm->um_ctlr];
131 	if (!vbmemalloc(1, reg, &dummypte, &putl)) {
132 		printf("hdc%d: vbmemalloc failed.\n", vm->um_ctlr);
133 		return(0);
134 	}
135 	hdc->hdc_reg = (struct registers *)putl;
136 
137 	/*
138 	 * try and ping the MID register; side effect of wbadaddr is to read
139 	 * the module id; the controller is bad if it's not an hdc, the hdc's
140 	 * writeable control store is not loaded, or the hdc failed the
141 	 * functional integrity test;
142 	 */
143 	if (wbadaddr(&hdc->hdc_reg->module_id, 4,
144 	    vtoph((struct process *)NULL, &id))) {
145 		printf("hdc%d: can't access module register.\n", vm->um_ctlr);
146 		return(0);
147 	}
148 	DELAY(10000);
149 	mtpr(PADC, 0);
150 	if (id.module_id != (u_char)HDC_MID) {
151 		printf("hdc%d: bad module id; id = %x.\n",
152 		    vm->um_ctlr, id.module_id);
153 		return(0);
154 	}
155 	if (id.code_rev == (u_char)0xff) {
156 		printf("hdc%d: micro-code not loaded.\n", vm->um_ctlr);
157 		return(0);
158 	}
159 	if (id.fit != (u_char)0xff) {
160 		printf("hdc%d: FIT test failed.\n", vm->um_ctlr);
161 		return(0);
162 	}
163 
164 	/* reset that pup; flag as inited */
165 	hdc->hdc_reg->soft_reset = 0;
166 	DELAY(1000000);
167 	hdc->hdc_flags |= HDC_INIT;
168 
169 	/* allocate page tables and i/o buffer. */
170 	if (!vbainit(&hdc->hdc_rbuf, MAXPHYS, VB_32BIT|VB_SCATTER)) {
171 		printf("hdc%d: vbainit failed\n", vm->um_ctlr);
172 		return (0);
173 	}
174 
175 	/* set pointer to master control block */
176 	hdc->hdc_mcbp =
177 	    (struct master_mcb *)vtoph((struct proc *)NULL, &hdc->hdc_mcb);
178 
179 	br = 0x17, cvec = HDCINTERRUPT + vm->um_ctlr;		/* XXX */
180 	return(sizeof(struct registers));
181 }
182 
183 /* ARGSUSED */
184 hdslave(vi, vdaddr)
185 	struct vba_device *vi;
186 	struct vddevice *vdaddr;
187 {
188 	register struct mcb *mcb;
189 	register struct disklabel *lp;
190 	register struct dksoftc *dk;
191 	static struct status status;
192 
193 	dk = &dksoftc[vi->ui_unit];
194 	dk->dk_unit = vi->ui_unit;
195 	dk->dk_ctlr = vi->ui_ctlr;
196 
197 	mcb = &dk->dk_mcb;
198 	mcb->command = HCMD_STATUS;
199 	mcb->chain[0].wcount = sizeof(struct status) / sizeof(long);
200 	mcb->chain[0].memadr  = (u_long)vtoph((struct process *)0, &status);
201 	if (hdimcb(dk)) {
202 		printf(" (no status)\n");
203 		return(0);
204 	}
205 
206 	/*
207 	 * Report the drive down if anything in the drive status looks bad.
208 	 * If the drive is offline and it is not on cylinder, then the drive
209 	 * is not there.  If there is a fault condition, the hdc will try to
210 	 * clear it when we read the disklabel information.
211 	 */
212 	if (!(status.drs&DRS_ONLINE)) {
213 		if (status.drs&DRS_ON_CYLINDER)
214 			printf(" (not online)\n");
215 		return(0);
216 	}
217 	if (status.drs&DRS_FAULT)
218 		printf(" (clearing fault)");
219 	printf("\n");
220 
221 	lp = &dk->dk_label;
222 #ifdef RAW_SIZE
223 	lp->d_secsize = status.bytes_per_sec;
224 #else
225 	lp->d_secsize = 512;
226 #endif
227 	lp->d_nsectors = status.max_sector + 1;
228 	lp->d_ntracks = status.max_head + 1;
229 	lp->d_ncylinders = status.max_cyl + 1;
230 	lp->d_secpercyl = lp->d_ntracks * lp->d_nsectors;
231 	lp->d_npartitions = 1;
232 	lp->d_partitions[0].p_offset = 0;
233 	lp->d_partitions[0].p_size = LABELSECTOR + 1;
234 	lp->d_rpm = status.rpm;
235 	lp->d_typename[0] = 'h';
236 	lp->d_typename[1] = 'd';
237 	lp->d_typename[2] = '\0';
238 #ifdef COMPAT_42
239 	dk->dk_def_cyl = status.def_cyl;
240 #endif
241 	return(1);
242 }
243 
244 hdattach(vi)
245 	register struct vba_device *vi;
246 {
247 	register struct dksoftc *dk;
248 	register struct disklabel *lp;
249 	register int unit;
250 
251 	unit = vi->ui_unit;
252 	if (hdinit(hdminor(unit, 0), 0)) {
253 		printf(": unknown drive type");
254 		return;
255 	}
256 	dk = &dksoftc[unit];
257 	lp = &dk->dk_label;
258 	hd_setsecsize(dk, lp);
259 	if (dk->dk_state == OPEN)
260 		printf(": %s <secsize %d, ntrak %d, ncyl %d, nsec %d>",
261 		    lp->d_typename, lp->d_secsize, lp->d_ntracks,
262 		    lp->d_ncylinders, lp->d_nsectors);
263 
264 	/*
265 	 * (60 / rpm) / (sectors per track * (bytes per sector / 2))
266 	 */
267 	if (vi->ui_dk >= 0)
268 		dk_mspw[vi->ui_dk] = 120.0 /
269 		    (lp->d_rpm * lp->d_nsectors * lp->d_secsize);
270 #ifdef notyet
271 	addswap(makedev(HDMAJOR, hdminor(unit, 0)), lp);
272 #endif
273 }
274 
275 hdopen(dev, flags, fmt)
276 	dev_t dev;
277 	int flags, fmt;
278 {
279 	register struct disklabel *lp;
280 	register struct dksoftc *dk;
281 	register struct partition *pp;
282 	register int unit;
283 	struct vba_device *vi;
284 	int s, error, part = hdpart(dev), mask = 1 << part;
285 	daddr_t start, end;
286 
287 	unit = hdunit(dev);
288 	if (unit >= NHD || (vi = hddinfo[unit]) == 0 || vi->ui_alive == 0)
289 		return(ENXIO);
290 	dk = &dksoftc[unit];
291 	lp = &dk->dk_label;
292 	s = spl7();
293 	while (dk->dk_state != OPEN && dk->dk_state != OPENRAW &&
294 	    dk->dk_state != CLOSED)
295 		sleep((caddr_t)dk, PZERO+1);
296 	splx(s);
297 	if (dk->dk_state != OPEN && dk->dk_state != OPENRAW)
298 		if (error = hdinit(dev, flags))
299 			return(error);
300 
301 	if (hdcwstart == 0) {
302 		timeout(hdcwatch, (caddr_t)0, hz);
303 		hdcwstart++;
304 	}
305 	/*
306 	 * Warn if a partion is opened that overlaps another partition
307 	 * which is open unless one is the "raw" partition (whole disk).
308 	 */
309 #define	RAWPART		8		/* 'x' partition */	/* XXX */
310 	if ((dk->dk_openpart & mask) == 0 && part != RAWPART) {
311 		pp = &lp->d_partitions[part];
312 		start = pp->p_offset;
313 		end = pp->p_offset + pp->p_size;
314 		for (pp = lp->d_partitions;
315 		     pp < &lp->d_partitions[lp->d_npartitions]; pp++) {
316 			if (pp->p_offset + pp->p_size <= start ||
317 			    pp->p_offset >= end)
318 				continue;
319 			if (pp - lp->d_partitions == RAWPART)
320 				continue;
321 			if (dk->dk_openpart & (1 << (pp - lp->d_partitions)))
322 				log(LOG_WARNING,
323 				    "hd%d%c: overlaps open partition (%c)\n",
324 				    unit, part + 'a',
325 				    pp - lp->d_partitions + 'a');
326 		}
327 	}
328 	if (part >= lp->d_npartitions)
329 		return(ENXIO);
330 	dk->dk_openpart |= mask;
331 	switch (fmt) {
332 	case S_IFCHR:
333 		dk->dk_copenpart |= mask;
334 		break;
335 	case S_IFBLK:
336 		dk->dk_bopenpart |= mask;
337 		break;
338 	}
339 	return(0);
340 }
341 
342 /* ARGSUSED */
343 hdclose(dev, flags, fmt)
344 	dev_t dev;
345 	int flags, fmt;
346 {
347 	register struct dksoftc *dk;
348 	int mask;
349 
350 	dk = &dksoftc[hdunit(dev)];
351 	mask = 1 << hdpart(dev);
352 	switch (fmt) {
353 	case S_IFCHR:
354 		dk->dk_copenpart &= ~mask;
355 		break;
356 	case S_IFBLK:
357 		dk->dk_bopenpart &= ~mask;
358 		break;
359 	}
360 	if (((dk->dk_copenpart | dk->dk_bopenpart) & mask) == 0)
361 		dk->dk_openpart &= ~mask;
362 	/*
363 	 * Should wait for i/o to complete on this partition
364 	 * even if others are open, but wait for work on blkflush().
365 	 */
366 	if (dk->dk_openpart == 0) {
367 		int s = spl7();
368 		while (dk->dk_utab.b_actf)
369 			sleep((caddr_t)dk, PZERO-1);
370 		splx(s);
371 		dk->dk_state = CLOSED;
372 		dk->dk_wlabel = 0;
373 	}
374 	return(0);
375 }
376 
377 hdinit(dev, flags)
378 	dev_t dev;
379 	int flags;
380 {
381 	register struct dksoftc *dk;
382 	register struct disklabel *lp;
383 	struct vba_device *vi;
384 	int error, unit;
385 	char *msg, *readdisklabel();
386 	extern int cold;
387 
388 	vi = hddinfo[unit = hdunit(dev)];
389 	dk = &dksoftc[unit];
390 	dk->dk_unit = vi->ui_slave;
391 	dk->dk_ctlr = vi->ui_ctlr;
392 
393 	if (flags & O_NDELAY) {
394 		dk->dk_state = OPENRAW;
395 		return(0);
396 	}
397 
398 	error = 0;
399 	lp = &dk->dk_label;
400 	dk->dk_state = RDLABEL;
401 	if (msg = readdisklabel(dev, hdstrategy, lp)) {
402 		if (cold) {
403 			printf(": %s\n", msg);
404 			dk->dk_state = CLOSED;
405 		} else {
406 			log(LOG_ERR, "hd%d: %s\n", unit, msg);
407 			dk->dk_state = OPENRAW;
408 		}
409 #ifdef COMPAT_42
410 		hdclock(vi->ui_ctlr);
411 		if (!(error = hdreadgeometry(dk)))
412 			dk->dk_state = OPEN;
413 		hdcunlock(vi->ui_ctlr);
414 #endif
415 	} else
416 		dk->dk_state = OPEN;
417 	wakeup((caddr_t)dk);
418 	return(error);
419 }
420 
421 hd_setsecsize(dk, lp)
422 	register struct dksoftc *dk;
423 	struct disklabel *lp;
424 {
425 	register int mul;
426 
427 	/*
428 	 * Calculate scaling shift for mapping
429 	 * DEV_BSIZE blocks to drive sectors.
430 	 */
431 	mul = DEV_BSIZE / lp->d_secsize;
432 	dk->dk_bshift = 0;
433 	while ((mul >>= 1) > 0)
434 		dk->dk_bshift++;
435 }
436 
437 /* ARGSUSED */
438 hddgo(vm)
439 	struct vba_device *vm;
440 {}
441 
442 extern int name_ext;
443 hdstrategy(bp)
444 	register struct buf *bp;
445 {
446 	register struct vba_device *vi;
447 	register struct disklabel *lp;
448 	register struct dksoftc *dk;
449 	struct buf *dp;
450 	register int unit;
451 	daddr_t sn, sz, maxsz;
452 	int part, s;
453 
454 	vi = hddinfo[unit = hdunit(bp->b_dev)];
455 	if (unit >= NHD || vi == 0 || vi->ui_alive == 0) {
456 		bp->b_error = ENXIO;
457 		goto bad;
458 	}
459 	dk = &dksoftc[unit];
460 	if (dk->dk_state < OPEN)
461 		goto q;
462 	if (dk->dk_state != OPEN && (bp->b_flags & B_READ) == 0) {
463 		bp->b_error = EROFS;
464 		goto bad;
465 	}
466 	part = hdpart(bp->b_dev);
467 	if ((dk->dk_openpart & (1 << part)) == 0) {
468 		bp->b_error = ENODEV;
469 		goto bad;
470 	}
471 	lp = &dk->dk_label;
472 	sz = (bp->b_bcount + lp->d_secsize - 1) / lp->d_secsize;
473 	maxsz = lp->d_partitions[part].p_size;
474 	sn = bp->b_blkno << dk->dk_bshift;
475 	if (sn + lp->d_partitions[part].p_offset <= LABELSECTOR &&
476 #if LABELSECTOR != 0
477 	    sn + lp->d_partitions[part].p_offset + sz > LABELSECTOR &&
478 #endif
479 	    (bp->b_flags & B_READ) == 0 && dk->dk_wlabel == 0) {
480 		bp->b_error = EROFS;
481 		goto bad;
482 	}
483 	if (sn < 0 || sn + sz > maxsz) {
484 		if (sn == maxsz) {
485 			bp->b_resid = bp->b_bcount;
486 			goto done;
487 		}
488 		sz = maxsz - sn;
489 		if (sz <= 0) {
490 			bp->b_error = EINVAL;
491 			goto bad;
492 		}
493 		bp->b_bcount = sz * lp->d_secsize;
494 	}
495 	bp->b_cylin = (sn + lp->d_partitions[part].p_offset) / lp->d_secpercyl;
496 
497 q:	s = spl7();
498 	dp = &dk->dk_utab;
499 	disksort(dp, bp);
500 	if (!dp->b_active) {
501 		(void)hdustart(vi);
502 		if (!vi->ui_mi->um_tab.b_active)
503 			hdcstart(vi->ui_mi);
504 	}
505 	splx(s);
506 	return;
507 bad:
508 	bp->b_flags |= B_ERROR;
509 done:
510 	biodone(bp);
511 }
512 
513 hdustart(vi)
514 	register struct vba_device *vi;
515 {
516 	register struct buf *bp, *dp;
517 	register struct vba_ctlr *vm;
518 	register struct dksoftc *dk;
519 
520 	dk = &dksoftc[vi->ui_unit];
521 	dp = &dk->dk_utab;
522 
523 	/* if queue empty, nothing to do.  impossible? */
524 	if (dp->b_actf == NULL)
525 		return;
526 
527 	/* place on controller transfer queue */
528 	vm = vi->ui_mi;
529 	if (vm->um_tab.b_actf == NULL)
530 		vm->um_tab.b_actf = dp;
531 	else
532 		vm->um_tab.b_actl->b_forw = dp;
533 	vm->um_tab.b_actl = dp;
534 	dp->b_forw = NULL;
535 	dp->b_active++;
536 }
537 
538 hdcstart(vm)
539 	register struct vba_ctlr *vm;
540 {
541 	register struct buf *bp;
542 	register struct dksoftc *dk;
543 	register struct disklabel *lp;
544 	register struct master_mcb *master;
545 	register struct mcb *mcb;
546 	struct vba_device *vi;
547 	struct hdcsoftc *hdc;
548 	struct buf *dp;
549 	int sn;
550 
551 	/* pull a request off the controller queue */
552 	for (;;) {
553 		if ((dp = vm->um_tab.b_actf) == NULL)
554 			return;
555 		if (bp = dp->b_actf)
556 			break;
557 		vm->um_tab.b_actf = dp->b_forw;
558 	}
559 
560 	/* mark controller active */
561 	vm->um_tab.b_active++;
562 
563 	vi = hddinfo[hdunit(bp->b_dev)];
564 	dk = &dksoftc[vi->ui_unit];
565 	lp = &dk->dk_label;
566 	sn = bp->b_blkno << dk->dk_bshift;
567 
568 	/* fill in mcb */
569 	mcb = &dk->dk_mcb;
570 	mcb->forw_phaddr = 0;
571 	/* mcb->priority = 0; */
572 	mcb->interrupt = 1;
573 	mcb->command = (bp->b_flags & B_READ) ? HCMD_READ:HCMD_WRITE;
574 	mcb->cyl = sn / lp->d_secpercyl;
575 	mcb->head = (sn / lp->d_nsectors) % lp->d_ntracks;
576 	mcb->sector = sn % lp->d_nsectors;
577 	mcb->drive = vi->ui_slave;
578 	/* mcb->context = 0;		/* what do we want on interrupt? */
579 
580 	hdc = &hdcsoftc[vm->um_ctlr];
581 	if (!hd_sgsetup(bp, hdc->hdc_rbuf, mcb->chain)) {
582 		mcb->chain[0].wcount = (bp->b_bcount+3) >> 2;
583 		mcb->chain[0].memadr =
584 		    vbasetup(bp, &hdc->hdc_rbuf, (int)lp->d_secsize);
585 	}
586 
587 	if (vi->ui_dk >= 0) {
588 		dk_busy |= 1<<vi->ui_dk;
589 		dk_xfer[vi->ui_dk]++;
590 		dk_wds[vi->ui_dk] += bp->b_bcount>>6;
591 	}
592 
593 	master = &hdc->hdc_mcb;
594 	master->mcw = MCL_QUEUED;
595 	master->interrupt = HDCINTERRUPT + vm->um_ctlr;
596 	master->forw_phaddr = (u_long)vtoph((struct proc *)NULL, mcb);
597 	hdc->hdc_reg->master_mcb = (u_long)hdc->hdc_mcbp;
598 }
599 
600 /*
601  * Wait for controller to finish current operation
602  * so that direct controller accesses can be done.
603  */
604 hdclock(ctlr)
605 	int ctlr;
606 {
607 	register struct vba_ctlr *vm = hdcminfo[ctlr];
608 	register struct hdcsoftc *hdc;
609 	int s;
610 
611 	hdc = &hdcsoftc[ctlr];
612 	s = spl7();
613 	while (vm->um_tab.b_active || hdc->hdc_flags & HDC_LOCKED) {
614 		hdc->hdc_flags |= HDC_WAIT;
615 		sleep((caddr_t)hdc, PRIBIO);
616 	}
617 	hdc->hdc_flags |= HDC_LOCKED;
618 	splx(s);
619 }
620 
621 /*
622  * Continue normal operations after pausing for
623  * munging the controller directly.
624  */
625 hdcunlock(ctlr)
626 	int ctlr;
627 {
628 	register struct vba_ctlr *vm;
629 	register struct hdcsoftc *hdc = &hdcsoftc[ctlr];
630 
631 	hdc->hdc_flags &= ~HDC_LOCKED;
632 	if (hdc->hdc_flags & HDC_WAIT) {
633 		hdc->hdc_flags &= ~HDC_WAIT;
634 		wakeup((caddr_t)hdc);
635 	} else {
636 		vm = hdcminfo[ctlr];
637 		if (vm->um_tab.b_actf)
638 			hdcstart(vm);
639 	}
640 }
641 
642 hdintr(ctlr)
643 	int ctlr;
644 {
645 	register struct buf *bp, *dp;
646 	register struct vba_ctlr *vm;
647 	register struct vba_device *vi;
648 	register struct hdcsoftc *hdc;
649 	register struct mcb *mcb;
650 	struct master_mcb *master;
651 	register int status;
652 	int timedout;
653 	struct dksoftc *dk;
654 
655 	hdc = &hdcsoftc[ctlr];
656 	master = &hdc->hdc_mcb;
657 	uncache(&master->mcs);
658 	uncache(&master->context);
659 
660 	vm = hdcminfo[ctlr];
661 	if (!vm->um_tab.b_active || !(master->mcs&MCS_DONE)) {
662 		printf("hd%d: stray interrupt\n", ctlr);
663 		return;
664 	}
665 
666 	dp = vm->um_tab.b_actf;
667 	bp = dp->b_actf;
668 	vi = hddinfo[hdunit(bp->b_dev)];
669 	dk = &dksoftc[vi->ui_unit];
670 	if (vi->ui_dk >= 0)
671 		dk_busy &= ~(1<<vi->ui_dk);
672 	timedout = (hdc->hdc_wticks >= HDCMAXTIME);
673 
674 	mcb = &dk->dk_mcb;
675 
676 	if (master->mcs & (MCS_SOFTERROR | MCS_FATALERROR) || timedout)
677 		hdcerror(ctlr, *(u_long *)master->xstatus);
678 	else {
679 		hdc->hdc_wticks = 0;
680 		if (vm->um_tab.b_active) {
681 			vm->um_tab.b_active = 0;
682 			vm->um_tab.b_actf = dp->b_forw;
683 			dp->b_active = 0;
684 			dp->b_errcnt = 0;
685 			dp->b_actf = bp->av_forw;
686 			bp->b_resid = 0;
687 			vbadone(bp, &hdc->hdc_rbuf);
688 			biodone(bp);
689 			/* start up now, if more work to do */
690 			if (dp->b_actf)
691 				hdustart(vi);
692 			else if (dk->dk_openpart == 0)
693 				wakeup((caddr_t)dk);
694 		}
695 	}
696 	/* if there are devices ready to transfer, start the controller. */
697 	if (hdc->hdc_flags & HDC_WAIT) {
698 		hdc->hdc_flags &= ~HDC_WAIT;
699 		wakeup((caddr_t)hdc);
700 	} else if (vm->um_tab.b_actf)
701 		hdcstart(vm);
702 }
703 
704 hdioctl(dev, command, data, flag)
705 	dev_t dev;
706 	int command, flag;
707 	caddr_t data;
708 {
709 	int error;
710 
711 	switch (command) {
712 
713 	default:
714 		error = ENOTTY;
715 		break;
716 	}
717 	return(error);
718 }
719 
720 /*
721  * Watch for lost interrupts.
722  */
723 hdcwatch()
724 {
725 	register struct hdcsoftc *hdc;
726 	register struct vba_ctlr **vmp;
727 	register int ctlr;
728 	int s;
729 
730 	timeout(hdcwatch, (caddr_t)0, hz);
731 	for (vmp = hdcminfo, hdc = hdcsoftc, ctlr = 0; ctlr < NHDC;
732 	    ++ctlr, ++vmp, ++hdc) {
733 		if (*vmp == 0 || (*vmp)->um_alive == 0)
734 			continue;
735 		s = spl7();
736 		if ((*vmp)->um_tab.b_active &&
737 		    hdc->hdc_wticks++ >= HDCMAXTIME) {
738 			printf("hd%d: lost interrupt\n", ctlr);
739 			hdintr(ctlr);
740 		}
741 		splx(s);
742 	}
743 }
744 
745 hddump(dev)
746 	dev_t dev;
747 {
748 	return(ENXIO);
749 }
750 
751 hdsize(dev)
752 	dev_t dev;
753 {
754 	register int unit = hdunit(dev);
755 	register struct dksoftc *dk;
756 	struct vba_device *vi;
757 	struct disklabel *lp;
758 
759 	if (unit >= NHD || (vi = hddinfo[unit]) == 0 || vi->ui_alive == 0 ||
760 	    (dk = &dksoftc[unit])->dk_state != OPEN)
761 		return (-1);
762 	lp = &dk->dk_label;
763 	return ((int)lp->d_partitions[hdpart(dev)].p_size >> dk->dk_bshift);
764 }
765 
766 hdimcb(dk)
767 	register struct dksoftc *dk;
768 {
769 	register struct master_mcb *master;
770 	register struct mcb *mcb;
771 	register struct hdcsoftc *hdc;
772 	int timeout;
773 
774 	/* fill in mcb */
775 	mcb = &dk->dk_mcb;
776 	mcb->interrupt = 0;
777 	mcb->forw_phaddr = 0;
778 	mcb->drive = dk->dk_unit;
779 
780 	hdc = &hdcsoftc[dk->dk_ctlr];
781 	master = &hdc->hdc_mcb;
782 
783 	/* fill in master mcb */
784 	master->mcw = MCL_IMMEDIATE;
785 	master->forw_phaddr = (u_long)vtoph((struct proc *)NULL, mcb);
786 	master->mcs = 0;
787 
788 	/* kick controller and wait */
789 	hdc->hdc_reg->master_mcb = (u_long)hdc->hdc_mcbp;
790 	for (timeout = 15000; timeout; --timeout) {
791 		DELAY(1000);
792 		mtpr(PADC, 0);
793 		if (master->mcs&MCS_FATALERROR) {
794 			printf("hdc%d: fatal error\n", dk->dk_ctlr);
795 			hdcerror(dk->dk_ctlr, *(u_long *)master->xstatus);
796 			return(1);
797 		}
798 		if (master->mcs&MCS_DONE)
799 			return(0);
800 	}
801 	printf("hdc%d: timed out\n", dk->dk_ctlr);
802 	return(1);
803 }
804 
805 hdcerror(ctlr, code)
806 	int ctlr;
807 	u_long code;
808 {
809 	printf("hd%d: ", ctlr);
810 	switch(code) {
811 #define	P(op, msg)	case op: printf("%s\n", msg); return;
812 	P(0x0100, "Invalid command code")
813 	P(0x0221, "Total longword count too large")
814 	P(0x0222, "Total longword count incorrect")
815 	P(0x0223, "Longword count of zero not permitted")
816 	P(0x0231, "Too many data chained items")
817 	P(0x0232, "Data chain not permitted for this command")
818 	P(0x0341, "Maximum logical cylinder address exceeded")
819 	P(0x0342, "Maximum logical head address exceeded")
820 	P(0x0343, "Maximum logical sectoraddress exceeded")
821 	P(0x0351, "Maximum physical cylinder address exceeded")
822 	P(0x0352, "Maximum physical head address exceeded")
823 	P(0x0353, "Maximum physical sectoraddress exceeded")
824 	P(0x0621, "Control store PROM revision incorrect")
825 	P(0x0642, "Power fail detected")
826 	P(0x0721, "Sector count test failed")
827 	P(0x0731, "First access test failed")
828 	P(0x0811, "Drive not online")
829 	P(0x0812, "Drive not ready")
830 	P(0x0813, "Drive seek error")
831 	P(0x0814, "Drive faulted")
832 	P(0x0815, "Drive reserved")
833 	P(0x0816, "Drive write protected")
834 	P(0x0841, "Timeout waiting for drive to go on-cylinder")
835 	P(0x0851, "Timeout waiting for a specific sector address")
836 	P(0x0921, "Correctable ECC error")
837 	P(0x0A11, "Attempt to spill-off of physical boundary")
838 	P(0x0A21, "Attempt to spill-off of logical boundary")
839 	P(0x0A41, "Unknown DDC status (PSREAD)")
840 	P(0x0A42, "Unknown DDC status (PSWRITE)")
841 	P(0x0A51, "Track relocation limit exceeded")
842 	P(0x0C00, "HFASM")
843 	P(0x0C01, "data field error")
844 	P(0x0C02, "sector not found")
845 	P(0x0C03, "sector overrun")
846 	P(0x0C04, "no data sync")
847 	P(0x0C05, "FIFO data lost")
848 	P(0x0C06, "correction failed")
849 	P(0x0C07, "late interlock")
850 	P(0x0D21, "Output data buffer parity error")
851 	P(0x0D31, "Input data transfer FIFO indicates overflow")
852 	P(0x0D32, "Input data buffer FIFO indicates overflow")
853 	P(0x0D41, "Longword count != 0 indicates underflow")
854 	P(0x0D42, "Output data buffer FIFO indicates underflow")
855 	P(0x0E01, "FT timeout -- DDC interrupt")
856 	P(0x0E02, "RDDB timeout -- IDTFINRDY -- and DDC interrupt")
857 	P(0x0E03, "RDDB timeout -- DDC interrupt")
858 	P(0x0E04, "RDDB timeout -- writing ZERO's to IDTF")
859 	P(0x0E05, "RDDB timeout -- IDTFINRDY -- and IDBFEMPTY+")
860 	P(0x0E06, "WRDB timeout -- ODTFOUTRDT -- and DDC interrupt")
861 	P(0x0E07, "WRDB timeout -- ODTFOUTRDT -- and DDC interrupt")
862 	P(0x0E08, "WRDB timeout -- DDC interrupt")
863 	P(0x0E09, "WRDB timeout -- ODBFFULL+ and DDC interrupt")
864 	P(0x0E0A, "VLT timeout -- DDC interrupt")
865 	P(0x0E0B, "WRBA timeout -- ODTFOUTRDY-")
866 	P(0x0F00, "Error log full")
867 	default:
868 		if (code >= 0x0B00 && code <= 0x0BFF)
869 			printf("Unknown DDC status type 0x%x.", code&0xff);
870 		else
871 			printf("Unknown error %lx\n", code);
872 	}
873 }
874 
875 #ifdef COMPAT_42
876 hdreadgeometry(dk)
877 	struct dksoftc *dk;
878 {
879 	static geometry_sector geometry;
880 	register struct mcb *mcb;
881 	register struct disklabel *lp;
882 	geometry_block *geo;
883 	int cnt;
884 
885 	/*
886 	 * Read the geometry block (at head = 0 sector = 0 of the drive
887 	 * definition cylinder), validate it (must have the correct version
888 	 * number, header, and checksum).
889 	 */
890 	mcb = &dk->dk_mcb;
891 	mcb->command = HCMD_READ;
892 	mcb->cyl = dk->dk_def_cyl;
893 	mcb->head = 0;
894 	mcb->sector = 0;
895 	mcb->chain[0].wcount = sizeof(geometry_sector) / sizeof(long);
896 	mcb->chain[0].memadr  = (u_long)vtoph((struct process *)0, &geometry);
897 	/* mcb->chain[0].memadr = (long)&geometry; */
898 	if (hdimcb(dk)) {
899  		printf("hd%d: can't read default geometry.\n", dk->dk_unit);
900 		return(1);
901 	}
902 	geo = &geometry.geometry_block;
903  	if (geo->version > 64000  ||  geo->version < 0) {
904  		printf("hd%d: bad default geometry version#.\n", dk->dk_unit);
905 		return(1);
906 	}
907  	if (bcmp(&geo->id[0], GB_ID, GB_ID_LEN)) {
908  		printf("hd%d: bad default geometry header.\n", dk->dk_unit);
909 		return(1);
910 	}
911 	GB_CHECKSUM(geo, cnt);
912 	if (geometry.checksum != cnt) {
913 		printf("hd%d: bad default geometry checksum.\n", dk->dk_unit);
914 		return(1);
915 	}
916 	lp = &dk->dk_label;
917 	/* 1K block in Harris geometry; convert to sectors for disklabels */
918 	for (cnt = 0; cnt < GB_MAXPART; cnt++) {
919 		lp->d_partitions[cnt].p_offset =
920 		    geo->partition[cnt].start * (1024 / lp->d_secsize);
921 		lp->d_partitions[cnt].p_size =
922 		    geo->partition[cnt].length * (1024 / lp->d_secsize);
923 	}
924 	lp->d_npartitions = GB_MAXPART;
925 	return(0);
926 }
927 #endif /* COMPAT_42 */
928 #endif /* NHD */
929