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