xref: /original-bsd/sys/tahoe/vba/hd.c (revision c47935e1)
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 MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE.
19  *
20  *	@(#)hd.c	7.4 (Berkeley) 05/01/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 
220 	lp = &dk->dk_label;
221 #ifdef RAW_SIZE
222 	lp->d_secsize = status.bytes_per_sec;
223 #else
224 	lp->d_secsize = 512;
225 #endif
226 	lp->d_nsectors = status.max_sector + 1;
227 	lp->d_ntracks = status.max_head + 1;
228 	lp->d_ncylinders = status.max_cyl + 1;
229 	lp->d_secpercyl = lp->d_ntracks * lp->d_nsectors;
230 	lp->d_npartitions = 1;
231 	lp->d_partitions[0].p_offset = 0;
232 	lp->d_partitions[0].p_size = LABELSECTOR + 1;
233 	lp->d_rpm = status.rpm;
234 	lp->d_typename[0] = 'h';
235 	lp->d_typename[1] = 'd';
236 	lp->d_typename[2] = '\0';
237 #ifdef COMPAT_42
238 	dk->dk_def_cyl = status.def_cyl;
239 #endif
240 	return(1);
241 }
242 
243 hdattach(vi)
244 	register struct vba_device *vi;
245 {
246 	register struct dksoftc *dk;
247 	register struct disklabel *lp;
248 	register int unit;
249 
250 	unit = vi->ui_unit;
251 	if (hdinit(hdminor(unit, 0), 0)) {
252 		printf(": unknown drive type");
253 		return;
254 	}
255 	dk = &dksoftc[unit];
256 	lp = &dk->dk_label;
257 	hd_setsecsize(dk, lp);
258 	if (dk->dk_state == OPEN)
259 		printf(": %s <secsize %d, ntrak %d, ncyl %d, nsec %d>",
260 		    lp->d_typename, lp->d_secsize, lp->d_ntracks,
261 		    lp->d_ncylinders, lp->d_nsectors);
262 
263 	/*
264 	 * (60 / rpm) / (sectors per track * (bytes per sector / 2))
265 	 */
266 	if (vi->ui_dk >= 0)
267 		dk_mspw[vi->ui_dk] = 120.0 /
268 		    (lp->d_rpm * lp->d_nsectors * lp->d_secsize);
269 #ifdef notyet
270 	addswap(makedev(HDMAJOR, hdminor(unit, 0)), lp);
271 #endif
272 }
273 
274 hdopen(dev, flags, fmt)
275 	dev_t dev;
276 	int flags, fmt;
277 {
278 	register struct disklabel *lp;
279 	register struct dksoftc *dk;
280 	register struct partition *pp;
281 	register int unit;
282 	struct vba_device *vi;
283 	int s, error, part = hdpart(dev), mask = 1 << part;
284 	daddr_t start, end;
285 
286 	unit = hdunit(dev);
287 	if (unit >= NHD || (vi = hddinfo[unit]) == 0 || vi->ui_alive == 0)
288 		return(ENXIO);
289 	dk = &dksoftc[unit];
290 	lp = &dk->dk_label;
291 	s = spl7();
292 	while (dk->dk_state != OPEN && dk->dk_state != OPENRAW &&
293 	    dk->dk_state != CLOSED)
294 		sleep((caddr_t)dk, PZERO+1);
295 	splx(s);
296 	if (dk->dk_state != OPEN && dk->dk_state != OPENRAW)
297 		if (error = hdinit(dev, flags))
298 			return(error);
299 
300 	if (hdcwstart == 0) {
301 		timeout(hdcwatch, (caddr_t)0, hz);
302 		hdcwstart++;
303 	}
304 	/*
305 	 * Warn if a partion is opened that overlaps another partition
306 	 * which is open unless one is the "raw" partition (whole disk).
307 	 */
308 #define	RAWPART		8		/* 'x' partition */	/* XXX */
309 	if ((dk->dk_openpart & mask) == 0 && part != RAWPART) {
310 		pp = &lp->d_partitions[part];
311 		start = pp->p_offset;
312 		end = pp->p_offset + pp->p_size;
313 		for (pp = lp->d_partitions;
314 		     pp < &lp->d_partitions[lp->d_npartitions]; pp++) {
315 			if (pp->p_offset + pp->p_size <= start ||
316 			    pp->p_offset >= end)
317 				continue;
318 			if (pp - lp->d_partitions == RAWPART)
319 				continue;
320 			if (dk->dk_openpart & (1 << (pp - lp->d_partitions)))
321 				log(LOG_WARNING,
322 				    "hd%d%c: overlaps open partition (%c)\n",
323 				    unit, part + 'a',
324 				    pp - lp->d_partitions + 'a');
325 		}
326 	}
327 	if (part >= lp->d_npartitions)
328 		return(ENXIO);
329 	dk->dk_openpart |= mask;
330 	switch (fmt) {
331 	case S_IFCHR:
332 		dk->dk_copenpart |= mask;
333 		break;
334 	case S_IFBLK:
335 		dk->dk_bopenpart |= mask;
336 		break;
337 	}
338 	return(0);
339 }
340 
341 /* ARGSUSED */
342 hdclose(dev, flags, fmt)
343 	dev_t dev;
344 	int flags, fmt;
345 {
346 	register struct dksoftc *dk;
347 	int mask;
348 
349 	dk = &dksoftc[hdunit(dev)];
350 	mask = 1 << hdpart(dev);
351 	switch (fmt) {
352 	case S_IFCHR:
353 		dk->dk_copenpart &= ~mask;
354 		break;
355 	case S_IFBLK:
356 		dk->dk_bopenpart &= ~mask;
357 		break;
358 	}
359 	if (((dk->dk_copenpart | dk->dk_bopenpart) & mask) == 0)
360 		dk->dk_openpart &= ~mask;
361 	/*
362 	 * Should wait for i/o to complete on this partition
363 	 * even if others are open, but wait for work on blkflush().
364 	 */
365 	if (dk->dk_openpart == 0) {
366 		int s = spl7();
367 		while (dk->dk_utab.b_actf)
368 			sleep((caddr_t)dk, PZERO-1);
369 		splx(s);
370 		dk->dk_state = CLOSED;
371 		dk->dk_wlabel = 0;
372 	}
373 	return(0);
374 }
375 
376 hdinit(dev, flags)
377 	dev_t dev;
378 	int flags;
379 {
380 	register struct dksoftc *dk;
381 	register struct disklabel *lp;
382 	struct vba_device *vi;
383 	int error, unit;
384 	char *msg, *readdisklabel();
385 	extern int cold;
386 
387 	vi = hddinfo[unit = hdunit(dev)];
388 	dk = &dksoftc[unit];
389 	dk->dk_unit = vi->ui_slave;
390 	dk->dk_ctlr = vi->ui_ctlr;
391 
392 	if (flags & O_NDELAY) {
393 		dk->dk_state = OPENRAW;
394 		return(0);
395 	}
396 
397 	error = 0;
398 	lp = &dk->dk_label;
399 	dk->dk_state = RDLABEL;
400 	if (msg = readdisklabel(dev, hdstrategy, lp)) {
401 		if (cold) {
402 			printf(": %s\n", msg);
403 			dk->dk_state = CLOSED;
404 		} else {
405 			log(LOG_ERR, "hd%d: %s\n", unit, msg);
406 			dk->dk_state = OPENRAW;
407 		}
408 #ifdef COMPAT_42
409 		hdclock(vi->ui_ctlr);
410 		if (!(error = hdreadgeometry(dk)))
411 			dk->dk_state = OPEN;
412 		hdcunlock(vi->ui_ctlr);
413 #endif
414 	} else
415 		dk->dk_state = OPEN;
416 	wakeup((caddr_t)dk);
417 	return(error);
418 }
419 
420 hd_setsecsize(dk, lp)
421 	register struct dksoftc *dk;
422 	struct disklabel *lp;
423 {
424 	register int mul;
425 
426 	/*
427 	 * Calculate scaling shift for mapping
428 	 * DEV_BSIZE blocks to drive sectors.
429 	 */
430 	mul = DEV_BSIZE / lp->d_secsize;
431 	dk->dk_bshift = 0;
432 	while ((mul >>= 1) > 0)
433 		dk->dk_bshift++;
434 }
435 
436 /* ARGSUSED */
437 hddgo(vm)
438 	struct vba_device *vm;
439 {}
440 
441 extern int name_ext;
442 hdstrategy(bp)
443 	register struct buf *bp;
444 {
445 	register struct vba_device *vi;
446 	register struct disklabel *lp;
447 	register struct dksoftc *dk;
448 	struct buf *dp;
449 	register int unit;
450 	daddr_t sn, sz, maxsz;
451 	int part, s;
452 
453 	vi = hddinfo[unit = hdunit(bp->b_dev)];
454 	if (unit >= NHD || vi == 0 || vi->ui_alive == 0) {
455 		bp->b_error = ENXIO;
456 		goto bad;
457 	}
458 	dk = &dksoftc[unit];
459 	if (dk->dk_state < OPEN)
460 		goto q;
461 	if (dk->dk_state != OPEN && (bp->b_flags & B_READ) == 0) {
462 		bp->b_error = EROFS;
463 		goto bad;
464 	}
465 	part = hdpart(bp->b_dev);
466 	if ((dk->dk_openpart & (1 << part)) == 0) {
467 		bp->b_error = ENODEV;
468 		goto bad;
469 	}
470 	lp = &dk->dk_label;
471 	sz = (bp->b_bcount + lp->d_secsize - 1) / lp->d_secsize;
472 	maxsz = lp->d_partitions[part].p_size;
473 	sn = bp->b_blkno << dk->dk_bshift;
474 	if (sn + lp->d_partitions[part].p_offset <= LABELSECTOR &&
475 #if LABELSECTOR != 0
476 	    sn + lp->d_partitions[part].p_offset + sz > LABELSECTOR &&
477 #endif
478 	    (bp->b_flags & B_READ) == 0 && dk->dk_wlabel == 0) {
479 		bp->b_error = EROFS;
480 		goto bad;
481 	}
482 	if (sn < 0 || sn + sz > maxsz) {
483 		if (sn == maxsz) {
484 			bp->b_resid = bp->b_bcount;
485 			goto done;
486 		}
487 		sz = maxsz - sn;
488 		if (sz <= 0) {
489 			bp->b_error = EINVAL;
490 			goto bad;
491 		}
492 		bp->b_bcount = sz * lp->d_secsize;
493 	}
494 	bp->b_cylin = (sn + lp->d_partitions[part].p_offset) / lp->d_secpercyl;
495 
496 q:	s = spl7();
497 	dp = &dk->dk_utab;
498 	disksort(dp, bp);
499 	if (!dp->b_active) {
500 		(void)hdustart(vi);
501 		if (!vi->ui_mi->um_tab.b_active)
502 			hdcstart(vi->ui_mi);
503 	}
504 	splx(s);
505 	return;
506 bad:
507 	bp->b_flags |= B_ERROR;
508 done:
509 	biodone(bp);
510 }
511 
512 hdustart(vi)
513 	register struct vba_device *vi;
514 {
515 	register struct buf *bp, *dp;
516 	register struct vba_ctlr *vm;
517 	register struct dksoftc *dk;
518 
519 	dk = &dksoftc[vi->ui_unit];
520 	dp = &dk->dk_utab;
521 
522 	/* if queue empty, nothing to do.  impossible? */
523 	if (dp->b_actf == NULL)
524 		return;
525 
526 	/* place on controller transfer queue */
527 	vm = vi->ui_mi;
528 	if (vm->um_tab.b_actf == NULL)
529 		vm->um_tab.b_actf = dp;
530 	else
531 		vm->um_tab.b_actl->b_forw = dp;
532 	vm->um_tab.b_actl = dp;
533 	dp->b_forw = NULL;
534 	dp->b_active++;
535 }
536 
537 hdcstart(vm)
538 	register struct vba_ctlr *vm;
539 {
540 	register struct buf *bp;
541 	register struct dksoftc *dk;
542 	register struct disklabel *lp;
543 	register struct master_mcb *master;
544 	register struct mcb *mcb;
545 	struct vba_device *vi;
546 	struct hdcsoftc *hdc;
547 	struct buf *dp;
548 	int sn;
549 
550 	/* pull a request off the controller queue */
551 	for (;;) {
552 		if ((dp = vm->um_tab.b_actf) == NULL)
553 			return;
554 		if (bp = dp->b_actf)
555 			break;
556 		vm->um_tab.b_actf = dp->b_forw;
557 	}
558 
559 	/* mark controller active */
560 	vm->um_tab.b_active++;
561 
562 	vi = hddinfo[hdunit(bp->b_dev)];
563 	dk = &dksoftc[vi->ui_unit];
564 	lp = &dk->dk_label;
565 	sn = bp->b_blkno << dk->dk_bshift;
566 
567 	/* fill in mcb */
568 	mcb = &dk->dk_mcb;
569 	mcb->forw_phaddr = 0;
570 	/* mcb->priority = 0; */
571 	mcb->interrupt = 1;
572 	mcb->command = (bp->b_flags & B_READ) ? HCMD_READ:HCMD_WRITE;
573 	mcb->cyl = bp->b_cylin;
574 /* assumes partition starts on cylinder boundary */
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 	/* if there are devices ready to transfer, start the controller. */
696 	if (hdc->hdc_flags & HDC_WAIT) {
697 		hdc->hdc_flags &= ~HDC_WAIT;
698 		wakeup((caddr_t)hdc);
699 	} else if (vm->um_tab.b_actf)
700 		hdcstart(vm);
701 }
702 
703 hdioctl(dev, cmd, data, flag)
704 	dev_t dev;
705 	int cmd, flag;
706 	caddr_t data;
707 {
708 	register int unit;
709 	register struct dksoftc *dk;
710 	register struct disklabel *lp;
711 	int error;
712 
713 	unit = hdunit(dev);
714 	dk = &dksoftc[unit];
715 	lp = &dk->dk_label;
716 	error = 0;
717 	switch (cmd) {
718 	case DIOCGDINFO:
719 		*(struct disklabel *)data = *lp;
720 		break;
721 	case DIOCGPART:
722 		((struct partinfo *)data)->disklab = lp;
723 		((struct partinfo *)data)->part =
724 		    &lp->d_partitions[hdpart(dev)];
725 		break;
726 	case DIOCSDINFO:
727 		if ((flag & FWRITE) == 0)
728 			error = EBADF;
729 		else
730 			error = setdisklabel(lp, (struct disklabel *)data,
731 			    (dk->dk_state == OPENRAW) ? 0 : dk->dk_openpart);
732 		if (error == 0 && dk->dk_state == OPENRAW)
733 			dk->dk_state = OPEN;
734 		break;
735 	case DIOCWLABEL:
736 		if ((flag & FWRITE) == 0)
737 			error = EBADF;
738 		else
739 			dk->dk_wlabel = *(int *)data;
740 		break;
741 	case DIOCWDINFO:
742 		if ((flag & FWRITE) == 0)
743 			error = EBADF;
744 		else if ((error = setdisklabel(lp, (struct disklabel *)data,
745 		    (dk->dk_state == OPENRAW) ? 0 : dk->dk_openpart)) == 0) {
746 			int wlab;
747 
748 			if (error == 0 && dk->dk_state == OPENRAW)
749 				dk->dk_state = OPEN;
750 			/* simulate opening partition 0 so write succeeds */
751 			dk->dk_openpart |= (1 << 0);		/* XXX */
752 			wlab = dk->dk_wlabel;
753 			dk->dk_wlabel = 1;
754 			error = writedisklabel(dev, hdstrategy, lp);
755 			dk->dk_openpart = dk->dk_copenpart | dk->dk_bopenpart;
756 			dk->dk_wlabel = wlab;
757 		}
758 		break;
759 	default:
760 		error = ENOTTY;
761 		break;
762 	}
763 	return (error);
764 }
765 
766 /*
767  * Watch for lost interrupts.
768  */
769 hdcwatch()
770 {
771 	register struct hdcsoftc *hdc;
772 	register struct vba_ctlr **vmp;
773 	register int ctlr;
774 	int s;
775 
776 	timeout(hdcwatch, (caddr_t)0, hz);
777 	for (vmp = hdcminfo, hdc = hdcsoftc, ctlr = 0; ctlr < NHDC;
778 	    ++ctlr, ++vmp, ++hdc) {
779 		if (*vmp == 0 || (*vmp)->um_alive == 0)
780 			continue;
781 		s = spl7();
782 		if ((*vmp)->um_tab.b_active &&
783 		    hdc->hdc_wticks++ >= HDCMAXTIME) {
784 			printf("hd%d: lost interrupt\n", ctlr);
785 			hdintr(ctlr);
786 		}
787 		splx(s);
788 	}
789 }
790 
791 hddump(dev)
792 	dev_t dev;
793 {
794 	return(ENXIO);
795 }
796 
797 hdsize(dev)
798 	dev_t dev;
799 {
800 	register int unit = hdunit(dev);
801 	register struct dksoftc *dk;
802 	struct vba_device *vi;
803 	struct disklabel *lp;
804 
805 	if (unit >= NHD || (vi = hddinfo[unit]) == 0 || vi->ui_alive == 0 ||
806 	    (dk = &dksoftc[unit])->dk_state != OPEN)
807 		return (-1);
808 	lp = &dk->dk_label;
809 	return ((int)lp->d_partitions[hdpart(dev)].p_size >> dk->dk_bshift);
810 }
811 
812 hdimcb(dk)
813 	register struct dksoftc *dk;
814 {
815 	register struct master_mcb *master;
816 	register struct mcb *mcb;
817 	register struct hdcsoftc *hdc;
818 	int timeout;
819 
820 	/* fill in mcb */
821 	mcb = &dk->dk_mcb;
822 	mcb->interrupt = 0;
823 	mcb->forw_phaddr = 0;
824 	mcb->drive = dk->dk_unit;
825 
826 	hdc = &hdcsoftc[dk->dk_ctlr];
827 	master = &hdc->hdc_mcb;
828 
829 	/* fill in master mcb */
830 	master->mcw = MCL_IMMEDIATE;
831 	master->forw_phaddr = (u_long)vtoph((struct proc *)NULL, mcb);
832 	master->mcs = 0;
833 
834 	/* kick controller and wait */
835 	hdc->hdc_reg->master_mcb = (u_long)hdc->hdc_mcbp;
836 	for (timeout = 15000; timeout; --timeout) {
837 		DELAY(1000);
838 		mtpr(PADC, 0);
839 		if (master->mcs&MCS_FATALERROR) {
840 			printf("hdc%d: fatal error\n", dk->dk_ctlr);
841 			hdcerror(dk->dk_ctlr, *(u_long *)master->xstatus);
842 			return(1);
843 		}
844 		if (master->mcs&MCS_DONE)
845 			return(0);
846 	}
847 	printf("hdc%d: timed out\n", dk->dk_ctlr);
848 	return(1);
849 }
850 
851 hdcerror(ctlr, code)
852 	int ctlr;
853 	u_long code;
854 {
855 	printf("hd%d: error %lx\n", ctlr, code);
856 }
857 
858 #ifdef COMPAT_42
859 hdreadgeometry(dk)
860 	struct dksoftc *dk;
861 {
862 	static geometry_sector geometry;
863 	register struct mcb *mcb;
864 	register struct disklabel *lp;
865 	geometry_block *geo;
866 	int cnt;
867 
868 	/*
869 	 * Read the geometry block (at head = 0 sector = 0 of the drive
870 	 * definition cylinder), validate it (must have the correct version
871 	 * number, header, and checksum).
872 	 */
873 	mcb = &dk->dk_mcb;
874 	mcb->command = HCMD_READ;
875 	mcb->cyl = dk->dk_def_cyl;
876 	mcb->head = 0;
877 	mcb->sector = 0;
878 	mcb->chain[0].wcount = sizeof(geometry_sector) / sizeof(long);
879 	mcb->chain[0].memadr  = (u_long)vtoph((struct process *)0, &geometry);
880 	/* mcb->chain[0].memadr = (long)&geometry; */
881 	if (hdimcb(dk)) {
882  		printf("hd%d: can't read default geometry.\n", dk->dk_unit);
883 		return(1);
884 	}
885 	geo = &geometry.geometry_block;
886  	if (geo->version > 64000  ||  geo->version < 0) {
887  		printf("hd%d: bad default geometry version#.\n", dk->dk_unit);
888 		return(1);
889 	}
890  	if (bcmp(&geo->id[0], GB_ID, GB_ID_LEN)) {
891  		printf("hd%d: bad default geometry header.\n", dk->dk_unit);
892 		return(1);
893 	}
894 	GB_CHECKSUM(geo, cnt);
895 	if (geometry.checksum != cnt) {
896 		printf("hd%d: bad default geometry checksum.\n", dk->dk_unit);
897 		return(1);
898 	}
899 	lp = &dk->dk_label;
900 
901 	/* 1K block in Harris geometry; convert to sectors for disklabels */
902 	for (cnt = 0; cnt < GB_MAXPART; cnt++) {
903 		lp->d_partitions[cnt].p_offset =
904 		    geo->partition[cnt].start * (1024 / lp->d_secsize);
905 		lp->d_partitions[cnt].p_size =
906 		    geo->partition[cnt].length * (1024 / lp->d_secsize);
907 	}
908 	lp->d_npartitions = GB_MAXPART;
909 	return(0);
910 }
911 #endif /* COMPAT_42 */
912 #endif /* NHD */
913