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