xref: /csrg-svn/sys/tahoe/vba/dr.c (revision 30139)
1 /*	dr.c	1.3	86/11/23	*/
2 
3 #include "dr.h"
4 #if NDR > 0
5 
6 /*      DRV11-W DMA interface driver.
7  */
8 
9 #include "../machine/mtpr.h"
10 #include "../machine/pte.h"
11 
12 #include "param.h"
13 #include "conf.h"
14 #include "dir.h"
15 #include "user.h"
16 #include "proc.h"
17 #include "map.h"
18 #include "ioctl.h"
19 #include "buf.h"
20 #include "vm.h"
21 #include "uio.h"
22 
23 #include "../tahoevba/vbavar.h"
24 #include "../tahoevba/drreg.h"
25 
26 #define YES 1
27 #define NO  0
28 
29 struct  vba_device  *drinfo[NDR];
30 struct  dr_aux dr_aux[NDR];
31 
32 caddr_t vtoph();
33 unsigned drminphys();
34 int     drprobe(), drintr(), drattach(), drtime(), drrwtimo();
35 int     drstrategy();
36 extern struct  vba_device  *drinfo[];
37 static long drstd[] = { 0 };
38 struct  vba_driver drdriver =
39 	{ drprobe, 0, drattach, 0, drstd, "rs", drinfo };
40 extern long hz;
41 
42 #define RSUNIT(dev) (minor(dev) & 7)
43 #define SPL_UP spl5
44 
45 /* -------- Per-unit data -------- */
46 
47 extern struct dr_aux dr_aux[];
48 
49 struct rs_data {
50     struct buf  rs_buf;
51     int         rs_ubainfo;
52     short       rs_debug;
53     short       rs_busy;
54     short       rs_tout;
55     short       rs_uid;
56     short       rs_isopen;
57     short       rs_func;
58 } rs_data[NDR];
59 
60 
61 #ifdef DR_DEBUG
62 long DR11 = 0;
63 #endif
64 
65 drprobe(reg, vi)
66     caddr_t reg;
67     struct vba_device *vi;
68 {
69     register int br, cvec;		/* must be r12, r11 */
70     register struct rsdevice *dr;
71     register ushort status;
72 
73     dr = (struct rsdevice *)reg;
74 #ifdef notdef
75     dr->dr_intvect = --vi->ui_hd->vh_lastiv;
76 #else
77     dr->dr_intvect = DRINTV+vi->ui_unit;
78 #endif
79 #ifdef DR_DEBUG
80     printf("dprobe: Set interrupt vector %lx and init\n",dr->dr_intvec);
81 #endif
82     /* generate interrupt here for autoconfig */
83     dr->dr_cstat = MCLR;		/* init board and device */
84     status = dr->dr_cstat;		/* read initial status */
85 #ifdef DR_DEBUG
86     printf("drprobe: Initial status %lx\n",status & 0xffff);
87 #endif
88     br = 0x18, cvec = dr->dr_intvect;	/* XXX */
89     return (sizeof (struct rsdevice));		/* DR11 exist */
90 }
91 
92 /* ARGSUSED */
93 drattach(ui)
94 struct vba_device *ui;
95 {
96     register struct dr_aux *rsd;
97 
98     rsd = &dr_aux[ui->ui_unit];
99     rsd->dr_flags = DR_PRES;		/* This dr11 is present */
100     rsd->dr_addr = (struct rsdevice *)ui->ui_addr; /* Save addr of this dr11 */
101     rsd->dr_istat = 0;
102     rsd->dr_bycnt = 0;
103     rsd->dr_cmd = 0;
104     rsd->currenttimo = 0;
105     return;
106 }
107 
108 dropen (dev, flag)
109 dev_t dev;
110 int flag;
111 {
112     register int unit = RSUNIT(dev);
113     register struct rsdevice *dr;
114     register struct dr_aux *rsd;
115 
116     if ((drinfo[unit] == 0) || (!drinfo[unit]->ui_alive))
117 	return ENXIO;
118 
119     dr = RSADDR(unit);
120     rsd = &dr_aux[unit];
121     if (rsd->dr_flags & DR_OPEN) {
122 #ifdef DR_DEBUG
123 	printf("\ndropen: dr11 unit %ld already open",unit);
124 #endif
125 	return ENXIO;      		/* DR11 already open */
126     }
127     rsd->dr_flags |= DR_OPEN;		/* Mark it OPEN */
128     rsd->dr_istat = 0;			/* Clear status of previous interrupt */
129     rsd->rtimoticks = hz;		/* Set read no stall timout to 1 sec */
130     rsd->wtimoticks = hz*60;		/* Set write no stall timout to 1 min */
131     dr->dr_cstat = DR_ZERO;		/* Clear function & latches */
132     dr->dr_pulse = (RDMA | RATN);	/* clear leftover attn & e-o-r flags */
133     drtimo(dev);			/* start the self kicker */
134     return 0;
135 }
136 
137 drclose (dev)
138 dev_t dev;
139 {
140     register int unit = RSUNIT(dev);
141     register struct dr_aux *dra;
142     register struct rsdevice *rs;
143     register short s;
144 
145     dra = &dr_aux[unit];
146     if (!(dra->dr_flags & DR_OPEN)) {
147 #ifdef DR_DEBUG
148 	printf("\ndrclose: DR11 device %ld not open",unit);
149 #endif
150 	return;
151     }
152     dra->dr_flags &= ~(DR_OPEN|DR_ACTV);
153     rs = dra->dr_addr;
154     s=SPL_UP();
155     rs->dr_cstat = DR_ZERO;
156     if (dra->dr_buf.b_flags & B_BUSY) {
157     	dra->dr_buf.b_flags &= ~B_BUSY;
158 	wakeup(&dra->dr_buf.b_flags);
159     }
160     splx(s);
161     return;
162 }
163 
164 
165 /*	drread() works exactly like drwrite() except that the
166 	B_READ flag is used when physio() is called
167 */
168 drread (dev, uio)
169 dev_t dev;
170 struct uio *uio;
171 {	register struct dr_aux *dra;
172 	register struct buf *bp;
173 	register long spl, err;
174     	register int unit = RSUNIT(dev);
175 
176     if (   uio->uio_iov->iov_len <= 0		/* Negative count */
177 	|| uio->uio_iov->iov_len & 1		/* odd count */
178 	|| (int)uio->uio_iov->iov_base & 1	/* odd destination address */
179        )
180 	return EINVAL;
181 
182 #ifdef DR_DEBUG
183     if (DR11 & 8) {
184 	printf("\ndrread: (len:%ld)(base:%lx)",
185     		uio->uio_iov->iov_len,(int)uio->uio_iov->iov_base);
186     }
187 #endif
188 
189     dra = &dr_aux[RSUNIT(dev)];
190     dra->dr_op = DR_READ;
191     bp =  &dra->dr_buf;
192     bp->b_resid = 0;
193     if (dra->dr_flags & DR_NORSTALL) {
194 	/* We are in no stall mode, start the timer, raise IPL so nothing
195 	   can stop us once the timer's running */
196 	spl = SPL_UP();
197 	timeout(drrwtimo,(caddr_t)((dra->currenttimo<<8) | unit),
198 				dra->rtimoticks);
199     	err = physio (drstrategy, bp, dev,B_READ, drminphys, uio);
200 	splx(spl);
201 	if (err)
202 		return(err);
203 	dra->currenttimo++;		/* Update current timeout number */
204 	/* Did we timeout */
205 	if (dra->dr_flags & DR_TMDM) {
206 		dra->dr_flags &= ~DR_TMDM;	/* Clear timeout flag */
207 		u.u_error = 0;		/* Made the error ourself, ignore it */
208 	}
209     }
210     else {
211     	return physio (drstrategy, bp, dev,B_READ, drminphys, uio);
212     }
213 }
214 
215 drwrite (dev, uio)
216 dev_t dev;
217 struct uio *uio;
218 {	register struct dr_aux *dra;
219 	register struct buf *bp;
220     	register int unit = RSUNIT(dev);
221 	register long spl, err;
222 
223     if (   uio->uio_iov->iov_len <= 0
224 	|| uio->uio_iov->iov_len & 1
225 	|| (int)uio->uio_iov->iov_base & 1
226        )
227 	return EINVAL;
228 
229 #ifdef DR_DEBUG
230     if (DR11 & 4) {
231 	printf("\ndrwrite: (len:%ld)(base:%lx)",
232     		uio->uio_iov->iov_len,(int)uio->uio_iov->iov_base);
233     }
234 #endif
235 
236     dra = &dr_aux[RSUNIT(dev)];
237     dra->dr_op = DR_WRITE;
238     bp =  &dra->dr_buf;
239     bp->b_resid = 0;
240     if (dra->dr_flags & DR_NOWSTALL) {
241 	/* We are in no stall mode, start the timer, raise IPL so nothing
242 	   can stop us once the timer's running */
243 	spl = SPL_UP();
244 	timeout(drrwtimo,(caddr_t)((dra->currenttimo<<8) | unit),
245 				dra->wtimoticks);
246     	err = physio (drstrategy, bp, dev,B_WRITE, drminphys, uio);
247 	splx(spl);
248 	if (err)
249 		return(err);
250 	dra->currenttimo++;		/* Update current timeout number */
251 	/* Did we timeout */
252 	if (dra->dr_flags & DR_TMDM) {
253 		dra->dr_flags &= ~DR_TMDM;	/* Clear timeout flag */
254 		u.u_error = 0;		/* Made the error ourself, ignore it */
255 	}
256     }
257     else {
258     	return physio (drstrategy, bp, dev,B_WRITE, drminphys, uio);
259     }
260 }
261 
262 /*  Routine used by calling program to issue commands to dr11 driver and
263     through it to the device.
264     It is also used to read status from the device and driver and to wait
265     for attention interrupts.
266     Status is returned in an 8 elements unsigned short integer array, the
267     first two elements of the array are also used to pass arguments to
268     drioctl() if required.
269     The function bits to be written to the dr11 are included in the cmd
270     argument. Even if they are not being written to the dr11 in a particular
271     drioctl() call, they will update the copy of cmd that is stored in the
272     driver. When drstrategy() is called, this updated copy is used if a
273     deferred function bit write has been specified. The "side effect" of
274     calls to the drioctl() requires that the last call prior to a read or
275     write has an appropriate copy of the function bits in cmd if they are
276     to be used in drstrategy().
277     When used as command value, the contents of data[0] is the command
278     parameter.
279 */
280 
281 drioctl(dev, cmd, data, flag)
282 dev_t dev;
283 int cmd;
284 long *data;
285 int flag;
286 {
287     register int unit = RSUNIT(dev);
288     register struct dr_aux *dra;
289     register struct rsdevice *rsaddr = RSADDR(unit);
290     struct dr11io dio;
291     ushort s, errcode, status;
292     long temp;
293 
294 #ifdef DR_DEBUG
295     if (DR11 & 0x10)
296     printf("\ndrioctl: (dev:%lx)(cmd:%lx)(data:%lx)(data[0]:%lx)",
297 	dev,cmd,data,data[0]);
298 #endif
299 
300     dra = &dr_aux[unit];
301     dra->dr_cmd = 0;		/* Fresh copy; clear all previous flags */
302 
303     switch (cmd) {
304 
305     case DRWAIT:
306 	/* Wait for attention interrupt */
307 #ifdef DR_DEBUG
308 	printf("\ndrioctl: wait for attention interrupt");
309 #endif
310 	s = SPL_UP();
311 	/* If the attention flag in dr_flags is set, it probably means that
312 	   an attention has arrived by the time a previous DMA end-of-range
313 	   interrupt was serviced. If ATRX is set, we will return with out
314 	   sleeping, since we have received an attention since the last call
315 	   to wait on attention.
316 	   This may not be appropriate for some applications.
317 	*/
318 	if (!(dra->dr_flags & DR_ATRX)) {
319 		dra->dr_flags |= DR_ATWT;	/* Set waiting flag */
320 		rsaddr->dr_pulse = IENB;	/* Enable interrupt; use pulse
321 						   reg. so function bits are
322 						   not changed */
323 		sleep((caddr_t)&dra->dr_cmd,DRPRI);
324 	}
325 	splx(s);
326 	break;
327 
328     case DRPIOW:
329 	/* Write to p-i/o register */
330 	rsaddr->dr_data = data[0];
331 	break;
332 
333     case DRPACL:
334 	/* Send pulse to device */
335 	rsaddr->dr_pulse = FCN2;
336 	break;
337 
338     case DRDACL:
339 	/* Defer alco pulse until go */
340 	dra->dr_cmd |= DR_DACL;
341 	break;
342 
343     case DRPCYL:
344 	/* Set cycle with next go */
345 	dra->dr_cmd |= DR_PCYL;
346 	break;
347 
348     case DRDFCN:
349 	/* Do not update function bits until next go issued */
350 	dra->dr_cmd |= DR_DFCN;
351 	break;
352 
353     case DRRATN:
354 	/* Reset attention flag -- use with extreme caution */
355 	rsaddr->dr_pulse = RATN;
356 	break;
357 
358     case DRRDMA:
359 	/* Reset DMA e-o-r flag -- should never used */
360 	rsaddr->dr_pulse = RDMA;
361 	break;
362 
363     case DRSFCN:
364 	/* Set function bits */
365 	temp = data[0] & DR_FMSK;
366 	rsaddr->dr_cstat = temp;	/* Write to control register */
367 	/* This has a very important side effect -- It clears the interrupt
368 	   enable flag. That is fine for this driver, but if it is desired
369 	   to leave interrupt enable at all times, it will be necessary to
370 	   to read the status register first to get IENB, or carry a software
371 	   flag that indicates whether interrupts are set, and or this into
372 	   the controll register value being written.
373 	*/
374 	break;
375 
376     case DRRPER:
377 	/* Clear parity flag */
378 	rsaddr->dr_pulse = RPER;
379 	break;
380 
381     case DRSETRSTALL:
382 	/* Set read stall mode. */
383 	dra->dr_flags &= (~DR_NORSTALL);
384 	break;
385 
386     case DRSETNORSTALL:
387 	/* Set no stall read  mode. */
388 	dra->dr_flags |= DR_NORSTALL;
389 	break;
390 
391     case DRGETRSTALL:
392 	/* Returns true if in read stall mode. */
393 	data[0]  = (dra->dr_flags & DR_NORSTALL)? 0 : 1;
394 	break;
395 
396     case DRSETRTIMEOUT:
397 	/* Set the number of ticks before a no stall read times out.
398 	   The argument is given in tenths of a second. */
399 	if (data[0] < 1) {
400 		u.u_error = EINVAL;
401 		temp = 1;
402 	}
403 	dra->rtimoticks = (data[0] * hz )/10;
404 	break;
405 
406     case DRGETRTIMEOUT:
407 	/* Returns the number of tenths of seconds before
408 	   a no stall read times out. */
409 	/* The argument is given in tenths of a second. */
410 	data[0] = ((dra->rtimoticks)*10)/hz;
411 	break;
412 
413     case DRSETWSTALL:
414 	/* Set write stall mode. */
415 	dra->dr_flags &= (~DR_NOWSTALL);
416 	break;
417 
418     case DRSETNOWSTALL:
419 	/* Set write stall mode. */
420 	dra->dr_flags |= DR_NOWSTALL;
421 	break;
422 
423     case DRGETWSTALL:
424 	/* Returns true if in write stall mode. */
425 	data[0] = (dra->dr_flags & DR_NOWSTALL)? 0 : 1;
426 	break;
427 
428     case DRSETWTIMEOUT:
429 	/* Set the number of ticks before a no stall write times out.
430 	   The argument is given in tenths of a second. */
431 	if (data[0] < 1) {
432 		u.u_error = EINVAL;
433 		temp = 1;
434 	}
435 	dra->wtimoticks = (data[0] * hz )/10;
436 	break;
437 
438     case DRGETWTIMEOUT:
439 	/* Returns the number of tenths of seconds before
440 	   a no stall write times out. */
441 	/* The argument is given in tenths of a second. */
442 	data[0] = ((dra->wtimoticks)*10)/hz;
443 	break;
444 
445     case DRWRITEREADY:
446 	/* Returns a value of 1 if the device can accept
447 	   data, 0 otherwise. Internally this is the
448 	   DR11-W STAT A bit. */
449 
450 	data[0] = (rsaddr->dr_cstat & STTA)? 1 : 0;
451 	break;
452 
453     case DRREADREADY:
454 	/* Returns a value of 1 if the device has data
455 	   for host to be read, 0 otherwise. Internally
456 	   this is the DR11-W STAT B bit. */
457 	data[0] = (rsaddr->dr_cstat & STTB)? 1 : 0;
458 	break;
459 
460     case DRBUSY:
461 	/* Returns a value of 1 if the device is busy,
462 	   0 otherwise. Internally this is the DR11-W
463 	   STAT C bit, but there is a bug in the Omega 500/FIFO interface
464 	   board that it cannot drive this signal low for certain DR11-W
465 	   ctlr such as the Ikon. We use the REDY signal of the CSR on
466 	   the Ikon DR11-W instead.
467 
468 	data[0] = (rsaddr->dr_cstat & STTC)? 1 : 0;
469 	*/
470 
471 	data[0] = ((rsaddr->dr_cstat & REDY)? 0 : 1);
472 	break;
473 
474     case DRRESET:
475 	rsaddr->dr_pulse = (MCLR|RDMA|RATN|RPER);/* Reset DMA ATN RPER flag */
476 	DELAY(0x1f000);
477 	while (!(rsaddr->dr_cstat & REDY)) {
478 		sleep((caddr_t)dra, DRPRI);	/* Wakeup by drtimo() */
479 	}
480     	dra->dr_istat = 0;
481     	dra->dr_cmd = 0;
482     	dra->currenttimo = 0;
483 	break;
484 
485     case DR11STAT: {
486 	register struct dr11io *dr = (struct dr11io *)data;
487     	/* Copy back dr11 status to user */
488     	dr->arg[0] = dra->dr_flags;
489     	dr->arg[1] = rsaddr->dr_cstat;
490     	dr->arg[2] = dra->dr_istat;	/* Status reg. at last interrupt */
491     	dr->arg[3] = rsaddr->dr_data;	/* P-i/o input data */
492     	status = (ushort)((rsaddr->dr_addmod << 8) & 0xff00);
493     	dr->arg[4] = status | (ushort)(rsaddr->dr_intvect & 0xff);
494     	dr->arg[5] = rsaddr->dr_range;
495     	dr->arg[6] = rsaddr->dr_rahi;
496     	dr->arg[7] = rsaddr->dr_ralo;
497 	break;
498     }
499     case DR11LOOP:
500 	/* Perform loopback test -- MUST HAVE LOOPBACK CABLE ATTACHED --
501 	   Test results are printed on system console */
502 	if (suser())
503 		dr11loop(rsaddr,dra,unit);
504 	break;
505 
506     default:
507 	printf("\ndrioctl: Invalid ioctl cmd : %lx",cmd);
508 	return EINVAL;
509     }
510 
511 #ifdef DR_DEBUG
512     if (DR11 & 0x10)
513     	printf("**** (data[0]:%lx)",data[0]);
514 #endif
515     return 0;
516 }
517 
518 #define NPAT 2
519 #define DMATBL 20
520 ushort tstpat[DMATBL] = { 0xAAAA, 0x5555};
521 long DMAin = 0;
522 
523 dr11loop(dr,dra,unit)
524 struct rsdevice *dr;
525 struct dr_aux *dra;
526 long unit;
527 {	register long result, ix;
528 	long baddr, wait;
529 
530 	dr->dr_cstat = MCLR;		/* Clear board & device, disable intr */
531 
532 	/* Perform loopback test -- MUST HAVE LOOPBACK CABLE ATTACHED --
533 	   Test results are printed on system console */
534 	printf("\n\t ----- DR11 unit %ld loopback test -----",unit);
535 
536 	printf("\n\t Program I/O ...");
537 	for (ix=0;ix<NPAT;ix++) {
538 		dr->dr_data = tstpat[ix];	/* Write to Data out register */
539 		result = (dr->dr_data & 0xFFFF);	/* Read it back */
540 		if (result != tstpat[ix]) {
541 			printf("Failed, expected : %lx --- actual : %lx",
542 				tstpat[ix],result);
543 			return;
544 		}
545 	}
546 
547 	printf("OK\n\t Functions & Status Bits ...");
548 	dr->dr_cstat = (FCN1 | FCN3);
549 	result = dr->dr_cstat & 0xffff;		/* Read them back */
550 	if ((result & (STTC | STTA)) != (STTC |STTA)) {
551 		printf("Failed, expected : %lx --- actual : %lx, ISR:%lx",
552 			(STTA|STTC),(result & (STTA|STTC)), result);
553 		return;
554 	}
555 	dr->dr_cstat = FCN2;
556 	result = dr->dr_cstat & 0xffff;		/* Read them back */
557 	if ((result & STTB) != STTB) {
558 		printf("Failed, expected : %lx --- actual : %lx, ISR:%lx",
559 			STTB,(result & STTB), result);
560 		return;
561 	}
562 
563 	printf("OK\n\t DMA output ...");
564 
565 	if (DMAin) goto dmain;
566 
567 	/* Initialize DMA data buffer */
568 	for(ix=0;ix<DMATBL;ix++) tstpat[ix] = 0xCCCC + ix;
569 	tstpat[DMATBL-1] = 0xCCCC;	/* Last word output */
570 
571 	/* Setup normal DMA */
572 	baddr = (long)vtoph(0,tstpat);		/* Virtual --> physical */
573     	dr->dr_walo = (ushort)((baddr >> 1) & 0xffff);
574     	dr->dr_wahi = (ushort)((baddr >> 17) & 0x7fff);
575 
576     	/* Set DMA range count: (number of words - 1) */
577     	dr->dr_range = (ushort)(DMATBL - 1);
578 
579     	/* Set  address modifier code to be used for DMA access to memory */
580     	dr->dr_addmod = (char)DRADDMOD;
581 
582     	/* Clear dmaf and attf to assure a clean dma start, also disable
583 	   attention interrupt
584 	*/
585     	dr->dr_pulse = (ushort)(RDMA|RATN|RMSK);  /* Use pulse register */
586     	dr->dr_cstat = (GO|CYCL);		  /* GO...... */
587 
588 	/* Wait for DMA complete; REDY and DMAF are true in ISR */
589 	wait = 0;
590 	while ((result=(dr->dr_cstat & (REDY | DMAF))) != (REDY|DMAF)) {
591 		printf("\n\tWait for DMA complete...ISR : %lx",result);
592 		if (++wait > 5) {
593 			printf("\n\t DMA output fails...timeout!!, ISR:%lx",
594 				result);
595 			return;
596 		}
597 	}
598 
599 	result = dr->dr_data & 0xffff;		/* Read last word output */
600 	if (result != 0xCCCC) {
601 		printf("\n\t Fails, expected : %lx --- actual : %lx",
602 			0xCCCC,result);
603 		return;
604 	}
605 
606 	printf("OK\n\t DMA input ...");
607 
608 dmain:
609 	dr->dr_data = 0x1111;		/* DMA input data */
610 	/* Setup normal DMA */
611 	baddr = (long)vtoph(0,tstpat);		/* Virtual --> physical */
612     	dr->dr_walo = (ushort)((baddr >> 1) & 0xffff);
613     	dr->dr_wahi = (ushort)((baddr >> 17) & 0x7fff);
614 
615     	/* Set DMA range count: (number of words - 1) */
616     	dr->dr_range = (ushort)(DMATBL - 1);
617 
618     	/* Set  address modifier code to be used for DMA access to memory */
619     	dr->dr_addmod = (char)DRADDMOD;
620 	/* Set FCN1 in ICR to DMA in*/
621 	dr->dr_cstat = FCN1;
622 
623 	if (!(dra->dr_flags & DR_LOOPTST)) {
624 		/* Use pulse reg */
625     		dr->dr_pulse = (ushort)(RDMA|RATN|RMSK|CYCL|GO);
626 		/* Wait for DMA complete; REDY and DMAF are true in ISR */
627 		wait = 0;
628 		while ((result=(dr->dr_cstat & (REDY | DMAF)))
629 						!= (REDY|DMAF)) {
630 			printf("\n\tWait for DMA to complete...ISR:%lx",result);
631 			if (++wait > 5) {
632 				printf("\n\t DMA input timeout!!, ISR:%lx",
633 					result);
634 				return;
635 			}
636 		}
637 	}
638 	else  {
639 		/* Enable DMA e-o-r interrupt */
640     		dr->dr_pulse = (ushort)(IENB|RDMA|RATN|CYCL|GO);
641 		/* Wait for DMA complete; DR_LOOPTST is false in dra->dr_flags*/
642 		wait = 0;
643 		while (dra->dr_flags & DR_LOOPTST) {
644 			result = dr->dr_cstat & 0xffff;
645 			printf("\n\tWait for DMA e-o-r intr...ISR:%lx",result);
646 			if (++wait > 7) {
647 				printf("\n\t DMA e-o-r timeout!!, ISR:%lx",
648 					result);
649 				dra->dr_flags &= ~DR_LOOPTST;
650 				return;
651 			}
652 		}
653 		dra->dr_flags |= DR_LOOPTST;
654 	}
655 
656 	mtpr(tstpat,P1DC);			/* Purge cache */
657 	mtpr((0x3ff+(long)tstpat),P1DC);
658 	for(ix=0;ix<DMATBL;ix++) {
659 		if (tstpat[ix] != 0x1111) {
660 			printf("\n\t Fails, ix:%ld,expected : %lx --- actual : %lx",
661 				ix,0x1111,tstpat[ix]);
662 			return;
663 		}
664 	}
665 	if (!(dra->dr_flags & DR_LOOPTST)) {
666 		dra->dr_flags |= DR_LOOPTST;
667 		printf(" OK..\n\tDMA end of range interrupt...");
668 		goto dmain;
669 	}
670 
671 
672 	printf(" OK..\n\tAttention interrupt....");
673 	/* Pulse FCN2 in pulse register with IENB */
674     	dr->dr_pulse = (ushort)(IENB|RDMA);
675     	dr->dr_pulse = (ushort)FCN2;
676 
677 	/* Wait for ATTN interrupt; DR_LOOPTST is false in dra->dr_flags*/
678 	wait = 0;
679 	while (dra->dr_flags & DR_LOOPTST) {
680 		result = dr->dr_cstat & 0xffff;
681 		printf("\n\tWait for Attention intr...ISR:%lx",result);
682 		if (++wait > 7) {
683 			printf("\n\t Attention interrupt timeout!!, ISR:%lx",
684 				result);
685 			dra->dr_flags &= ~DR_LOOPTST;
686 			return;
687 		}
688 	}
689 	dra->dr_flags &= ~DR_LOOPTST;
690 	printf(" OK..\n\tDone...");
691 }
692 
693 /* Reset state on Unibus reset */
694 drreset(uban)
695 int uban;
696 {
697     register int i;
698     register struct vba_device *ui;
699     register struct dr_aux *dra;
700 
701     for (i = 0; i < NDR; i++, dra++) {
702 	if (   (ui = drinfo[i]) == 0
703 	    || !ui->ui_alive
704 	    || ui->ui_vbanum != uban
705 	   )
706 	    continue;
707 	printf("\ndrreset: %ld",i);
708 	/* Do something; reset board */
709     }
710     return;
711 }
712 
713 /*
714  * An interrupt is caused either by an error,
715  * base address overflow, or transfer complete
716  */
717 drintr (unit)
718 register long unit;
719 {
720     register struct dr_aux *dra = &dr_aux[unit];
721     register struct rsdevice *rsaddr = RSADDR(unit);
722     register struct buf *bp;
723     register short status, csrtmp;
724 
725     status = rsaddr->dr_cstat & 0xffff;		/* get board status register */
726     dra->dr_istat = status;
727 
728 #ifdef DR_DEBUG
729     if (DR11 & 2)
730     	printf("\ndrintr: dr11 status : %lx",status & 0xffff);
731 #endif
732 
733     if (dra->dr_flags & DR_LOOPTST) {
734 	/* Controller is doing loopback test */
735     	dra->dr_flags &= ~DR_LOOPTST;
736 	return;
737     }
738 
739     /* Make sure this is not a stray interrupt; at least one of dmaf or attf
740        must be set. Note that if the dr11 interrupt enable latch is reset
741        during a hardware interrupt ack sequence, and by the we get to this
742        point in the interrupt code it will be 0. This is done to give the
743        programmer some control over how the two more-or-less independent
744        interrupt sources on the board are handled.
745        If the attention flag is set when drstrategy() is called to start a
746        dma read or write an interrupt will be generated as soon as the
747        strategy routine enables interrupts for dma end-of-range. This will
748        cause execution of the interrupt routine (not necessarily bad) and
749        will cause the interrupt enable mask to be reset (very bad since the
750        dma end-of-range condition will not be able to generate an interrupt
751        when it occurs) causing the dma operation to time-out (even though
752        the dma transfer will be done successfully) or hang the process if a
753        software time-out capability is not implemented. One way to avoid
754        this situation is to check for a pending attention interrupt (attf
755        set) by calling drioctl() before doing a read or a write. For the
756        time being this driver will solve the problem by clearing the attf
757        flag in the status register before enabling interrupts in drstrategy().
758 
759        **** The IKON 10084 for which this driver is written will set both
760        attf and dmaf if dma is terminated by an attention pulse. This will
761        cause a wakeup(&dr_aux), which will be ignored since it is not being
762        waited on, and an iodone(bp) which is the desired action. Some other
763        dr11 emulators, in particular the IKON 10077 for the Multibus, donot
764        dmaf in this case. This may require some addtional code in the inter-
765        rupt routine to ensure that en iodone(bp) is issued when dma is term-
766        inated by attention.
767     */
768 
769     bp = dra->dr_actf;
770     if (!(status & (ATTF | DMAF))) {
771 	printf("\ndrintr: Stray interrupt, dr11 status : %lx",status);
772 	return;
773     }
774     if (status & DMAF) {
775 	/* End-of-range interrupt */
776 	dra->dr_flags |= DR_DMAX;
777 
778 #ifdef DR_DEBUG
779     if (DR11 & 2)
780 	printf("\ndrintr: e-o-r interrupt,cstat:%lx,dr_flags:%lx",
781 		status&0xffff,dra->dr_flags & DR_ACTV);
782 #endif
783 	if (!(dra->dr_flags & DR_ACTV)) {
784 		/* We are not doing DMA !! */
785 		bp->b_flags |= B_ERROR;
786 	}
787 	else {
788 		if (dra->dr_op == DR_READ) mtpr(bp->b_un.b_addr,P1DC);
789 		dra->dr_bycnt -= bp->b_bcount;
790 		if (dra->dr_bycnt >0) {
791 			bp->b_un.b_addr += bp->b_bcount;
792 			bp->b_bcount = (dra->dr_bycnt > NBPG) ? NBPG:
793 					dra->dr_bycnt;
794 			drstart(rsaddr,dra,bp);
795 			return;
796 		}
797 	}
798 	dra->dr_flags &= ~DR_ACTV;
799 	wakeup(dra);			/* Wakeup proc waiting in drwait() */
800 	rsaddr->dr_pulse = (RPER|RDMA|RATN);	/* reset dma e-o-r flag */
801     }
802 
803     /* Now test for attention interrupt -- It may be set in addition to
804        the dma e-o-r interrupt. If we get one we will issue a wakeup to
805        the drioctl() routine which is presumable waiting for one.
806        The program may have to monitor the attention interrupt received
807        flag in addition to doing waits for the interrupt. Futhermore,
808        interrupts are not enabled unless dma is in progress or drioctl()
809        has been called to wait for attention -- this may produce some
810        strange results if attf is set on the dr11 when a read or a write
811        is initiated, since that will enables interrupts.
812        **** The appropriate code for this interrupt routine will probably
813        be rather application dependent.
814     */
815 
816     if (status & ATTF) {
817 	dra->dr_flags |= DR_ATRX;
818 	dra->dr_flags &= ~DR_ATWT;
819 	rsaddr->dr_cstat = RATN;	/* reset attention flag */
820 	wakeup((caddr_t)&dra->dr_cmd);
821 	/* Some applications which use attention to terminate dma may also
822 	   want to issue an iodone() here to wakeup physio().
823  	*/
824     }
825     return;
826 }
827 
828 unsigned
829 drminphys(bp)
830 struct buf *bp;
831 {
832     if (bp->b_bcount > 65536)
833 	bp->b_bcount = 65536;
834 }
835 
836 /*
837  *  This routine performs the device unique operations on the DR11W
838  *  it is passed as an argument to and invoked by physio
839  */
840 drstrategy (bp)
841 register struct buf *bp;
842 {
843     register int s;
844     int unit = RSUNIT(bp->b_dev);
845     register struct rsdevice *rsaddr = RSADDR(unit);
846     register struct dr_aux *dra = &dr_aux[unit];
847     register short go = 0;
848     register long baddr, ok;
849 #ifdef DR_DEBUG
850     register char *caddr;
851     long drva();
852 #endif
853 
854 
855     if (!(dra->dr_flags & DR_OPEN)) {
856 	/* Device not open */
857 	bp->b_error = ENXIO;
858 	bp->b_flags |= B_ERROR;
859 	iodone (bp);
860 	return;
861     }
862 
863     while (dra->dr_flags & DR_ACTV) {
864 	/* Device is active; should never be in here... */
865 	sleep((caddr_t)&dra->dr_flags,DRPRI);
866     }
867 
868     dra->dr_actf = bp;
869 
870 #ifdef DR_DEBUG
871     drva(dra,bp->b_proc,bp->b_un.b_addr,bp->b_bcount);
872 #endif
873 
874     dra->dr_oba = bp->b_un.b_addr;	/* Save original addr, count */
875     dra->dr_obc = bp->b_bcount;
876     dra->dr_bycnt = bp->b_bcount;	/* Save xfer count used by drintr() */
877 
878     if ((((long)bp->b_un.b_addr & 0x3fffffff) >> PGSHIFT) !=
879 	((((long)bp->b_un.b_addr & 0x3fffffff) + bp->b_bcount) >> PGSHIFT)) {
880     	bp->b_bcount = NBPG - (((long)bp->b_un.b_addr) & PGOFSET);
881     }
882 
883     dra->dr_flags |= DR_ACTV;	/* Mark it active (use in intr handler) */
884     s = SPL_UP();
885     drstart(rsaddr,dra,bp);
886     splx(s);
887 
888     ok = drwait(rsaddr,dra);
889 #ifdef DR_DEBUG
890     if (DR11 & 0x40) {
891 	caddr = (char *)dra->dr_oba;
892     	if (dra->dr_op == DR_READ)
893 		printf("\nAfter read: (%lx)(%lx)",caddr[0]&0xff,caddr[1]&0xff);
894     }
895 #endif
896     dra->dr_flags &= ~DR_ACTV;		/* Clear active flag */
897     bp->b_un.b_addr = dra->dr_oba;	/* Restore original addr, count */
898     bp->b_bcount = dra->dr_obc;
899 
900     if (!ok) bp->b_flags |= B_ERROR;
901     iodone(bp);				/* Mark buffer B_DONE,so physstrat()
902 					   in ml/machdep.c won't sleep */
903     wakeup((caddr_t)&dra->dr_flags);
904 
905     /* Return to the calling program (physio()). Physio() will sleep
906        until awaken by a call to iodone() in the interupt handler --
907        which will be called by the dispatcher when it receives dma
908        end-of-range interrupt.
909     */
910     return;
911 }
912 
913 drwait(rs,dr)
914 register struct rsdevice *rs;
915 register struct dr_aux *dr;
916 {
917 	register long status, s;
918 
919 	s = SPL_UP();
920     	while (dr->dr_flags & DR_ACTV)
921 		sleep((caddr_t)dr,DRPRI);
922 	splx(s);
923 
924 	if (dr->dr_flags & DR_TMDM) {
925 		/* DMA timed out */
926 		dr->dr_flags &= ~DR_TMDM;
927 		return(0);
928 	}
929 	else {
930 		if (rs->dr_cstat & (PERR|BERR|TERR)) {
931 			(dr->dr_actf)->b_flags |= B_ERROR;
932 			return(0);
933 		}
934 	}
935 	dr->dr_flags &= ~DR_DMAX;
936 	return(1);
937 }
938 
939 
940 drrwtimo(tinfo)
941 register unsigned long tinfo;
942 /*
943  * 	The lower 8-bit of tinfo is the minor device number, the
944  *	remaining higher 8-bit is the current timout number
945 */
946 {	register long unit = tinfo & 0xff;
947 	register struct dr_aux *dr = &dr_aux[unit];
948 	register struct rsdevice *rs = dr->dr_addr;
949 
950 	/* If this is not the timeout that drwrite/drread is waiting
951 	   for then we should just go away */
952 	if ((tinfo & (~0xff)) != (dr->currenttimo << 8)) return;
953 
954 	/* Mark the device timed out */
955 	dr->dr_flags |= DR_TMDM;
956 	dr->dr_flags &= ~DR_ACTV;
957 	rs->dr_pulse = RMSK;			/* Inihibit interrupt */
958 	rs->dr_pulse = (RPER|RDMA|RATN|IENB);	/* Clear DMA logic */
959 
960 	/* Some applications will not issue a master after dma timeout,
961 	   since doing so sends an INIT H pulse to the external device,
962 	   which may produce undesirable side-effects.  */
963 
964 	/* Wake up process waiting in drwait() and flag the error */
965 	(dr->dr_actf)->b_flags |= B_ERROR;
966 	wakeup((caddr_t)dr->dr_cmd);
967 }
968 
969 
970 /*
971  *	Kick the driver every second
972 */
973 drtimo(dev)
974 dev_t dev;
975 {
976     	register int unit = RSUNIT(dev);
977 	register struct dr_aux *dr;
978 
979     	dr = &dr_aux[unit];
980 	if (dr->dr_flags & DR_OPEN)
981 		timeout(drtimo,(caddr_t)dev,hz);
982 	wakeup((caddr_t)dr);	/* Wakeup any process waiting for interrupt */
983 }
984 
985 
986 #ifdef DR_DEBUG
987 
988 drva(dra,p,va,bcnt)
989 struct dr_aux *dra;
990 struct proc *p;
991 char *va;
992 long bcnt;
993 {	register long first, last , np;
994 
995 	if (DR11 & 0x20)  {
996 		first = ((long)(vtoph(p,va))) >> 10;
997 		last = ((long)(vtoph(p,va+bcnt))) >> 10;
998 		np = bcnt / 0x3ff;
999 		printf("\ndrva: (op:%ld)(first:%ld)(last:%ld)(np:%ld)(cnt:%ld)",
1000 			dra->dr_op,first,last,np,bcnt);
1001 	}
1002 }
1003 #endif
1004 
1005 
1006 drstart(rsaddr,dra,bp)
1007 register struct rsdevice *rsaddr;
1008 register struct dr_aux *dra;
1009 register struct buf *bp;
1010 {	register long baddr;
1011 	ushort go;
1012 	register char *caddr;
1013 
1014 #ifdef DR_DEBUG
1015 	if ((dra->dr_op == DR_READ) && (DR11 & 8)) {
1016 		printf("\ndrstart: READ, bcnt:%ld",bp->b_bcount);
1017     		caddr = (char *)bp->b_un.b_addr;
1018 		printf(",(%lx)(%lx)",caddr[0]&0xff,caddr[1]&0xff);
1019 	}
1020 #endif
1021     /* we are doing raw IO, bp->b_un.b_addr is user's address */
1022     baddr = (long)vtoph(bp->b_proc,(caddr_t)bp->b_un.b_addr);
1023 
1024     /* Set DMA address into DR11 interace registers: DR11 requires that
1025        the address be right shifted 1 bit position before it is written
1026        to the board (The board will left shift it one bit position before
1027        it places the address on the bus
1028     */
1029     rsaddr->dr_walo = (ushort)((baddr >> 1) & 0xffff);
1030     rsaddr->dr_wahi = (ushort)((baddr >> 17) & 0x7fff);
1031 
1032     /* Set DMA range count: (number of words - 1) */
1033     rsaddr->dr_range = (ushort)((bp->b_bcount >> 1) - 1);
1034 
1035     /* Set address modifier code to be used for DMA access to memory */
1036     rsaddr->dr_addmod = (char)DRADDMOD;
1037 
1038     /* Now determine whether this is a read or a write. ***** This is
1039        probably only usefull for link mode operation, since dr11 doesnot
1040        controll the direction of data transfer. The C1 control input
1041        controls whether the hardware is doing a read or a write. In link
1042        mode this is controlled by function 1 latch (looped back by the
1043        cable) and could be set the program. In the general case, the dr11
1044        doesnot know in advance what the direction of transfer is - although
1045        the program and protocol logic probably is
1046     */
1047 
1048 #ifdef DR_DEBUG
1049    if (DR11 & 1)
1050     printf("\ndrstrat: about to GO..,dr_cmd:%lx,drstat:%lx,drcnt:%ld,cdata:%lx,OP:%ld",
1051 	dra->dr_cmd,rsaddr->dr_cstat,rsaddr->dr_range,rsaddr->dr_data,dra->dr_op);
1052 #endif
1053 
1054     /* Update function latches may have been done already by drioctl() if
1055        request from drioctl()
1056     */
1057     if (dra->dr_cmd & DR_DFCN) {
1058 	/* deferred function write */
1059     	dra->dr_cmd &= ~DR_DFCN;	/* Clear request */
1060 	go = dra->dr_cmd & DR_FMSK;	/* mask out fcn bits */
1061 	rsaddr->dr_cstat = go;		/* Write it to the board */
1062     }
1063 
1064     /* Clear dmaf and attf to assure a clean dma start */
1065     rsaddr->dr_pulse = (ushort)(RATN|RDMA|RPER);
1066     rsaddr->dr_cstat = (ushort)(IENB|GO|CYCL|dra->dr_op); /* GO...... */
1067 
1068     /* Now check for software cycle request -- usually by transmitter in
1069        link mode.
1070     */
1071     if (dra->dr_cmd & DR_PCYL) {
1072     	dra->dr_cmd &= ~DR_PCYL;	/* Clear request */
1073 	rsaddr->dr_pulse = CYCL;	/* Use pulse register again */
1074     }
1075 
1076     /* Now check for deferred ACLO FCNT2 pulse request -- usually to tell
1077        the transmitter (via its attention) that we have enabled dma.
1078     */
1079     if (dra->dr_cmd & DR_DACL) {
1080     	dra->dr_cmd &= ~DR_DACL;	/* Clear request */
1081 	rsaddr->dr_pulse = FCN2;	/* Use pulse register again */
1082     }
1083 }
1084 
1085 #endif  NDR
1086