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