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