xref: /csrg-svn/sys/tahoe/vba/dr.c (revision 30138)
1 /*	dr.c	1.2	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_intvec = --vi->ui_hd->vh_lastiv;
76 #else
77     dr->dr_intvec = 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_intvec;	/* 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     	/* Copy back dr11 status to user */
487     	data->arg[0] = dra->dr_flags;
488     	data->arg[1] = rsaddr->dr_cstat;
489     	data->arg[2] = dra->dr_istat;	/* Status reg. at last interrupt */
490     	data->arg[3] = rsaddr->dr_data;	/* P-i/o input data */
491     	status = (ushort)((rsaddr->dr_addmod << 8) & 0xff00);
492     	data->arg[4] = status | (ushort)(rsaddr->dr_intvect & 0xff);
493     	data->arg[5] = rsaddr->dr_range;
494     	data->arg[6] = rsaddr->dr_rahi;
495     	data->arg[7] = rsaddr->dr_ralo;
496 	break;
497     case DR11LOOP:
498 	/* Perform loopback test -- MUST HAVE LOOPBACK CABLE ATTACHED --
499 	   Test results are printed on system console */
500 	if (suser())
501 		dr11loop(rsaddr,dra,unit);
502 	break;
503 
504     default:
505 	printf("\ndrioctl: Invalid ioctl cmd : %lx",cmd);
506 	return EINVAL;
507     }
508 
509 #ifdef DR_DEBUG
510     if (DR11 & 0x10)
511     	printf("**** (data[0]:%lx)",data[0]);
512 #endif
513     return 0;
514 }
515 
516 #define NPAT 2
517 #define DMATBL 20
518 ushort tstpat[DMATBL] = { 0xAAAA, 0x5555};
519 long DMAin = 0;
520 
521 dr11loop(dr,dra,unit)
522 struct rsdevice *dr;
523 struct dr_aux *dra;
524 long unit;
525 {	register long result, ix;
526 	long baddr, wait;
527 
528 	dr->dr_cstat = MCLR;		/* Clear board & device, disable intr */
529 
530 	/* Perform loopback test -- MUST HAVE LOOPBACK CABLE ATTACHED --
531 	   Test results are printed on system console */
532 	printf("\n\t ----- DR11 unit %ld loopback test -----",unit);
533 
534 	printf("\n\t Program I/O ...");
535 	for (ix=0;ix<NPAT;ix++) {
536 		dr->dr_data = tstpat[ix];	/* Write to Data out register */
537 		result = (dr->dr_data & 0xFFFF);	/* Read it back */
538 		if (result != tstpat[ix]) {
539 			printf("Failed, expected : %lx --- actual : %lx",
540 				tstpat[ix],result);
541 			return;
542 		}
543 	}
544 
545 	printf("OK\n\t Functions & Status Bits ...");
546 	dr->dr_cstat = (FCN1 | FCN3);
547 	result = dr->dr_cstat & 0xffff;		/* Read them back */
548 	if ((result & (STTC | STTA)) != (STTC |STTA)) {
549 		printf("Failed, expected : %lx --- actual : %lx, ISR:%lx",
550 			(STTA|STTC),(result & (STTA|STTC)), result);
551 		return;
552 	}
553 	dr->dr_cstat = FCN2;
554 	result = dr->dr_cstat & 0xffff;		/* Read them back */
555 	if ((result & STTB) != STTB) {
556 		printf("Failed, expected : %lx --- actual : %lx, ISR:%lx",
557 			STTB,(result & STTB), result);
558 		return;
559 	}
560 
561 	printf("OK\n\t DMA output ...");
562 
563 	if (DMAin) goto dmain;
564 
565 	/* Initialize DMA data buffer */
566 	for(ix=0;ix<DMATBL;ix++) tstpat[ix] = 0xCCCC + ix;
567 	tstpat[DMATBL-1] = 0xCCCC;	/* Last word output */
568 
569 	/* Setup normal DMA */
570 	baddr = (long)vtoph(0,tstpat);		/* Virtual --> physical */
571     	dr->dr_walo = (ushort)((baddr >> 1) & 0xffff);
572     	dr->dr_wahi = (ushort)((baddr >> 17) & 0x7fff);
573 
574     	/* Set DMA range count: (number of words - 1) */
575     	dr->dr_range = (ushort)(DMATBL - 1);
576 
577     	/* Set  address modifier code to be used for DMA access to memory */
578     	dr->dr_addmod = (char)DRADDMOD;
579 
580     	/* Clear dmaf and attf to assure a clean dma start, also disable
581 	   attention interrupt
582 	*/
583     	dr->dr_pulse = (ushort)(RDMA|RATN|RMSK);  /* Use pulse register */
584     	dr->dr_cstat = (GO|CYCL);		  /* GO...... */
585 
586 	/* Wait for DMA complete; REDY and DMAF are true in ISR */
587 	wait = 0;
588 	while ((result=(dr->dr_cstat & (REDY | DMAF))) != (REDY|DMAF)) {
589 		printf("\n\tWait for DMA complete...ISR : %lx",result);
590 		if (++wait > 5) {
591 			printf("\n\t DMA output fails...timeout!!, ISR:%lx",
592 				result);
593 			return;
594 		}
595 	}
596 
597 	result = dr->dr_data & 0xffff;		/* Read last word output */
598 	if (result != 0xCCCC) {
599 		printf("\n\t Fails, expected : %lx --- actual : %lx",
600 			0xCCCC,result);
601 		return;
602 	}
603 
604 	printf("OK\n\t DMA input ...");
605 
606 dmain:
607 	dr->dr_data = 0x1111;		/* DMA input data */
608 	/* Setup normal DMA */
609 	baddr = (long)vtoph(0,tstpat);		/* Virtual --> physical */
610     	dr->dr_walo = (ushort)((baddr >> 1) & 0xffff);
611     	dr->dr_wahi = (ushort)((baddr >> 17) & 0x7fff);
612 
613     	/* Set DMA range count: (number of words - 1) */
614     	dr->dr_range = (ushort)(DMATBL - 1);
615 
616     	/* Set  address modifier code to be used for DMA access to memory */
617     	dr->dr_addmod = (char)DRADDMOD;
618 	/* Set FCN1 in ICR to DMA in*/
619 	dr->dr_cstat = FCN1;
620 
621 	if (!(dra->dr_flags & DR_LOOPTST)) {
622 		/* Use pulse reg */
623     		dr->dr_pulse = (ushort)(RDMA|RATN|RMSK|CYCL|GO);
624 		/* Wait for DMA complete; REDY and DMAF are true in ISR */
625 		wait = 0;
626 		while ((result=(dr->dr_cstat & (REDY | DMAF)))
627 						!= (REDY|DMAF)) {
628 			printf("\n\tWait for DMA to complete...ISR:%lx",result);
629 			if (++wait > 5) {
630 				printf("\n\t DMA input timeout!!, ISR:%lx",
631 					result);
632 				return;
633 			}
634 		}
635 	}
636 	else  {
637 		/* Enable DMA e-o-r interrupt */
638     		dr->dr_pulse = (ushort)(IENB|RDMA|RATN|CYCL|GO);
639 		/* Wait for DMA complete; DR_LOOPTST is false in dra->dr_flags*/
640 		wait = 0;
641 		while (dra->dr_flags & DR_LOOPTST) {
642 			result = dr->dr_cstat & 0xffff;
643 			printf("\n\tWait for DMA e-o-r intr...ISR:%lx",result);
644 			if (++wait > 7) {
645 				printf("\n\t DMA e-o-r timeout!!, ISR:%lx",
646 					result);
647 				dra->dr_flags &= ~DR_LOOPTST;
648 				return;
649 			}
650 		}
651 		dra->dr_flags |= DR_LOOPTST;
652 	}
653 
654 	mtpr(tstpat,P1DC);			/* Purge cache */
655 	mtpr((0x3ff+(long)tstpat),P1DC);
656 	for(ix=0;ix<DMATBL;ix++) {
657 		if (tstpat[ix] != 0x1111) {
658 			printf("\n\t Fails, ix:%ld,expected : %lx --- actual : %lx",
659 				ix,0x1111,tstpat[ix]);
660 			return;
661 		}
662 	}
663 	if (!(dra->dr_flags & DR_LOOPTST)) {
664 		dra->dr_flags |= DR_LOOPTST;
665 		printf(" OK..\n\tDMA end of range interrupt...");
666 		goto dmain;
667 	}
668 
669 
670 	printf(" OK..\n\tAttention interrupt....");
671 	/* Pulse FCN2 in pulse register with IENB */
672     	dr->dr_pulse = (ushort)(IENB|RDMA);
673     	dr->dr_pulse = (ushort)FCN2;
674 
675 	/* Wait for ATTN interrupt; DR_LOOPTST is false in dra->dr_flags*/
676 	wait = 0;
677 	while (dra->dr_flags & DR_LOOPTST) {
678 		result = dr->dr_cstat & 0xffff;
679 		printf("\n\tWait for Attention intr...ISR:%lx",result);
680 		if (++wait > 7) {
681 			printf("\n\t Attention interrupt timeout!!, ISR:%lx",
682 				result);
683 			dra->dr_flags &= ~DR_LOOPTST;
684 			return;
685 		}
686 	}
687 	dra->dr_flags &= ~DR_LOOPTST;
688 	printf(" OK..\n\tDone...");
689 }
690 
691 /* Reset state on Unibus reset */
692 drreset(uban)
693 int uban;
694 {
695     register int i;
696     register struct vba_device *ui;
697     register struct dr_aux *dra;
698 
699     for (i = 0; i < NDR; i++, dra++) {
700 	if (   (ui = drinfo[i]) == 0
701 	    || !ui->ui_alive
702 	    || ui->ui_vbanum != uban
703 	   )
704 	    continue;
705 	printf("\ndrreset: %ld",i);
706 	/* Do something; reset board */
707     }
708     return;
709 }
710 
711 /*
712  * An interrupt is caused either by an error,
713  * base address overflow, or transfer complete
714  */
715 drintr (unit)
716 register long unit;
717 {
718     register struct dr_aux *dra = &dr_aux[unit];
719     register struct rsdevice *rsaddr = RSADDR(unit);
720     register struct buf *bp;
721     register short status, csrtmp;
722 
723     status = rsaddr->dr_cstat & 0xffff;		/* get board status register */
724     dra->dr_istat = status;
725 
726 #ifdef DR_DEBUG
727     if (DR11 & 2)
728     	printf("\ndrintr: dr11 status : %lx",status & 0xffff);
729 #endif
730 
731     if (dra->dr_flags & DR_LOOPTST) {
732 	/* Controller is doing loopback test */
733     	dra->dr_flags &= ~DR_LOOPTST;
734 	return;
735     }
736 
737     /* Make sure this is not a stray interrupt; at least one of dmaf or attf
738        must be set. Note that if the dr11 interrupt enable latch is reset
739        during a hardware interrupt ack sequence, and by the we get to this
740        point in the interrupt code it will be 0. This is done to give the
741        programmer some control over how the two more-or-less independent
742        interrupt sources on the board are handled.
743        If the attention flag is set when drstrategy() is called to start a
744        dma read or write an interrupt will be generated as soon as the
745        strategy routine enables interrupts for dma end-of-range. This will
746        cause execution of the interrupt routine (not necessarily bad) and
747        will cause the interrupt enable mask to be reset (very bad since the
748        dma end-of-range condition will not be able to generate an interrupt
749        when it occurs) causing the dma operation to time-out (even though
750        the dma transfer will be done successfully) or hang the process if a
751        software time-out capability is not implemented. One way to avoid
752        this situation is to check for a pending attention interrupt (attf
753        set) by calling drioctl() before doing a read or a write. For the
754        time being this driver will solve the problem by clearing the attf
755        flag in the status register before enabling interrupts in drstrategy().
756 
757        **** The IKON 10084 for which this driver is written will set both
758        attf and dmaf if dma is terminated by an attention pulse. This will
759        cause a wakeup(&dr_aux), which will be ignored since it is not being
760        waited on, and an iodone(bp) which is the desired action. Some other
761        dr11 emulators, in particular the IKON 10077 for the Multibus, donot
762        dmaf in this case. This may require some addtional code in the inter-
763        rupt routine to ensure that en iodone(bp) is issued when dma is term-
764        inated by attention.
765     */
766 
767     bp = dra->dr_actf;
768     if (!(status & (ATTF | DMAF))) {
769 	printf("\ndrintr: Stray interrupt, dr11 status : %lx",status);
770 	return;
771     }
772     if (status & DMAF) {
773 	/* End-of-range interrupt */
774 	dra->dr_flags |= DR_DMAX;
775 
776 #ifdef DR_DEBUG
777     if (DR11 & 2)
778 	printf("\ndrintr: e-o-r interrupt,cstat:%lx,dr_flags:%lx",
779 		status&0xffff,dra->dr_flags & DR_ACTV);
780 #endif
781 	if (!(dra->dr_flags & DR_ACTV)) {
782 		/* We are not doing DMA !! */
783 		bp->b_flags |= B_ERROR;
784 	}
785 	else {
786 		if (dra->dr_op == DR_READ) mtpr(bp->b_un.b_addr,P1DC);
787 		dra->dr_bycnt -= bp->b_bcount;
788 		if (dra->dr_bycnt >0) {
789 			bp->b_un.b_addr += bp->b_bcount;
790 			bp->b_bcount = (dra->dr_bycnt > NBPG) ? NBPG:
791 					dra->dr_bycnt;
792 			drstart(rsaddr,dra,bp);
793 			return;
794 		}
795 	}
796 	dra->dr_flags &= ~DR_ACTV;
797 	wakeup(dra);			/* Wakeup proc waiting in drwait() */
798 	rsaddr->dr_pulse = (RPER|RDMA|RATN);	/* reset dma e-o-r flag */
799     }
800 
801     /* Now test for attention interrupt -- It may be set in addition to
802        the dma e-o-r interrupt. If we get one we will issue a wakeup to
803        the drioctl() routine which is presumable waiting for one.
804        The program may have to monitor the attention interrupt received
805        flag in addition to doing waits for the interrupt. Futhermore,
806        interrupts are not enabled unless dma is in progress or drioctl()
807        has been called to wait for attention -- this may produce some
808        strange results if attf is set on the dr11 when a read or a write
809        is initiated, since that will enables interrupts.
810        **** The appropriate code for this interrupt routine will probably
811        be rather application dependent.
812     */
813 
814     if (status & ATTF) {
815 	dra->dr_flags |= DR_ATRX;
816 	dra->dr_flags &= ~DR_ATWT;
817 	rsaddr->dr_cstat = RATN;	/* reset attention flag */
818 	wakeup((caddr_t)&dra->dr_cmd);
819 	/* Some applications which use attention to terminate dma may also
820 	   want to issue an iodone() here to wakeup physio().
821  	*/
822     }
823     return;
824 }
825 
826 unsigned
827 drminphys(bp)
828 struct buf *bp;
829 {
830     if (bp->b_bcount > 65536)
831 	bp->b_bcount = 65536;
832 }
833 
834 /*
835  *  This routine performs the device unique operations on the DR11W
836  *  it is passed as an argument to and invoked by physio
837  */
838 drstrategy (bp)
839 register struct buf *bp;
840 {
841     register int s;
842     int unit = RSUNIT(bp->b_dev);
843     register struct rsdevice *rsaddr = RSADDR(unit);
844     register struct dr_aux *dra = &dr_aux[unit];
845     register short go = 0;
846     register long baddr, ok;
847 #ifdef DR_DEBUG
848     register char *caddr;
849     long drva();
850 #endif
851 
852 
853     if (!(dra->dr_flags & DR_OPEN)) {
854 	/* Device not open */
855 	bp->b_error = ENXIO;
856 	bp->b_flags |= B_ERROR;
857 	iodone (bp);
858 	return;
859     }
860 
861     while (dra->dr_flags & DR_ACTV) {
862 	/* Device is active; should never be in here... */
863 	sleep((caddr_t)&dra->dr_flags,DRPRI);
864     }
865 
866     dra->dr_actf = bp;
867 
868 #ifdef DR_DEBUG
869     drva(dra,bp->b_proc,bp->b_un.b_addr,bp->b_bcount);
870 #endif
871 
872     dra->dr_oba = bp->b_un.b_addr;	/* Save original addr, count */
873     dra->dr_obc = bp->b_bcount;
874     dra->dr_bycnt = bp->b_bcount;	/* Save xfer count used by drintr() */
875 
876     if ((((long)bp->b_un.b_addr & 0x3fffffff) >> PGSHIFT) !=
877 	((((long)bp->b_un.b_addr & 0x3fffffff) + bp->b_bcount) >> PGSHIFT)) {
878     	bp->b_bcount = NBPG - (((long)bp->b_un.b_addr) & PGOFSET);
879     }
880 
881     dra->dr_flags |= DR_ACTV;	/* Mark it active (use in intr handler) */
882     s = SPL_UP();
883     drstart(rsaddr,dra,bp);
884     splx(s);
885 
886     ok = drwait(rsaddr,dra);
887 #ifdef DR_DEBUG
888     if (DR11 & 0x40) {
889 	caddr = (char *)dra->dr_oba;
890     	if (dra->dr_op == DR_READ)
891 		printf("\nAfter read: (%lx)(%lx)",caddr[0]&0xff,caddr[1]&0xff);
892     }
893 #endif
894     dra->dr_flags &= ~DR_ACTV;		/* Clear active flag */
895     bp->b_un.b_addr = dra->dr_oba;	/* Restore original addr, count */
896     bp->b_bcount = dra->dr_obc;
897 
898     if (!ok) bp->b_flags |= B_ERROR;
899     iodone(bp);				/* Mark buffer B_DONE,so physstrat()
900 					   in ml/machdep.c won't sleep */
901     wakeup((caddr_t)&dra->dr_flags);
902 
903     /* Return to the calling program (physio()). Physio() will sleep
904        until awaken by a call to iodone() in the interupt handler --
905        which will be called by the dispatcher when it receives dma
906        end-of-range interrupt.
907     */
908     return;
909 }
910 
911 drwait(rs,dr)
912 register struct rsdevice *rs;
913 register struct dr_aux *dr;
914 {
915 	register long status, s;
916 
917 	s = SPL_UP();
918     	while (dr->dr_flags & DR_ACTV)
919 		sleep((caddr_t)dr,DRPRI);
920 	splx(s);
921 
922 	if (dr->dr_flags & DR_TMDM) {
923 		/* DMA timed out */
924 		dr->dr_flags &= ~DR_TMDM;
925 		return(0);
926 	}
927 	else {
928 		if (rs->dr_cstat & (PERR|BERR|TERR)) {
929 			(dr->dr_actf)->b_flags |= B_ERROR;
930 			return(0);
931 		}
932 	}
933 	dr->dr_flags &= ~DR_DMAX;
934 	return(1);
935 }
936 
937 
938 drrwtimo(tinfo)
939 register unsigned long tinfo;
940 /*
941  * 	The lower 8-bit of tinfo is the minor device number, the
942  *	remaining higher 8-bit is the current timout number
943 */
944 {	register long unit = tinfo & 0xff;
945 	register struct dr_aux *dr = &dr_aux[unit];
946 	register struct rsdevice *rs = dr->dr_addr;
947 
948 	/* If this is not the timeout that drwrite/drread is waiting
949 	   for then we should just go away */
950 	if ((tinfo & (~0xff)) != (dr->currenttimo << 8)) return;
951 
952 	/* Mark the device timed out */
953 	dr->dr_flags |= DR_TMDM;
954 	dr->dr_flags &= ~DR_ACTV;
955 	rs->dr_pulse = RMSK;			/* Inihibit interrupt */
956 	rs->dr_pulse = (RPER|RDMA|RATN|IENB);	/* Clear DMA logic */
957 
958 	/* Some applications will not issue a master after dma timeout,
959 	   since doing so sends an INIT H pulse to the external device,
960 	   which may produce undesirable side-effects.  */
961 
962 	/* Wake up process waiting in drwait() and flag the error */
963 	(dr->dr_actf)->b_flags |= B_ERROR;
964 	wakeup((caddr_t)dr->dr_cmd);
965 }
966 
967 
968 /*
969  *	Kick the driver every second
970 */
971 drtimo(dev)
972 dev_t dev;
973 {
974     	register int unit = RSUNIT(dev);
975 	register struct dr_aux *dr;
976 
977     	dr = &dr_aux[unit];
978 	if (dr->dr_flags & DR_OPEN)
979 		timeout(drtimo,(caddr_t)dev,hz);
980 	wakeup((caddr_t)dr);	/* Wakeup any process waiting for interrupt */
981 }
982 
983 
984 #ifdef DR_DEBUG
985 
986 drva(dra,p,va,bcnt)
987 struct dr_aux *dra;
988 struct proc *p;
989 char *va;
990 long bcnt;
991 {	register long first, last , np;
992 
993 	if (DR11 & 0x20)  {
994 		first = ((long)(vtoph(p,va))) >> 10;
995 		last = ((long)(vtoph(p,va+bcnt))) >> 10;
996 		np = bcnt / 0x3ff;
997 		printf("\ndrva: (op:%ld)(first:%ld)(last:%ld)(np:%ld)(cnt:%ld)",
998 			dra->dr_op,first,last,np,bcnt);
999 	}
1000 }
1001 #endif
1002 
1003 
1004 drstart(rsaddr,dra,bp)
1005 register struct rsdevice *rsaddr;
1006 register struct dr_aux *dra;
1007 register struct buf *bp;
1008 {	register long baddr;
1009 	ushort go;
1010 	register char *caddr;
1011 
1012 #ifdef DR_DEBUG
1013 	if ((dra->dr_op == DR_READ) && (DR11 & 8)) {
1014 		printf("\ndrstart: READ, bcnt:%ld",bp->b_bcount);
1015     		caddr = (char *)bp->b_un.b_addr;
1016 		printf(",(%lx)(%lx)",caddr[0]&0xff,caddr[1]&0xff);
1017 	}
1018 #endif
1019     /* we are doing raw IO, bp->b_un.b_addr is user's address */
1020     baddr = (long)vtoph(bp->b_proc,(caddr_t)bp->b_un.b_addr);
1021 
1022     /* Set DMA address into DR11 interace registers: DR11 requires that
1023        the address be right shifted 1 bit position before it is written
1024        to the board (The board will left shift it one bit position before
1025        it places the address on the bus
1026     */
1027     rsaddr->dr_walo = (ushort)((baddr >> 1) & 0xffff);
1028     rsaddr->dr_wahi = (ushort)((baddr >> 17) & 0x7fff);
1029 
1030     /* Set DMA range count: (number of words - 1) */
1031     rsaddr->dr_range = (ushort)((bp->b_bcount >> 1) - 1);
1032 
1033     /* Set address modifier code to be used for DMA access to memory */
1034     rsaddr->dr_addmod = (char)DRADDMOD;
1035 
1036     /* Now determine whether this is a read or a write. ***** This is
1037        probably only usefull for link mode operation, since dr11 doesnot
1038        controll the direction of data transfer. The C1 control input
1039        controls whether the hardware is doing a read or a write. In link
1040        mode this is controlled by function 1 latch (looped back by the
1041        cable) and could be set the program. In the general case, the dr11
1042        doesnot know in advance what the direction of transfer is - although
1043        the program and protocol logic probably is
1044     */
1045 
1046 #ifdef DR_DEBUG
1047    if (DR11 & 1)
1048     printf("\ndrstrat: about to GO..,dr_cmd:%lx,drstat:%lx,drcnt:%ld,cdata:%lx,OP:%ld",
1049 	dra->dr_cmd,rsaddr->dr_cstat,rsaddr->dr_range,rsaddr->dr_data,dra->dr_op);
1050 #endif
1051 
1052     /* Update function latches may have been done already by drioctl() if
1053        request from drioctl()
1054     */
1055     if (dra->dr_cmd & DR_DFCN) {
1056 	/* deferred function write */
1057     	dra->dr_cmd &= ~DR_DFCN;	/* Clear request */
1058 	go = dra->dr_cmd & DR_FMSK;	/* mask out fcn bits */
1059 	rsaddr->dr_cstat = go;		/* Write it to the board */
1060     }
1061 
1062     /* Clear dmaf and attf to assure a clean dma start */
1063     rsaddr->dr_pulse = (ushort)(RATN|RDMA|RPER);
1064     rsaddr->dr_cstat = (ushort)(IENB|GO|CYCL|dra->dr_op); /* GO...... */
1065 
1066     /* Now check for software cycle request -- usually by transmitter in
1067        link mode.
1068     */
1069     if (dra->dr_cmd & DR_PCYL) {
1070     	dra->dr_cmd &= ~DR_PCYL;	/* Clear request */
1071 	rsaddr->dr_pulse = CYCL;	/* Use pulse register again */
1072     }
1073 
1074     /* Now check for deferred ACLO FCNT2 pulse request -- usually to tell
1075        the transmitter (via its attention) that we have enabled dma.
1076     */
1077     if (dra->dr_cmd & DR_DACL) {
1078     	dra->dr_cmd &= ~DR_DACL;	/* Clear request */
1079 	rsaddr->dr_pulse = FCN2;	/* Use pulse register again */
1080     }
1081 }
1082 
1083 #endif  NDR
1084