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