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