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