xref: /csrg-svn/sys/tahoe/vba/vd.c (revision 29921)
1*29921Skarels /*	vd.c	1.10	86/10/28	*/
224004Ssam 
329564Ssam #include "dk.h"
424004Ssam #if NVD > 0
524004Ssam /*
629564Ssam  * VDDC - Versabus SMD/SMDE driver.
725675Ssam  */
825877Ssam #ifdef VDDCPERF
925877Ssam #define	DOSCOPE
1025877Ssam #endif
1125877Ssam 
1225675Ssam #include "../tahoe/mtpr.h"
1325675Ssam #include "../tahoe/pte.h"
1424004Ssam 
1525675Ssam #include "param.h"
1625675Ssam #include "buf.h"
1725675Ssam #include "cmap.h"
1825675Ssam #include "conf.h"
1925675Ssam #include "dir.h"
2029564Ssam #include "dkstat.h"
2125675Ssam #include "map.h"
2225675Ssam #include "systm.h"
2325675Ssam #include "user.h"
2425675Ssam #include "vmmac.h"
2525675Ssam #include "proc.h"
2625675Ssam #include "uio.h"
2724004Ssam 
2825675Ssam #include "../tahoevba/vbavar.h"
2925675Ssam #define	VDGENDATA
3025928Ssam #include "../tahoevba/vdreg.h"
3125675Ssam #undef VDGENDATA
3225877Ssam #include "../tahoevba/scope.h"
3324004Ssam 
3425925Ssam #define	VDMAXIO		(MAXBPTE*NBPG)
3525675Ssam #define	DUMPSIZE	64	/* controller limit */
3624004Ssam 
3724004Ssam #define VDUNIT(x)	(minor(x) >> 3)
3825675Ssam #define FILSYS(x)	(minor(x) & 0x07)
3925675Ssam #define PHYS(x)		(vtoph((struct proc *)0, (unsigned)(x)))
4024004Ssam 
4125675Ssam #define CTLR_ERROR	1
4225675Ssam #define DRIVE_ERROR	2
4325675Ssam #define HARD_DATA_ERROR	3
4425675Ssam #define SOFT_DATA_ERROR	4
45*29921Skarels #define	WRITE_PROTECT	5
4624004Ssam 
4725675Ssam #define b_cylin	b_resid
4825675Ssam #define b_daddr	b_error
4924004Ssam 
5024004Ssam struct	vba_ctlr *vdminfo[NVD];
5129564Ssam struct  vba_device *vddinfo[NDK];
5225675Ssam int	vdprobe(), vdslave(), vdattach(), vddgo();
5325675Ssam struct	vba_driver vddriver =
5429564Ssam     { vdprobe, vdslave, vdattach, vddgo, vddcaddr, "dk",
5525675Ssam       vddinfo, "vd", vdminfo };
5624004Ssam 
5724004Ssam /*
5825675Ssam  * Per-drive state.
5925675Ssam  */
6025675Ssam typedef struct {
6125675Ssam 	struct	buf raw_q_element;
6225675Ssam 	short	sec_per_blk;
6325675Ssam 	short	sec_per_cyl;
6425675Ssam 	char	status;
6525675Ssam 	struct	buf xfer_queue;
6625675Ssam 	int	drive_type;
6725675Ssam 	fs_tab	info;
6825675Ssam } unit_tab;
6924004Ssam 
7024004Ssam /*
7125675Ssam  * Per-controller state.
7225675Ssam  */
7325675Ssam typedef struct {
7425675Ssam 	char	ctlr_type;	/* controller type */
7525925Ssam 	struct	pte *map;	/* i/o page map */
7625925Ssam 	caddr_t	utl;		/* mapped i/o space */
7725675Ssam 	u_int	cur_slave:8;	/* last active unit number */
78*29921Skarels 	u_int	int_expected:1;	/* expect an interrupt */
7925675Ssam 	u_int	ctlr_started:1;	/* start command was issued */
8025675Ssam 	u_int	overlap_seeks:1;/* should overlap seeks */
8125925Ssam 	u_int	initdone:1;	/* controller initialization completed */
8225675Ssam 	u_int	off_cylinder:16;/* off cylinder bit map */
8325675Ssam 	u_int	unit_type[16];	/* slave types */
8425675Ssam 	u_int	cur_cyl[16];	/* cylinder last selected */
8525675Ssam 	long	cur_trk[16];	/* track last selected */
8625675Ssam 	fmt_mdcb ctlr_mdcb;	/* controller mdcb */
8725675Ssam 	fmt_dcb	ctlr_dcb;	/* r/w dcb */
8825675Ssam 	fmt_dcb	seek_dcb[4];	/* dcbs for overlapped seeks */
8925950Ssam 	caddr_t	rawbuf;		/* buffer for raw+swap i/o */
9025675Ssam } ctlr_tab;
9124004Ssam 
9225925Ssam ctlr_tab vdctlr_info[NVD];
9329564Ssam unit_tab vdunit_info[NDK];
9424004Ssam 
9524004Ssam /*
9625675Ssam  * See if the controller is really there; if so, initialize it.
9725675Ssam  */
9825857Ssam vdprobe(reg, vm)
9925857Ssam 	caddr_t reg;
10025857Ssam 	struct vba_ctlr *vm;
10125675Ssam {
10225857Ssam 	register br, cvec;		/* must be r12, r11 */
10325925Ssam 	register cdr *addr = (cdr *)reg;
10425925Ssam 	register ctlr_tab *ci;
10525925Ssam 	int i;
10625857Ssam 
10725857Ssam 	if (badaddr((caddr_t)reg, 2))
10825675Ssam 		return (0);
10925925Ssam 	ci = &vdctlr_info[vm->um_ctlr];
11025925Ssam 	addr->cdr_reset = 0xffffffff;
11125675Ssam 	DELAY(1000000);
11225925Ssam 	if (addr->cdr_reset != (unsigned)0xffffffff) {
11325925Ssam 		ci->ctlr_type = SMDCTLR;
11425925Ssam 		ci->overlap_seeks = 0;
11525675Ssam 		DELAY(1000000);
11625675Ssam 	} else {
11725925Ssam 		ci->overlap_seeks = 1;
11825925Ssam 		ci->ctlr_type = SMD_ECTLR;
11925925Ssam 		addr->cdr_reserved = 0x0;
12025675Ssam 		DELAY(3000000);
12125925Ssam 		addr->cdr_csr = 0;
12225925Ssam 		addr->mdcb_tcf = AM_ENPDA;
12325925Ssam 		addr->dcb_tcf = AM_ENPDA;
12425925Ssam 		addr->trail_tcf = AM_ENPDA;
12525925Ssam 		addr->data_tcf = AM_ENPDA;
126*29921Skarels 		addr->cdr_ccf = CCF_SEN | CCF_DER | CCF_STS |
127*29921Skarels 		    XMD_32BIT | BSZ_16WRD |
12825925Ssam 		    CCF_ENP | CCF_EPE | CCF_EDE | CCF_ECE | CCF_ERR;
12925675Ssam 	}
13025925Ssam 	/*
13125950Ssam 	 * Allocate page tables and i/o buffer.
13225925Ssam 	 */
13325925Ssam 	vbmapalloc(btoc(VDMAXIO)+1, &ci->map, &ci->utl);
13425950Ssam 	ci->rawbuf = calloc(VDMAXIO);
13525925Ssam 	/*
13625925Ssam 	 * Initialize all the drives to be of an unknown type.
13725925Ssam 	 */
13825925Ssam 	for (i = 0; i < 15; i++)
13925925Ssam 		ci->unit_type[i] = UNKNOWN;
14025857Ssam 	br = 0x17, cvec = 0xe0 + vm->um_ctlr;	/* XXX */
14125925Ssam 	return (sizeof (*addr));
14225675Ssam }
14324004Ssam 
14424004Ssam /*
14525675Ssam  * See if a drive is really there
14625675Ssam  * Try to reset/configure the drive, then test its status.
14725675Ssam  */
14825675Ssam vdslave(vi, addr)
14925675Ssam 	register struct vba_device *vi;
15025675Ssam 	register cdr *addr;
15125675Ssam {
15225675Ssam 	register ctlr_tab *ci = &vdctlr_info[vi->ui_ctlr];
15325675Ssam 	register unit_tab *ui = &vdunit_info[vi->ui_unit];
15425675Ssam 	register fmt_mdcb *mdcb = &ci->ctlr_mdcb;
15525675Ssam 	register fmt_dcb *dcb = &ci->ctlr_dcb;
15625675Ssam 	register int type;
15724004Ssam 
15825925Ssam 	if (!ci->initdone) {
15925925Ssam 		printf("vd%d: %s controller\n", vi->ui_ctlr,
16029564Ssam 		    ci->ctlr_type == SMDCTLR ? "smd" : "smde");
16125925Ssam 		if (vdnotrailer(addr, vi->ui_ctlr, vi->ui_slave, INIT, 10) &
16225925Ssam 		    HRDERR) {
16325925Ssam 			printf("vd%d: init error\n", vi->ui_ctlr);
16425675Ssam 			return (0);
16525675Ssam 		}
16625925Ssam 		if (vdnotrailer(addr, vi->ui_ctlr, vi->ui_slave, DIAG, 10) &
16725925Ssam 		    HRDERR) {
16825925Ssam 			printf("vd%d: diagnostic error\n", vi->ui_ctlr);
16925675Ssam 			return (0);
17025675Ssam 		}
17125925Ssam 		ci->initdone = 1;
17225675Ssam 	}
17325675Ssam 	/*
17425675Ssam 	 * Seek on all drive types starting from the largest one.
17525675Ssam 	 * a successful seek to the last sector/cylinder/track verifies
17625675Ssam 	 * the drive type connected to this port.
17725675Ssam 	 */
17825675Ssam 	for (type = 0; type < nvddrv; type++) {
17925675Ssam 		/* XXX */
18025675Ssam 		if (ci->ctlr_type == SMDCTLR && vdst[type].nsec != 32)
18125675Ssam 			continue;
18225675Ssam 		/* XXX */
18325675Ssam 		if (!vdconfigure_drive(addr, vi->ui_ctlr, vi->ui_slave, type,0))
18425675Ssam 			return (0);
18525675Ssam 		dcb->opcode = (short)RD;
18625675Ssam 		dcb->intflg = NOINT;
18725675Ssam 		dcb->nxtdcb = (fmt_dcb *)0;	/* end of chain */
18825675Ssam 		dcb->operrsta = 0;
18925675Ssam 		dcb->devselect = (char)(vi->ui_slave);
19025675Ssam 		dcb->trailcnt = (char)(sizeof (trrw) / sizeof (long));
19125675Ssam 		dcb->trail.rwtrail.memadr = (char *)PHYS(ci->rawbuf);
19225675Ssam 		dcb->trail.rwtrail.wcount = vdst[type].secsize/sizeof(short);
19325675Ssam 		dcb->trail.rwtrail.disk.cylinder = vdst[type].ncyl - 2;
19425675Ssam 		dcb->trail.rwtrail.disk.track = vdst[type].ntrak - 1;
19525675Ssam 		dcb->trail.rwtrail.disk.sector = vdst[type].nsec - 1;
19625675Ssam 		mdcb->firstdcb = (fmt_dcb *)(PHYS(dcb));
19725675Ssam 		mdcb->vddcstat = 0;
19825675Ssam 		VDDC_ATTENTION(addr, (fmt_mdcb *)(PHYS(mdcb)), ci->ctlr_type);
19925925Ssam 		if (!vdpoll(ci, addr, 60))
20025675Ssam 			printf(" during probe\n");
20125675Ssam 		if ((dcb->operrsta&HRDERR) == 0)
20225675Ssam 			break;
20325675Ssam 	}
20425675Ssam 	if (type >= nvddrv) {
20525675Ssam 		/*
20625675Ssam 		 * If reached here, a drive which is not defined in the
207*29921Skarels 		 * 'vdst' tables is connected. Cannot set its type.
20825675Ssam 		 */
20929564Ssam 		printf("dk%d: unknown drive type\n", vi->ui_unit);
21025675Ssam 		return (0);
21125675Ssam 	}
21225675Ssam 	ui->drive_type = type;
21325675Ssam 	ui->info = vdst[type];
21425675Ssam 	ui->sec_per_blk = DEV_BSIZE / ui->info.secsize;
21525675Ssam 	vi->ui_type = type;
21625675Ssam  	vi->ui_dk = 1;
21725675Ssam 	return (1);
21824004Ssam }
21924004Ssam 
22025675Ssam vdconfigure_drive(addr, ctlr, slave, type, pass)
22125675Ssam 	register cdr *addr;
22225675Ssam 	int ctlr, slave, type, pass;
22324004Ssam {
22425675Ssam 	register ctlr_tab *ci = &vdctlr_info[ctlr];
22525675Ssam 
22625675Ssam 	ci->ctlr_dcb.opcode = RSTCFG;		/* command */
22725675Ssam 	ci->ctlr_dcb.intflg = NOINT;
22825675Ssam 	ci->ctlr_dcb.nxtdcb = (fmt_dcb *)0;	/* end of chain */
22925675Ssam 	ci->ctlr_dcb.operrsta = 0;
23025675Ssam 	ci->ctlr_dcb.devselect = (char)slave;
23125675Ssam 	ci->ctlr_dcb.trail.rstrail.ncyl = vdst[type].ncyl;
23225675Ssam 	ci->ctlr_dcb.trail.rstrail.nsurfaces = vdst[type].ntrak;
23325675Ssam 	if (ci->ctlr_type == SMD_ECTLR) {
234*29921Skarels 		ci->ctlr_dcb.trailcnt = (char)5;
23525675Ssam 		ci->ctlr_dcb.trail.rstrail.nsectors = vdst[type].nsec;
23625675Ssam 		ci->ctlr_dcb.trail.rstrail.slip_sec = vdst[type].nslip;
237*29921Skarels 		ci->ctlr_dcb.trail.rstrail.recovery = 0x18f;
23825675Ssam 	} else
23925675Ssam 		ci->ctlr_dcb.trailcnt = (char)2;
24025675Ssam 	ci->ctlr_mdcb.firstdcb = (fmt_dcb *)(PHYS(&ci->ctlr_dcb));
24125675Ssam 	ci->ctlr_mdcb.vddcstat = 0;
24225675Ssam 	VDDC_ATTENTION(addr, (fmt_mdcb *)(PHYS(&ci->ctlr_mdcb)), ci->ctlr_type);
24325925Ssam 	if (!vdpoll(ci, addr, 5)) {
24425675Ssam 		printf(" during config\n");
24525675Ssam 		return (0);
24625675Ssam 	}
24725675Ssam 	if (ci->ctlr_dcb.operrsta & HRDERR) {
24825675Ssam 		if ((ci->ctlr_dcb.operrsta & (NOTCYLERR|DRVNRDY)) == 0)
24925675Ssam 			printf("vd%d: drive %d: config error\n", ctlr, slave);
25025675Ssam 		else if (pass == 0) {
25125675Ssam 			vdstart_drive(addr, ctlr, slave);
25225675Ssam 			return (vdconfigure_drive(addr, ctlr, slave, type, 1));
25325675Ssam 		} else if (pass == 2)
25425675Ssam 			return (vdconfigure_drive(addr, ctlr, slave, type, 3));
25525675Ssam 		return (0);
25625675Ssam 	}
25725675Ssam 	return (1);
25824004Ssam }
25924004Ssam 
26025675Ssam vdstart_drive(addr, ctlr, slave)
26125675Ssam 	cdr *addr;
26225675Ssam 	register int ctlr, slave;
26324004Ssam {
26425675Ssam 	int error = 0;
26524004Ssam 
26625675Ssam 	printf("vd%d: starting drive %d, wait...", ctlr, slave);
26725675Ssam 	if (vdctlr_info[ctlr].ctlr_started) {
268*29921Skarels #ifdef notdef
26925675Ssam printf("DELAY(5500000)...");
27025675Ssam 		DELAY(5500000);
271*29921Skarels #endif
27225675Ssam 		goto done;
27324004Ssam 	}
27425675Ssam 	vdctlr_info[ctlr].ctlr_started = 1;
27525675Ssam 	error = vdnotrailer(addr, ctlr, 0, VDSTART, (slave*6)+62) & HRDERR;
27625675Ssam 	if (!error) {
277*29921Skarels #ifdef notdef
27825675Ssam 		DELAY((slave * 5500000) + 62000000);
279*29921Skarels #endif
28024004Ssam 	}
28125675Ssam done:
28225675Ssam 	printf("\n");
28325675Ssam 	return (error == 0);
28425675Ssam }
28524004Ssam 
28625675Ssam vdnotrailer(addr, ctlr, unit, function, time)
28725675Ssam 	register cdr *addr;
28825675Ssam 	int ctlr, unit, function, time;
28924004Ssam {
29025925Ssam 	register ctlr_tab *ci = &vdctlr_info[ctlr];
29125925Ssam 	fmt_mdcb *mdcb = &ci->ctlr_mdcb;
29225925Ssam 	fmt_dcb *dcb = &ci->ctlr_dcb;
29324004Ssam 
29425675Ssam 	dcb->opcode = function;		/* command */
29524004Ssam 	dcb->intflg = NOINT;
29625675Ssam 	dcb->nxtdcb = (fmt_dcb *)0;	/* end of chain */
29725675Ssam 	dcb->operrsta = 0;
29825675Ssam 	dcb->devselect = (char)unit;
29924004Ssam 	dcb->trailcnt = (char)0;
30025675Ssam 	mdcb->firstdcb = (fmt_dcb *)(PHYS(dcb));
30124004Ssam 	mdcb->vddcstat = 0;
30225925Ssam 	VDDC_ATTENTION(addr, (fmt_mdcb *)(PHYS(mdcb)), ci->ctlr_type);
30325925Ssam 	if (!vdpoll(ci, addr, time)) {
30425675Ssam 		printf(" during init\n");
30525675Ssam 		return (DCBCMP|ANYERR|HRDERR|OPABRT);
30624004Ssam 	}
30725675Ssam 	return (dcb->operrsta);
30825675Ssam }
30924004Ssam 
31025675Ssam vdattach(vi)
31125675Ssam 	register struct vba_device *vi;
31225675Ssam {
31325675Ssam 	register unit_tab *ui = &vdunit_info[vi->ui_unit];
31425675Ssam 	register ctlr_tab *ci = &vdctlr_info[vi->ui_ctlr];
31525675Ssam 	register struct buf *cq = &vi->ui_mi->um_tab;
31625675Ssam 	register struct buf *uq = cq->b_forw;
31725675Ssam 	register struct buf *start_queue = uq;
31825675Ssam 	register fs_tab	*fs = &ui->info;
31925675Ssam 
32025675Ssam 	ui->info = vdst[vi->ui_type];
32125675Ssam 	ui->sec_per_blk = DEV_BSIZE / ui->info.secsize;
32225675Ssam 	ui->sec_per_cyl = ui->info.nsec * ui->info.ntrak;
32325675Ssam 	ui->xfer_queue.b_dev = vi->ui_slave;
32425675Ssam 	ci->unit_type[vi->ui_slave] = vi->ui_type;
32525675Ssam 	/* load unit into controller's active unit list */
32625675Ssam 	if (uq == NULL) {
32725675Ssam 		cq->b_forw = &ui->xfer_queue;
32825675Ssam 		ui->xfer_queue.b_forw = &ui->xfer_queue;
32925675Ssam 		ui->xfer_queue.b_back = &ui->xfer_queue;
33025675Ssam 	} else {
33125675Ssam 		while (uq->b_forw != start_queue)
33225675Ssam 			uq = uq->b_forw;
33325675Ssam 		ui->xfer_queue.b_forw = start_queue;
33425675Ssam 		ui->xfer_queue.b_back = uq;
33525675Ssam 		uq->b_forw = &ui->xfer_queue;
33625675Ssam 		start_queue->b_back = &ui->xfer_queue;
33725675Ssam 	}
338*29921Skarels 	printf("dk%d: %s <ntrak %d, ncyl %d, nsec %d>\n",
339*29921Skarels 	    vi->ui_unit, fs->type_name,
340*29921Skarels 	    ui->info.ntrak, ui->info.ncyl, ui->info.nsec);
34124004Ssam 	/*
34225675Ssam 	 * (60 / rpm) / (number of sectors per track * (bytes per sector / 2))
34324004Ssam 	 */
34425675Ssam 	dk_mspw[vi->ui_unit] = 120.0 / (fs->rpm * fs->nsec * fs->secsize);
34524004Ssam }
34624004Ssam 
34725675Ssam /*ARGSUSED*/
34825675Ssam vddgo(um)
34925675Ssam 	struct vba_ctlr *um;
35024004Ssam {
35124004Ssam 
35224004Ssam }
35324004Ssam 
35424004Ssam vdstrategy(bp)
35525675Ssam 	register struct buf *bp;
35624004Ssam {
35725675Ssam 	register int unit = VDUNIT(bp->b_dev);
35825675Ssam 	register struct vba_device *vi = vddinfo[unit];
35925675Ssam 	register par_tab *par;
36025675Ssam 	register unit_tab *ui;
36125675Ssam 	register fs_tab *fs;
36225675Ssam 	register int blks, bn, s;
36324004Ssam 
36425675Ssam 	if (bp->b_bcount == 0 || vi == 0 || vi->ui_alive == 0)
36525675Ssam 		goto bad;
36625675Ssam 	ui = &vdunit_info[unit];
36725675Ssam 	fs = &ui->info;
36825675Ssam 	par = &fs->partition[FILSYS(bp->b_dev)];
36925675Ssam 	blks = (bp->b_bcount + DEV_BSIZE-1) >> DEV_BSHIFT;
37025675Ssam 	if (bp->b_blkno + blks >= par->par_len) {
37125675Ssam 		blks = par->par_len - bp->b_blkno;
37225675Ssam 		if (blks <= 0)
37325675Ssam 			goto bad;
37425675Ssam 		bp->b_bcount = blks * DEV_BSIZE;
37525675Ssam 	}
37625675Ssam 	bn = bp->b_blkno + par->par_start;
37725675Ssam 	bn *= ui->sec_per_blk;
37825675Ssam 	bp->b_daddr = (bn / fs->nsec) % fs->ntrak;
37925675Ssam 	bp->b_cylin = bn / ui->sec_per_cyl;
38025675Ssam 	vbasetup(bp, ui->info.secsize);
38125675Ssam 	s = spl7();
38225675Ssam 	if (ui->xfer_queue.av_forw == NULL) {
38325675Ssam 		register ctlr_tab *ci = &vdctlr_info[vi->ui_ctlr];
38425675Ssam 		int slave = vi->ui_slave;
38524004Ssam 
38625675Ssam 		if (bp->b_cylin != ci->cur_cyl[slave] ||
38725675Ssam 		    bp->b_daddr != ci->cur_trk[slave])
38825675Ssam 			ci->off_cylinder |= 1 << slave;
38924004Ssam 	}
39025675Ssam 	bp->b_daddr |= (bn % fs->nsec) << 8;
39125675Ssam 	disksort(&ui->xfer_queue, bp);
39225675Ssam 	if (!vddinfo[unit]->ui_mi->um_tab.b_active++) {
39325675Ssam 		splx(s);
39425675Ssam 		vdstart(vddinfo[unit]->ui_mi);
39525675Ssam 	} else
39625675Ssam 		splx(s);
39724004Ssam 	return;
39825675Ssam bad:
39925675Ssam 	bp->b_flags |= B_ERROR, bp->b_error = ENXIO;
40025675Ssam 	bp->b_resid = bp->b_bcount;
40124004Ssam 	iodone(bp);
40224004Ssam }
40324004Ssam 
40424004Ssam /*
40524004Ssam  * Start up a transfer on a drive.
40624004Ssam  */
40725675Ssam vdstart(ci)
40825675Ssam 	register struct vba_ctlr *ci;
40924004Ssam {
41025675Ssam 	register struct buf *cq = &ci->um_tab;
41125675Ssam 	register struct buf *uq = cq->b_forw;
41224004Ssam 
41325675Ssam 	/* search for next ready unit */
41425675Ssam 	cq->b_forw = cq->b_forw->b_forw;
41525675Ssam 	uq = cq->b_forw;
41625675Ssam 	do {
41725675Ssam 		if (uq->av_forw != NULL) {
41825675Ssam 			cq->b_forw = uq;
41925675Ssam 			vdexecute(ci, uq);
42025675Ssam 			return;
42125675Ssam 		}
42225675Ssam 		uq = uq->b_forw;
42325675Ssam 	} while (uq != cq->b_forw);
42425675Ssam }
42525675Ssam 
42625675Ssam /*
42725675Ssam  * Initiate seeks for all drives off-cylinder.
42825675Ssam  */
42925675Ssam vdload_seeks(ci, uq)
43025675Ssam 	register ctlr_tab *ci;
43125675Ssam 	register struct buf *uq;
43225675Ssam {
43325675Ssam 	register int unit, slave, nseeks;
43425675Ssam 	register fmt_dcb *dcb;
43525675Ssam 	register struct buf *bp;
43625675Ssam 	register struct buf *start_queue = uq;
43725675Ssam 
43825675Ssam 	nseeks = 0;
43925675Ssam 	do {
44025675Ssam 		bp = uq->av_forw;
44125675Ssam 		if (bp != NULL) {
44225675Ssam 			unit = VDUNIT(bp->b_dev);
44325675Ssam 			slave = vddinfo[unit]->ui_slave;
44425675Ssam 			if (ci->off_cylinder & (1 << slave)) {
44525675Ssam 				ci->off_cylinder &= ~(1 << slave);
44625675Ssam 				if (ci->cur_cyl[slave] != bp->b_cylin) {
44725675Ssam 					ci->cur_cyl[slave] = bp->b_cylin;
44825675Ssam 					dk_seek[unit]++;
44925675Ssam 				}
45025675Ssam 				ci->cur_trk[slave] = bp->b_daddr&0xff;
45125675Ssam 				dcb = &ci->seek_dcb[nseeks++];
45225675Ssam 				dcb->opcode = SEEK;
45325675Ssam 				dcb->intflg = NOINT | INT_PBA;
45425675Ssam 				dcb->operrsta = 0;
45525675Ssam 				dcb->devselect = (char)slave;
45625675Ssam 				dcb->trailcnt = (char)1;
45725675Ssam 				dcb->trail.sktrail.skaddr.cylinder =
45825675Ssam 				    bp->b_cylin;
45925675Ssam 				dcb->trail.sktrail.skaddr.track =
46025675Ssam 				    bp->b_daddr & 0xff;
46125675Ssam 				dcb->trail.sktrail.skaddr.sector = 0;
46225675Ssam 			}
46325675Ssam 		}
46425675Ssam 		uq = uq->b_forw;
46525675Ssam 	} while (uq != start_queue && nseeks < 4);
46625675Ssam 	return (nseeks);
46725675Ssam }
46825675Ssam 
46925675Ssam extern	vd_int_timeout();
47025675Ssam /*
47125675Ssam  * Execute the next command on the unit queue uq.
47225675Ssam  */
47325675Ssam vdexecute(controller_info, uq)
47425675Ssam 	register struct vba_ctlr *controller_info;
47525675Ssam 	register struct buf *uq;
47625675Ssam {
47725675Ssam 	register struct	buf *bp = uq->av_forw;
47825675Ssam 	register int ctlr = controller_info->um_ctlr;
47925675Ssam 	register ctlr_tab *ci = &vdctlr_info[ctlr];
48025675Ssam 	register int unit = VDUNIT(bp->b_dev);
48125675Ssam 	register int slave = vddinfo[unit]->ui_slave;
48225675Ssam 	register fmt_mdcb *mdcb = &ci->ctlr_mdcb;
48325675Ssam 	register fmt_dcb *dcb = &ci->ctlr_dcb;
48425675Ssam 
48524004Ssam 	/*
48625675Ssam 	 * If there are overlapped seeks to perform, shuffle
48725675Ssam 	 * them to the front of the queue and get them started
48825675Ssam 	 * before any data transfers (to get some parallelism).
48924004Ssam 	 */
49025675Ssam 	if ((ci->off_cylinder & ~(1<<slave)) && ci->overlap_seeks) {
49125675Ssam 		register int i, nseeks;
49225675Ssam 
49325675Ssam 		/* setup seek requests in seek-q */
49425675Ssam 		nseeks = vdload_seeks(ci, uq);
49525675Ssam 		/* place at the front of the master q */
49625675Ssam 		mdcb->firstdcb = (fmt_dcb *)PHYS(&ci->seek_dcb[0]);
49725675Ssam 		/* shuffle any remaining seeks up in the seek-q */
49825675Ssam 		for (i = 1; i < nseeks; i++)
49925675Ssam 			ci->seek_dcb[i-1].nxtdcb =
50025675Ssam 			    (fmt_dcb *)PHYS(&ci->seek_dcb[i]);
50125675Ssam 		ci->seek_dcb[nseeks-1].nxtdcb = (fmt_dcb *)PHYS(dcb);
50225675Ssam 	} else {
50325675Ssam 		if (bp->b_cylin != ci->cur_cyl[slave]) {
50425675Ssam 			ci->cur_cyl[slave] = bp->b_cylin;
50525675Ssam 			dk_seek[unit]++;
50625675Ssam 		}
50725675Ssam 		ci->cur_trk[slave] = bp->b_daddr & 0xff;
50825675Ssam 		ci->off_cylinder = 0;
50925675Ssam 		mdcb->firstdcb = (fmt_dcb *)(PHYS(dcb));
51024004Ssam 	}
51124004Ssam 	dcb->opcode = (bp->b_flags & B_READ) ? RD : WD;
51225675Ssam 	dcb->intflg = INTDONE;
51325675Ssam 	dcb->nxtdcb = (fmt_dcb *)0;	/* end of chain */
51424004Ssam 	dcb->operrsta = 0;
51525675Ssam 	dcb->devselect = (char)slave;
51625675Ssam 	dcb->trailcnt = (char)(sizeof (trrw) / sizeof (long));
51725675Ssam 	dcb->trail.rwtrail.memadr = (char *)
51825675Ssam 	    vbastart(bp, ci->rawbuf, (long *)ci->map, ci->utl);
51925675Ssam 	dcb->trail.rwtrail.wcount = (short)((bp->b_bcount+1) / sizeof (short));
52025675Ssam 	dcb->trail.rwtrail.disk.cylinder = bp->b_cylin;
52125675Ssam 	dcb->trail.rwtrail.disk.track = bp->b_daddr & 0xff;
52225675Ssam 	dcb->trail.rwtrail.disk.sector = bp->b_daddr >> 8;
52325675Ssam 	mdcb->vddcstat = 0;
52425675Ssam    	dk_wds[unit] += bp->b_bcount / 32;
52525675Ssam 	ci->int_expected = 1;
52625675Ssam 	timeout(vd_int_timeout, (caddr_t)ctlr, 20*60);
52725675Ssam   	dk_busy |= 1 << unit;
52825675Ssam 	scope_out(1);
52925675Ssam 	VDDC_ATTENTION((cdr *)(vdminfo[ctlr]->um_addr),
53025675Ssam 	    (fmt_mdcb *)(PHYS(mdcb)), ci->ctlr_type);
53125675Ssam }
53224004Ssam 
53324004Ssam /*
53425675Ssam  * Watch for lost interrupts.
53525675Ssam  */
53625675Ssam vd_int_timeout(ctlr)
53725675Ssam 	register int ctlr;
53825675Ssam {
53925675Ssam 	register ctlr_tab *ci = &vdctlr_info[ctlr];
54025675Ssam 	register fmt_dcb *dcb = &ci->ctlr_dcb;
54124004Ssam 
54225675Ssam 	uncache(&dcb->operrsta);
543*29921Skarels 	printf("vd%d: lost interrupt, status %b", ctlr, dcb->operrsta, ERRBITS);
54425675Ssam 	if (ci->ctlr_type == SMD_ECTLR) {
54525675Ssam 		uncache(&dcb->err_code);
54625675Ssam 		printf(", error code %x", dcb->err_code);
54724004Ssam 	}
54825675Ssam 	printf("\n");
54925675Ssam 	if ((dcb->operrsta&DCBCMP) == 0) {
55025675Ssam 		VDDC_ABORT((cdr *)(vdminfo[ctlr]->um_addr), ci->ctlr_type);
55125675Ssam 		dcb->operrsta |= DCBUSC | DCBABT | ANYERR | HRDERR | CTLRERR;
55225675Ssam 	}
55325675Ssam 	vdintr(ctlr);
55424004Ssam }
55524004Ssam 
55624004Ssam /*
55724004Ssam  * Handle a disk interrupt.
55824004Ssam  */
55925675Ssam vdintr(ctlr)
56025675Ssam 	register int ctlr;
56124004Ssam {
56225675Ssam 	register ctlr_tab *ci;
56325675Ssam 	register struct buf *cq, *uq, *bp;
56425675Ssam 	register int slave, unit;
56525675Ssam 	register fmt_mdcb  *mdcb;
56625675Ssam 	register fmt_dcb *dcb;
56725675Ssam 	int code, s;
56824004Ssam 
56925675Ssam 	untimeout(vd_int_timeout, (caddr_t)ctlr);
57024004Ssam 	scope_out(2);
57125675Ssam 	ci = &vdctlr_info[ctlr];
57225675Ssam 	if (!ci->int_expected) {
57325675Ssam 		printf("vd%d: stray interrupt\n", ctlr);
57424004Ssam 		return;
57524004Ssam 	}
57625675Ssam 	/*
57725675Ssam 	 * Take first request off controller's queue.
57825675Ssam 	 */
57925675Ssam 	cq = &vdminfo[ctlr]->um_tab;
58025675Ssam 	uq = cq->b_forw;
58125675Ssam 	bp = uq->av_forw;
58224004Ssam 	unit = VDUNIT(bp->b_dev);
58325675Ssam 	dk_busy &= ~(1 << unit);
58425675Ssam 	dk_xfer[unit]++;
58525675Ssam 	ci->int_expected = 0;
58625675Ssam 	/* find associated control blocks */
58725675Ssam 	mdcb = &ci->ctlr_mdcb, uncache(&mdcb->intdcb);
58825675Ssam 	dcb = &ci->ctlr_dcb, uncache(&dcb->operrsta);
58925675Ssam 	if (ci->ctlr_type == SMD_ECTLR)
59025675Ssam 		uncache(&dcb->err_code);
59125675Ssam 	slave = uq->b_dev;
59225675Ssam 	switch (code = vddecode_error(dcb)) {
59324004Ssam 
59425675Ssam 	case CTLR_ERROR:
59525675Ssam 	case DRIVE_ERROR:
59625675Ssam 		if (cq->b_errcnt >= 2)
59725675Ssam 			vdhard_error(ci, bp, dcb);
59825675Ssam 		if (code == CTLR_ERROR)
59925675Ssam 			vdreset_ctlr((cdr *)vdminfo[ctlr]->um_addr, ctlr);
60025675Ssam 		else
60125675Ssam 			reset_drive((cdr *)vdminfo[ctlr]->um_addr, ctlr,
60225675Ssam 			    slave, 2);
60325675Ssam 		if (cq->b_errcnt++ < 2) {	/* retry error */
60425675Ssam 			cq->b_forw = uq->b_back;
60525675Ssam 			vdstart(vdminfo[ctlr]);
60625675Ssam 			return;
60725675Ssam 		}
60825675Ssam 		bp->b_resid = bp->b_bcount;
60925675Ssam 		break;
61025675Ssam 
61125675Ssam 	case HARD_DATA_ERROR:
612*29921Skarels 	case WRITE_PROTECT:
61325675Ssam 		vdhard_error(ci, bp, dcb);
61425675Ssam 		bp->b_resid = 0;
61525675Ssam 		break;
61625675Ssam 
61725675Ssam 	case SOFT_DATA_ERROR:
61825675Ssam 		vdsoft_error(ci, bp, dcb);
61925675Ssam 		/* fall thru... */
62025675Ssam 
62125675Ssam 	default:			/* operation completed */
62225675Ssam 		bp->b_error = 0;
62325675Ssam 		bp->b_resid = 0;
62425675Ssam 		break;
62524004Ssam 	}
62625675Ssam 	vbadone(bp, ci->rawbuf, (long *)ci->map, ci->utl);
62725675Ssam 	/*
62825675Ssam 	 * Take next request on this unit q, or, if none,
62925675Ssam 	 * the next request on the next active unit q.
63025675Ssam 	 */
63125675Ssam 	s = spl7();
63225675Ssam 	uq->av_forw = bp->av_forw;
63325675Ssam 	if (uq->av_back != bp) {
63425675Ssam 		register struct buf *next;
63524004Ssam 
63625675Ssam 		unit = VDUNIT(uq->av_forw->b_dev);
63725675Ssam 		slave = vddinfo[unit]->ui_slave;
63825675Ssam 		next = uq->av_forw;
63925675Ssam 		if (next->b_cylin != ci->cur_cyl[slave] ||
64025675Ssam 		    (next->b_daddr & 0xff) != ci->cur_trk[slave])
64125675Ssam 			ci->off_cylinder |= 1 << slave;
64225675Ssam 	} else
64325675Ssam 		uq->av_back = NULL;
64425675Ssam 	splx(s);
64525675Ssam 	/* reset controller state */
64625675Ssam 	cq->b_errcnt = 0;
64725675Ssam 	cq->b_active--;
64824004Ssam 	scope_out(3);
64925675Ssam 	if (bp->b_flags & B_ERROR)
65025675Ssam 		bp->b_error = EIO;
65124004Ssam 	iodone(bp);
65225675Ssam 	vdstart(vdminfo[ctlr]);
65324004Ssam }
65424004Ssam 
65525675Ssam /*
65625675Ssam  * Convert controller status to internal operation/error code.
65725675Ssam  */
65825675Ssam vddecode_error(dcb)
65925675Ssam 	register fmt_dcb *dcb;
66025675Ssam {
66124004Ssam 
66225675Ssam 	if (dcb->operrsta & HRDERR) {
663*29921Skarels 		if (dcb->operrsta & WPTERR)
664*29921Skarels 			return (WRITE_PROTECT);
665*29921Skarels 		if (dcb->operrsta & (HCRCERR | HCMPERR | UCDATERR |
66625675Ssam 		    DSEEKERR | NOTCYLERR |DRVNRDY | INVDADR))
66725675Ssam 			return (DRIVE_ERROR);
66825675Ssam 		if (dcb->operrsta & (CTLRERR | OPABRT | INVCMD | DNEMEM))
66925675Ssam 			return (CTLR_ERROR);
67025675Ssam 		return (HARD_DATA_ERROR);
67125675Ssam 	}
67225675Ssam 	if (dcb->operrsta & SFTERR)
67325675Ssam 		return (SOFT_DATA_ERROR);
67425675Ssam 	return (0);
67525675Ssam }
67625675Ssam 
67725675Ssam /*
67825675Ssam  * Report a hard error.
67925675Ssam  */
68025675Ssam vdhard_error(ci, bp, dcb)
68125675Ssam 	ctlr_tab *ci;
68225675Ssam 	register struct buf *bp;
68325675Ssam 	register fmt_dcb *dcb;
68425675Ssam {
68525675Ssam 	unit_tab *ui = &vdunit_info[VDUNIT(bp->b_dev)];
68625675Ssam 
68725675Ssam 	bp->b_flags |= B_ERROR;
68825675Ssam 	harderr(bp, ui->info.type_name);
689*29921Skarels 	if (dcb->operrsta & WPTERR)
690*29921Skarels 		printf("write protected");
691*29921Skarels 	else {
692*29921Skarels 		printf("status %b", dcb->operrsta, ERRBITS);
693*29921Skarels 		if (ci->ctlr_type == SMD_ECTLR)
694*29921Skarels 			printf(" ecode %x", dcb->err_code);
695*29921Skarels 	}
69625675Ssam 	printf("\n");
69725675Ssam }
69825675Ssam 
69925675Ssam /*
70025675Ssam  * Report a soft error.
70125675Ssam  */
70225675Ssam vdsoft_error(ci, bp, dcb)
70325675Ssam 	ctlr_tab *ci;
70425675Ssam 	register struct buf *bp;
70525675Ssam 	register fmt_dcb *dcb;
70625675Ssam {
70725675Ssam 	unit_tab *ui = &vdunit_info[VDUNIT(bp->b_dev)];
70825675Ssam 
709*29921Skarels 	printf("dk%d%c: soft error sn%d status %b", minor(bp->b_dev) >> 3,
710*29921Skarels 	    'a'+(minor(bp->b_dev)&07), bp->b_blkno, dcb->operrsta, ERRBITS);
71125675Ssam 	if (ci->ctlr_type == SMD_ECTLR)
71225675Ssam 		printf(" ecode %x", dcb->err_code);
71325675Ssam 	printf("\n");
71425675Ssam }
71525675Ssam 
71625675Ssam /*ARGSUSED*/
71725675Ssam vdopen(dev, flag)
71825675Ssam 	dev_t dev;
71925675Ssam 	int flag;
72025675Ssam {
72125675Ssam 	register unit = VDUNIT(dev);
72225675Ssam 	register struct vba_device *vi = vddinfo[unit];
72325675Ssam 
72425675Ssam 	if (vi == 0 || vi->ui_alive == 0 || vi->ui_type >= nvddrv)
72525675Ssam 		return (ENXIO);
72625675Ssam 	if (vdunit_info[unit].info.partition[FILSYS(dev)].par_len == 0)
72725675Ssam 		return (ENXIO);
72825675Ssam 	return (0);
72925675Ssam }
73025675Ssam 
73124004Ssam vdread(dev, uio)
73225675Ssam 	dev_t dev;
73325675Ssam 	struct uio *uio;
73424004Ssam {
73524004Ssam 	register int unit = VDUNIT(dev);
73625675Ssam 	register unit_tab *ui = &vdunit_info[unit];
73724004Ssam 
73829564Ssam 	if (unit >= NDK)
73925675Ssam 		return (ENXIO);
74025675Ssam 	return (physio(vdstrategy, &ui->raw_q_element, dev, B_READ,
74125675Ssam 	    minphys, uio));
74224004Ssam }
74324004Ssam 
74424004Ssam vdwrite(dev, uio)
74525675Ssam 	dev_t dev;
74625675Ssam 	struct uio *uio;
74724004Ssam {
74824004Ssam 	register int unit = VDUNIT(dev);
74925675Ssam 	register unit_tab *ui = &vdunit_info[unit];
75024004Ssam 
75129564Ssam 	if (unit >= NDK)
75225675Ssam 		return (ENXIO);
75325675Ssam 	return (physio(vdstrategy, &ui->raw_q_element, dev, B_WRITE,
75425675Ssam 	    minphys, uio));
75524004Ssam }
75624004Ssam 
75724004Ssam /*
75825675Ssam  * Crash dump.
75924004Ssam  */
76025675Ssam vddump(dev)
76125675Ssam 	dev_t dev;
76224004Ssam {
76325675Ssam 	register int unit = VDUNIT(dev);
76425675Ssam 	register unit_tab *ui = &vdunit_info[unit];
76525675Ssam 	register fs_tab *fs = &ui->info;
76625675Ssam 	register int ctlr = vddinfo[unit]->ui_ctlr;
76725675Ssam 	register struct vba_ctlr *vba_vdctlr_info = vdminfo[ctlr];
76825675Ssam 	register int filsys = FILSYS(dev);
76925675Ssam 	register cdr *addr = (cdr *)(vba_vdctlr_info->um_addr);
77025675Ssam 	register int cur_blk, blkcount, blocks;
77125675Ssam 	caddr_t memaddr;
77224004Ssam 
77325675Ssam 	vdreset_ctlr(addr, ctlr);
77424004Ssam 	blkcount = maxfree - 2;		/* In 1k byte pages */
77525675Ssam 	if (dumplo + blkcount > fs->partition[filsys].par_len) {
77625675Ssam 		blkcount = fs->partition[filsys].par_len - dumplo;
77725675Ssam 		printf("vd%d: Dump truncated to %dMB\n", unit, blkcount/1024);
77825675Ssam 	}
77925675Ssam 	cur_blk = fs->partition[filsys].par_start + dumplo;
78025675Ssam 	memaddr = 0;
78124004Ssam 	while (blkcount > 0) {
78225675Ssam 		blocks = MIN(blkcount, DUMPSIZE);
78325675Ssam 		if (!vdwrite_block(addr, ctlr, unit, memaddr, cur_blk, blocks))
78425675Ssam 			return (EIO);
78525675Ssam 		blkcount -= blocks;
78625675Ssam 		memaddr += blocks * NBPG;
78725675Ssam 		cur_blk += blocks;
78824004Ssam 	}
78925675Ssam 	return (0);
79024004Ssam }
79124004Ssam 
79225675Ssam /*
79325675Ssam  * Write a block to disk during a crash dump.
79425675Ssam  */
79525675Ssam vdwrite_block(caddr, ctlr, unit, addr, block, blocks)
79625675Ssam 	register cdr *caddr;
79725675Ssam 	register int ctlr, unit;
79825675Ssam 	register caddr_t addr;
79925675Ssam 	register int block, blocks;
80024004Ssam {
80125925Ssam 	register ctlr_tab *ci = &vdctlr_info[ctlr];
80225925Ssam 	register fmt_mdcb *mdcb = &ci->ctlr_mdcb;
80325925Ssam 	register fmt_dcb *dcb = &ci->ctlr_dcb;
80425675Ssam 	register unit_tab *ui = &vdunit_info[unit];
80525675Ssam 	register fs_tab	 *fs = &ui->info;
80624004Ssam 
80725675Ssam 	block *= (int)ui->sec_per_blk;
80825675Ssam 	blocks *= (int)ui->sec_per_blk;
80925675Ssam 	mdcb->firstdcb = (fmt_dcb *)(PHYS(dcb));
81025675Ssam 	dcb->intflg = NOINT;
81125675Ssam 	dcb->opcode = WD;
81225675Ssam 	dcb->operrsta = 0;
81325675Ssam 	dcb->devselect = (char)(vddinfo[unit])->ui_slave;
81425675Ssam 	dcb->trailcnt = (char)(sizeof (trrw) / sizeof (long));
81525675Ssam 	dcb->trail.rwtrail.memadr = addr;
81625675Ssam 	dcb->trail.rwtrail.wcount = (short)
81725675Ssam 	    ((blocks * fs->secsize)/ sizeof (short));
81825675Ssam 	dcb->trail.rwtrail.disk.cylinder = (short)(block / ui->sec_per_cyl);
81925675Ssam 	dcb->trail.rwtrail.disk.track = (char)((block / fs->nsec) % fs->ntrak);
82025675Ssam 	dcb->trail.rwtrail.disk.sector = (char)(block % fs->nsec);
82125925Ssam 	VDDC_ATTENTION(caddr, (fmt_mdcb *)(PHYS(mdcb)), ci->ctlr_type);
82225925Ssam 	if (!vdpoll(ci, caddr, 5)) {
82325675Ssam 		printf(" during dump\n");
82425675Ssam 		return (0);
82525675Ssam 	}
82625675Ssam 	if (dcb->operrsta & HRDERR) {
827*29921Skarels 		printf("dk%d: hard error, status=%b\n", unit,
828*29921Skarels 		    dcb->operrsta, ERRBITS);
82925675Ssam 		return (0);
83025675Ssam 	}
83125675Ssam 	return (1);
83224004Ssam }
83324004Ssam 
83424004Ssam vdsize(dev)
83525675Ssam 	dev_t dev;
83624004Ssam {
83725675Ssam 	struct vba_device *vi = vddinfo[VDUNIT(dev)];
83824004Ssam 
83925675Ssam 	if (vi == 0 || vi->ui_alive == 0 || vi->ui_type >= nvddrv)
84025675Ssam 		return (-1);
84125675Ssam 	return (vdunit_info[VDUNIT(dev)].info.partition[FILSYS(dev)].par_len);
84224004Ssam }
84324004Ssam 
84425675Ssam /*
84525675Ssam  * Perform a controller reset.
84625675Ssam  */
84725675Ssam vdreset_ctlr(addr, ctlr)
84825675Ssam 	register cdr *addr;
84925675Ssam 	register int ctlr;
85024004Ssam {
85125675Ssam 	register struct buf *cq = &vdminfo[ctlr]->um_tab;
85225675Ssam 	register struct buf *uq = cq->b_forw;
85325675Ssam 	register ctlr_tab *ci = &vdctlr_info[ctlr];
85425675Ssam 
85525675Ssam 	VDDC_RESET(addr, ci->ctlr_type);
85625675Ssam 	ci->ctlr_started = 0;
85725675Ssam 	if (ci->ctlr_type == SMD_ECTLR) {
85825675Ssam 		addr->cdr_csr = 0;
85925675Ssam 		addr->mdcb_tcf = AM_ENPDA;
86025675Ssam 		addr->dcb_tcf = AM_ENPDA;
86125675Ssam 		addr->trail_tcf = AM_ENPDA;
86225675Ssam 		addr->data_tcf = AM_ENPDA;
86325675Ssam 		addr->cdr_ccf = CCF_STS | XMD_32BIT | BSZ_16WRD |
86425675Ssam 		    CCF_ENP | CCF_EPE | CCF_EDE | CCF_ECE | CCF_ERR;
86525675Ssam 	}
86625675Ssam 	if (vdnotrailer(addr, ctlr, 0, INIT, 10) & HRDERR) {
86725675Ssam 		printf("failed to init\n");
86825675Ssam 		return (0);
86925675Ssam 	}
87025675Ssam 	if (vdnotrailer(addr, ctlr, 0, DIAG, 10) & HRDERR) {
87125675Ssam 		printf("diagnostic error\n");
87225675Ssam 		return (0);
87325675Ssam 	}
87425675Ssam 	/*  reset all units attached to controller */
87525675Ssam 	uq = cq->b_forw;
87625675Ssam 	do {
87725675Ssam 		reset_drive(addr, ctlr, uq->b_dev, 0);
87825675Ssam 		uq = uq->b_forw;
87925675Ssam 	} while (uq != cq->b_forw);
88025675Ssam 	return (1);
88125675Ssam }
88224004Ssam 
88325675Ssam /*
88425675Ssam  * Perform a reset on a drive.
88525675Ssam  */
88625675Ssam reset_drive(addr, ctlr, slave, start)
88725675Ssam 	register cdr *addr;
88825675Ssam 	register int ctlr, slave, start;
88925675Ssam {
89025675Ssam 	register int type = vdctlr_info[ctlr].unit_type[slave];
89125675Ssam 
89225675Ssam 	if (type == UNKNOWN)
89325675Ssam 		return;
89425675Ssam 	if (!vdconfigure_drive(addr, ctlr, slave, type, start))
89525675Ssam 		printf("vd%d: drive %d: couldn't reset\n", ctlr, slave);
89625675Ssam }
89725675Ssam 
89825925Ssam /*
89925925Ssam  * Poll controller until operation completes
90025925Ssam  * or timeout expires.
90125925Ssam  */
90225925Ssam vdpoll(ci, addr, t)
90325925Ssam 	register ctlr_tab *ci;
90425925Ssam 	register cdr *addr;
90525925Ssam 	register int t;
90625925Ssam {
90725925Ssam 	register fmt_dcb *dcb = &ci->ctlr_dcb;
90825925Ssam 
90925925Ssam 	t *= 1000;
91025925Ssam 	uncache(&dcb->operrsta);
91125925Ssam 	while ((dcb->operrsta&(DCBCMP|DCBABT)) == 0) {
91225925Ssam 		DELAY(1000);
91325925Ssam 		uncache(&dcb->operrsta);
91425925Ssam 		if (--t <= 0) {
91525925Ssam 			printf("vd%d: controller timeout", ci-vdctlr_info);
91625925Ssam 			VDDC_ABORT(addr, ci->ctlr_type);
91725925Ssam 			DELAY(30000);
91825925Ssam 			uncache(&dcb->operrsta);
91925925Ssam 			return (0);
92025925Ssam 		}
92125925Ssam 	}
92225925Ssam 	if (ci->ctlr_type == SMD_ECTLR) {
92325925Ssam 		uncache(&addr->cdr_csr);
92425925Ssam 		while (addr->cdr_csr&CS_GO) {
92525925Ssam 			DELAY(50);
92625925Ssam 			uncache(&addr->cdr_csr);
92725925Ssam 		}
92825925Ssam 		DELAY(300);
92925925Ssam 	}
93025925Ssam 	DELAY(200);
93125925Ssam 	uncache(&dcb->operrsta);
93225925Ssam 	return (1);
93325925Ssam }
93425925Ssam 
93525675Ssam #ifdef notdef
93625675Ssam /*
93725675Ssam  * Dump the mdcb and DCB for diagnostic purposes.
93825675Ssam  */
93925675Ssam vdprintdcb(lp)
94025675Ssam 	register long *lp;
94125675Ssam {
94225675Ssam 	register int i, dcb, tc;
94325675Ssam 
94425675Ssam 	for (dcb = 0; lp; lp = (long *)(*lp), dcb++) {
94525675Ssam 		lp = (long *)((long)lp | 0xc0000000);
94625675Ssam 		printf("\nDump of dcb%d@%x:", dcb, lp);
94725675Ssam 		for (i = 0, tc = lp[3] & 0xff; i < tc+7; i++)
94825675Ssam 			printf(" %lx", lp[i]);
94925675Ssam 		printf("\n");
95024004Ssam 	}
95125675Ssam 	DELAY(1750000);
95224004Ssam }
95324004Ssam #endif
95425675Ssam #endif
955