xref: /csrg-svn/sys/tahoe/vba/hd.c (revision 37565)
133165Sbostic /*
237097Sbostic  * Copyright (c) 1988 The Regents of the University of California.
337097Sbostic  * All rights reserved.
433165Sbostic  *
537097Sbostic  * This code is derived from software contributed to Berkeley by
637097Sbostic  * Harris Corp.
737097Sbostic  *
837097Sbostic  * Redistribution and use in source and binary forms are permitted
937097Sbostic  * provided that the above copyright notice and this paragraph are
1037097Sbostic  * duplicated in all such forms and that any documentation,
1137097Sbostic  * advertising materials, and other materials related to such
1237097Sbostic  * distribution and use acknowledge that the software was developed
1337097Sbostic  * by the University of California, Berkeley.  The name of the
1437097Sbostic  * University may not be used to endorse or promote products derived
1537097Sbostic  * from this software without specific prior written permission.
1637097Sbostic  * THIS SOFTWARE IS PROVIDED ``AS IS'' AND WITHOUT ANY EXPRESS OR
1737097Sbostic  * IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED
18*37565Sbostic  * WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE.
1937097Sbostic  *
20*37565Sbostic  *	@(#)hd.c	7.4 (Berkeley) 05/01/89
2133165Sbostic  */
2233165Sbostic 
2337097Sbostic #include "hd.h"
2433165Sbostic 
2537097Sbostic #if NHD > 0
2637097Sbostic #include "param.h"
2737097Sbostic #include "buf.h"
2837097Sbostic #include "conf.h"
2937097Sbostic #include "dir.h"
3037097Sbostic #include "dkstat.h"
3137097Sbostic #include "disklabel.h"
3237097Sbostic #include "file.h"
3337097Sbostic #include "systm.h"
3437097Sbostic #include "vmmac.h"
3537097Sbostic #include "time.h"
3637097Sbostic #include "proc.h"
3737097Sbostic #include "uio.h"
3837097Sbostic #include "syslog.h"
3937097Sbostic #include "kernel.h"
4037097Sbostic #include "ioctl.h"
4137097Sbostic #include "stat.h"
4237097Sbostic #include "errno.h"
4337097Sbostic 
4437097Sbostic #include "../tahoe/cpu.h"
4537097Sbostic #include "../tahoe/mtpr.h"
4637097Sbostic 
4737097Sbostic #include "../tahoevba/vbavar.h"
4837097Sbostic #include "../tahoevba/hdreg.h"
4937097Sbostic 
5037097Sbostic #define	b_cylin	b_resid
5137097Sbostic 
5237097Sbostic #define	hdunit(dev)		(minor(dev)>>3)
5337097Sbostic #define	hdpart(dev)		(minor(dev)&0x07)
5437097Sbostic #define	hdminor(unit, part)	(((unit)<<3)|(part))
5537097Sbostic 
5637097Sbostic struct vba_ctlr *hdcminfo[NHDC];
5737097Sbostic struct vba_device *hddinfo[NHD];
5837097Sbostic int hdcprobe(), hdslave(), hdattach(), hddgo(), hdstrategy();
5937097Sbostic struct vba_driver hdcdriver =
6037097Sbostic     { hdcprobe, hdslave, hdattach, hddgo, 0L, "hd", hddinfo, "hdc", hdcminfo };
6137097Sbostic 
6233165Sbostic /*
6337097Sbostic  * Per-controller state.
6433165Sbostic  */
6537097Sbostic struct hdcsoftc {
6637097Sbostic 	u_short	hdc_flags;
6737097Sbostic #define	HDC_INIT	0x01	/* controller initialized */
6837097Sbostic #define	HDC_STARTED	0x02	/* start command issued */
6937097Sbostic #define	HDC_LOCKED	0x04	/* locked for direct controller access */
7037097Sbostic #define	HDC_WAIT	0x08	/* someone needs direct controller access */
7137097Sbostic 	u_short	hdc_wticks;		/* timeout */
7237097Sbostic 	struct master_mcb *hdc_mcbp;	/* address of controller mcb */
7337097Sbostic 	struct registers *hdc_reg;	/* base address of i/o regs */
7437097Sbostic 	struct vb_buf hdc_rbuf;		/* vba resources */
7537097Sbostic 	struct master_mcb hdc_mcb;	/* controller mcb */
7637097Sbostic } hdcsoftc[NHDC];
7733165Sbostic 
7837097Sbostic #define	HDCMAXTIME	20		/* max time for operation, sec. */
7937097Sbostic #define	HDCINTERRUPT	0xf0		/* interrupt vector */
8033165Sbostic 
8133165Sbostic /*
8237097Sbostic  * Per-drive state; probably everything should be "hd_", not "dk_",
8337097Sbostic  * but it's not worth it, and dk is a better mnemonic for disk anyway.
8433165Sbostic  */
8537097Sbostic struct dksoftc {
8637097Sbostic #ifdef COMPAT_42
8737097Sbostic 	u_short	dk_def_cyl;	/* definition track cylinder address */
8837097Sbostic #endif
8937097Sbostic 	int	dk_state;	/* open fsm */
9037097Sbostic 	u_short	dk_bshift;	/* shift for * (DEV_BSIZE / sectorsize) XXX */
9137097Sbostic 	int	dk_wlabel;	/* if label sector is writeable */
9237097Sbostic 	u_long	dk_copenpart;	/* character units open on this drive */
9337097Sbostic 	u_long	dk_bopenpart;	/* block units open on this drive */
9437097Sbostic 	u_long	dk_openpart;	/* all units open on this drive */
9537097Sbostic 	int	dk_unit;	/* unit# */
9637097Sbostic 	int	dk_ctlr;	/* controller# */
9737097Sbostic 	int	dk_format;	/* if format program is using disk */
9837097Sbostic 	struct buf dk_utab;		/* i/o queue header */
9937097Sbostic 	struct disklabel dk_label;	/* disklabel for this disk */
10037097Sbostic 	struct mcb dk_mcb;		/* disk mcb */
10137097Sbostic } dksoftc[NHD];
10233165Sbostic 
10333165Sbostic /*
10437097Sbostic  * Drive states.  Used during steps of open/initialization.
10537097Sbostic  * States < OPEN (> 0) are transient, during an open operation.
10637097Sbostic  * OPENRAW is used for unlabeled disks, to allow format operations.
10733165Sbostic  */
10837097Sbostic #define	CLOSED		0		/* disk is closed */
10937097Sbostic #define	WANTOPEN	1		/* open requested, not started */
11037097Sbostic #define	WANTOPENRAW	2		/* open requested, no label */
11137097Sbostic #define	RDLABEL		3		/* reading pack label */
11237097Sbostic #define	OPEN		4		/* intialized and ready */
11337097Sbostic #define	OPENRAW		5		/* open, no label */
11433165Sbostic 
11537097Sbostic int hdcwstart, hdcwatch();
11633165Sbostic 
11737097Sbostic /* see if the controller is really there, if so, init it. */
11837097Sbostic /* ARGSUSED */
11937097Sbostic hdcprobe(reg, vm)
12037097Sbostic 	caddr_t reg;
12137097Sbostic 	/* register */ struct vba_ctlr *vm;
12233165Sbostic {
12337097Sbostic 	register int br, cvec;		/* must be r12, r11 */
12437097Sbostic 	register struct hdcsoftc *hdc;
12537097Sbostic 	static struct module_id id;
12637097Sbostic 	struct pte *dummypte;
12737097Sbostic 	caddr_t putl;
12833165Sbostic 
12937097Sbostic 	/* initialize the hdc controller structure. */
13037097Sbostic 	hdc = &hdcsoftc[vm->um_ctlr];
13137097Sbostic 	if (!vbmemalloc(1, reg, &dummypte, &putl)) {
13237097Sbostic 		printf("hdc%d: vbmemalloc failed.\n", vm->um_ctlr);
13337097Sbostic 		return(0);
13433165Sbostic 	}
13537097Sbostic 	hdc->hdc_reg = (struct registers *)putl;
13633165Sbostic 
13733165Sbostic 	/*
13837097Sbostic 	 * try and ping the MID register; side effect of wbadaddr is to read
13937097Sbostic 	 * the module id; the controller is bad if it's not an hdc, the hdc's
14037097Sbostic 	 * writeable control store is not loaded, or the hdc failed the
14137097Sbostic 	 * functional integrity test;
14233165Sbostic 	 */
14337097Sbostic 	if (wbadaddr(&hdc->hdc_reg->module_id, 4,
14437097Sbostic 	    vtoph((struct process *)NULL, &id))) {
14537097Sbostic 		printf("hdc%d: can't access module register.\n", vm->um_ctlr);
14637097Sbostic 		return(0);
14737097Sbostic 	}
14837097Sbostic 	DELAY(10000);
14937097Sbostic 	mtpr(PADC, 0);
15037097Sbostic 	if (id.module_id != (u_char)HDC_MID) {
15137097Sbostic 		printf("hdc%d: bad module id; id = %x.\n",
15237097Sbostic 		    vm->um_ctlr, id.module_id);
15337097Sbostic 		return(0);
15437097Sbostic 	}
15537097Sbostic 	if (id.code_rev == (u_char)0xff) {
15637097Sbostic 		printf("hdc%d: micro-code not loaded.\n", vm->um_ctlr);
15737097Sbostic 		return(0);
15837097Sbostic 	}
15937097Sbostic 	if (id.fit != (u_char)0xff) {
16037097Sbostic 		printf("hdc%d: FIT test failed.\n", vm->um_ctlr);
16137097Sbostic 		return(0);
16237097Sbostic 	}
16333165Sbostic 
16437097Sbostic 	/* reset that pup; flag as inited */
16537097Sbostic 	hdc->hdc_reg->soft_reset = 0;
16637097Sbostic 	DELAY(1000000);
16737097Sbostic 	hdc->hdc_flags |= HDC_INIT;
16833165Sbostic 
16937097Sbostic 	/* allocate page tables and i/o buffer. */
17037097Sbostic 	if (!vbainit(&hdc->hdc_rbuf, MAXPHYS, VB_32BIT|VB_SCATTER)) {
17137097Sbostic 		printf("hdc%d: vbainit failed\n", vm->um_ctlr);
17237097Sbostic 		return (0);
17337097Sbostic 	}
17433165Sbostic 
17537097Sbostic 	/* set pointer to master control block */
17637097Sbostic 	hdc->hdc_mcbp =
17737097Sbostic 	    (struct master_mcb *)vtoph((struct proc *)NULL, &hdc->hdc_mcb);
17837097Sbostic 
17937097Sbostic 	br = 0x17, cvec = HDCINTERRUPT + vm->um_ctlr;		/* XXX */
18037097Sbostic 	return(sizeof(struct registers));
18133165Sbostic }
18233165Sbostic 
18337097Sbostic /* ARGSUSED */
18437097Sbostic hdslave(vi, vdaddr)
18537097Sbostic 	struct vba_device *vi;
18637097Sbostic 	struct vddevice *vdaddr;
18733165Sbostic {
18837097Sbostic 	register struct mcb *mcb;
18937097Sbostic 	register struct disklabel *lp;
19037097Sbostic 	register struct dksoftc *dk;
19137097Sbostic 	static struct status status;
19233165Sbostic 
19337097Sbostic 	dk = &dksoftc[vi->ui_unit];
19437097Sbostic 	dk->dk_unit = vi->ui_unit;
19537097Sbostic 	dk->dk_ctlr = vi->ui_ctlr;
19633165Sbostic 
19737097Sbostic 	mcb = &dk->dk_mcb;
19837097Sbostic 	mcb->command = HCMD_STATUS;
19937097Sbostic 	mcb->chain[0].wcount = sizeof(struct status) / sizeof(long);
20037097Sbostic 	mcb->chain[0].memadr  = (u_long)vtoph((struct process *)0, &status);
20137097Sbostic 	if (hdimcb(dk)) {
20237097Sbostic 		printf(" (no status)\n");
20337097Sbostic 		return(0);
20433165Sbostic 	}
20533165Sbostic 
20633165Sbostic 	/*
20737097Sbostic 	 * Report the drive down if anything in the drive status looks bad.
20837097Sbostic 	 * If the drive is offline and it is not on cylinder, then the drive
20937097Sbostic 	 * is not there.  If there is a fault condition, the hdc will try to
21037097Sbostic 	 * clear it when we read the disklabel information.
21133165Sbostic 	 */
21237097Sbostic 	if (!(status.drs&DRS_ONLINE)) {
21337097Sbostic 		if (status.drs&DRS_ON_CYLINDER)
21437097Sbostic 			printf(" (not online)\n");
21537097Sbostic 		return(0);
21633165Sbostic 	}
21737097Sbostic 	if (status.drs&DRS_FAULT)
21837097Sbostic 		printf(" (clearing fault)");
21933165Sbostic 
22037097Sbostic 	lp = &dk->dk_label;
22137097Sbostic #ifdef RAW_SIZE
22237097Sbostic 	lp->d_secsize = status.bytes_per_sec;
22337097Sbostic #else
22437097Sbostic 	lp->d_secsize = 512;
22537097Sbostic #endif
22637097Sbostic 	lp->d_nsectors = status.max_sector + 1;
22737097Sbostic 	lp->d_ntracks = status.max_head + 1;
22837097Sbostic 	lp->d_ncylinders = status.max_cyl + 1;
22937097Sbostic 	lp->d_secpercyl = lp->d_ntracks * lp->d_nsectors;
23037097Sbostic 	lp->d_npartitions = 1;
23137097Sbostic 	lp->d_partitions[0].p_offset = 0;
23237097Sbostic 	lp->d_partitions[0].p_size = LABELSECTOR + 1;
23337097Sbostic 	lp->d_rpm = status.rpm;
23437097Sbostic 	lp->d_typename[0] = 'h';
23537097Sbostic 	lp->d_typename[1] = 'd';
23637097Sbostic 	lp->d_typename[2] = '\0';
23737097Sbostic #ifdef COMPAT_42
23837097Sbostic 	dk->dk_def_cyl = status.def_cyl;
23937097Sbostic #endif
24037097Sbostic 	return(1);
24133165Sbostic }
24233165Sbostic 
24337097Sbostic hdattach(vi)
24437097Sbostic 	register struct vba_device *vi;
24533165Sbostic {
24637097Sbostic 	register struct dksoftc *dk;
24737097Sbostic 	register struct disklabel *lp;
24837097Sbostic 	register int unit;
24933165Sbostic 
25037097Sbostic 	unit = vi->ui_unit;
25137097Sbostic 	if (hdinit(hdminor(unit, 0), 0)) {
25237097Sbostic 		printf(": unknown drive type");
25337097Sbostic 		return;
25433165Sbostic 	}
25537097Sbostic 	dk = &dksoftc[unit];
25637097Sbostic 	lp = &dk->dk_label;
25737097Sbostic 	hd_setsecsize(dk, lp);
25837097Sbostic 	if (dk->dk_state == OPEN)
25937097Sbostic 		printf(": %s <secsize %d, ntrak %d, ncyl %d, nsec %d>",
26037097Sbostic 		    lp->d_typename, lp->d_secsize, lp->d_ntracks,
26137097Sbostic 		    lp->d_ncylinders, lp->d_nsectors);
26233165Sbostic 
26337097Sbostic 	/*
26437097Sbostic 	 * (60 / rpm) / (sectors per track * (bytes per sector / 2))
26537097Sbostic 	 */
26637097Sbostic 	if (vi->ui_dk >= 0)
26737097Sbostic 		dk_mspw[vi->ui_dk] = 120.0 /
26837097Sbostic 		    (lp->d_rpm * lp->d_nsectors * lp->d_secsize);
26937097Sbostic #ifdef notyet
27037097Sbostic 	addswap(makedev(HDMAJOR, hdminor(unit, 0)), lp);
27137097Sbostic #endif
27237097Sbostic }
27333165Sbostic 
27437097Sbostic hdopen(dev, flags, fmt)
27537097Sbostic 	dev_t dev;
27637097Sbostic 	int flags, fmt;
27733165Sbostic {
27837097Sbostic 	register struct disklabel *lp;
27937097Sbostic 	register struct dksoftc *dk;
28037097Sbostic 	register struct partition *pp;
28137097Sbostic 	register int unit;
28237097Sbostic 	struct vba_device *vi;
28337097Sbostic 	int s, error, part = hdpart(dev), mask = 1 << part;
28437097Sbostic 	daddr_t start, end;
28533165Sbostic 
28637097Sbostic 	unit = hdunit(dev);
28737097Sbostic 	if (unit >= NHD || (vi = hddinfo[unit]) == 0 || vi->ui_alive == 0)
28837097Sbostic 		return(ENXIO);
28937097Sbostic 	dk = &dksoftc[unit];
29037097Sbostic 	lp = &dk->dk_label;
29137097Sbostic 	s = spl7();
29237097Sbostic 	while (dk->dk_state != OPEN && dk->dk_state != OPENRAW &&
29337097Sbostic 	    dk->dk_state != CLOSED)
29437097Sbostic 		sleep((caddr_t)dk, PZERO+1);
29537097Sbostic 	splx(s);
29637097Sbostic 	if (dk->dk_state != OPEN && dk->dk_state != OPENRAW)
29737097Sbostic 		if (error = hdinit(dev, flags))
29837097Sbostic 			return(error);
29933165Sbostic 
30037097Sbostic 	if (hdcwstart == 0) {
30137097Sbostic 		timeout(hdcwatch, (caddr_t)0, hz);
30237097Sbostic 		hdcwstart++;
30337097Sbostic 	}
30433165Sbostic 	/*
30537097Sbostic 	 * Warn if a partion is opened that overlaps another partition
30637097Sbostic 	 * which is open unless one is the "raw" partition (whole disk).
30733165Sbostic 	 */
30837097Sbostic #define	RAWPART		8		/* 'x' partition */	/* XXX */
30937097Sbostic 	if ((dk->dk_openpart & mask) == 0 && part != RAWPART) {
31037097Sbostic 		pp = &lp->d_partitions[part];
31137097Sbostic 		start = pp->p_offset;
31237097Sbostic 		end = pp->p_offset + pp->p_size;
31337097Sbostic 		for (pp = lp->d_partitions;
31437097Sbostic 		     pp < &lp->d_partitions[lp->d_npartitions]; pp++) {
31537097Sbostic 			if (pp->p_offset + pp->p_size <= start ||
31637097Sbostic 			    pp->p_offset >= end)
31737097Sbostic 				continue;
31837097Sbostic 			if (pp - lp->d_partitions == RAWPART)
31937097Sbostic 				continue;
32037097Sbostic 			if (dk->dk_openpart & (1 << (pp - lp->d_partitions)))
32137097Sbostic 				log(LOG_WARNING,
32237097Sbostic 				    "hd%d%c: overlaps open partition (%c)\n",
32337097Sbostic 				    unit, part + 'a',
32437097Sbostic 				    pp - lp->d_partitions + 'a');
32537097Sbostic 		}
32637097Sbostic 	}
32737097Sbostic 	if (part >= lp->d_npartitions)
32837097Sbostic 		return(ENXIO);
32937097Sbostic 	dk->dk_openpart |= mask;
33037097Sbostic 	switch (fmt) {
33137097Sbostic 	case S_IFCHR:
33237097Sbostic 		dk->dk_copenpart |= mask;
33333165Sbostic 		break;
33437097Sbostic 	case S_IFBLK:
33537097Sbostic 		dk->dk_bopenpart |= mask;
33637097Sbostic 		break;
33733165Sbostic 	}
33837097Sbostic 	return(0);
33933165Sbostic }
34033165Sbostic 
34137097Sbostic /* ARGSUSED */
34237097Sbostic hdclose(dev, flags, fmt)
34337097Sbostic 	dev_t dev;
34437097Sbostic 	int flags, fmt;
34533165Sbostic {
34637097Sbostic 	register struct dksoftc *dk;
34737097Sbostic 	int mask;
34833165Sbostic 
34937097Sbostic 	dk = &dksoftc[hdunit(dev)];
35037097Sbostic 	mask = 1 << hdpart(dev);
35137097Sbostic 	switch (fmt) {
35237097Sbostic 	case S_IFCHR:
35337097Sbostic 		dk->dk_copenpart &= ~mask;
35437097Sbostic 		break;
35537097Sbostic 	case S_IFBLK:
35637097Sbostic 		dk->dk_bopenpart &= ~mask;
35737097Sbostic 		break;
35833165Sbostic 	}
35937097Sbostic 	if (((dk->dk_copenpart | dk->dk_bopenpart) & mask) == 0)
36037097Sbostic 		dk->dk_openpart &= ~mask;
36133165Sbostic 	/*
36237097Sbostic 	 * Should wait for i/o to complete on this partition
36337097Sbostic 	 * even if others are open, but wait for work on blkflush().
36433165Sbostic 	 */
36537097Sbostic 	if (dk->dk_openpart == 0) {
36637097Sbostic 		int s = spl7();
36737097Sbostic 		while (dk->dk_utab.b_actf)
36837097Sbostic 			sleep((caddr_t)dk, PZERO-1);
36937097Sbostic 		splx(s);
37037097Sbostic 		dk->dk_state = CLOSED;
37137097Sbostic 		dk->dk_wlabel = 0;
37233165Sbostic 	}
37337097Sbostic 	return(0);
37437097Sbostic }
37533165Sbostic 
37637097Sbostic hdinit(dev, flags)
37737097Sbostic 	dev_t dev;
37837097Sbostic 	int flags;
37937097Sbostic {
38037097Sbostic 	register struct dksoftc *dk;
38137097Sbostic 	register struct disklabel *lp;
38237097Sbostic 	struct vba_device *vi;
38337097Sbostic 	int error, unit;
38437097Sbostic 	char *msg, *readdisklabel();
38537097Sbostic 	extern int cold;
38633165Sbostic 
38737097Sbostic 	vi = hddinfo[unit = hdunit(dev)];
38837097Sbostic 	dk = &dksoftc[unit];
38937097Sbostic 	dk->dk_unit = vi->ui_slave;
39037097Sbostic 	dk->dk_ctlr = vi->ui_ctlr;
39133165Sbostic 
39237097Sbostic 	if (flags & O_NDELAY) {
39337097Sbostic 		dk->dk_state = OPENRAW;
39437097Sbostic 		return(0);
39537097Sbostic 	}
39633165Sbostic 
39737097Sbostic 	error = 0;
39837097Sbostic 	lp = &dk->dk_label;
39937097Sbostic 	dk->dk_state = RDLABEL;
40037097Sbostic 	if (msg = readdisklabel(dev, hdstrategy, lp)) {
40137097Sbostic 		if (cold) {
40237097Sbostic 			printf(": %s\n", msg);
40337097Sbostic 			dk->dk_state = CLOSED;
40437097Sbostic 		} else {
40537097Sbostic 			log(LOG_ERR, "hd%d: %s\n", unit, msg);
40637097Sbostic 			dk->dk_state = OPENRAW;
40733165Sbostic 		}
40837097Sbostic #ifdef COMPAT_42
40937097Sbostic 		hdclock(vi->ui_ctlr);
41037097Sbostic 		if (!(error = hdreadgeometry(dk)))
41137097Sbostic 			dk->dk_state = OPEN;
41237097Sbostic 		hdcunlock(vi->ui_ctlr);
41337097Sbostic #endif
41437097Sbostic 	} else
41537097Sbostic 		dk->dk_state = OPEN;
41637097Sbostic 	wakeup((caddr_t)dk);
41737097Sbostic 	return(error);
41837097Sbostic }
41933165Sbostic 
42037097Sbostic hd_setsecsize(dk, lp)
42137097Sbostic 	register struct dksoftc *dk;
42237097Sbostic 	struct disklabel *lp;
42337097Sbostic {
42437097Sbostic 	register int mul;
42537097Sbostic 
42633165Sbostic 	/*
42737097Sbostic 	 * Calculate scaling shift for mapping
42837097Sbostic 	 * DEV_BSIZE blocks to drive sectors.
42933165Sbostic 	 */
43037097Sbostic 	mul = DEV_BSIZE / lp->d_secsize;
43137097Sbostic 	dk->dk_bshift = 0;
43237097Sbostic 	while ((mul >>= 1) > 0)
43337097Sbostic 		dk->dk_bshift++;
43437097Sbostic }
43533165Sbostic 
43637097Sbostic /* ARGSUSED */
43737097Sbostic hddgo(vm)
43837097Sbostic 	struct vba_device *vm;
43937097Sbostic {}
44033165Sbostic 
44137097Sbostic extern int name_ext;
44237097Sbostic hdstrategy(bp)
44337097Sbostic 	register struct buf *bp;
44437097Sbostic {
44537097Sbostic 	register struct vba_device *vi;
44637097Sbostic 	register struct disklabel *lp;
44737097Sbostic 	register struct dksoftc *dk;
44837097Sbostic 	struct buf *dp;
44937097Sbostic 	register int unit;
45037097Sbostic 	daddr_t sn, sz, maxsz;
45137097Sbostic 	int part, s;
45233165Sbostic 
45337097Sbostic 	vi = hddinfo[unit = hdunit(bp->b_dev)];
45437097Sbostic 	if (unit >= NHD || vi == 0 || vi->ui_alive == 0) {
45537097Sbostic 		bp->b_error = ENXIO;
45637097Sbostic 		goto bad;
45737097Sbostic 	}
45837097Sbostic 	dk = &dksoftc[unit];
45937097Sbostic 	if (dk->dk_state < OPEN)
46037097Sbostic 		goto q;
46137097Sbostic 	if (dk->dk_state != OPEN && (bp->b_flags & B_READ) == 0) {
46237097Sbostic 		bp->b_error = EROFS;
46337097Sbostic 		goto bad;
46437097Sbostic 	}
46537097Sbostic 	part = hdpart(bp->b_dev);
46637097Sbostic 	if ((dk->dk_openpart & (1 << part)) == 0) {
46737097Sbostic 		bp->b_error = ENODEV;
46837097Sbostic 		goto bad;
46937097Sbostic 	}
47037097Sbostic 	lp = &dk->dk_label;
47137097Sbostic 	sz = (bp->b_bcount + lp->d_secsize - 1) / lp->d_secsize;
47237097Sbostic 	maxsz = lp->d_partitions[part].p_size;
47337097Sbostic 	sn = bp->b_blkno << dk->dk_bshift;
47437097Sbostic 	if (sn + lp->d_partitions[part].p_offset <= LABELSECTOR &&
47537097Sbostic #if LABELSECTOR != 0
47637097Sbostic 	    sn + lp->d_partitions[part].p_offset + sz > LABELSECTOR &&
47733165Sbostic #endif
47837097Sbostic 	    (bp->b_flags & B_READ) == 0 && dk->dk_wlabel == 0) {
47937097Sbostic 		bp->b_error = EROFS;
48037097Sbostic 		goto bad;
48133165Sbostic 	}
48237097Sbostic 	if (sn < 0 || sn + sz > maxsz) {
48337097Sbostic 		if (sn == maxsz) {
48437097Sbostic 			bp->b_resid = bp->b_bcount;
48537097Sbostic 			goto done;
48637097Sbostic 		}
48737097Sbostic 		sz = maxsz - sn;
48837097Sbostic 		if (sz <= 0) {
48937097Sbostic 			bp->b_error = EINVAL;
49037097Sbostic 			goto bad;
49137097Sbostic 		}
49237097Sbostic 		bp->b_bcount = sz * lp->d_secsize;
49337097Sbostic 	}
49437097Sbostic 	bp->b_cylin = (sn + lp->d_partitions[part].p_offset) / lp->d_secpercyl;
49533165Sbostic 
49637097Sbostic q:	s = spl7();
49737097Sbostic 	dp = &dk->dk_utab;
49837097Sbostic 	disksort(dp, bp);
49937097Sbostic 	if (!dp->b_active) {
50037097Sbostic 		(void)hdustart(vi);
50137097Sbostic 		if (!vi->ui_mi->um_tab.b_active)
50237097Sbostic 			hdcstart(vi->ui_mi);
50337097Sbostic 	}
50437097Sbostic 	splx(s);
50533165Sbostic 	return;
50637097Sbostic bad:
50737097Sbostic 	bp->b_flags |= B_ERROR;
50837097Sbostic done:
50937097Sbostic 	biodone(bp);
51033165Sbostic }
51133165Sbostic 
51237097Sbostic hdustart(vi)
51337097Sbostic 	register struct vba_device *vi;
51433165Sbostic {
51537097Sbostic 	register struct buf *bp, *dp;
51637097Sbostic 	register struct vba_ctlr *vm;
51737097Sbostic 	register struct dksoftc *dk;
51833165Sbostic 
51937097Sbostic 	dk = &dksoftc[vi->ui_unit];
52037097Sbostic 	dp = &dk->dk_utab;
52133165Sbostic 
52237097Sbostic 	/* if queue empty, nothing to do.  impossible? */
52337097Sbostic 	if (dp->b_actf == NULL)
52437097Sbostic 		return;
52533165Sbostic 
52637097Sbostic 	/* place on controller transfer queue */
52737097Sbostic 	vm = vi->ui_mi;
52837097Sbostic 	if (vm->um_tab.b_actf == NULL)
52937097Sbostic 		vm->um_tab.b_actf = dp;
53037097Sbostic 	else
53137097Sbostic 		vm->um_tab.b_actl->b_forw = dp;
53237097Sbostic 	vm->um_tab.b_actl = dp;
53337097Sbostic 	dp->b_forw = NULL;
53437097Sbostic 	dp->b_active++;
53537097Sbostic }
53633165Sbostic 
53737097Sbostic hdcstart(vm)
53837097Sbostic 	register struct vba_ctlr *vm;
53937097Sbostic {
54037097Sbostic 	register struct buf *bp;
54137097Sbostic 	register struct dksoftc *dk;
54237097Sbostic 	register struct disklabel *lp;
54337097Sbostic 	register struct master_mcb *master;
54437097Sbostic 	register struct mcb *mcb;
54537097Sbostic 	struct vba_device *vi;
54637097Sbostic 	struct hdcsoftc *hdc;
54737097Sbostic 	struct buf *dp;
54837097Sbostic 	int sn;
54933165Sbostic 
55037097Sbostic 	/* pull a request off the controller queue */
55137097Sbostic 	for (;;) {
55237097Sbostic 		if ((dp = vm->um_tab.b_actf) == NULL)
55337097Sbostic 			return;
55437097Sbostic 		if (bp = dp->b_actf)
55537097Sbostic 			break;
55637097Sbostic 		vm->um_tab.b_actf = dp->b_forw;
55733165Sbostic 	}
55833165Sbostic 
55937097Sbostic 	/* mark controller active */
56037097Sbostic 	vm->um_tab.b_active++;
56133165Sbostic 
56237097Sbostic 	vi = hddinfo[hdunit(bp->b_dev)];
56337097Sbostic 	dk = &dksoftc[vi->ui_unit];
56437097Sbostic 	lp = &dk->dk_label;
56537097Sbostic 	sn = bp->b_blkno << dk->dk_bshift;
56633165Sbostic 
56737097Sbostic 	/* fill in mcb */
56837097Sbostic 	mcb = &dk->dk_mcb;
56937097Sbostic 	mcb->forw_phaddr = 0;
57037097Sbostic 	/* mcb->priority = 0; */
57137097Sbostic 	mcb->interrupt = 1;
57237097Sbostic 	mcb->command = (bp->b_flags & B_READ) ? HCMD_READ:HCMD_WRITE;
573*37565Sbostic 	mcb->cyl = bp->b_cylin;
574*37565Sbostic /* assumes partition starts on cylinder boundary */
57537097Sbostic 	mcb->head = (sn / lp->d_nsectors) % lp->d_ntracks;
57637097Sbostic 	mcb->sector = sn % lp->d_nsectors;
57737097Sbostic 	mcb->drive = vi->ui_slave;
57837097Sbostic 	/* mcb->context = 0;		/* what do we want on interrupt? */
57933165Sbostic 
58037097Sbostic 	hdc = &hdcsoftc[vm->um_ctlr];
58137097Sbostic 	if (!hd_sgsetup(bp, hdc->hdc_rbuf, mcb->chain)) {
58237097Sbostic 		mcb->chain[0].wcount = (bp->b_bcount+3) >> 2;
58337097Sbostic 		mcb->chain[0].memadr =
58437097Sbostic 		    vbasetup(bp, &hdc->hdc_rbuf, (int)lp->d_secsize);
58533165Sbostic 	}
58633165Sbostic 
58737097Sbostic 	if (vi->ui_dk >= 0) {
58837097Sbostic 		dk_busy |= 1<<vi->ui_dk;
58937097Sbostic 		dk_xfer[vi->ui_dk]++;
59037097Sbostic 		dk_wds[vi->ui_dk] += bp->b_bcount>>6;
59137097Sbostic 	}
59233165Sbostic 
59337097Sbostic 	master = &hdc->hdc_mcb;
59437097Sbostic 	master->mcw = MCL_QUEUED;
59537097Sbostic 	master->interrupt = HDCINTERRUPT + vm->um_ctlr;
59637097Sbostic 	master->forw_phaddr = (u_long)vtoph((struct proc *)NULL, mcb);
59737097Sbostic 	hdc->hdc_reg->master_mcb = (u_long)hdc->hdc_mcbp;
59837097Sbostic }
59933165Sbostic 
60037097Sbostic /*
60137097Sbostic  * Wait for controller to finish current operation
60237097Sbostic  * so that direct controller accesses can be done.
60337097Sbostic  */
60437097Sbostic hdclock(ctlr)
60537097Sbostic 	int ctlr;
60637097Sbostic {
60737097Sbostic 	register struct vba_ctlr *vm = hdcminfo[ctlr];
60837097Sbostic 	register struct hdcsoftc *hdc;
60937097Sbostic 	int s;
61033165Sbostic 
61137097Sbostic 	hdc = &hdcsoftc[ctlr];
61237097Sbostic 	s = spl7();
61337097Sbostic 	while (vm->um_tab.b_active || hdc->hdc_flags & HDC_LOCKED) {
61437097Sbostic 		hdc->hdc_flags |= HDC_WAIT;
61537097Sbostic 		sleep((caddr_t)hdc, PRIBIO);
61633165Sbostic 	}
61737097Sbostic 	hdc->hdc_flags |= HDC_LOCKED;
61837097Sbostic 	splx(s);
61937097Sbostic }
62033165Sbostic 
62137097Sbostic /*
62237097Sbostic  * Continue normal operations after pausing for
62337097Sbostic  * munging the controller directly.
62437097Sbostic  */
62537097Sbostic hdcunlock(ctlr)
62637097Sbostic 	int ctlr;
62737097Sbostic {
62837097Sbostic 	register struct vba_ctlr *vm;
62937097Sbostic 	register struct hdcsoftc *hdc = &hdcsoftc[ctlr];
63033165Sbostic 
63137097Sbostic 	hdc->hdc_flags &= ~HDC_LOCKED;
63237097Sbostic 	if (hdc->hdc_flags & HDC_WAIT) {
63337097Sbostic 		hdc->hdc_flags &= ~HDC_WAIT;
63437097Sbostic 		wakeup((caddr_t)hdc);
63537097Sbostic 	} else {
63637097Sbostic 		vm = hdcminfo[ctlr];
63737097Sbostic 		if (vm->um_tab.b_actf)
63837097Sbostic 			hdcstart(vm);
63933165Sbostic 	}
64037097Sbostic }
64133165Sbostic 
64237097Sbostic hdintr(ctlr)
64337097Sbostic 	int ctlr;
64437097Sbostic {
64537097Sbostic 	register struct buf *bp, *dp;
64637097Sbostic 	register struct vba_ctlr *vm;
64737097Sbostic 	register struct vba_device *vi;
64837097Sbostic 	register struct hdcsoftc *hdc;
64937097Sbostic 	register struct mcb *mcb;
65037097Sbostic 	struct master_mcb *master;
65137097Sbostic 	register int status;
65237097Sbostic 	int timedout;
65337097Sbostic 	struct dksoftc *dk;
65433165Sbostic 
65537097Sbostic 	hdc = &hdcsoftc[ctlr];
65637097Sbostic 	master = &hdc->hdc_mcb;
65737097Sbostic 	uncache(&master->mcs);
65837097Sbostic 	uncache(&master->context);
65933165Sbostic 
66037097Sbostic 	vm = hdcminfo[ctlr];
66137097Sbostic 	if (!vm->um_tab.b_active || !(master->mcs&MCS_DONE)) {
66237097Sbostic 		printf("hd%d: stray interrupt\n", ctlr);
66337097Sbostic 		return;
66433165Sbostic 	}
66533165Sbostic 
66637097Sbostic 	dp = vm->um_tab.b_actf;
66737097Sbostic 	bp = dp->b_actf;
66837097Sbostic 	vi = hddinfo[hdunit(bp->b_dev)];
66937097Sbostic 	dk = &dksoftc[vi->ui_unit];
67037097Sbostic 	if (vi->ui_dk >= 0)
67137097Sbostic 		dk_busy &= ~(1<<vi->ui_dk);
67237097Sbostic 	timedout = (hdc->hdc_wticks >= HDCMAXTIME);
67333165Sbostic 
67437097Sbostic 	mcb = &dk->dk_mcb;
67533165Sbostic 
67637097Sbostic 	if (master->mcs & (MCS_SOFTERROR | MCS_FATALERROR) || timedout)
67737097Sbostic 		hdcerror(ctlr, *(u_long *)master->xstatus);
678*37565Sbostic 	else
67937097Sbostic 		hdc->hdc_wticks = 0;
680*37565Sbostic 	if (vm->um_tab.b_active) {
681*37565Sbostic 		vm->um_tab.b_active = 0;
682*37565Sbostic 		vm->um_tab.b_actf = dp->b_forw;
683*37565Sbostic 		dp->b_active = 0;
684*37565Sbostic 		dp->b_errcnt = 0;
685*37565Sbostic 		dp->b_actf = bp->av_forw;
686*37565Sbostic 		bp->b_resid = 0;
687*37565Sbostic 		vbadone(bp, &hdc->hdc_rbuf);
688*37565Sbostic 		biodone(bp);
689*37565Sbostic 		/* start up now, if more work to do */
690*37565Sbostic 		if (dp->b_actf)
691*37565Sbostic 			hdustart(vi);
692*37565Sbostic 		else if (dk->dk_openpart == 0)
693*37565Sbostic 			wakeup((caddr_t)dk);
69433165Sbostic 	}
69537097Sbostic 	/* if there are devices ready to transfer, start the controller. */
69637097Sbostic 	if (hdc->hdc_flags & HDC_WAIT) {
69737097Sbostic 		hdc->hdc_flags &= ~HDC_WAIT;
69837097Sbostic 		wakeup((caddr_t)hdc);
69937097Sbostic 	} else if (vm->um_tab.b_actf)
70037097Sbostic 		hdcstart(vm);
70137097Sbostic }
70233165Sbostic 
703*37565Sbostic hdioctl(dev, cmd, data, flag)
70437097Sbostic 	dev_t dev;
705*37565Sbostic 	int cmd, flag;
70637097Sbostic 	caddr_t data;
70737097Sbostic {
708*37565Sbostic 	register int unit;
709*37565Sbostic 	register struct dksoftc *dk;
710*37565Sbostic 	register struct disklabel *lp;
71137097Sbostic 	int error;
71233165Sbostic 
713*37565Sbostic 	unit = hdunit(dev);
714*37565Sbostic 	dk = &dksoftc[unit];
715*37565Sbostic 	lp = &dk->dk_label;
716*37565Sbostic 	error = 0;
717*37565Sbostic 	switch (cmd) {
718*37565Sbostic 	case DIOCGDINFO:
719*37565Sbostic 		*(struct disklabel *)data = *lp;
720*37565Sbostic 		break;
721*37565Sbostic 	case DIOCGPART:
722*37565Sbostic 		((struct partinfo *)data)->disklab = lp;
723*37565Sbostic 		((struct partinfo *)data)->part =
724*37565Sbostic 		    &lp->d_partitions[hdpart(dev)];
725*37565Sbostic 		break;
726*37565Sbostic 	case DIOCSDINFO:
727*37565Sbostic 		if ((flag & FWRITE) == 0)
728*37565Sbostic 			error = EBADF;
729*37565Sbostic 		else
730*37565Sbostic 			error = setdisklabel(lp, (struct disklabel *)data,
731*37565Sbostic 			    (dk->dk_state == OPENRAW) ? 0 : dk->dk_openpart);
732*37565Sbostic 		if (error == 0 && dk->dk_state == OPENRAW)
733*37565Sbostic 			dk->dk_state = OPEN;
734*37565Sbostic 		break;
735*37565Sbostic 	case DIOCWLABEL:
736*37565Sbostic 		if ((flag & FWRITE) == 0)
737*37565Sbostic 			error = EBADF;
738*37565Sbostic 		else
739*37565Sbostic 			dk->dk_wlabel = *(int *)data;
740*37565Sbostic 		break;
741*37565Sbostic 	case DIOCWDINFO:
742*37565Sbostic 		if ((flag & FWRITE) == 0)
743*37565Sbostic 			error = EBADF;
744*37565Sbostic 		else if ((error = setdisklabel(lp, (struct disklabel *)data,
745*37565Sbostic 		    (dk->dk_state == OPENRAW) ? 0 : dk->dk_openpart)) == 0) {
746*37565Sbostic 			int wlab;
74733165Sbostic 
748*37565Sbostic 			if (error == 0 && dk->dk_state == OPENRAW)
749*37565Sbostic 				dk->dk_state = OPEN;
750*37565Sbostic 			/* simulate opening partition 0 so write succeeds */
751*37565Sbostic 			dk->dk_openpart |= (1 << 0);		/* XXX */
752*37565Sbostic 			wlab = dk->dk_wlabel;
753*37565Sbostic 			dk->dk_wlabel = 1;
754*37565Sbostic 			error = writedisklabel(dev, hdstrategy, lp);
755*37565Sbostic 			dk->dk_openpart = dk->dk_copenpart | dk->dk_bopenpart;
756*37565Sbostic 			dk->dk_wlabel = wlab;
757*37565Sbostic 		}
758*37565Sbostic 		break;
75937097Sbostic 	default:
76037097Sbostic 		error = ENOTTY;
76133165Sbostic 		break;
76233165Sbostic 	}
763*37565Sbostic 	return (error);
76437097Sbostic }
76533165Sbostic 
76637097Sbostic /*
76737097Sbostic  * Watch for lost interrupts.
76837097Sbostic  */
76937097Sbostic hdcwatch()
77037097Sbostic {
77137097Sbostic 	register struct hdcsoftc *hdc;
77237097Sbostic 	register struct vba_ctlr **vmp;
77337097Sbostic 	register int ctlr;
77437097Sbostic 	int s;
77533165Sbostic 
77637097Sbostic 	timeout(hdcwatch, (caddr_t)0, hz);
77737097Sbostic 	for (vmp = hdcminfo, hdc = hdcsoftc, ctlr = 0; ctlr < NHDC;
77837097Sbostic 	    ++ctlr, ++vmp, ++hdc) {
77937097Sbostic 		if (*vmp == 0 || (*vmp)->um_alive == 0)
78037097Sbostic 			continue;
78137097Sbostic 		s = spl7();
78237097Sbostic 		if ((*vmp)->um_tab.b_active &&
78337097Sbostic 		    hdc->hdc_wticks++ >= HDCMAXTIME) {
78437097Sbostic 			printf("hd%d: lost interrupt\n", ctlr);
78537097Sbostic 			hdintr(ctlr);
78633165Sbostic 		}
78737097Sbostic 		splx(s);
78833165Sbostic 	}
78933165Sbostic }
79033165Sbostic 
79137097Sbostic hddump(dev)
79237097Sbostic 	dev_t dev;
79333165Sbostic {
79437097Sbostic 	return(ENXIO);
79533165Sbostic }
79633165Sbostic 
79737097Sbostic hdsize(dev)
79837097Sbostic 	dev_t dev;
79933165Sbostic {
80037097Sbostic 	register int unit = hdunit(dev);
80137097Sbostic 	register struct dksoftc *dk;
80237097Sbostic 	struct vba_device *vi;
80337097Sbostic 	struct disklabel *lp;
80433165Sbostic 
80537097Sbostic 	if (unit >= NHD || (vi = hddinfo[unit]) == 0 || vi->ui_alive == 0 ||
80637097Sbostic 	    (dk = &dksoftc[unit])->dk_state != OPEN)
80737097Sbostic 		return (-1);
80837097Sbostic 	lp = &dk->dk_label;
80937097Sbostic 	return ((int)lp->d_partitions[hdpart(dev)].p_size >> dk->dk_bshift);
81033165Sbostic }
81133165Sbostic 
81237097Sbostic hdimcb(dk)
81337097Sbostic 	register struct dksoftc *dk;
81433165Sbostic {
81537097Sbostic 	register struct master_mcb *master;
81637097Sbostic 	register struct mcb *mcb;
81737097Sbostic 	register struct hdcsoftc *hdc;
81837097Sbostic 	int timeout;
81933165Sbostic 
82037097Sbostic 	/* fill in mcb */
82137097Sbostic 	mcb = &dk->dk_mcb;
82237097Sbostic 	mcb->interrupt = 0;
82337097Sbostic 	mcb->forw_phaddr = 0;
82437097Sbostic 	mcb->drive = dk->dk_unit;
82533165Sbostic 
82637097Sbostic 	hdc = &hdcsoftc[dk->dk_ctlr];
82737097Sbostic 	master = &hdc->hdc_mcb;
82833165Sbostic 
82937097Sbostic 	/* fill in master mcb */
83037097Sbostic 	master->mcw = MCL_IMMEDIATE;
83137097Sbostic 	master->forw_phaddr = (u_long)vtoph((struct proc *)NULL, mcb);
83237097Sbostic 	master->mcs = 0;
83333165Sbostic 
83437097Sbostic 	/* kick controller and wait */
83537097Sbostic 	hdc->hdc_reg->master_mcb = (u_long)hdc->hdc_mcbp;
83637097Sbostic 	for (timeout = 15000; timeout; --timeout) {
83737097Sbostic 		DELAY(1000);
83837097Sbostic 		mtpr(PADC, 0);
83937097Sbostic 		if (master->mcs&MCS_FATALERROR) {
84037097Sbostic 			printf("hdc%d: fatal error\n", dk->dk_ctlr);
84137097Sbostic 			hdcerror(dk->dk_ctlr, *(u_long *)master->xstatus);
84237097Sbostic 			return(1);
84337097Sbostic 		}
84437097Sbostic 		if (master->mcs&MCS_DONE)
84537097Sbostic 			return(0);
84633165Sbostic 	}
84737097Sbostic 	printf("hdc%d: timed out\n", dk->dk_ctlr);
84837097Sbostic 	return(1);
84933165Sbostic }
85033165Sbostic 
85137097Sbostic hdcerror(ctlr, code)
85237097Sbostic 	int ctlr;
85337097Sbostic 	u_long code;
85433165Sbostic {
855*37565Sbostic 	printf("hd%d: error %lx\n", ctlr, code);
85633165Sbostic }
85733165Sbostic 
85837097Sbostic #ifdef COMPAT_42
85937097Sbostic hdreadgeometry(dk)
86037097Sbostic 	struct dksoftc *dk;
86133165Sbostic {
86237097Sbostic 	static geometry_sector geometry;
86337097Sbostic 	register struct mcb *mcb;
86437097Sbostic 	register struct disklabel *lp;
86537097Sbostic 	geometry_block *geo;
86637097Sbostic 	int cnt;
86733165Sbostic 
86833165Sbostic 	/*
86937097Sbostic 	 * Read the geometry block (at head = 0 sector = 0 of the drive
87037097Sbostic 	 * definition cylinder), validate it (must have the correct version
87137097Sbostic 	 * number, header, and checksum).
87233165Sbostic 	 */
87337097Sbostic 	mcb = &dk->dk_mcb;
87437097Sbostic 	mcb->command = HCMD_READ;
87537097Sbostic 	mcb->cyl = dk->dk_def_cyl;
87637097Sbostic 	mcb->head = 0;
87737097Sbostic 	mcb->sector = 0;
87837097Sbostic 	mcb->chain[0].wcount = sizeof(geometry_sector) / sizeof(long);
87937097Sbostic 	mcb->chain[0].memadr  = (u_long)vtoph((struct process *)0, &geometry);
88037097Sbostic 	/* mcb->chain[0].memadr = (long)&geometry; */
88137097Sbostic 	if (hdimcb(dk)) {
88237097Sbostic  		printf("hd%d: can't read default geometry.\n", dk->dk_unit);
88337097Sbostic 		return(1);
88433165Sbostic 	}
88537097Sbostic 	geo = &geometry.geometry_block;
88637097Sbostic  	if (geo->version > 64000  ||  geo->version < 0) {
88737097Sbostic  		printf("hd%d: bad default geometry version#.\n", dk->dk_unit);
88837097Sbostic 		return(1);
88933165Sbostic 	}
89037097Sbostic  	if (bcmp(&geo->id[0], GB_ID, GB_ID_LEN)) {
89137097Sbostic  		printf("hd%d: bad default geometry header.\n", dk->dk_unit);
89237097Sbostic 		return(1);
89333165Sbostic 	}
89437097Sbostic 	GB_CHECKSUM(geo, cnt);
89537097Sbostic 	if (geometry.checksum != cnt) {
89637097Sbostic 		printf("hd%d: bad default geometry checksum.\n", dk->dk_unit);
89737097Sbostic 		return(1);
89833165Sbostic 	}
89937097Sbostic 	lp = &dk->dk_label;
900*37565Sbostic 
90137097Sbostic 	/* 1K block in Harris geometry; convert to sectors for disklabels */
90237097Sbostic 	for (cnt = 0; cnt < GB_MAXPART; cnt++) {
90337097Sbostic 		lp->d_partitions[cnt].p_offset =
90437097Sbostic 		    geo->partition[cnt].start * (1024 / lp->d_secsize);
90537097Sbostic 		lp->d_partitions[cnt].p_size =
90637097Sbostic 		    geo->partition[cnt].length * (1024 / lp->d_secsize);
90733165Sbostic 	}
90837097Sbostic 	lp->d_npartitions = GB_MAXPART;
90937097Sbostic 	return(0);
91033165Sbostic }
91137097Sbostic #endif /* COMPAT_42 */
91237097Sbostic #endif /* NHD */
913