xref: /csrg-svn/sys/tahoe/vba/vd.c (revision 24004)
1*24004Ssam /*	vd.c	1.1	85/07/21	*/
2*24004Ssam 
3*24004Ssam #include "fsd.h"
4*24004Ssam #if NVD > 0
5*24004Ssam /*
6*24004Ssam **	VDDC Driver - Versabus to SMD direct interface version.
7*24004Ssam **		Written for TAHOE vmunix, CCI-WDC 9/1/83.
8*24004Ssam */
9*24004Ssam 
10*24004Ssam #include "../h/param.h"
11*24004Ssam #include "../h/buf.h"
12*24004Ssam #include "../h/cmap.h"
13*24004Ssam #include "../h/conf.h"
14*24004Ssam #include "../h/dir.h"
15*24004Ssam #include "../h/dk.h"
16*24004Ssam #include "../h/map.h"
17*24004Ssam #include "../machine/mtpr.h"
18*24004Ssam #include "../machine/pte.h"
19*24004Ssam #include "../h/systm.h"
20*24004Ssam #include "../vba/vbavar.h"
21*24004Ssam #include "../h/user.h"
22*24004Ssam #include "../h/vmmac.h"
23*24004Ssam #include "../h/proc.h"
24*24004Ssam #include "../h/uio.h"
25*24004Ssam #include "../vba/vddc.h"
26*24004Ssam 
27*24004Ssam int	vddebug = 1;	/* if = 1, error messages are printed on the console */
28*24004Ssam int	vdintflg = 0;	/* if = 1, interrupts are handled by the driver,
29*24004Ssam 			 * otherwise they are just ignored. (during setup) */
30*24004Ssam 
31*24004Ssam static struct size FSD[] = {
32*24004Ssam     9600,       0,	/* minor 0/ 8/16/24 = fsd0a - fsd3a - cyl   0 -  59*/
33*24004Ssam    12000,    9600,	/* minor 1/ 9/17/25 = fsd0b - fsd3b - cyl  60 - 134*/
34*24004Ssam   108480,   21600,	/* minor 2/10/18/26 = fsd0c - fsd3c - cyl 135 - 812*/
35*24004Ssam     1600,  130080,	/* minor 3/11/19/27 = fsd0d - fsd3d - cyl 813 - 822*/
36*24004Ssam   130080,       0,	/* minor 4/12/20/28 = fsd0e - fsd3e - cyl   0 - 812*/
37*24004Ssam   131680,       0,	/* minor 5/13/21/29 = fsd0f - fsd3f - cyl   0 - 822*/
38*24004Ssam        0,	0,	/* Non existent minor device */
39*24004Ssam        0,	0,	/* Non existent minor device */
40*24004Ssam        0,	0,	/* Non existent minor device */
41*24004Ssam        0,	0,	/* Non existent minor device */
42*24004Ssam        0,	0,	/* Non existent minor device */
43*24004Ssam        0,	0,	/* Non existent minor device */
44*24004Ssam        0,	0,	/* Non existent minor device */
45*24004Ssam        0,	0,	/* Non existent minor device */
46*24004Ssam        0,	0,	/* Non existent minor device */
47*24004Ssam        0,	0,	/* Non existent minor device */
48*24004Ssam };
49*24004Ssam 
50*24004Ssam static struct size	SMD[]= {
51*24004Ssam     20064,	0, 	/* minor 32/40/48/56 = smd0a - smd3a cyl 0- 65 */
52*24004Ssam     13680,  20064, 	/* minor 33/41/49/57 = smd0b - smd3b cyl 66- 110 */
53*24004Ssam    214928,  33744, 	/* minor 34/42/50/58 = smd0c - smd3c cyl 111-817 */
54*24004Ssam      1520, 248672, 	/* minor 35/43/51/59 = smd0d - smd3d cyl 818-822 */
55*24004Ssam    248672,	0, 	/* minor 36/44/52/60 = smd0e - smd3e cyl 0-817 */
56*24004Ssam    250192,	0, 	/* minor 37/45/53/61 = smd0f - smd3f cyl 0-822 */
57*24004Ssam 	0,	0, 	/* minor 38/46/54/62 = smd0g - smd3g */
58*24004Ssam 	0,	0, 	/* minor 39/47/55/63 = smd0h - smd3h */
59*24004Ssam 	0,	0,	/* Non existent minor device */
60*24004Ssam 	0,	0,	/* Non existent minor device */
61*24004Ssam 	0,	0,	/* Non existent minor device */
62*24004Ssam 	0,	0,	/* Non existent minor device */
63*24004Ssam 	0,	0,	/* Non existent minor device */
64*24004Ssam 	0,	0,	/* Non existent minor device */
65*24004Ssam 	0,	0,	/* Non existent minor device */
66*24004Ssam 	0,	0,	/* Non existent minor device */
67*24004Ssam };
68*24004Ssam 
69*24004Ssam static struct size XFSD[] = {
70*24004Ssam     20352,	0, 	/* minor 64/72/80/88 = xfsd0a - xfsd3a cyl 0- 52 */
71*24004Ssam     20352,  20352, 	/* minor 65/73/81/89 = xfsd0b - xfsd3b cyl 53- 105 */
72*24004Ssam    230400,  40704, 	/* minor 66/74/82/90 = xfsd0c - xfsd3c cyl 106-705 */
73*24004Ssam      1920, 271104, 	/* minor 67/75/83/91 = xfsd0d - xfsd3d cyl 706-710 */
74*24004Ssam    271104,	0, 	/* minor 68/76/84/92 = xfsd0e - xfsd3e cyl 0-705 */
75*24004Ssam    273024,	0, 	/* minor 69/77/85/93 = xfsd0f - xfsd3f cyl 0-710 */
76*24004Ssam 	0,	0, 	/* minor 70/78/86/94 = xfsd0g - xfsd3g */
77*24004Ssam 	0,	0, 	/* minor 71/79/87/95 = xfsd0h - xfsd3h */
78*24004Ssam 	0,	0,	/* Non existent minor device */
79*24004Ssam 	0,	0,	/* Non existent minor device */
80*24004Ssam 	0,	0,	/* Non existent minor device */
81*24004Ssam 	0,	0,	/* Non existent minor device */
82*24004Ssam 	0,	0,	/* Non existent minor device */
83*24004Ssam 	0,	0,	/* Non existent minor device */
84*24004Ssam 	0,	0,	/* Non existent minor device */
85*24004Ssam 	0,	0,	/* Non existent minor device */
86*24004Ssam };
87*24004Ssam 
88*24004Ssam /*
89*24004Ssam /*
90*24004Ssam /* Layout of minor number assignments for the VDDC devices.
91*24004Ssam /*
92*24004Ssam /* 	  1
93*24004Ssam /*	  5		            3 2   0
94*24004Ssam /*	 +---------------------------+-----+
95*24004Ssam /*	 |     		 Unit number | FLS |
96*24004Ssam /*	 +---------------------------+-----+
97*24004Ssam /*			      	   |    |_____ File system # ( 0-7 )
98*24004Ssam /*			      	   |__________ Unit # in the system
99*24004Ssam /*
100*24004Ssam /********************************************************/
101*24004Ssam 
102*24004Ssam #define VDUNIT(x)	(minor(x) >> 3)
103*24004Ssam #define FLSYS(x)	(minor(x) & 0x07)
104*24004Ssam #define PHYS(x)		( vtoph( 0, (int) (x) ) )
105*24004Ssam 
106*24004Ssam 
107*24004Ssam /* Drive types should be in order of drive capacity for auto-configuration */
108*24004Ssam /* e.g: smallest capacity = drive type 0, highest capacity = type NXPDRV-1 */
109*24004Ssam 
110*24004Ssam struct vdst {
111*24004Ssam 	short nsect;
112*24004Ssam 	short ntrak;
113*24004Ssam 	short nspc;
114*24004Ssam 	short ncyl;
115*24004Ssam 	struct size *sizes;
116*24004Ssam 	short dtype;		/* type as in byte 5 (drive) of iopb */
117*24004Ssam 	char	*name;		/* drive name for autoconf */
118*24004Ssam } vdst[] = {
119*24004Ssam 
120*24004Ssam 16,	10,	16*10,	823,	FSD,	0,	"fsd",
121*24004Ssam 16,	19,	16*19,	823,	SMD,	1, 	"smd",
122*24004Ssam 16,	24,	16*24,  711,   XFSD,	2,	"xfd"
123*24004Ssam };
124*24004Ssam 
125*24004Ssam 
126*24004Ssam struct	vba_ctlr *vdminfo[NVD];
127*24004Ssam struct  vba_device *vddinfo[NFSD];
128*24004Ssam 
129*24004Ssam /*
130*24004Ssam **	Internal Functions
131*24004Ssam */
132*24004Ssam int	vdopen();
133*24004Ssam int	vdclose();
134*24004Ssam int	vdprobe();		/* See if VDDC is really there */
135*24004Ssam int	vd_setup();		/* Called from vdprobe */
136*24004Ssam int	vdslave();		/* See if drive is really there */
137*24004Ssam int	vdattach();
138*24004Ssam int	vddgo();
139*24004Ssam int	vdstrategy();		/* VDDC strategy routine */
140*24004Ssam int	vdstart();		/* Top level interface to device queue */
141*24004Ssam int	vdintr();		/* Top Level ISR */
142*24004Ssam int	vdread();		/* raw i/o read routine */
143*24004Ssam int	vdwrite();		/* raw i/o write routine */
144*24004Ssam int	vddump();		/* dump routine */
145*24004Ssam int	vdsize();		/* sizes for swapconfig */
146*24004Ssam int	dskrst();		/* reset a drive after hard error */
147*24004Ssam 
148*24004Ssam long	vdstd[] = {
149*24004Ssam 		0x0f2000 };
150*24004Ssam 
151*24004Ssam struct	vba_driver vddriver = {
152*24004Ssam 	vdprobe, vdslave, vdattach, vddgo, vdstd,
153*24004Ssam 	"smd/fsd", vddinfo, "vd", vdminfo
154*24004Ssam };
155*24004Ssam 
156*24004Ssam struct	buf	vdutab[NFSD];
157*24004Ssam struct 	buf	rvdbuf[NFSD];
158*24004Ssam char	vdbuf[NVD][MAXBPTE * NBPG];	/* internal buffer for raw/swap i/o */
159*24004Ssam long	vdbufused[NVD];
160*24004Ssam extern char	vd0utl[],vd1utl[],vd2utl[],vd3utl[];
161*24004Ssam 
162*24004Ssam /*
163*24004Ssam **	Disk Address
164*24004Ssam */
165*24004Ssam struct	dskadr	{
166*24004Ssam 	char	track;		/* all 8 bits */
167*24004Ssam 	char	sector;		/* low order 5 bits */
168*24004Ssam 	short	cylinder;	/* low order 12 bits */
169*24004Ssam };
170*24004Ssam 
171*24004Ssam /*
172*24004Ssam **	DCB Trailer Formats
173*24004Ssam **********************************/
174*24004Ssam 
175*24004Ssam /*
176*24004Ssam **	Read / Write Trailer
177*24004Ssam */
178*24004Ssam struct	trrw	{
179*24004Ssam 	char	*memadr;			/* memory address */
180*24004Ssam 	long	wcount;				/* 16 bit word count */
181*24004Ssam 	struct	dskadr	disk;			/* disk address */
182*24004Ssam };
183*24004Ssam 
184*24004Ssam /*
185*24004Ssam **	Format Trailer
186*24004Ssam */
187*24004Ssam struct	trfmt	{
188*24004Ssam 	char	*addr;			/* data buffer to be filled on sector*/
189*24004Ssam 	long	nsectors;		/* # of sectors to be formatted */
190*24004Ssam 	struct	dskadr	disk;
191*24004Ssam 	struct	dskadr  hdr;
192*24004Ssam };
193*24004Ssam 
194*24004Ssam /*
195*24004Ssam **	Reset / Configure Trailer
196*24004Ssam */
197*24004Ssam struct	treset	{
198*24004Ssam 	long	ncyl;		/* # cylinders */
199*24004Ssam 	long	nsurfaces;	/* # surfaces */
200*24004Ssam };				/* # of sectors is defined by VDDC */
201*24004Ssam 				/* to be 32/track of 512 data bytes each */
202*24004Ssam 
203*24004Ssam /*
204*24004Ssam **	Seek Trailer
205*24004Ssam */
206*24004Ssam struct	trseek	{
207*24004Ssam 	struct	dskadr	disk;
208*24004Ssam };
209*24004Ssam 
210*24004Ssam /*
211*24004Ssam **	DCB Format
212*24004Ssam */
213*24004Ssam struct	fmt_dcb	{
214*24004Ssam 	struct	fmt_dcb	*nxtdcb;	/* next dcb in chain or End of Chain */
215*24004Ssam 	short	intflg;			/* interrupt settings and flags */
216*24004Ssam 	short	opcode;			/* DCB Command code etc... */
217*24004Ssam 	long	operrsta;		/* Error & Status info */
218*24004Ssam 	short	fill;			/* not used */
219*24004Ssam 	char	devselect;		/* Drive selection */
220*24004Ssam 	char	trailcnt;		/* Trailer Word Count */
221*24004Ssam 	long	err_memadr;		/* Error memory address */
222*24004Ssam 	short	fill2;
223*24004Ssam 	short	err_wcount;		/* Error word count */
224*24004Ssam 	short	err_track;		/* Error track/sector */
225*24004Ssam 	short	err_cyl;		/* Error cylinder adr */
226*24004Ssam 	union	{
227*24004Ssam 		struct	trrw	rwtrail;	/* read/write trailer */
228*24004Ssam 		struct	trfmt	fmtrail;	/* format trailer */
229*24004Ssam 		struct	treset	resetrail;	/* reset/configure trailer */
230*24004Ssam 		struct	trseek	seektrail;	/* seek trailer */
231*24004Ssam 	} trail;
232*24004Ssam };
233*24004Ssam 
234*24004Ssam /*
235*24004Ssam **	MDCB Format
236*24004Ssam */
237*24004Ssam struct	fmt_mdcb	{
238*24004Ssam 	struct	fmt_dcb	*firstdcb;	/* first dcb in chain */
239*24004Ssam 	struct	fmt_dcb	*procdcb;	/* dcb being processed */
240*24004Ssam 	struct	fmt_dcb	*intdcb;	/* dcb causing interrupt */
241*24004Ssam 	long	vddcstat;		/* VDDC status */
242*24004Ssam }mdcbx[NVD];
243*24004Ssam 
244*24004Ssam /*
245*24004Ssam **	DCB
246*24004Ssam */
247*24004Ssam 
248*24004Ssam struct	fmt_dcb		dcbx[NVD];
249*24004Ssam 
250*24004Ssam int vdtimeout;
251*24004Ssam #define	POLLTILLDONE(x, name) { \
252*24004Ssam 	vdtimeout = 1000*(x); \
253*24004Ssam 	uncache((char *)&dcb->operrsta); \
254*24004Ssam 	while (! (dcb->operrsta & DCBCMP)) { \
255*24004Ssam 		DELAY(1000); \
256*24004Ssam 		vdtimeout--; \
257*24004Ssam 		uncache((char *)&dcb->operrsta); \
258*24004Ssam 		if (vdtimeout <=0) { \
259*24004Ssam 			printf("vd: timeout on %s\n", name);\
260*24004Ssam 			return(0); \
261*24004Ssam 		} \
262*24004Ssam 	} \
263*24004Ssam }
264*24004Ssam 
265*24004Ssam /*
266*24004Ssam **	See if the controller is really there.
267*24004Ssam **	if TRUE - initialize the controller.
268*24004Ssam */
269*24004Ssam vdprobe(cntrl_vaddr)
270*24004Ssam caddr_t cntrl_vaddr;
271*24004Ssam {
272*24004Ssam 	if ( badaddr(cntrl_vaddr,2) ) return(0); /* no controller */
273*24004Ssam 	else
274*24004Ssam 		if (vd_setup(cntrl_vaddr))	/* initialize the controller */
275*24004Ssam 			return(1);
276*24004Ssam 		else return(0);		/* initialization error */
277*24004Ssam }
278*24004Ssam 
279*24004Ssam vd_setup(cntrl_vaddr)
280*24004Ssam caddr_t cntrl_vaddr;
281*24004Ssam {
282*24004Ssam 	register struct fmt_dcb *dcb = &dcbx[0];
283*24004Ssam 	register struct fmt_mdcb *mdcb = &mdcbx[0];
284*24004Ssam 	int j;
285*24004Ssam 
286*24004Ssam 	VDDC_RESET(cntrl_vaddr);		/* Reset the controller */
287*24004Ssam 		/* Burn some time ...... needed after accessing reset port */
288*24004Ssam 	for (j=0; j<20; j++)
289*24004Ssam 		DELAY(1000);
290*24004Ssam 
291*24004Ssam 	/* setup & issue INIT to initialize VDDC */
292*24004Ssam 
293*24004Ssam 	dcb->opcode = INIT;
294*24004Ssam 	dcb->nxtdcb = (struct fmt_dcb *)0;
295*24004Ssam 	dcb->intflg = NOINT;
296*24004Ssam 	mdcb->firstdcb = (struct fmt_dcb *)PHYS(dcb);
297*24004Ssam 	dcb->operrsta  = 0;
298*24004Ssam 	VDDC_ATTENTION(cntrl_vaddr,PHYS(mdcb) );	/* do it */
299*24004Ssam 	POLLTILLDONE(1,"INIT");		/* poll till done */
300*24004Ssam 	if (dcb->operrsta & HRDERR) {
301*24004Ssam 		if (vddebug)
302*24004Ssam 			printf("vd: init error, err=%b\n",
303*24004Ssam 			    dcb->operrsta, ERRBITS);
304*24004Ssam 		return(0);
305*24004Ssam 	}
306*24004Ssam 	/* setup & issue DIAGNOSE */
307*24004Ssam 
308*24004Ssam 	dcb->opcode = DIAG;
309*24004Ssam 	dcb->nxtdcb = (struct fmt_dcb *)0;
310*24004Ssam 	dcb->intflg = NOINT;
311*24004Ssam 	mdcb->firstdcb = (struct fmt_dcb *)PHYS(dcb);
312*24004Ssam 	dcb->operrsta  = 0;
313*24004Ssam 	VDDC_ATTENTION(cntrl_vaddr,PHYS(mdcb) )	/* do it */
314*24004Ssam 	POLLTILLDONE(1,"DIAG")		/* poll till done */
315*24004Ssam 	if (dcb->operrsta & HRDERR) {
316*24004Ssam 		if (vddebug)
317*24004Ssam 			printf("vd: diagnose error, err=%b\n",
318*24004Ssam 			    dcb->operrsta, ERRBITS);
319*24004Ssam 		return(0);
320*24004Ssam 	}
321*24004Ssam 	/* Start drives command */
322*24004Ssam #ifdef notdef
323*24004Ssam 	dcb->opcode = VDSTART;
324*24004Ssam 	dcb->nxtdcb = (struct fmt_dcb *)0;
325*24004Ssam 	dcb->intflg = NOINT;
326*24004Ssam 	mdcb->firstdcb = (struct fmt_dcb *)PHYS(dcb);
327*24004Ssam 	dcb->operrsta  = 0;
328*24004Ssam 	VDDC_ATTENTION(cntrl_vaddr,PHYS(mdcb) )	/* do it */
329*24004Ssam 	POLLTILLDONE(20,"VDSTART")		/* poll till done */
330*24004Ssam 	if (dcb->operrsta & HRDERR) {
331*24004Ssam 		if (vddebug)
332*24004Ssam 			printf("vd: start error, err=%b\n",
333*24004Ssam 			    dcb->operrsta, ERRBITS);
334*24004Ssam 		return(0);
335*24004Ssam 	}
336*24004Ssam #endif
337*24004Ssam 	return(1);
338*24004Ssam    }
339*24004Ssam 
340*24004Ssam /*
341*24004Ssam  * See if a drive is really there
342*24004Ssam  * Try to Reset/Configure the drive, then test its status.
343*24004Ssam */
344*24004Ssam vdslave(ui,cntrl_vaddr)
345*24004Ssam register struct vba_device *ui;
346*24004Ssam register caddr_t cntrl_vaddr;
347*24004Ssam {
348*24004Ssam 	register struct fmt_dcb	*dcb = &dcbx[0];
349*24004Ssam 	register struct fmt_mdcb *mdcb = &mdcbx[ui->ui_ctlr];
350*24004Ssam 	register struct vdst *st;
351*24004Ssam 	int dsktype;
352*24004Ssam 
353*24004Ssam 	/*
354*24004Ssam 	**  check drive status - see if drive exists.
355*24004Ssam 	*/
356*24004Ssam 	dcb->opcode = VDSTATUS;
357*24004Ssam 	dcb->intflg = NOINT;
358*24004Ssam 	dcb->operrsta  = 0;
359*24004Ssam 	dcb->devselect = (char)ui->ui_slave;
360*24004Ssam 	dcb->trailcnt = (char)0;
361*24004Ssam 	mdcb->firstdcb = (struct fmt_dcb *)PHYS(dcb);
362*24004Ssam 	mdcb->vddcstat = 0;
363*24004Ssam 	VDDC_ATTENTION(cntrl_vaddr,PHYS(mdcb))	/* do it */
364*24004Ssam 	POLLTILLDONE(5,"VDSTATUS")
365*24004Ssam #ifdef notdef
366*24004Ssam 	if (dcb->operrsta & HRDERR) {
367*24004Ssam 		if (vddebug)
368*24004Ssam 		  printf("vd%d: status error, err=%b\n", ui->ui_unit,
369*24004Ssam 		      dcb->operrsta, ERRBITS);
370*24004Ssam 		return(0);
371*24004Ssam 	}
372*24004Ssam #endif
373*24004Ssam 	uncache((char *)&mdcb->vddcstat);
374*24004Ssam 	if (mdcb->vddcstat & DRVNRDY) return(0); /* not ready-> non existent */
375*24004Ssam 
376*24004Ssam 	/*
377*24004Ssam 	 * drive is alive, now get its type!
378*24004Ssam 	 * Seek on all drive types starting from the largest one.
379*24004Ssam 	 * a sucessful seek to the last sector/cylinder/track verifies
380*24004Ssam 	 * the drive type connected to this port.
381*24004Ssam 	 */
382*24004Ssam 	for (dsktype = NVDDRV-1; dsktype >= 0; dsktype--) {
383*24004Ssam 		st = &vdst[dsktype];
384*24004Ssam 		dcb->opcode = RSTCFG;		/* configure drive command */
385*24004Ssam 		dcb->intflg = NOINT;
386*24004Ssam 		dcb->operrsta  = 0;
387*24004Ssam 		dcb->trail.resetrail.ncyl = st->ncyl;
388*24004Ssam 		dcb->trail.resetrail.nsurfaces = st->ntrak;
389*24004Ssam 		dcb->devselect = (char)ui->ui_slave;
390*24004Ssam 		dcb->trailcnt = (char)2;
391*24004Ssam 		mdcb->firstdcb = (struct fmt_dcb *)PHYS(dcb);
392*24004Ssam 		VDDC_ATTENTION(cntrl_vaddr,PHYS(mdcb) )	/* do it */
393*24004Ssam 		POLLTILLDONE(3,"RSTCFG")
394*24004Ssam 		if (dcb->operrsta & HRDERR) {
395*24004Ssam 			if (vddebug)
396*24004Ssam 				printf("vd%d: reset error, err=%b\n",
397*24004Ssam 				    ui->ui_unit, dcb->operrsta, ERRBITS);
398*24004Ssam 			return(0);
399*24004Ssam 		}
400*24004Ssam 		mdcb->firstdcb = (struct fmt_dcb *)PHYS(dcb);
401*24004Ssam 		dcb->intflg = NOINT;
402*24004Ssam 		dcb->opcode =  RD;
403*24004Ssam 		dcb->operrsta = 0;
404*24004Ssam 		dcb->devselect = (char)ui->ui_slave;
405*24004Ssam 		dcb->trailcnt = (char)3;
406*24004Ssam 		dcb->trail.rwtrail.memadr = (char *)PHYS(vdbuf);
407*24004Ssam 		dcb->trail.rwtrail.wcount = 256;
408*24004Ssam 		dcb->trail.rwtrail.disk.cylinder = st->ncyl -4;
409*24004Ssam 		dcb->trail.rwtrail.disk.track = st->ntrak -1;
410*24004Ssam 		dcb->trail.rwtrail.disk.sector = 0;
411*24004Ssam 		VDDC_ATTENTION(cntrl_vaddr,PHYS(mdcb) )	/* do it */
412*24004Ssam 		POLLTILLDONE(5,"RD")
413*24004Ssam if (vddebug)
414*24004Ssam 	printf("vd%d: cyl %d, trk %d, sec %d, operrsta err=%b\n",
415*24004Ssam 	   ui->ui_unit,
416*24004Ssam 	   dcb->trail.rwtrail.disk.cylinder,
417*24004Ssam 	   dcb->trail.rwtrail.disk.track,
418*24004Ssam 	   dcb->trail.rwtrail.disk.sector,
419*24004Ssam 	   dcb->operrsta, ERRBITS);
420*24004Ssam 		if ( (dcb->operrsta & HRDERR) == 0)
421*24004Ssam 		/* found the drive type! */
422*24004Ssam 			break;
423*24004Ssam 	}
424*24004Ssam 	if (dsktype < 0) {
425*24004Ssam 		/* If reached here, a drive which is not defined in the
426*24004Ssam 		 * 'vdst' tables is connected. Cannot set it's type.
427*24004Ssam 		 */
428*24004Ssam 		printf("vd%d: unrecognized drive type\n", ui->ui_unit);
429*24004Ssam 		return(0);
430*24004Ssam 	}
431*24004Ssam 	ui->ui_type = dsktype;
432*24004Ssam 	vddriver.ud_dname = st->name;
433*24004Ssam 	return(1);
434*24004Ssam }
435*24004Ssam 
436*24004Ssam vdattach(ui)
437*24004Ssam struct vba_device *ui;
438*24004Ssam {
439*24004Ssam 	if (ui->ui_dk >= 0)
440*24004Ssam 		dk_mspw[ui->ui_dk] = .0000020345;	/* BAD VALUE */
441*24004Ssam }
442*24004Ssam 
443*24004Ssam vddgo(um)
444*24004Ssam struct vba_ctlr *um;
445*24004Ssam {
446*24004Ssam }
447*24004Ssam 
448*24004Ssam vdstrategy(bp)
449*24004Ssam register struct buf *bp;
450*24004Ssam {
451*24004Ssam 	register struct vba_device *ui;
452*24004Ssam 	register struct vba_ctlr *um;
453*24004Ssam 	register int unit;
454*24004Ssam 	register struct buf *dp;
455*24004Ssam 	register struct size *sizep;
456*24004Ssam 	int index, blocks, s;
457*24004Ssam 
458*24004Ssam 	vdintflg = 1;		/* enable interrupts handling by the driver */
459*24004Ssam 	blocks = (bp->b_bcount + DEV_BSIZE - 1) >> DEV_BSHIFT;
460*24004Ssam 	unit = VDUNIT(bp->b_dev);
461*24004Ssam 	ui = vddinfo[unit];
462*24004Ssam 	if (ui == 0 || ui->ui_alive == 0) goto bad1;
463*24004Ssam 	index = FLSYS(bp->b_dev); /* get file system index */
464*24004Ssam 	sizep = vdst[ui->ui_type].sizes;
465*24004Ssam 	if (bp->b_blkno < 0 ||
466*24004Ssam 	 (dkblock(bp)+blocks > sizep[index].nblocks))	/* disk overflow */
467*24004Ssam 		goto bad1;
468*24004Ssam 	s = spl8();
469*24004Ssam 	dp = &vdutab[ui->ui_unit];
470*24004Ssam 	bp->b_resid = bp->b_blkno + sizep[index].block0;
471*24004Ssam 					/* block # plays same role as
472*24004Ssam 					   cylinder # for disksort, as long
473*24004Ssam 					   as increasing blocks correspond to
474*24004Ssam 					   increasing cylinders on disk */
475*24004Ssam 
476*24004Ssam 	buf_setup (bp, SECTSIZ);
477*24004Ssam 
478*24004Ssam 	disksort(dp, bp);
479*24004Ssam 	if (dp->b_active == 0) {	/* unit is on controller queue */
480*24004Ssam 		/* put the device on the controller queue */
481*24004Ssam 		dp->b_forw = NULL;		/* end of queue indicator */
482*24004Ssam 		um = ui->ui_mi;		/* get controller structure !! */
483*24004Ssam 		if (um->um_tab.b_actf == NULL)	/* controller queue is empty */
484*24004Ssam 			um->um_tab.b_actf = dp;
485*24004Ssam 		else
486*24004Ssam 			um->um_tab.b_actl->b_forw = dp; /* add into queue */
487*24004Ssam 		um->um_tab.b_actl = dp;		/* update queue tail */
488*24004Ssam 		dp->b_active ++;
489*24004Ssam 	}
490*24004Ssam 	bp = &ui->ui_mi->um_tab;	/* controller structure addr */
491*24004Ssam 	if (bp->b_actf && 		/* cntrl queue not empty */
492*24004Ssam 		bp->b_active == 0)	/* controller not active */
493*24004Ssam 		(void) vdstart(ui->ui_mi);/* go start I/O */
494*24004Ssam 	splx(s);
495*24004Ssam 	return;
496*24004Ssam 
497*24004Ssam bad1:
498*24004Ssam 	bp->b_flags |= B_ERROR;
499*24004Ssam 	iodone(bp);
500*24004Ssam 	return;
501*24004Ssam }
502*24004Ssam 
503*24004Ssam 
504*24004Ssam /*
505*24004Ssam  * Start up a transfer on a drive.
506*24004Ssam  */
507*24004Ssam vdstart(um)
508*24004Ssam register struct vba_ctlr *um;
509*24004Ssam {
510*24004Ssam 	register struct buf *bp, *dp;
511*24004Ssam 	register struct fmt_dcb *dcb = &dcbx[um->um_ctlr];
512*24004Ssam 	register struct fmt_mdcb *mdcb;
513*24004Ssam 	register struct size *sizep;	/* Pointer to one of the tables */
514*24004Ssam 	register struct vdst *st;
515*24004Ssam 	register int index ;		/* Index in the relevant table */
516*24004Ssam 	register int phadr;		/* Buffer's physical address */
517*24004Ssam 	register caddr_t cntrl_vaddr = um->um_addr;
518*24004Ssam 	int	sblock, unit;
519*24004Ssam 	int ct;
520*24004Ssam 
521*24004Ssam loop:
522*24004Ssam 	/*
523*24004Ssam 	 * Pull a request off the controller queue
524*24004Ssam 	 */
525*24004Ssam 	if ((dp = um->um_tab.b_actf) == NULL)
526*24004Ssam 		return ;
527*24004Ssam 	if ((bp = dp->b_actf) == NULL) {
528*24004Ssam 		dp->b_active = 0;	/* device removed from ctlr queue */
529*24004Ssam 		um->um_tab.b_actf = dp->b_forw;
530*24004Ssam 		goto loop;
531*24004Ssam 	}
532*24004Ssam 	/*
533*24004Ssam 		 * Mark controller busy, and
534*24004Ssam 		 * prepare a command packet for the controller.
535*24004Ssam 		 */
536*24004Ssam 	um->um_tab.b_active++;
537*24004Ssam 	unit = VDUNIT(bp->b_dev);
538*24004Ssam 	st = &vdst[vddinfo[unit]->ui_type];
539*24004Ssam 	mdcb = &mdcbx[vddinfo[unit]->ui_ctlr];
540*24004Ssam 	index = FLSYS(bp->b_dev);
541*24004Ssam 	sizep = st->sizes;
542*24004Ssam 	mdcb->firstdcb = (struct fmt_dcb *)PHYS(dcb);
543*24004Ssam 	dcb->intflg = INTDUN;		/* interrupt on completion */
544*24004Ssam 	dcb->opcode = (bp->b_flags & B_READ) ? RD : WD;
545*24004Ssam 	dcb->operrsta = 0;
546*24004Ssam 	dcb->devselect = (char)(vddinfo[unit])->ui_slave;
547*24004Ssam 	dcb->trailcnt = (char)3;
548*24004Ssam 	ct = vddinfo[unit]->ui_ctlr;
549*24004Ssam 
550*24004Ssam 	switch (ct) {
551*24004Ssam 		case 0:
552*24004Ssam 			phadr = get_ioadr(bp, vdbuf[0], VD0map, (caddr_t)vd0utl);
553*24004Ssam 			break;
554*24004Ssam 		case 1:
555*24004Ssam 			phadr = get_ioadr(bp, vdbuf[1], VD1map, (caddr_t)vd1utl);
556*24004Ssam 			break;
557*24004Ssam 		case 2:
558*24004Ssam 			phadr = get_ioadr(bp, vdbuf[2], VD2map, (caddr_t)vd2utl);
559*24004Ssam 			break;
560*24004Ssam 		case 3:
561*24004Ssam 			phadr = get_ioadr(bp, vdbuf[3], VD3map, (caddr_t)vd3utl);
562*24004Ssam 			break;
563*24004Ssam 	}
564*24004Ssam /*
565*24004Ssam 	phadr = get_ioadr(bp, vdbuf, IOmap, (caddr_t)ioutl);
566*24004Ssam */
567*24004Ssam 
568*24004Ssam 	if (vddinfo[unit]->ui_dk >= 0) {
569*24004Ssam 		int dku = vddinfo[unit]->ui_dk;
570*24004Ssam 		dk_busy |= 1<<dku;
571*24004Ssam 		dk_xfer[dku]++;
572*24004Ssam 		dk_wds[dku] += bp->b_bcount>>6;
573*24004Ssam 	}
574*24004Ssam 	dcb->trail.rwtrail.memadr = (char *)phadr;
575*24004Ssam 	dcb->trail.rwtrail.wcount = (bp->b_bcount + 1) / 2;
576*24004Ssam 	sblock = sizep[index].block0 + bp->b_blkno;
577*24004Ssam 	dcb->trail.rwtrail.disk.cylinder = (short)(sblock / st->nspc);
578*24004Ssam 	dcb->trail.rwtrail.disk.track = (char)((sblock % st->nspc) / st->nsect);
579*24004Ssam 	dcb->trail.rwtrail.disk.sector = (char)(sblock*2 % (st->nsect*2));
580*24004Ssam 
581*24004Ssam #ifdef VDDCPERF
582*24004Ssam 	scope_out(1);
583*24004Ssam #endif
584*24004Ssam 
585*24004Ssam 	VDDC_ATTENTION(cntrl_vaddr,PHYS(mdcb))	/* do it */
586*24004Ssam }
587*24004Ssam 
588*24004Ssam 
589*24004Ssam /*
590*24004Ssam  * Handle a disk interrupt.
591*24004Ssam  */
592*24004Ssam vdintr(vdnum)
593*24004Ssam register vdnum;
594*24004Ssam {
595*24004Ssam 	register struct buf *bp, *dp;
596*24004Ssam 	register struct vba_ctlr *um = vdminfo[vdnum];
597*24004Ssam 	register struct fmt_dcb *dcb = &dcbx[vdnum];
598*24004Ssam 	register struct fmt_mdcb *mdcb = &mdcbx[vdnum];
599*24004Ssam 	register struct vdst *st;
600*24004Ssam 	int unit;
601*24004Ssam 	struct vba_device *ui;
602*24004Ssam 
603*24004Ssam #ifdef VDDCPERF
604*24004Ssam 	scope_out(2);
605*24004Ssam #endif
606*24004Ssam 	if (intenable == 0 || vdintflg == 0) 	/* ignore all interrupts */
607*24004Ssam 		return;
608*24004Ssam 	if (um->um_tab.b_active == NULL) return;/* unexpected interrupt */
609*24004Ssam 	uncache((char *)&mdcb->intdcb);
610*24004Ssam 	uncache((char *)&dcb->operrsta);
611*24004Ssam 	if ( mdcb->intdcb != (struct fmt_dcb *)PHYS(dcb)) {	/* dcb causing interrupt */
612*24004Ssam 		printf("vd%d: bad dcb=%x (phys=%x)\n",
613*24004Ssam 		    vdnum, mdcb->intdcb, PHYS(dcb));
614*24004Ssam 		return;
615*24004Ssam 	}
616*24004Ssam 	if (! (dcb->operrsta & DCBCMP))	{ /* unexpected interrupt */
617*24004Ssam 		printf("vd%d: unexpected interrupt, err=%b\n", vdnum,
618*24004Ssam 		    dcb->operrsta, ERRBITS);
619*24004Ssam 		return;
620*24004Ssam 	}
621*24004Ssam 	dp = um->um_tab.b_actf;		/* device queue head in ctlr queue */
622*24004Ssam 	bp = dp->b_actf;		/* first buffer in device queue */
623*24004Ssam 	unit = VDUNIT(bp->b_dev);
624*24004Ssam 	ui = vddinfo[unit];
625*24004Ssam 	if (ui->ui_dk >= 0)
626*24004Ssam 		dk_busy &= ~(1 << ui->ui_dk);
627*24004Ssam 	if (dcb->operrsta & (HRDERR|SFTERR)) {
628*24004Ssam 		st = &vdst[ui->ui_type];
629*24004Ssam 		if (dcb->operrsta & HRDERR) {
630*24004Ssam 			harderr(bp, &st->name[7]);
631*24004Ssam 			printf("status=%b\n", dcb->operrsta, ERRBITS);
632*24004Ssam 			dskrst(bp);
633*24004Ssam 			bp->b_flags |= B_ERROR;
634*24004Ssam 		} else
635*24004Ssam #define	SECTOR(x)	((x)*2)
636*24004Ssam 			printf("%s%d: soft error sn%d status=%b\n", &st->name[7], unit,
637*24004Ssam 			   SECTOR(bp->b_blkno + st->sizes[FLSYS(bp->b_dev)].block0),
638*24004Ssam 			   dcb->operrsta, ERRBITS);
639*24004Ssam 	}
640*24004Ssam 	switch (vdnum) {
641*24004Ssam 		case 0:
642*24004Ssam 			end_transfer(bp, vdbuf[0], VD0map, (caddr_t)vd0utl);
643*24004Ssam 			break;
644*24004Ssam 		case 1:
645*24004Ssam 			end_transfer(bp, vdbuf[1], VD1map, (caddr_t)vd1utl);
646*24004Ssam 			break;
647*24004Ssam 		case 2:
648*24004Ssam 			end_transfer(bp, vdbuf[2], VD2map, (caddr_t)vd2utl);
649*24004Ssam 			break;
650*24004Ssam 		case 3:
651*24004Ssam 			end_transfer(bp, vdbuf[3], VD3map, (caddr_t)vd3utl);
652*24004Ssam 			break;
653*24004Ssam 	}
654*24004Ssam 
655*24004Ssam 	um->um_tab.b_active = 0;
656*24004Ssam 	um->um_tab.b_errcnt = 0;
657*24004Ssam 	if (dp->b_forw != NULL) {		/* more than 1 unit on queue */
658*24004Ssam 		um->um_tab.b_actf = dp->b_forw;	/* next device on ctlr queue */
659*24004Ssam 		dp->b_forw = um->um_tab.b_actl->b_forw;	/* be last in queue */
660*24004Ssam 		um->um_tab.b_actl->b_forw = dp;	/* last points now to dp */
661*24004Ssam 		um->um_tab.b_actl = dp;		/* pointer in ctlr structure */
662*24004Ssam 	}
663*24004Ssam 	dp->b_errcnt = 0;
664*24004Ssam 	dp->b_actf = bp->av_forw;		/* remove first from queue */
665*24004Ssam 	bp->b_resid = 0;	/* All data read here */
666*24004Ssam 
667*24004Ssam #ifdef VDDCPERF
668*24004Ssam 	scope_out(3);
669*24004Ssam #endif
670*24004Ssam 
671*24004Ssam 	iodone(bp);
672*24004Ssam 	vdstart(um);		/* start requests for next device on queue */
673*24004Ssam }
674*24004Ssam 
675*24004Ssam 
676*24004Ssam vdread(dev, uio)
677*24004Ssam dev_t dev;
678*24004Ssam struct uio *uio;
679*24004Ssam {
680*24004Ssam 	register int unit = VDUNIT(dev);
681*24004Ssam 	register int error;
682*24004Ssam 	register int ct;
683*24004Ssam 	register int s;
684*24004Ssam 
685*24004Ssam 	if (unit >= NFSD)
686*24004Ssam 		error = ENXIO;
687*24004Ssam 	else {
688*24004Ssam 		ct = vddinfo[unit]->ui_ctlr;
689*24004Ssam 		s = spl8();
690*24004Ssam 		while (vdbufused[ct]) sleep (&vdbufused[ct],PRIBIO+1);
691*24004Ssam 		vdbufused[ct] = 1;
692*24004Ssam 		splx(s);
693*24004Ssam 		error = physio(vdstrategy, &rvdbuf[unit], dev, B_READ, minphys, uio);
694*24004Ssam 		vdbufused[ct] = 0;
695*24004Ssam 		wakeup (&vdbufused[ct]);
696*24004Ssam 	}
697*24004Ssam 	return error;
698*24004Ssam }
699*24004Ssam 
700*24004Ssam vdwrite(dev, uio)
701*24004Ssam dev_t dev;
702*24004Ssam struct uio *uio;
703*24004Ssam {
704*24004Ssam 	register int unit = VDUNIT(dev);
705*24004Ssam 	register int error;
706*24004Ssam 	register int ct;
707*24004Ssam 	register int s;
708*24004Ssam 
709*24004Ssam 	if (unit >= NFSD)
710*24004Ssam 		error = ENXIO;
711*24004Ssam 	else {
712*24004Ssam 		ct = vddinfo[unit]->ui_ctlr;
713*24004Ssam 		s = spl8();
714*24004Ssam 		while (vdbufused[ct]) sleep (&vdbufused[ct],PRIBIO+1);
715*24004Ssam 		vdbufused[ct] = 1;
716*24004Ssam 		splx(s);
717*24004Ssam 		error = physio(vdstrategy, &rvdbuf[unit], dev, B_WRITE, minphys, uio);
718*24004Ssam 		vdbufused[ct] = 0;
719*24004Ssam 		wakeup (&vdbufused[ct]);
720*24004Ssam 	}
721*24004Ssam 	return error;
722*24004Ssam }
723*24004Ssam 
724*24004Ssam #define	DUMPSIZE	32	/* Up to 32k at a time - controller limit */
725*24004Ssam 
726*24004Ssam vddump(dev)
727*24004Ssam dev_t	dev;
728*24004Ssam /*
729*24004Ssam  * Dump the main memory to the given device.
730*24004Ssam  */
731*24004Ssam {
732*24004Ssam 	register struct vba_ctlr *um;
733*24004Ssam 	register struct fmt_dcb *dcb = &dcbx[0];
734*24004Ssam 	register struct fmt_mdcb *mdcb = &mdcbx[0];
735*24004Ssam 	register struct vdst *st;
736*24004Ssam 	register int unit;
737*24004Ssam 	register caddr_t cntrl_vaddr ;
738*24004Ssam 	register struct size *sizep;	/* Pointer to one of the tables */
739*24004Ssam 	int index,sblock,blkcount,thiscount;
740*24004Ssam 	int	memaddr;
741*24004Ssam 
742*24004Ssam 	unit = VDUNIT(dev);
743*24004Ssam 	um = (vddinfo[unit])->ui_mi;
744*24004Ssam 	st = &vdst[(vddinfo[unit])->ui_type];
745*24004Ssam 	dcb = &dcbx[um->um_ctlr];
746*24004Ssam 	cntrl_vaddr = um->um_addr;
747*24004Ssam 	memaddr = 0x0;
748*24004Ssam 	index = FLSYS(dev);
749*24004Ssam 	sizep = st->sizes;
750*24004Ssam 	blkcount = maxfree - 2;		/* In 1k byte pages */
751*24004Ssam 	if (dumplo + blkcount > sizep[index].nblocks) return(EINVAL);
752*24004Ssam 	sblock = sizep[index].block0 + dumplo;
753*24004Ssam 	while (blkcount > 0) {
754*24004Ssam 		thiscount = MIN (blkcount, DUMPSIZE);
755*24004Ssam 		mdcb->firstdcb = (struct fmt_dcb *)PHYS(dcb);
756*24004Ssam 		dcb->intflg = NOINT;
757*24004Ssam 		dcb->opcode = WD;
758*24004Ssam 		dcb->operrsta = 0;
759*24004Ssam 		dcb->devselect = (char)(vddinfo[unit])->ui_slave;
760*24004Ssam 		dcb->trailcnt = (char)3;
761*24004Ssam 		dcb->trail.rwtrail.memadr = (char *)memaddr;
762*24004Ssam 		dcb->trail.rwtrail.wcount = thiscount*512;
763*24004Ssam 		dcb->trail.rwtrail.disk.cylinder= (short)(sblock/st->nspc);
764*24004Ssam 		dcb->trail.rwtrail.disk.track = (char)((sblock % st->nspc)
765*24004Ssam 			/ st->nsect);
766*24004Ssam 		dcb->trail.rwtrail.disk.sector = (char)(sblock*2 % (st->nsect*2));
767*24004Ssam 		VDDC_ATTENTION(cntrl_vaddr,PHYS(mdcb) )	/* do it */
768*24004Ssam 		POLLTILLDONE(5,"WD");
769*24004Ssam 		if (dcb->operrsta & HRDERR) {
770*24004Ssam 			if (vddebug)
771*24004Ssam 				printf("vd%d: i/o error, err=%b\n", unit,
772*24004Ssam 				    dcb->operrsta, ERRBITS);
773*24004Ssam 			return(EIO);
774*24004Ssam 		};
775*24004Ssam 		blkcount -= thiscount;
776*24004Ssam 		memaddr += thiscount*NBPG;
777*24004Ssam 		sblock += thiscount;
778*24004Ssam 	}
779*24004Ssam 	return(0);
780*24004Ssam }
781*24004Ssam 
782*24004Ssam vdopen(dev, flag)
783*24004Ssam register dev_t dev;
784*24004Ssam int flag;
785*24004Ssam {
786*24004Ssam 	register struct vba_device *ui;
787*24004Ssam 	register unit = VDUNIT(dev);
788*24004Ssam 
789*24004Ssam 	ui = vddinfo[unit];
790*24004Ssam 	if (ui == 0 || ui->ui_alive == 0 || ui->ui_type >= NVDDRV)
791*24004Ssam 		return ENXIO;
792*24004Ssam 	return 0;
793*24004Ssam }
794*24004Ssam 
795*24004Ssam vdsize(dev)
796*24004Ssam register dev_t dev;
797*24004Ssam {
798*24004Ssam 	register struct vba_device *ui;
799*24004Ssam 	register unit = VDUNIT(dev);
800*24004Ssam 
801*24004Ssam 	ui = vddinfo[unit];
802*24004Ssam 	if (ui == 0 || ui->ui_alive == 0 || ui->ui_type >= NVDDRV)
803*24004Ssam 		return -1;
804*24004Ssam 	return vdst[ui->ui_type].sizes[FLSYS(dev)].nblocks;
805*24004Ssam }
806*24004Ssam 
807*24004Ssam /* reset a drive after a hard error */
808*24004Ssam dskrst(bp)
809*24004Ssam 	register struct buf *bp;
810*24004Ssam {
811*24004Ssam 	register struct vdst *st;
812*24004Ssam 	register struct fmt_dcb *dcb;
813*24004Ssam 	register struct fmt_mdcb *mdcb;
814*24004Ssam 	register struct vba_device *ui;
815*24004Ssam 	register caddr_t cntrl_vaddr ;
816*24004Ssam 	int unit;
817*24004Ssam 
818*24004Ssam 	unit = VDUNIT(bp->b_dev);
819*24004Ssam 	ui = vddinfo[unit];
820*24004Ssam 	mdcb = &mdcbx[ui->ui_ctlr];
821*24004Ssam 	dcb = &dcbx[ui->ui_ctlr];
822*24004Ssam 	cntrl_vaddr = (ui->ui_mi)->um_addr;
823*24004Ssam 	st = &vdst[vddinfo[unit]->ui_type];
824*24004Ssam 	dcb->opcode = RSTCFG;		/* configure drive command */
825*24004Ssam 	dcb->intflg = NOINT;
826*24004Ssam 	dcb->operrsta  = 0;
827*24004Ssam 	dcb->trail.resetrail.ncyl = st->ncyl;
828*24004Ssam 	dcb->trail.resetrail.nsurfaces = st->ntrak;
829*24004Ssam 	dcb->devselect = (char)ui->ui_slave;
830*24004Ssam 	dcb->trailcnt = (char)2;
831*24004Ssam 	mdcb->firstdcb = (struct fmt_dcb *)PHYS(dcb);
832*24004Ssam 	VDDC_ATTENTION(cntrl_vaddr,PHYS(mdcb) )	/* do it */
833*24004Ssam 	POLLTILLDONE(3,"reset")
834*24004Ssam 	if (dcb->operrsta & HRDERR) {
835*24004Ssam 		if (vddebug) {
836*24004Ssam 			harderr(bp, &st->name[7]);
837*24004Ssam 			printf("reset failed, err=%b\n", dcb->operrsta,ERRBITS);
838*24004Ssam 		}
839*24004Ssam 	}
840*24004Ssam }
841*24004Ssam #endif
842