xref: /csrg-svn/sys/tahoe/vba/dr.c (revision 30294)
1*30294Ssam /*	dr.c	1.6	86/12/15	*/
229651Ssam 
329651Ssam #include "dr.h"
429651Ssam #if NDR > 0
5*30294Ssam /*
6*30294Ssam  * DRV11-W DMA interface driver.
7*30294Ssam  *
830227Ssam  * UNTESTED WITH 4.3
929651Ssam  */
1029651Ssam #include "../machine/mtpr.h"
1129651Ssam #include "../machine/pte.h"
1229651Ssam 
1329651Ssam #include "param.h"
1429651Ssam #include "conf.h"
1529651Ssam #include "dir.h"
1629651Ssam #include "user.h"
1729651Ssam #include "proc.h"
1829651Ssam #include "map.h"
1929651Ssam #include "ioctl.h"
2029651Ssam #include "buf.h"
2129651Ssam #include "vm.h"
2229651Ssam #include "uio.h"
23*30294Ssam #include "kernel.h"
2429651Ssam 
2529651Ssam #include "../tahoevba/vbavar.h"
2629651Ssam #include "../tahoevba/drreg.h"
2729651Ssam 
2829651Ssam #define YES 1
2929651Ssam #define NO  0
3029651Ssam 
3129651Ssam struct  vba_device  *drinfo[NDR];
3229651Ssam struct  dr_aux dr_aux[NDR];
3329651Ssam 
3429651Ssam unsigned drminphys();
35*30294Ssam int	 drprobe(), drintr(), drattach(), drtimo(), drrwtimo();
36*30294Ssam int	 drstrategy();
37*30294Ssam extern	struct  vba_device  *drinfo[];
38*30294Ssam static	long drstd[] = { 0 };
3929651Ssam struct  vba_driver drdriver =
40*30294Ssam     { drprobe, 0, drattach, 0, drstd, "rs", drinfo };
4129651Ssam 
4229651Ssam #define RSUNIT(dev) (minor(dev) & 7)
4329651Ssam #define SPL_UP spl5
4429651Ssam 
4529651Ssam /* -------- Per-unit data -------- */
4629651Ssam 
4729651Ssam extern struct dr_aux dr_aux[];
4829651Ssam 
4929651Ssam #ifdef DR_DEBUG
50*30294Ssam long	DR11 = 0;
5129651Ssam #endif
5229651Ssam 
5329651Ssam drprobe(reg, vi)
54*30294Ssam 	caddr_t reg;
55*30294Ssam 	struct vba_device *vi;
5629651Ssam {
57*30294Ssam 	register int br, cvec;		/* must be r12, r11 */
58*30294Ssam 	struct rsdevice *dr;
5929651Ssam 
60*30294Ssam #ifdef lint
61*30294Ssam 	br = 0; cvec = br; br = cvec;
62*30294Ssam 	drintr(0);
6329651Ssam #endif
64*30294Ssam 	if (badaddr(reg, 2))
65*30294Ssam 		return (0);
66*30294Ssam 	dr = (struct rsdevice *)reg;
67*30294Ssam 	dr->dr_intvect = --vi->ui_hd->vh_lastiv;
6829651Ssam #ifdef DR_DEBUG
69*30294Ssam 	printf("dprobe: Set interrupt vector %lx and init\n",dr->dr_intvec);
7029651Ssam #endif
71*30294Ssam 	/* generate interrupt here for autoconfig */
72*30294Ssam 	dr->dr_cstat = MCLR;		/* init board and device */
7329651Ssam #ifdef DR_DEBUG
74*30294Ssam 	printf("drprobe: Initial status %lx\n", dr->dr_cstat);
7529651Ssam #endif
76*30294Ssam 	br = 0x18, cvec = dr->dr_intvect;	/* XXX */
77*30294Ssam 	return (sizeof (struct rsdevice));		/* DR11 exist */
7829651Ssam }
7929651Ssam 
8029651Ssam /* ARGSUSED */
8129651Ssam drattach(ui)
82*30294Ssam 	struct vba_device *ui;
8329651Ssam {
84*30294Ssam 	register struct dr_aux *rsd;
8529651Ssam 
86*30294Ssam 	rsd = &dr_aux[ui->ui_unit];
87*30294Ssam 	rsd->dr_flags = DR_PRES;		/* This dr11 is present */
88*30294Ssam 	rsd->dr_addr = (struct rsdevice *)ui->ui_addr; /* Save addr of this dr11 */
89*30294Ssam 	rsd->dr_istat = 0;
90*30294Ssam 	rsd->dr_bycnt = 0;
91*30294Ssam 	rsd->dr_cmd = 0;
92*30294Ssam 	rsd->currenttimo = 0;
9329651Ssam }
9429651Ssam 
95*30294Ssam /*ARGSUSED*/
96*30294Ssam dropen(dev, flag)
97*30294Ssam 	dev_t dev;
98*30294Ssam 	int flag;
9929651Ssam {
100*30294Ssam 	register int unit = RSUNIT(dev);
101*30294Ssam 	register struct rsdevice *dr;
102*30294Ssam 	register struct dr_aux *rsd;
10329651Ssam 
104*30294Ssam 	if (drinfo[unit] == 0 || !drinfo[unit]->ui_alive)
105*30294Ssam 		return (ENXIO);
106*30294Ssam 	dr = RSADDR(unit);
107*30294Ssam 	rsd = &dr_aux[unit];
108*30294Ssam 	if (rsd->dr_flags & DR_OPEN) {
10929651Ssam #ifdef DR_DEBUG
110*30294Ssam 		printf("\ndropen: dr11 unit %ld already open",unit);
11129651Ssam #endif
112*30294Ssam 		return (ENXIO);	  		/* DR11 already open */
113*30294Ssam 	}
114*30294Ssam 	rsd->dr_flags |= DR_OPEN;	/* Mark it OPEN */
115*30294Ssam 	rsd->dr_istat = 0;		/* Clear status of previous interrupt */
116*30294Ssam 	rsd->rtimoticks = hz;		/* Set read no stall timout to 1 sec */
117*30294Ssam 	rsd->wtimoticks = hz*60;	/* Set write no stall timout to 1 min */
118*30294Ssam 	dr->dr_cstat = DR_ZERO;		/* Clear function & latches */
119*30294Ssam 	dr->dr_pulse = (RDMA | RATN);	/* clear leftover attn & e-o-r flags */
120*30294Ssam 	drtimo(dev);			/* start the self kicker */
121*30294Ssam 	return (0);
12229651Ssam }
12329651Ssam 
12429651Ssam drclose (dev)
125*30294Ssam 	dev_t dev;
12629651Ssam {
127*30294Ssam 	register int unit = RSUNIT(dev);
128*30294Ssam 	register struct dr_aux *dra;
129*30294Ssam 	register struct rsdevice *rs;
130*30294Ssam 	register short s;
13129651Ssam 
132*30294Ssam 	dra = &dr_aux[unit];
133*30294Ssam 	if ((dra->dr_flags & DR_OPEN) == 0) {
13429651Ssam #ifdef DR_DEBUG
135*30294Ssam 		printf("\ndrclose: DR11 device %ld not open",unit);
13629651Ssam #endif
137*30294Ssam 		return;
138*30294Ssam 	}
139*30294Ssam 	dra->dr_flags &= ~(DR_OPEN|DR_ACTV);
140*30294Ssam 	rs = dra->dr_addr;
141*30294Ssam 	s = SPL_UP();
142*30294Ssam 	rs->dr_cstat = DR_ZERO;
143*30294Ssam 	if (dra->dr_buf.b_flags & B_BUSY) {
144*30294Ssam 		dra->dr_buf.b_flags &= ~B_BUSY;
145*30294Ssam 		wakeup((caddr_t)&dra->dr_buf.b_flags);
146*30294Ssam 	}
147*30294Ssam 	splx(s);
14829651Ssam }
14929651Ssam 
15029651Ssam 
15129651Ssam /*	drread() works exactly like drwrite() except that the
15229651Ssam 	B_READ flag is used when physio() is called
15329651Ssam */
15429651Ssam drread (dev, uio)
155*30294Ssam 	dev_t dev;
156*30294Ssam 	struct uio *uio;
15729651Ssam {	register struct dr_aux *dra;
15829651Ssam 	register struct buf *bp;
159*30294Ssam 	register int spl, err;
160*30294Ssam 	register int unit = RSUNIT(dev);
16129651Ssam 
162*30294Ssam 	if (uio->uio_iov->iov_len <= 0 ||	/* Negative count */
163*30294Ssam 	    uio->uio_iov->iov_len & 1 ||	/* odd count */
164*30294Ssam 	    (int)uio->uio_iov->iov_base & 1)	/* odd destination address */
165*30294Ssam 		return (EINVAL);
16629651Ssam #ifdef DR_DEBUG
167*30294Ssam 	if (DR11 & 8)
168*30294Ssam 		printf("\ndrread: (len:%ld)(base:%lx)",
169*30294Ssam 		    uio->uio_iov->iov_len,(int)uio->uio_iov->iov_base);
17029651Ssam #endif
171*30294Ssam 	dra = &dr_aux[RSUNIT(dev)];
172*30294Ssam 	dra->dr_op = DR_READ;
173*30294Ssam 	bp =  &dra->dr_buf;
174*30294Ssam 	bp->b_resid = 0;
175*30294Ssam 	if (dra->dr_flags & DR_NORSTALL) {
176*30294Ssam 		/*
177*30294Ssam 		 * We are in no stall mode, start the timer,
178*30294Ssam 		 * raise IPL so nothing can stop us once the
179*30294Ssam 		 * timer's running
180*30294Ssam 		 */
181*30294Ssam 		spl = SPL_UP();
182*30294Ssam 		timeout(drrwtimo, (caddr_t)((dra->currenttimo<<8) | unit),
183*30294Ssam 		    (int)dra->rtimoticks);
184*30294Ssam 		err = physio(drstrategy, bp, dev,B_READ, drminphys, uio);
185*30294Ssam 		splx(spl);
186*30294Ssam 		if (err)
187*30294Ssam 			return (err);
188*30294Ssam 		dra->currenttimo++;	/* Update current timeout number */
189*30294Ssam 		/* Did we timeout */
190*30294Ssam 		if (dra->dr_flags & DR_TMDM) {
191*30294Ssam 			dra->dr_flags &= ~DR_TMDM; /* Clear timeout flag */
192*30294Ssam 			u.u_error = 0;	/* Made the error ourself, ignore it */
193*30294Ssam 		}
194*30294Ssam 		return (err);
19529651Ssam 	}
196*30294Ssam 	return (physio(drstrategy, bp, dev,B_READ, drminphys, uio));
19729651Ssam }
19829651Ssam 
199*30294Ssam drwrite(dev, uio)
200*30294Ssam 	dev_t dev;
201*30294Ssam 	struct uio *uio;
20229651Ssam {	register struct dr_aux *dra;
20329651Ssam 	register struct buf *bp;
204*30294Ssam 	register int unit = RSUNIT(dev);
205*30294Ssam 	int spl, err;
20629651Ssam 
207*30294Ssam 	if (uio->uio_iov->iov_len <= 0 || uio->uio_iov->iov_len & 1 ||
208*30294Ssam 	    (int)uio->uio_iov->iov_base & 1)
209*30294Ssam 		return (EINVAL);
21029651Ssam #ifdef DR_DEBUG
211*30294Ssam 	if (DR11 & 4)
212*30294Ssam 		printf("\ndrwrite: (len:%ld)(base:%lx)",
213*30294Ssam 		    uio->uio_iov->iov_len,(int)uio->uio_iov->iov_base);
21429651Ssam #endif
215*30294Ssam 	dra = &dr_aux[RSUNIT(dev)];
216*30294Ssam 	dra->dr_op = DR_WRITE;
217*30294Ssam 	bp =  &dra->dr_buf;
218*30294Ssam 	bp->b_resid = 0;
219*30294Ssam 	if (dra->dr_flags & DR_NOWSTALL) {
220*30294Ssam 		/*
221*30294Ssam 		 * We are in no stall mode, start the timer,
222*30294Ssam 		 * raise IPL so nothing can stop us once the
223*30294Ssam 		 * timer's running
224*30294Ssam 		 */
225*30294Ssam 		spl = SPL_UP();
226*30294Ssam 		timeout(drrwtimo,(caddr_t)((dra->currenttimo<<8) | unit),
227*30294Ssam 		    (int)dra->wtimoticks);
228*30294Ssam 		err = physio (drstrategy, bp, dev,B_WRITE, drminphys, uio);
229*30294Ssam 		splx(spl);
230*30294Ssam 		if (err)
231*30294Ssam 			return (err);
232*30294Ssam 		dra->currenttimo++;	/* Update current timeout number */
233*30294Ssam 		/* Did we timeout */
234*30294Ssam 		if (dra->dr_flags & DR_TMDM) {
235*30294Ssam 			dra->dr_flags &= ~DR_TMDM;	/* Clear timeout flag */
236*30294Ssam 			u.u_error = 0;	/* Made the error ourself, ignore it */
237*30294Ssam 		}
238*30294Ssam 		return (err);
23929651Ssam 	}
240*30294Ssam 	return (physio(drstrategy, bp, dev,B_WRITE, drminphys, uio));
24129651Ssam }
24229651Ssam 
243*30294Ssam /*
244*30294Ssam  * Routine used by calling program to issue commands to dr11 driver and
245*30294Ssam  * through it to the device.
246*30294Ssam  * It is also used to read status from the device and driver and to wait
247*30294Ssam  * for attention interrupts.
248*30294Ssam  * Status is returned in an 8 elements unsigned short integer array, the
249*30294Ssam  * first two elements of the array are also used to pass arguments to
250*30294Ssam  * drioctl() if required.
251*30294Ssam  * The function bits to be written to the dr11 are included in the cmd
252*30294Ssam  * argument. Even if they are not being written to the dr11 in a particular
253*30294Ssam  * drioctl() call, they will update the copy of cmd that is stored in the
254*30294Ssam  * driver. When drstrategy() is called, this updated copy is used if a
255*30294Ssam  * deferred function bit write has been specified. The "side effect" of
256*30294Ssam  * calls to the drioctl() requires that the last call prior to a read or
257*30294Ssam  * write has an appropriate copy of the function bits in cmd if they are
258*30294Ssam  * to be used in drstrategy().
259*30294Ssam  * When used as command value, the contents of data[0] is the command
260*30294Ssam  * parameter.
261*30294Ssam  */
262*30294Ssam drioctl(dev, cmd, data)
263*30294Ssam 	dev_t dev;
264*30294Ssam 	int cmd;
265*30294Ssam 	long *data;
26629651Ssam {
267*30294Ssam 	register int unit = RSUNIT(dev);
268*30294Ssam 	register struct dr_aux *dra;
269*30294Ssam 	register struct rsdevice *rsaddr = RSADDR(unit);
270*30294Ssam 	int s;
271*30294Ssam 	u_short status;
272*30294Ssam 	long temp;
27329651Ssam 
27429651Ssam #ifdef DR_DEBUG
275*30294Ssam 	if (DR11 & 0x10)
276*30294Ssam 		printf("\ndrioctl: (dev:%lx)(cmd:%lx)(data:%lx)(data[0]:%lx)",
277*30294Ssam 		    dev,cmd,data,data[0]);
27829651Ssam #endif
279*30294Ssam 	dra = &dr_aux[unit];
280*30294Ssam 	dra->dr_cmd = 0;	/* Fresh copy; clear all previous flags */
281*30294Ssam 	switch (cmd) {
28229651Ssam 
283*30294Ssam 	case DRWAIT:		/* Wait for attention interrupt */
28429651Ssam #ifdef DR_DEBUG
285*30294Ssam 		printf("\ndrioctl: wait for attention interrupt");
28629651Ssam #endif
287*30294Ssam 		s = SPL_UP();
288*30294Ssam 		/*
289*30294Ssam 		 * If the attention flag in dr_flags is set, it probably
290*30294Ssam 		 * means that an attention has arrived by the time a
291*30294Ssam 		 * previous DMA end-of-range interrupt was serviced. If
292*30294Ssam 		 * ATRX is set, we will return with out sleeping, since
293*30294Ssam 		 * we have received an attention since the last call to
294*30294Ssam 		 * wait on attention.  This may not be appropriate for
295*30294Ssam 		 * some applications.
296*30294Ssam 		 */
297*30294Ssam 		if ((dra->dr_flags & DR_ATRX) == 0) {
298*30294Ssam 			dra->dr_flags |= DR_ATWT;	/* Set waiting flag */
299*30294Ssam 			/*
300*30294Ssam 			 * Enable interrupt; use pulse reg.
301*30294Ssam 			 * so function bits are not changed
302*30294Ssam 			 */
303*30294Ssam 			rsaddr->dr_pulse = IENB;
304*30294Ssam 			sleep((caddr_t)&dra->dr_cmd, DRPRI);
305*30294Ssam 		}
306*30294Ssam 		splx(s);
307*30294Ssam 		break;
30829651Ssam 
309*30294Ssam 	case DRPIOW:			/* Write to p-i/o register */
310*30294Ssam 		rsaddr->dr_data = data[0];
311*30294Ssam 		break;
31229651Ssam 
313*30294Ssam 	case DRPACL:			/* Send pulse to device */
314*30294Ssam 		rsaddr->dr_pulse = FCN2;
315*30294Ssam 		break;
31629651Ssam 
317*30294Ssam 	case DRDACL:			/* Defer alco pulse until go */
318*30294Ssam 		dra->dr_cmd |= DR_DACL;
319*30294Ssam 		break;
32029651Ssam 
321*30294Ssam 	case DRPCYL:			/* Set cycle with next go */
322*30294Ssam 		dra->dr_cmd |= DR_PCYL;
323*30294Ssam 		break;
32429651Ssam 
325*30294Ssam 	case DRDFCN:			/* Update function with next go */
326*30294Ssam 		dra->dr_cmd |= DR_DFCN;
327*30294Ssam 		break;
32829651Ssam 
329*30294Ssam 	case DRRATN:			/* Reset attention flag */
330*30294Ssam 		rsaddr->dr_pulse = RATN;
331*30294Ssam 		break;
33229651Ssam 
333*30294Ssam 	case DRRDMA:			/* Reset DMA e-o-r flag */
334*30294Ssam 		rsaddr->dr_pulse = RDMA;
335*30294Ssam 		break;
33629651Ssam 
337*30294Ssam 	case DRSFCN:			/* Set function bits */
338*30294Ssam 		temp = data[0] & DR_FMSK;
339*30294Ssam 		/*
340*30294Ssam 		 * This has a very important side effect -- It clears
341*30294Ssam 		 * the interrupt enable flag. That is fine for this driver,
342*30294Ssam 		 * but if it is desired to leave interrupt enable at all
343*30294Ssam 		 * times, it will be necessary to read the status register
344*30294Ssam 		 * first to get IENB, or carry a software flag that indicates
345*30294Ssam 		 * whether interrupts are set, and or this into the control
346*30294Ssam 		 * register value being written.
347*30294Ssam 		 */
348*30294Ssam 		rsaddr->dr_cstat = temp;
349*30294Ssam 		break;
35029651Ssam 
351*30294Ssam 	case DRRPER:			/* Clear parity flag */
352*30294Ssam 		rsaddr->dr_pulse = RPER;
353*30294Ssam 		break;
35429651Ssam 
355*30294Ssam 	case DRSETRSTALL:		/* Set read stall mode. */
356*30294Ssam 		dra->dr_flags &= (~DR_NORSTALL);
357*30294Ssam 		break;
35829651Ssam 
359*30294Ssam 	case DRSETNORSTALL:		/* Set no stall read  mode. */
360*30294Ssam 		dra->dr_flags |= DR_NORSTALL;
361*30294Ssam 		break;
36229651Ssam 
363*30294Ssam 	case DRGETRSTALL:		/* Returns true if in read stall mode */
364*30294Ssam 		data[0]  = (dra->dr_flags & DR_NORSTALL)? 0 : 1;
365*30294Ssam 		break;
36629651Ssam 
367*30294Ssam 	case DRSETRTIMEOUT:		/* Set read stall timeout (1/10 secs) */
368*30294Ssam 		if (data[0] < 1) {
369*30294Ssam 			u.u_error = EINVAL;
370*30294Ssam 			temp = 1;
371*30294Ssam 		}
372*30294Ssam 		dra->rtimoticks = (data[0] * hz )/10;
373*30294Ssam 		break;
37429651Ssam 
375*30294Ssam 	case DRGETRTIMEOUT:		/* Return read stall timeout */
376*30294Ssam 		data[0] = ((dra->rtimoticks)*10)/hz;
377*30294Ssam 		break;
37829651Ssam 
379*30294Ssam 	case DRSETWSTALL:		/* Set write stall mode. */
380*30294Ssam 		dra->dr_flags &= (~DR_NOWSTALL);
381*30294Ssam 		break;
38229651Ssam 
383*30294Ssam 	case DRSETNOWSTALL:		/* Set write stall mode. */
384*30294Ssam 		dra->dr_flags |= DR_NOWSTALL;
385*30294Ssam 		break;
38629651Ssam 
387*30294Ssam 	case DRGETWSTALL:		/* Return true if in write stall mode */
388*30294Ssam 		data[0] = (dra->dr_flags & DR_NOWSTALL)? 0 : 1;
389*30294Ssam 		break;
39029651Ssam 
391*30294Ssam 	case DRSETWTIMEOUT:		/* Set write stall timeout (1/10's) */
392*30294Ssam 		if (data[0] < 1) {
393*30294Ssam 			u.u_error = EINVAL;
394*30294Ssam 			temp = 1;
395*30294Ssam 		}
396*30294Ssam 		dra->wtimoticks = (data[0] * hz )/10;
397*30294Ssam 		break;
39829651Ssam 
399*30294Ssam 	case DRGETWTIMEOUT:		/* Return write stall timeout */
400*30294Ssam 		data[0] = ((dra->wtimoticks)*10)/hz;
401*30294Ssam 		break;
40229651Ssam 
403*30294Ssam 	case DRWRITEREADY:		/* Return true if can write data */
404*30294Ssam 		data[0] = (rsaddr->dr_cstat & STTA)? 1 : 0;
405*30294Ssam 		break;
40629651Ssam 
407*30294Ssam 	case DRREADREADY:		/* Return true if data to be read */
408*30294Ssam 		data[0] = (rsaddr->dr_cstat & STTB)? 1 : 0;
409*30294Ssam 		break;
41029651Ssam 
411*30294Ssam 	case DRBUSY:			/* Return true if device busy */
412*30294Ssam 		/*
413*30294Ssam 		 * Internally this is the DR11-W
414*30294Ssam 		 * STAT C bit, but there is a bug in the Omega 500/FIFO
415*30294Ssam 		 * interface board that it cannot drive this signal low
416*30294Ssam 		 * for certain DR11-W ctlr such as the Ikon. We use the
417*30294Ssam 		 * REDY signal of the CSR on the Ikon DR11-W instead.
418*30294Ssam 		 */
419*30294Ssam #ifdef notdef
420*30294Ssam 		data[0] = (rsaddr->dr_cstat & STTC)? 1 : 0;
421*30294Ssam #else
422*30294Ssam 		data[0] = ((rsaddr->dr_cstat & REDY)? 0 : 1);
423*30294Ssam #endif
424*30294Ssam 		break;
42529651Ssam 
426*30294Ssam 	case DRRESET:			/* Reset device */
427*30294Ssam 		/* Reset DMA ATN RPER flag */
428*30294Ssam 		rsaddr->dr_pulse = (MCLR|RDMA|RATN|RPER);
429*30294Ssam 		DELAY(0x1f000);
430*30294Ssam 		while ((rsaddr->dr_cstat & REDY) == 0)
431*30294Ssam 			sleep((caddr_t)dra, DRPRI);	/* Wakeup by drtimo() */
432*30294Ssam 		dra->dr_istat = 0;
433*30294Ssam 		dra->dr_cmd = 0;
434*30294Ssam 		dra->currenttimo = 0;
435*30294Ssam 		break;
43629651Ssam 
437*30294Ssam 	case DR11STAT: {		/* Copy back dr11 status to user */
438*30294Ssam 		register struct dr11io *dr = (struct dr11io *)data;
439*30294Ssam 		dr->arg[0] = dra->dr_flags;
440*30294Ssam 		dr->arg[1] = rsaddr->dr_cstat;
441*30294Ssam 		dr->arg[2] = dra->dr_istat;	/* Status at last interrupt */
442*30294Ssam 		dr->arg[3] = rsaddr->dr_data;	/* P-i/o input data */
443*30294Ssam 		status = (u_short)((rsaddr->dr_addmod << 8) & 0xff00);
444*30294Ssam 		dr->arg[4] = status | (u_short)(rsaddr->dr_intvect & 0xff);
445*30294Ssam 		dr->arg[5] = rsaddr->dr_range;
446*30294Ssam 		dr->arg[6] = rsaddr->dr_rahi;
447*30294Ssam 		dr->arg[7] = rsaddr->dr_ralo;
448*30294Ssam 		break;
449*30294Ssam 	}
450*30294Ssam 	case DR11LOOP:			/* Perform loopback test */
451*30294Ssam 		/*
452*30294Ssam 		 * NB: MUST HAVE LOOPBACK CABLE ATTACHED --
453*30294Ssam 		 * Test results are printed on system console
454*30294Ssam 		 */
455*30294Ssam 		if (suser())
456*30294Ssam 			dr11loop(rsaddr, dra, unit);
457*30294Ssam 		break;
45829651Ssam 
459*30294Ssam 	default:
460*30294Ssam 		return (EINVAL);
46129651Ssam 	}
46229651Ssam #ifdef DR_DEBUG
463*30294Ssam 	if (DR11 & 0x10)
464*30294Ssam 		printf("**** (data[0]:%lx)",data[0]);
46529651Ssam #endif
466*30294Ssam 	return (0);
46729651Ssam }
46829651Ssam 
469*30294Ssam #define NPAT	2
470*30294Ssam #define DMATBL	20
471*30294Ssam u_short	tstpat[DMATBL] = { 0xAAAA, 0x5555};
472*30294Ssam long	DMAin = 0;
47330138Ssam 
474*30294Ssam /*
475*30294Ssam  * Perform loopback test -- MUST HAVE LOOPBACK CABLE ATTACHED
476*30294Ssam  * Test results are printed on system console
477*30294Ssam  */
478*30294Ssam dr11loop(dr, dra, unit)
479*30294Ssam 	struct rsdevice *dr;
480*30294Ssam 	struct dr_aux *dra;
481*30294Ssam 	int unit;
482*30294Ssam {
483*30294Ssam 	register long result, ix;
484*30294Ssam 	long addr, wait;
48530138Ssam 
48630138Ssam 	dr->dr_cstat = MCLR;		/* Clear board & device, disable intr */
487*30294Ssam 	printf("\n\t ----- DR11 unit %ld loopback test -----", unit);
48830138Ssam 	printf("\n\t Program I/O ...");
48930138Ssam 	for (ix=0;ix<NPAT;ix++) {
49030138Ssam 		dr->dr_data = tstpat[ix];	/* Write to Data out register */
491*30294Ssam 		result = dr->dr_data & 0xFFFF;	/* Read it back */
49230138Ssam 		if (result != tstpat[ix]) {
49330138Ssam 			printf("Failed, expected : %lx --- actual : %lx",
494*30294Ssam 				tstpat[ix], result);
49530138Ssam 			return;
49630138Ssam 		}
49730138Ssam 	}
49830138Ssam 	printf("OK\n\t Functions & Status Bits ...");
49930138Ssam 	dr->dr_cstat = (FCN1 | FCN3);
50030138Ssam 	result = dr->dr_cstat & 0xffff;		/* Read them back */
50130138Ssam 	if ((result & (STTC | STTA)) != (STTC |STTA)) {
50230138Ssam 		printf("Failed, expected : %lx --- actual : %lx, ISR:%lx",
503*30294Ssam 			(STTA|STTC), (result & (STTA|STTC)), result);
50430138Ssam 		return;
50530138Ssam 	}
50630138Ssam 	dr->dr_cstat = FCN2;
50730138Ssam 	result = dr->dr_cstat & 0xffff;		/* Read them back */
50830138Ssam 	if ((result & STTB) != STTB) {
50930138Ssam 		printf("Failed, expected : %lx --- actual : %lx, ISR:%lx",
510*30294Ssam 			STTB, (result & STTB), result);
51130138Ssam 		return;
51230138Ssam 	}
51330138Ssam 	printf("OK\n\t DMA output ...");
514*30294Ssam 	if (DMAin)
515*30294Ssam 		goto dmain;
51630138Ssam 	/* Initialize DMA data buffer */
517*30294Ssam 	for (ix=0; ix<DMATBL; ix++)
518*30294Ssam 		tstpat[ix] = 0xCCCC + ix;
51930138Ssam 	tstpat[DMATBL-1] = 0xCCCC;	/* Last word output */
52030138Ssam 	/* Setup normal DMA */
521*30294Ssam 	addr = (long)vtoph((struct proc *)0, (unsigned)tstpat);
522*30294Ssam 	dr->dr_walo = (addr >> 1) & 0xffff;
523*30294Ssam 	dr->dr_wahi = (addr >> 17) & 0x7fff;
524*30294Ssam 	/* Set DMA range count: (number of words - 1) */
525*30294Ssam 	dr->dr_range = DMATBL - 1;
526*30294Ssam 	/* Set address modifier code to be used for DMA access to memory */
527*30294Ssam 	dr->dr_addmod = DRADDMOD;
52830138Ssam 
529*30294Ssam 	/*
530*30294Ssam 	 * Clear dmaf and attf to assure a clean dma start, also disable
531*30294Ssam 	 * attention interrupt
532*30294Ssam 	 */
533*30294Ssam 	dr->dr_pulse = RDMA|RATN|RMSK;  /* Use pulse register */
534*30294Ssam 	dr->dr_cstat = GO|CYCL;		  /* GO...... */
53530138Ssam 
53630138Ssam 	/* Wait for DMA complete; REDY and DMAF are true in ISR */
53730138Ssam 	wait = 0;
538*30294Ssam 	while ((result=(dr->dr_cstat & (REDY|DMAF))) != (REDY|DMAF)) {
539*30294Ssam 		printf("\n\tWait for DMA complete...ISR : %lx", result);
54030138Ssam 		if (++wait > 5) {
54130138Ssam 			printf("\n\t DMA output fails...timeout!!, ISR:%lx",
54230138Ssam 				result);
54330138Ssam 			return;
54430138Ssam 		}
54530138Ssam 	}
54630138Ssam 	result = dr->dr_data & 0xffff;		/* Read last word output */
54730138Ssam 	if (result != 0xCCCC) {
54830138Ssam 		printf("\n\t Fails, expected : %lx --- actual : %lx",
549*30294Ssam 			0xCCCC, result);
55030138Ssam 		return;
55130138Ssam 	}
55230138Ssam 	printf("OK\n\t DMA input ...");
55330138Ssam dmain:
55430138Ssam 	dr->dr_data = 0x1111;		/* DMA input data */
55530138Ssam 	/* Setup normal DMA */
556*30294Ssam 	addr = (long)vtoph((struct proc *)0, (unsigned)tstpat);
557*30294Ssam 	dr->dr_walo = (addr >> 1) & 0xffff;
558*30294Ssam 	dr->dr_wahi = (addr >> 17) & 0x7fff;
559*30294Ssam 	dr->dr_range = DMATBL - 1;
560*30294Ssam 	dr->dr_addmod = (char)DRADDMOD;
561*30294Ssam 	dr->dr_cstat = FCN1;		/* Set FCN1 in ICR to DMA in*/
562*30294Ssam 	if ((dra->dr_flags & DR_LOOPTST) == 0) {
56330138Ssam 		/* Use pulse reg */
564*30294Ssam 		dr->dr_pulse = RDMA|RATN|RMSK|CYCL|GO;
56530138Ssam 		/* Wait for DMA complete; REDY and DMAF are true in ISR */
56630138Ssam 		wait = 0;
567*30294Ssam 		while ((result=(dr->dr_cstat & (REDY|DMAF))) != (REDY|DMAF)) {
56830138Ssam 			printf("\n\tWait for DMA to complete...ISR:%lx",result);
56930138Ssam 			if (++wait > 5) {
57030138Ssam 				printf("\n\t DMA input timeout!!, ISR:%lx",
57130138Ssam 					result);
57230138Ssam 				return;
57330138Ssam 			}
57430138Ssam 		}
575*30294Ssam 	} else  {
57630138Ssam 		/* Enable DMA e-o-r interrupt */
577*30294Ssam 		dr->dr_pulse = IENB|RDMA|RATN|CYCL|GO;
57830138Ssam 		/* Wait for DMA complete; DR_LOOPTST is false in dra->dr_flags*/
57930138Ssam 		wait = 0;
58030138Ssam 		while (dra->dr_flags & DR_LOOPTST) {
58130138Ssam 			result = dr->dr_cstat & 0xffff;
582*30294Ssam 			printf("\n\tWait for DMA e-o-r intr...ISR:%lx", result);
58330138Ssam 			if (++wait > 7) {
58430138Ssam 				printf("\n\t DMA e-o-r timeout!!, ISR:%lx",
58530138Ssam 					result);
58630138Ssam 				dra->dr_flags &= ~DR_LOOPTST;
58730138Ssam 				return;
58830138Ssam 			}
58930138Ssam 		}
59030138Ssam 		dra->dr_flags |= DR_LOOPTST;
59130138Ssam 	}
592*30294Ssam 	mtpr(P1DC, tstpat);			/* Purge cache */
593*30294Ssam 	mtpr(P1DC, 0x3ff+tstpat);
594*30294Ssam 	for (ix=0; ix<DMATBL; ix++) {
59530138Ssam 		if (tstpat[ix] != 0x1111) {
596*30294Ssam 			printf("\n\t Fails, ix:%d, expected:%x --- actual:%x",
597*30294Ssam 				ix, 0x1111, tstpat[ix]);
59830138Ssam 			return;
59930138Ssam 		}
60030138Ssam 	}
601*30294Ssam 	if ((dra->dr_flags & DR_LOOPTST) == 0) {
60230138Ssam 		dra->dr_flags |= DR_LOOPTST;
60330138Ssam 		printf(" OK..\n\tDMA end of range interrupt...");
60430138Ssam 		goto dmain;
60530138Ssam 	}
60630138Ssam 	printf(" OK..\n\tAttention interrupt....");
607*30294Ssam 	dr->dr_pulse = IENB|RDMA;
608*30294Ssam 	dr->dr_pulse = FCN2;
60930138Ssam 	/* Wait for ATTN interrupt; DR_LOOPTST is false in dra->dr_flags*/
61030138Ssam 	wait = 0;
61130138Ssam 	while (dra->dr_flags & DR_LOOPTST) {
61230138Ssam 		result = dr->dr_cstat & 0xffff;
61330138Ssam 		printf("\n\tWait for Attention intr...ISR:%lx",result);
61430138Ssam 		if (++wait > 7) {
61530138Ssam 			printf("\n\t Attention interrupt timeout!!, ISR:%lx",
61630138Ssam 				result);
61730138Ssam 			dra->dr_flags &= ~DR_LOOPTST;
61830138Ssam 			return;
61930138Ssam 		}
62030138Ssam 	}
62130138Ssam 	dra->dr_flags &= ~DR_LOOPTST;
62230138Ssam 	printf(" OK..\n\tDone...");
62330138Ssam }
62430138Ssam 
62529651Ssam /* Reset state on Unibus reset */
626*30294Ssam /*ARGSUSED*/
62729651Ssam drreset(uban)
628*30294Ssam 	int uban;
62929651Ssam {
63029651Ssam 
63129651Ssam }
63229651Ssam 
63329651Ssam /*
63429651Ssam  * An interrupt is caused either by an error,
63529651Ssam  * base address overflow, or transfer complete
63629651Ssam  */
637*30294Ssam drintr(dr11)
638*30294Ssam 	int dr11;
63929651Ssam {
640*30294Ssam 	register struct dr_aux *dra = &dr_aux[dr11];
641*30294Ssam 	register struct rsdevice *rsaddr = RSADDR(dr11);
642*30294Ssam 	register struct buf *bp;
643*30294Ssam 	register short status;
64429651Ssam 
645*30294Ssam 	status = rsaddr->dr_cstat & 0xffff;	/* get board status register */
646*30294Ssam 	dra->dr_istat = status;
64729651Ssam #ifdef DR_DEBUG
648*30294Ssam 	if (DR11 & 2)
649*30294Ssam 		printf("\ndrintr: dr11 status : %lx",status & 0xffff);
65029651Ssam #endif
651*30294Ssam 	if (dra->dr_flags & DR_LOOPTST) {	/* doing loopback test */
652*30294Ssam 		dra->dr_flags &= ~DR_LOOPTST;
653*30294Ssam 		return;
654*30294Ssam 	}
655*30294Ssam 	/*
656*30294Ssam 	 * Make sure this is not a stray interrupt; at least one of dmaf or attf
657*30294Ssam 	 * must be set. Note that if the dr11 interrupt enable latch is reset
658*30294Ssam 	 * during a hardware interrupt ack sequence, and by the we get to this
659*30294Ssam 	 * point in the interrupt code it will be 0. This is done to give the
660*30294Ssam 	 * programmer some control over how the two more-or-less independent
661*30294Ssam 	 * interrupt sources on the board are handled.
662*30294Ssam 	 * If the attention flag is set when drstrategy() is called to start a
663*30294Ssam 	 * dma read or write an interrupt will be generated as soon as the
664*30294Ssam 	 * strategy routine enables interrupts for dma end-of-range. This will
665*30294Ssam 	 * cause execution of the interrupt routine (not necessarily bad) and
666*30294Ssam 	 * will cause the interrupt enable mask to be reset (very bad since the
667*30294Ssam 	 * dma end-of-range condition will not be able to generate an interrupt
668*30294Ssam 	 * when it occurs) causing the dma operation to time-out (even though
669*30294Ssam 	 * the dma transfer will be done successfully) or hang the process if a
670*30294Ssam 	 * software time-out capability is not implemented. One way to avoid
671*30294Ssam 	 * this situation is to check for a pending attention interrupt (attf
672*30294Ssam 	 * set) by calling drioctl() before doing a read or a write. For the
673*30294Ssam 	 * time being this driver will solve the problem by clearing the attf
674*30294Ssam 	 * flag in the status register before enabling interrupts in
675*30294Ssam 	 * drstrategy().
676*30294Ssam 	 *
677*30294Ssam 	 * **** The IKON 10084 for which this driver is written will set both
678*30294Ssam 	 * attf and dmaf if dma is terminated by an attention pulse. This will
679*30294Ssam 	 * cause a wakeup(&dr_aux), which will be ignored since it is not being
680*30294Ssam 	 * waited on, and an iodone(bp) which is the desired action. Some other
681*30294Ssam 	 * dr11 emulators, in particular the IKON 10077 for the Multibus, donot
682*30294Ssam 	 * dmaf in this case. This may require some addtional code in the inter-
683*30294Ssam 	 * rupt routine to ensure that en iodone(bp) is issued when dma is term-
684*30294Ssam 	 * inated by attention.
685*30294Ssam 	 */
686*30294Ssam 	bp = dra->dr_actf;
687*30294Ssam 	if ((status & (ATTF | DMAF)) == 0) {
688*30294Ssam 		printf("dr%d: stray interrupt, status=%x", dr11, status);
689*30294Ssam 		return;
690*30294Ssam 	}
691*30294Ssam 	if (status & DMAF) {		/* End-of-range interrupt */
692*30294Ssam 		dra->dr_flags |= DR_DMAX;
69329651Ssam 
69429651Ssam #ifdef DR_DEBUG
695*30294Ssam 		if (DR11 & 2)
696*30294Ssam 		printf("\ndrintr: e-o-r interrupt,cstat:%lx,dr_flags:%lx",
697*30294Ssam 			status&0xffff, dra->dr_flags & DR_ACTV);
69829651Ssam #endif
699*30294Ssam 		if ((dra->dr_flags & DR_ACTV) == 0) {
700*30294Ssam 			/* We are not doing DMA !! */
701*30294Ssam 			bp->b_flags |= B_ERROR;
702*30294Ssam 		} else {
703*30294Ssam 			if (dra->dr_op == DR_READ)
704*30294Ssam 				mtpr(P1DC, bp->b_un.b_addr);
705*30294Ssam 			dra->dr_bycnt -= bp->b_bcount;
706*30294Ssam 			if (dra->dr_bycnt >0) {
707*30294Ssam 				bp->b_un.b_addr += bp->b_bcount;
708*30294Ssam 				bp->b_bcount = (dra->dr_bycnt > NBPG) ? NBPG:
70929651Ssam 					dra->dr_bycnt;
710*30294Ssam 				drstart(rsaddr, dra, bp);
711*30294Ssam 				return;
712*30294Ssam 			}
71329651Ssam 		}
714*30294Ssam 		dra->dr_flags &= ~DR_ACTV;
715*30294Ssam 		wakeup((caddr_t)dra);		/* Wakeup waiting in drwait() */
716*30294Ssam 		rsaddr->dr_pulse = (RPER|RDMA|RATN); /* reset dma e-o-r flag */
71729651Ssam 	}
718*30294Ssam 	/*
719*30294Ssam 	 * Now test for attention interrupt -- It may be set in addition to
720*30294Ssam 	 * the dma e-o-r interrupt. If we get one we will issue a wakeup to
721*30294Ssam 	 * the drioctl() routine which is presumable waiting for one.
722*30294Ssam 	 * The program may have to monitor the attention interrupt received
723*30294Ssam 	 * flag in addition to doing waits for the interrupt. Futhermore,
724*30294Ssam 	 * interrupts are not enabled unless dma is in progress or drioctl()
725*30294Ssam 	 * has been called to wait for attention -- this may produce some
726*30294Ssam 	 * strange results if attf is set on the dr11 when a read or a write
727*30294Ssam 	 * is initiated, since that will enables interrupts.
728*30294Ssam 	 * **** The appropriate code for this interrupt routine will probably
729*30294Ssam 	 * be rather application dependent.
730*30294Ssam 	 */
731*30294Ssam 	if (status & ATTF) {
732*30294Ssam 		dra->dr_flags |= DR_ATRX;
733*30294Ssam 		dra->dr_flags &= ~DR_ATWT;
734*30294Ssam 		rsaddr->dr_cstat = RATN;	/* reset attention flag */
735*30294Ssam 		/*
736*30294Ssam 		 * Some applications which use attention to terminate
737*30294Ssam 		 * dma may also want to issue an iodone() here to
738*30294Ssam 		 * wakeup physio().
739*30294Ssam 		 */
740*30294Ssam 		wakeup((caddr_t)&dra->dr_cmd);
741*30294Ssam 	}
74229651Ssam }
74329651Ssam 
74429651Ssam unsigned
74529651Ssam drminphys(bp)
746*30294Ssam 	struct buf *bp;
74729651Ssam {
748*30294Ssam 
749*30294Ssam 	if (bp->b_bcount > 65536)
750*30294Ssam 		bp->b_bcount = 65536;
75129651Ssam }
75229651Ssam 
75329651Ssam /*
754*30294Ssam  * This routine performs the device unique operations on the DR11W
755*30294Ssam  * it is passed as an argument to and invoked by physio
75629651Ssam  */
75729651Ssam drstrategy (bp)
758*30294Ssam 	register struct buf *bp;
75929651Ssam {
760*30294Ssam 	register int s;
761*30294Ssam 	int unit = RSUNIT(bp->b_dev);
762*30294Ssam 	register struct rsdevice *rsaddr = RSADDR(unit);
763*30294Ssam 	register struct dr_aux *dra = &dr_aux[unit];
764*30294Ssam 	register int ok;
76529651Ssam #ifdef DR_DEBUG
766*30294Ssam 	register char *caddr;
767*30294Ssam 	long drva();
76829651Ssam #endif
76929651Ssam 
770*30294Ssam 	if ((dra->dr_flags & DR_OPEN) == 0) {	/* Device not open */
771*30294Ssam 		bp->b_error = ENXIO;
772*30294Ssam 		bp->b_flags |= B_ERROR;
773*30294Ssam 		iodone (bp);
774*30294Ssam 		return;
775*30294Ssam 	}
776*30294Ssam 	while (dra->dr_flags & DR_ACTV)
777*30294Ssam 		/* Device is active; should never be in here... */
778*30294Ssam 		sleep((caddr_t)&dra->dr_flags,DRPRI);
779*30294Ssam 	dra->dr_actf = bp;
78029651Ssam #ifdef DR_DEBUG
781*30294Ssam 	drva(dra, bp->b_proc, bp->b_un.b_addr, bp->b_bcount);
78229651Ssam #endif
783*30294Ssam 	dra->dr_oba = bp->b_un.b_addr;	/* Save original addr, count */
784*30294Ssam 	dra->dr_obc = bp->b_bcount;
785*30294Ssam 	dra->dr_bycnt = bp->b_bcount;	/* Save xfer count used by drintr() */
786*30294Ssam 	if ((((long)bp->b_un.b_addr & 0x3fffffff) >> PGSHIFT) !=
787*30294Ssam 	    ((((long)bp->b_un.b_addr & 0x3fffffff) + bp->b_bcount) >> PGSHIFT))
788*30294Ssam 		bp->b_bcount = NBPG - (((long)bp->b_un.b_addr) & PGOFSET);
789*30294Ssam 	dra->dr_flags |= DR_ACTV;	/* Mark active (use in intr handler) */
790*30294Ssam 	s = SPL_UP();
791*30294Ssam 	drstart(rsaddr,dra,bp);
792*30294Ssam 	splx(s);
793*30294Ssam 	ok = drwait(rsaddr,dra);
79429651Ssam #ifdef DR_DEBUG
795*30294Ssam 	if (DR11 & 0x40) {
796*30294Ssam 		caddr = (char *)dra->dr_oba;
797*30294Ssam 		if (dra->dr_op == DR_READ)
798*30294Ssam 			printf("\nAfter read: (%lx)(%lx)",
799*30294Ssam 			    caddr[0]&0xff, caddr[1]&0xff);
800*30294Ssam 	}
80129651Ssam #endif
802*30294Ssam 	dra->dr_flags &= ~DR_ACTV;		/* Clear active flag */
803*30294Ssam 	bp->b_un.b_addr = dra->dr_oba;	/* Restore original addr, count */
804*30294Ssam 	bp->b_bcount = dra->dr_obc;
805*30294Ssam 	if (!ok)
806*30294Ssam 		bp->b_flags |= B_ERROR;
807*30294Ssam 	/* Mark buffer B_DONE,so physstrat() in ml/machdep.c won't sleep */
808*30294Ssam 	iodone(bp);
809*30294Ssam 	wakeup((caddr_t)&dra->dr_flags);
810*30294Ssam 	/*
811*30294Ssam 	 * Return to the calling program (physio()). Physio() will sleep
812*30294Ssam 	 * until awaken by a call to iodone() in the interupt handler --
813*30294Ssam 	 * which will be called by the dispatcher when it receives dma
814*30294Ssam 	 * end-of-range interrupt.
815*30294Ssam 	 */
81629651Ssam }
81729651Ssam 
818*30294Ssam drwait(rs, dr)
819*30294Ssam 	register struct rsdevice *rs;
820*30294Ssam 	register struct dr_aux *dr;
82129651Ssam {
822*30294Ssam 	int s;
82329651Ssam 
82429651Ssam 	s = SPL_UP();
825*30294Ssam 	while (dr->dr_flags & DR_ACTV)
826*30294Ssam 		sleep((caddr_t)dr, DRPRI);
82729651Ssam 	splx(s);
828*30294Ssam 	if (dr->dr_flags & DR_TMDM) {		/* DMA timed out */
82929651Ssam 		dr->dr_flags &= ~DR_TMDM;
830*30294Ssam 		return (0);
83129651Ssam 	}
832*30294Ssam 	if (rs->dr_cstat & (PERR|BERR|TERR)) {
833*30294Ssam 		dr->dr_actf->b_flags |= B_ERROR;
834*30294Ssam 		return (0);
83529651Ssam 	}
83629651Ssam 	dr->dr_flags &= ~DR_DMAX;
837*30294Ssam 	return (1);
83829651Ssam }
83929651Ssam 
840*30294Ssam /*
841*30294Ssam  *
842*30294Ssam  * The lower 8-bit of tinfo is the minor device number, the
843*30294Ssam  * remaining higher 8-bit is the current timout number
844*30294Ssam  */
84529651Ssam drrwtimo(tinfo)
846*30294Ssam 	register u_long tinfo;
847*30294Ssam {
848*30294Ssam 	register long unit = tinfo & 0xff;
84929651Ssam 	register struct dr_aux *dr = &dr_aux[unit];
85029651Ssam 	register struct rsdevice *rs = dr->dr_addr;
85129651Ssam 
852*30294Ssam 	/*
853*30294Ssam 	 * If this is not the timeout that drwrite/drread is waiting
854*30294Ssam 	 * for then we should just go away
855*30294Ssam 	 */
856*30294Ssam 	if ((tinfo &~ 0xff) != (dr->currenttimo << 8))
857*30294Ssam 		return;
85829651Ssam 	/* Mark the device timed out */
85929651Ssam 	dr->dr_flags |= DR_TMDM;
86029651Ssam 	dr->dr_flags &= ~DR_ACTV;
86129651Ssam 	rs->dr_pulse = RMSK;			/* Inihibit interrupt */
86229651Ssam 	rs->dr_pulse = (RPER|RDMA|RATN|IENB);	/* Clear DMA logic */
863*30294Ssam 	/*
864*30294Ssam 	 * Some applications will not issue a master after dma timeout,
865*30294Ssam 	 * since doing so sends an INIT H pulse to the external device,
866*30294Ssam 	 * which may produce undesirable side-effects.
867*30294Ssam 	 */
86829651Ssam 	/* Wake up process waiting in drwait() and flag the error */
869*30294Ssam 	dr->dr_actf->b_flags |= B_ERROR;
87029651Ssam 	wakeup((caddr_t)dr->dr_cmd);
87129651Ssam }
87229651Ssam 
87329651Ssam /*
874*30294Ssam  * Kick the driver every second
875*30294Ssam  */
87629651Ssam drtimo(dev)
877*30294Ssam 	dev_t dev;
87829651Ssam {
879*30294Ssam 	register int unit = RSUNIT(dev);
88029651Ssam 	register struct dr_aux *dr;
88129651Ssam 
882*30294Ssam 	dr = &dr_aux[unit];
88329651Ssam 	if (dr->dr_flags & DR_OPEN)
884*30294Ssam 		timeout(drtimo, (caddr_t)dev, hz);
88529651Ssam 	wakeup((caddr_t)dr);	/* Wakeup any process waiting for interrupt */
88629651Ssam }
88729651Ssam 
88829651Ssam #ifdef DR_DEBUG
889*30294Ssam drva(dra, p, va, bcnt)
890*30294Ssam 	struct dr_aux *dra;
891*30294Ssam 	struct proc *p;
892*30294Ssam 	char *va;
893*30294Ssam 	long bcnt;
894*30294Ssam {
895*30294Ssam 	register long first, last , np;
89629651Ssam 
89729651Ssam 	if (DR11 & 0x20)  {
898*30294Ssam 		first = ((long)(vtoph(p, (unsigned)va))) >> 10;
899*30294Ssam 		last = ((long)(vtoph(p, (unsigned)va+bcnt))) >> 10;
90029651Ssam 		np = bcnt / 0x3ff;
90129651Ssam 		printf("\ndrva: (op:%ld)(first:%ld)(last:%ld)(np:%ld)(cnt:%ld)",
90229651Ssam 			dra->dr_op,first,last,np,bcnt);
90329651Ssam 	}
90429651Ssam }
90529651Ssam #endif
90629651Ssam 
907*30294Ssam drstart(rsaddr, dra, bp)
908*30294Ssam 	register struct rsdevice *rsaddr;
909*30294Ssam 	register struct dr_aux *dra;
910*30294Ssam 	register struct buf *bp;
911*30294Ssam {
912*30294Ssam 	register long addr;
913*30294Ssam 	u_short go;
91429651Ssam 
91529651Ssam #ifdef DR_DEBUG
916*30294Ssam 	if (dra->dr_op == DR_READ && (DR11 & 8)) {
917*30294Ssam 		char *caddr = (char *)bp->b_un.b_addr;
91829651Ssam 		printf("\ndrstart: READ, bcnt:%ld",bp->b_bcount);
91929651Ssam 		printf(",(%lx)(%lx)",caddr[0]&0xff,caddr[1]&0xff);
92029651Ssam 	}
92129651Ssam #endif
922*30294Ssam 	/* we are doing raw IO, bp->b_un.b_addr is user's address */
923*30294Ssam 	addr = (long)vtoph(bp->b_proc, (unsigned)bp->b_un.b_addr);
924*30294Ssam 	/*
925*30294Ssam 	 * Set DMA address into DR11 interace registers: DR11 requires that
926*30294Ssam 	 * the address be right shifted 1 bit position before it is written
927*30294Ssam 	 * to the board (The board will left shift it one bit position before
928*30294Ssam 	 * it places the address on the bus
929*30294Ssam 	 */
930*30294Ssam 	rsaddr->dr_walo = (addr >> 1) & 0xffff;
931*30294Ssam 	rsaddr->dr_wahi = (addr >> 17) & 0x7fff;
932*30294Ssam 	/* Set DMA range count: (number of words - 1) */
933*30294Ssam 	rsaddr->dr_range = (bp->b_bcount >> 1) - 1;
934*30294Ssam 	/* Set address modifier code to be used for DMA access to memory */
935*30294Ssam 	rsaddr->dr_addmod = DRADDMOD;
936*30294Ssam 	/*
937*30294Ssam 	 * Now determine whether this is a read or a write. ***** This is
938*30294Ssam 	 * probably only usefull for link mode operation, since dr11 doesnot
939*30294Ssam 	 * controll the direction of data transfer. The C1 control input
940*30294Ssam 	 * controls whether the hardware is doing a read or a write. In link
941*30294Ssam 	 * mode this is controlled by function 1 latch (looped back by the
942*30294Ssam 	 * cable) and could be set the program. In the general case, the dr11
943*30294Ssam 	 * doesnot know in advance what the direction of transfer is - although
944*30294Ssam 	 * the program and protocol logic probably is
945*30294Ssam 	 */
94629651Ssam #ifdef DR_DEBUG
947*30294Ssam 	if (DR11 & 1)
948*30294Ssam 		printf(
949*30294Ssam "\ndrstrat: about to GO..,dr_cmd:%lx,drstat:%lx,drcnt:%ld,cdata:%lx,OP:%ld",
950*30294Ssam 		    dra->dr_cmd, rsaddr->dr_cstat, rsaddr->dr_range,
951*30294Ssam 		    rsaddr->dr_data, dra->dr_op);
95229651Ssam #endif
953*30294Ssam 	/*
954*30294Ssam 	 * Update function latches may have been done already by drioctl() if
955*30294Ssam 	 * request from drioctl()
956*30294Ssam 	 */
957*30294Ssam 	if (dra->dr_cmd & DR_DFCN) {		/* deferred function write */
958*30294Ssam 		dra->dr_cmd &= ~DR_DFCN;	/* Clear request */
959*30294Ssam 		go = dra->dr_cmd & DR_FMSK;	/* mask out fcn bits */
960*30294Ssam 		rsaddr->dr_cstat = go;		/* Write it to the board */
961*30294Ssam 	}
962*30294Ssam 	/* Clear dmaf and attf to assure a clean dma start */
963*30294Ssam 	rsaddr->dr_pulse = RATN|RDMA|RPER;
964*30294Ssam 	rsaddr->dr_cstat = IENB|GO|CYCL|dra->dr_op; /* GO...... */
965*30294Ssam 	/*
966*30294Ssam 	 * Now check for software cycle request -- usually
967*30294Ssam 	 * by transmitter in link mode.
968*30294Ssam 	 */
969*30294Ssam 	if (dra->dr_cmd & DR_PCYL) {
970*30294Ssam 		dra->dr_cmd &= ~DR_PCYL;	/* Clear request */
971*30294Ssam 		rsaddr->dr_pulse = CYCL;	/* Use pulse register again */
972*30294Ssam 	}
973*30294Ssam 	/*
974*30294Ssam 	 * Now check for deferred ACLO FCNT2 pulse request -- usually to tell
975*30294Ssam 	 * the transmitter (via its attention) that we have enabled dma.
976*30294Ssam 	 */
977*30294Ssam 	if (dra->dr_cmd & DR_DACL) {
978*30294Ssam 		dra->dr_cmd &= ~DR_DACL;	/* Clear request */
979*30294Ssam 		rsaddr->dr_pulse = FCN2;	/* Use pulse register again */
980*30294Ssam 	}
98129651Ssam }
98229651Ssam #endif  NDR
983