xref: /csrg-svn/sys/tahoe/vba/dr.c (revision 35514)
134406Skarels /*
2*35514Sbostic  * Copyright (c) 1988 The Regents of the University of California.
3*35514Sbostic  * All rights reserved.
4*35514Sbostic  *
5*35514Sbostic  * This code is derived from software contributed to Berkeley by
6*35514Sbostic  * Computer Consoles Inc.
7*35514Sbostic  *
8*35514Sbostic  * Redistribution and use in source and binary forms are permitted
9*35514Sbostic  * provided that the above copyright notice and this paragraph are
10*35514Sbostic  * duplicated in all such forms and that any documentation,
11*35514Sbostic  * advertising materials, and other materials related to such
12*35514Sbostic  * distribution and use acknowledge that the software was developed
13*35514Sbostic  * by the University of California, Berkeley.  The name of the
14*35514Sbostic  * University may not be used to endorse or promote products derived
15*35514Sbostic  * from this software without specific prior written permission.
16*35514Sbostic  * THIS SOFTWARE IS PROVIDED ``AS IS'' AND WITHOUT ANY EXPRESS OR
17*35514Sbostic  * IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED
18*35514Sbostic  * WARRANTIES OF MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE.
19*35514Sbostic  *
20*35514Sbostic  *	@(#)dr.c	7.2 (Berkeley) 09/16/88
2134406Skarels  */
2229651Ssam 
2329651Ssam #include "dr.h"
2429651Ssam #if NDR > 0
2530294Ssam /*
2630294Ssam  * DRV11-W DMA interface driver.
2730294Ssam  *
2830227Ssam  * UNTESTED WITH 4.3
2929651Ssam  */
3029651Ssam #include "../machine/mtpr.h"
3129651Ssam #include "../machine/pte.h"
3229651Ssam 
3329651Ssam #include "param.h"
3429651Ssam #include "conf.h"
3529651Ssam #include "dir.h"
3629651Ssam #include "user.h"
3729651Ssam #include "proc.h"
3829651Ssam #include "map.h"
3929651Ssam #include "ioctl.h"
4029651Ssam #include "buf.h"
4129651Ssam #include "vm.h"
4229651Ssam #include "uio.h"
4330294Ssam #include "kernel.h"
4429651Ssam 
4529651Ssam #include "../tahoevba/vbavar.h"
4629651Ssam #include "../tahoevba/drreg.h"
4729651Ssam 
4829651Ssam #define YES 1
4929651Ssam #define NO  0
5029651Ssam 
5129651Ssam struct  vba_device  *drinfo[NDR];
5229651Ssam struct  dr_aux dr_aux[NDR];
5329651Ssam 
5429651Ssam unsigned drminphys();
5530294Ssam int	 drprobe(), drintr(), drattach(), drtimo(), drrwtimo();
5630294Ssam int	 drstrategy();
5730294Ssam extern	struct  vba_device  *drinfo[];
5830294Ssam static	long drstd[] = { 0 };
5929651Ssam struct  vba_driver drdriver =
6030294Ssam     { drprobe, 0, drattach, 0, drstd, "rs", drinfo };
6129651Ssam 
6229651Ssam #define RSUNIT(dev) (minor(dev) & 7)
6329651Ssam #define SPL_UP spl5
6429651Ssam 
6529651Ssam /* -------- Per-unit data -------- */
6629651Ssam 
6729651Ssam extern struct dr_aux dr_aux[];
6829651Ssam 
6929651Ssam #ifdef DR_DEBUG
7030294Ssam long	DR11 = 0;
7129651Ssam #endif
7229651Ssam 
7329651Ssam drprobe(reg, vi)
7430294Ssam 	caddr_t reg;
7530294Ssam 	struct vba_device *vi;
7629651Ssam {
7730294Ssam 	register int br, cvec;		/* must be r12, r11 */
7830294Ssam 	struct rsdevice *dr;
7929651Ssam 
8030294Ssam #ifdef lint
8130294Ssam 	br = 0; cvec = br; br = cvec;
8230294Ssam 	drintr(0);
8329651Ssam #endif
8430294Ssam 	if (badaddr(reg, 2))
8530294Ssam 		return (0);
8630294Ssam 	dr = (struct rsdevice *)reg;
8730294Ssam 	dr->dr_intvect = --vi->ui_hd->vh_lastiv;
8829651Ssam #ifdef DR_DEBUG
8930294Ssam 	printf("dprobe: Set interrupt vector %lx and init\n",dr->dr_intvec);
9029651Ssam #endif
9130294Ssam 	/* generate interrupt here for autoconfig */
9230294Ssam 	dr->dr_cstat = MCLR;		/* init board and device */
9329651Ssam #ifdef DR_DEBUG
9430294Ssam 	printf("drprobe: Initial status %lx\n", dr->dr_cstat);
9529651Ssam #endif
9630294Ssam 	br = 0x18, cvec = dr->dr_intvect;	/* XXX */
9730294Ssam 	return (sizeof (struct rsdevice));		/* DR11 exist */
9829651Ssam }
9929651Ssam 
10029651Ssam /* ARGSUSED */
10129651Ssam drattach(ui)
10230294Ssam 	struct vba_device *ui;
10329651Ssam {
10430294Ssam 	register struct dr_aux *rsd;
10529651Ssam 
10630294Ssam 	rsd = &dr_aux[ui->ui_unit];
10730294Ssam 	rsd->dr_flags = DR_PRES;		/* This dr11 is present */
10830294Ssam 	rsd->dr_addr = (struct rsdevice *)ui->ui_addr; /* Save addr of this dr11 */
10930294Ssam 	rsd->dr_istat = 0;
11030294Ssam 	rsd->dr_bycnt = 0;
11130294Ssam 	rsd->dr_cmd = 0;
11230294Ssam 	rsd->currenttimo = 0;
11329651Ssam }
11429651Ssam 
11530294Ssam /*ARGSUSED*/
11630294Ssam dropen(dev, flag)
11730294Ssam 	dev_t dev;
11830294Ssam 	int flag;
11929651Ssam {
12030294Ssam 	register int unit = RSUNIT(dev);
12130294Ssam 	register struct rsdevice *dr;
12230294Ssam 	register struct dr_aux *rsd;
12329651Ssam 
12430294Ssam 	if (drinfo[unit] == 0 || !drinfo[unit]->ui_alive)
12530294Ssam 		return (ENXIO);
12630294Ssam 	dr = RSADDR(unit);
12730294Ssam 	rsd = &dr_aux[unit];
12830294Ssam 	if (rsd->dr_flags & DR_OPEN) {
12929651Ssam #ifdef DR_DEBUG
13030294Ssam 		printf("\ndropen: dr11 unit %ld already open",unit);
13129651Ssam #endif
13230294Ssam 		return (ENXIO);	  		/* DR11 already open */
13330294Ssam 	}
13430294Ssam 	rsd->dr_flags |= DR_OPEN;	/* Mark it OPEN */
13530294Ssam 	rsd->dr_istat = 0;		/* Clear status of previous interrupt */
13630294Ssam 	rsd->rtimoticks = hz;		/* Set read no stall timout to 1 sec */
13730294Ssam 	rsd->wtimoticks = hz*60;	/* Set write no stall timout to 1 min */
13830294Ssam 	dr->dr_cstat = DR_ZERO;		/* Clear function & latches */
13930294Ssam 	dr->dr_pulse = (RDMA | RATN);	/* clear leftover attn & e-o-r flags */
14030294Ssam 	drtimo(dev);			/* start the self kicker */
14130294Ssam 	return (0);
14229651Ssam }
14329651Ssam 
14429651Ssam drclose (dev)
14530294Ssam 	dev_t dev;
14629651Ssam {
14730294Ssam 	register int unit = RSUNIT(dev);
14830294Ssam 	register struct dr_aux *dra;
14930294Ssam 	register struct rsdevice *rs;
15030294Ssam 	register short s;
15129651Ssam 
15230294Ssam 	dra = &dr_aux[unit];
15330294Ssam 	if ((dra->dr_flags & DR_OPEN) == 0) {
15429651Ssam #ifdef DR_DEBUG
15530294Ssam 		printf("\ndrclose: DR11 device %ld not open",unit);
15629651Ssam #endif
15730294Ssam 		return;
15830294Ssam 	}
15930294Ssam 	dra->dr_flags &= ~(DR_OPEN|DR_ACTV);
16030294Ssam 	rs = dra->dr_addr;
16130294Ssam 	s = SPL_UP();
16230294Ssam 	rs->dr_cstat = DR_ZERO;
16330294Ssam 	if (dra->dr_buf.b_flags & B_BUSY) {
16430294Ssam 		dra->dr_buf.b_flags &= ~B_BUSY;
16530294Ssam 		wakeup((caddr_t)&dra->dr_buf.b_flags);
16630294Ssam 	}
16730294Ssam 	splx(s);
16829651Ssam }
16929651Ssam 
17029651Ssam 
17129651Ssam /*	drread() works exactly like drwrite() except that the
17229651Ssam 	B_READ flag is used when physio() is called
17329651Ssam */
17429651Ssam drread (dev, uio)
17530294Ssam 	dev_t dev;
17630294Ssam 	struct uio *uio;
17729651Ssam {	register struct dr_aux *dra;
17829651Ssam 	register struct buf *bp;
17930294Ssam 	register int spl, err;
18030294Ssam 	register int unit = RSUNIT(dev);
18129651Ssam 
18230294Ssam 	if (uio->uio_iov->iov_len <= 0 ||	/* Negative count */
18330294Ssam 	    uio->uio_iov->iov_len & 1 ||	/* odd count */
18430294Ssam 	    (int)uio->uio_iov->iov_base & 1)	/* odd destination address */
18530294Ssam 		return (EINVAL);
18629651Ssam #ifdef DR_DEBUG
18730294Ssam 	if (DR11 & 8)
18830294Ssam 		printf("\ndrread: (len:%ld)(base:%lx)",
18930294Ssam 		    uio->uio_iov->iov_len,(int)uio->uio_iov->iov_base);
19029651Ssam #endif
19130294Ssam 	dra = &dr_aux[RSUNIT(dev)];
19230294Ssam 	dra->dr_op = DR_READ;
19330294Ssam 	bp =  &dra->dr_buf;
19430294Ssam 	bp->b_resid = 0;
19530294Ssam 	if (dra->dr_flags & DR_NORSTALL) {
19630294Ssam 		/*
19730294Ssam 		 * We are in no stall mode, start the timer,
19830294Ssam 		 * raise IPL so nothing can stop us once the
19930294Ssam 		 * timer's running
20030294Ssam 		 */
20130294Ssam 		spl = SPL_UP();
20230294Ssam 		timeout(drrwtimo, (caddr_t)((dra->currenttimo<<8) | unit),
20330294Ssam 		    (int)dra->rtimoticks);
20430294Ssam 		err = physio(drstrategy, bp, dev,B_READ, drminphys, uio);
20530294Ssam 		splx(spl);
20630294Ssam 		if (err)
20730294Ssam 			return (err);
20830294Ssam 		dra->currenttimo++;	/* Update current timeout number */
20930294Ssam 		/* Did we timeout */
21030294Ssam 		if (dra->dr_flags & DR_TMDM) {
21130294Ssam 			dra->dr_flags &= ~DR_TMDM; /* Clear timeout flag */
21230294Ssam 			u.u_error = 0;	/* Made the error ourself, ignore it */
21330294Ssam 		}
21430294Ssam 		return (err);
21529651Ssam 	}
21630294Ssam 	return (physio(drstrategy, bp, dev,B_READ, drminphys, uio));
21729651Ssam }
21829651Ssam 
21930294Ssam drwrite(dev, uio)
22030294Ssam 	dev_t dev;
22130294Ssam 	struct uio *uio;
22229651Ssam {	register struct dr_aux *dra;
22329651Ssam 	register struct buf *bp;
22430294Ssam 	register int unit = RSUNIT(dev);
22530294Ssam 	int spl, err;
22629651Ssam 
22730294Ssam 	if (uio->uio_iov->iov_len <= 0 || uio->uio_iov->iov_len & 1 ||
22830294Ssam 	    (int)uio->uio_iov->iov_base & 1)
22930294Ssam 		return (EINVAL);
23029651Ssam #ifdef DR_DEBUG
23130294Ssam 	if (DR11 & 4)
23230294Ssam 		printf("\ndrwrite: (len:%ld)(base:%lx)",
23330294Ssam 		    uio->uio_iov->iov_len,(int)uio->uio_iov->iov_base);
23429651Ssam #endif
23530294Ssam 	dra = &dr_aux[RSUNIT(dev)];
23630294Ssam 	dra->dr_op = DR_WRITE;
23730294Ssam 	bp =  &dra->dr_buf;
23830294Ssam 	bp->b_resid = 0;
23930294Ssam 	if (dra->dr_flags & DR_NOWSTALL) {
24030294Ssam 		/*
24130294Ssam 		 * We are in no stall mode, start the timer,
24230294Ssam 		 * raise IPL so nothing can stop us once the
24330294Ssam 		 * timer's running
24430294Ssam 		 */
24530294Ssam 		spl = SPL_UP();
24630294Ssam 		timeout(drrwtimo,(caddr_t)((dra->currenttimo<<8) | unit),
24730294Ssam 		    (int)dra->wtimoticks);
24830294Ssam 		err = physio (drstrategy, bp, dev,B_WRITE, drminphys, uio);
24930294Ssam 		splx(spl);
25030294Ssam 		if (err)
25130294Ssam 			return (err);
25230294Ssam 		dra->currenttimo++;	/* Update current timeout number */
25330294Ssam 		/* Did we timeout */
25430294Ssam 		if (dra->dr_flags & DR_TMDM) {
25530294Ssam 			dra->dr_flags &= ~DR_TMDM;	/* Clear timeout flag */
25630294Ssam 			u.u_error = 0;	/* Made the error ourself, ignore it */
25730294Ssam 		}
25830294Ssam 		return (err);
25929651Ssam 	}
26030294Ssam 	return (physio(drstrategy, bp, dev,B_WRITE, drminphys, uio));
26129651Ssam }
26229651Ssam 
26330294Ssam /*
26430294Ssam  * Routine used by calling program to issue commands to dr11 driver and
26530294Ssam  * through it to the device.
26630294Ssam  * It is also used to read status from the device and driver and to wait
26730294Ssam  * for attention interrupts.
26830294Ssam  * Status is returned in an 8 elements unsigned short integer array, the
26930294Ssam  * first two elements of the array are also used to pass arguments to
27030294Ssam  * drioctl() if required.
27130294Ssam  * The function bits to be written to the dr11 are included in the cmd
27230294Ssam  * argument. Even if they are not being written to the dr11 in a particular
27330294Ssam  * drioctl() call, they will update the copy of cmd that is stored in the
27430294Ssam  * driver. When drstrategy() is called, this updated copy is used if a
27530294Ssam  * deferred function bit write has been specified. The "side effect" of
27630294Ssam  * calls to the drioctl() requires that the last call prior to a read or
27730294Ssam  * write has an appropriate copy of the function bits in cmd if they are
27830294Ssam  * to be used in drstrategy().
27930294Ssam  * When used as command value, the contents of data[0] is the command
28030294Ssam  * parameter.
28130294Ssam  */
28230294Ssam drioctl(dev, cmd, data)
28330294Ssam 	dev_t dev;
28430294Ssam 	int cmd;
28530294Ssam 	long *data;
28629651Ssam {
28730294Ssam 	register int unit = RSUNIT(dev);
28830294Ssam 	register struct dr_aux *dra;
28930294Ssam 	register struct rsdevice *rsaddr = RSADDR(unit);
29030294Ssam 	int s;
29130294Ssam 	u_short status;
29230294Ssam 	long temp;
29329651Ssam 
29429651Ssam #ifdef DR_DEBUG
29530294Ssam 	if (DR11 & 0x10)
29630294Ssam 		printf("\ndrioctl: (dev:%lx)(cmd:%lx)(data:%lx)(data[0]:%lx)",
29730294Ssam 		    dev,cmd,data,data[0]);
29829651Ssam #endif
29930294Ssam 	dra = &dr_aux[unit];
30030294Ssam 	dra->dr_cmd = 0;	/* Fresh copy; clear all previous flags */
30130294Ssam 	switch (cmd) {
30229651Ssam 
30330294Ssam 	case DRWAIT:		/* Wait for attention interrupt */
30429651Ssam #ifdef DR_DEBUG
30530294Ssam 		printf("\ndrioctl: wait for attention interrupt");
30629651Ssam #endif
30730294Ssam 		s = SPL_UP();
30830294Ssam 		/*
30930294Ssam 		 * If the attention flag in dr_flags is set, it probably
31030294Ssam 		 * means that an attention has arrived by the time a
31130294Ssam 		 * previous DMA end-of-range interrupt was serviced. If
31230294Ssam 		 * ATRX is set, we will return with out sleeping, since
31330294Ssam 		 * we have received an attention since the last call to
31430294Ssam 		 * wait on attention.  This may not be appropriate for
31530294Ssam 		 * some applications.
31630294Ssam 		 */
31730294Ssam 		if ((dra->dr_flags & DR_ATRX) == 0) {
31830294Ssam 			dra->dr_flags |= DR_ATWT;	/* Set waiting flag */
31930294Ssam 			/*
32030294Ssam 			 * Enable interrupt; use pulse reg.
32130294Ssam 			 * so function bits are not changed
32230294Ssam 			 */
32330294Ssam 			rsaddr->dr_pulse = IENB;
32430294Ssam 			sleep((caddr_t)&dra->dr_cmd, DRPRI);
32530294Ssam 		}
32630294Ssam 		splx(s);
32730294Ssam 		break;
32829651Ssam 
32930294Ssam 	case DRPIOW:			/* Write to p-i/o register */
33030294Ssam 		rsaddr->dr_data = data[0];
33130294Ssam 		break;
33229651Ssam 
33330294Ssam 	case DRPACL:			/* Send pulse to device */
33430294Ssam 		rsaddr->dr_pulse = FCN2;
33530294Ssam 		break;
33629651Ssam 
33730294Ssam 	case DRDACL:			/* Defer alco pulse until go */
33830294Ssam 		dra->dr_cmd |= DR_DACL;
33930294Ssam 		break;
34029651Ssam 
34130294Ssam 	case DRPCYL:			/* Set cycle with next go */
34230294Ssam 		dra->dr_cmd |= DR_PCYL;
34330294Ssam 		break;
34429651Ssam 
34530294Ssam 	case DRDFCN:			/* Update function with next go */
34630294Ssam 		dra->dr_cmd |= DR_DFCN;
34730294Ssam 		break;
34829651Ssam 
34930294Ssam 	case DRRATN:			/* Reset attention flag */
35030294Ssam 		rsaddr->dr_pulse = RATN;
35130294Ssam 		break;
35229651Ssam 
35330294Ssam 	case DRRDMA:			/* Reset DMA e-o-r flag */
35430294Ssam 		rsaddr->dr_pulse = RDMA;
35530294Ssam 		break;
35629651Ssam 
35730294Ssam 	case DRSFCN:			/* Set function bits */
35830294Ssam 		temp = data[0] & DR_FMSK;
35930294Ssam 		/*
36030294Ssam 		 * This has a very important side effect -- It clears
36130294Ssam 		 * the interrupt enable flag. That is fine for this driver,
36230294Ssam 		 * but if it is desired to leave interrupt enable at all
36330294Ssam 		 * times, it will be necessary to read the status register
36430294Ssam 		 * first to get IENB, or carry a software flag that indicates
36530294Ssam 		 * whether interrupts are set, and or this into the control
36630294Ssam 		 * register value being written.
36730294Ssam 		 */
36830294Ssam 		rsaddr->dr_cstat = temp;
36930294Ssam 		break;
37029651Ssam 
37130294Ssam 	case DRRPER:			/* Clear parity flag */
37230294Ssam 		rsaddr->dr_pulse = RPER;
37330294Ssam 		break;
37429651Ssam 
37530294Ssam 	case DRSETRSTALL:		/* Set read stall mode. */
37630294Ssam 		dra->dr_flags &= (~DR_NORSTALL);
37730294Ssam 		break;
37829651Ssam 
37930294Ssam 	case DRSETNORSTALL:		/* Set no stall read  mode. */
38030294Ssam 		dra->dr_flags |= DR_NORSTALL;
38130294Ssam 		break;
38229651Ssam 
38330294Ssam 	case DRGETRSTALL:		/* Returns true if in read stall mode */
38430294Ssam 		data[0]  = (dra->dr_flags & DR_NORSTALL)? 0 : 1;
38530294Ssam 		break;
38629651Ssam 
38730294Ssam 	case DRSETRTIMEOUT:		/* Set read stall timeout (1/10 secs) */
38830294Ssam 		if (data[0] < 1) {
38930294Ssam 			u.u_error = EINVAL;
39030294Ssam 			temp = 1;
39130294Ssam 		}
39230294Ssam 		dra->rtimoticks = (data[0] * hz )/10;
39330294Ssam 		break;
39429651Ssam 
39530294Ssam 	case DRGETRTIMEOUT:		/* Return read stall timeout */
39630294Ssam 		data[0] = ((dra->rtimoticks)*10)/hz;
39730294Ssam 		break;
39829651Ssam 
39930294Ssam 	case DRSETWSTALL:		/* Set write stall mode. */
40030294Ssam 		dra->dr_flags &= (~DR_NOWSTALL);
40130294Ssam 		break;
40229651Ssam 
40330294Ssam 	case DRSETNOWSTALL:		/* Set write stall mode. */
40430294Ssam 		dra->dr_flags |= DR_NOWSTALL;
40530294Ssam 		break;
40629651Ssam 
40730294Ssam 	case DRGETWSTALL:		/* Return true if in write stall mode */
40830294Ssam 		data[0] = (dra->dr_flags & DR_NOWSTALL)? 0 : 1;
40930294Ssam 		break;
41029651Ssam 
41130294Ssam 	case DRSETWTIMEOUT:		/* Set write stall timeout (1/10's) */
41230294Ssam 		if (data[0] < 1) {
41330294Ssam 			u.u_error = EINVAL;
41430294Ssam 			temp = 1;
41530294Ssam 		}
41630294Ssam 		dra->wtimoticks = (data[0] * hz )/10;
41730294Ssam 		break;
41829651Ssam 
41930294Ssam 	case DRGETWTIMEOUT:		/* Return write stall timeout */
42030294Ssam 		data[0] = ((dra->wtimoticks)*10)/hz;
42130294Ssam 		break;
42229651Ssam 
42330294Ssam 	case DRWRITEREADY:		/* Return true if can write data */
42430294Ssam 		data[0] = (rsaddr->dr_cstat & STTA)? 1 : 0;
42530294Ssam 		break;
42629651Ssam 
42730294Ssam 	case DRREADREADY:		/* Return true if data to be read */
42830294Ssam 		data[0] = (rsaddr->dr_cstat & STTB)? 1 : 0;
42930294Ssam 		break;
43029651Ssam 
43130294Ssam 	case DRBUSY:			/* Return true if device busy */
43230294Ssam 		/*
43330294Ssam 		 * Internally this is the DR11-W
43430294Ssam 		 * STAT C bit, but there is a bug in the Omega 500/FIFO
43530294Ssam 		 * interface board that it cannot drive this signal low
43630294Ssam 		 * for certain DR11-W ctlr such as the Ikon. We use the
43730294Ssam 		 * REDY signal of the CSR on the Ikon DR11-W instead.
43830294Ssam 		 */
43930294Ssam #ifdef notdef
44030294Ssam 		data[0] = (rsaddr->dr_cstat & STTC)? 1 : 0;
44130294Ssam #else
44230294Ssam 		data[0] = ((rsaddr->dr_cstat & REDY)? 0 : 1);
44330294Ssam #endif
44430294Ssam 		break;
44529651Ssam 
44630294Ssam 	case DRRESET:			/* Reset device */
44730294Ssam 		/* Reset DMA ATN RPER flag */
44830294Ssam 		rsaddr->dr_pulse = (MCLR|RDMA|RATN|RPER);
44930294Ssam 		DELAY(0x1f000);
45030294Ssam 		while ((rsaddr->dr_cstat & REDY) == 0)
45130294Ssam 			sleep((caddr_t)dra, DRPRI);	/* Wakeup by drtimo() */
45230294Ssam 		dra->dr_istat = 0;
45330294Ssam 		dra->dr_cmd = 0;
45430294Ssam 		dra->currenttimo = 0;
45530294Ssam 		break;
45629651Ssam 
45730294Ssam 	case DR11STAT: {		/* Copy back dr11 status to user */
45830294Ssam 		register struct dr11io *dr = (struct dr11io *)data;
45930294Ssam 		dr->arg[0] = dra->dr_flags;
46030294Ssam 		dr->arg[1] = rsaddr->dr_cstat;
46130294Ssam 		dr->arg[2] = dra->dr_istat;	/* Status at last interrupt */
46230294Ssam 		dr->arg[3] = rsaddr->dr_data;	/* P-i/o input data */
46330294Ssam 		status = (u_short)((rsaddr->dr_addmod << 8) & 0xff00);
46430294Ssam 		dr->arg[4] = status | (u_short)(rsaddr->dr_intvect & 0xff);
46530294Ssam 		dr->arg[5] = rsaddr->dr_range;
46630294Ssam 		dr->arg[6] = rsaddr->dr_rahi;
46730294Ssam 		dr->arg[7] = rsaddr->dr_ralo;
46830294Ssam 		break;
46930294Ssam 	}
47030294Ssam 	case DR11LOOP:			/* Perform loopback test */
47130294Ssam 		/*
47230294Ssam 		 * NB: MUST HAVE LOOPBACK CABLE ATTACHED --
47330294Ssam 		 * Test results are printed on system console
47430294Ssam 		 */
47530294Ssam 		if (suser())
47630294Ssam 			dr11loop(rsaddr, dra, unit);
47730294Ssam 		break;
47829651Ssam 
47930294Ssam 	default:
48030294Ssam 		return (EINVAL);
48129651Ssam 	}
48229651Ssam #ifdef DR_DEBUG
48330294Ssam 	if (DR11 & 0x10)
48430294Ssam 		printf("**** (data[0]:%lx)",data[0]);
48529651Ssam #endif
48630294Ssam 	return (0);
48729651Ssam }
48829651Ssam 
48930294Ssam #define NPAT	2
49030294Ssam #define DMATBL	20
49130294Ssam u_short	tstpat[DMATBL] = { 0xAAAA, 0x5555};
49230294Ssam long	DMAin = 0;
49330138Ssam 
49430294Ssam /*
49530294Ssam  * Perform loopback test -- MUST HAVE LOOPBACK CABLE ATTACHED
49630294Ssam  * Test results are printed on system console
49730294Ssam  */
49830294Ssam dr11loop(dr, dra, unit)
49930294Ssam 	struct rsdevice *dr;
50030294Ssam 	struct dr_aux *dra;
50130294Ssam 	int unit;
50230294Ssam {
50330294Ssam 	register long result, ix;
50430294Ssam 	long addr, wait;
50530138Ssam 
50630138Ssam 	dr->dr_cstat = MCLR;		/* Clear board & device, disable intr */
50730294Ssam 	printf("\n\t ----- DR11 unit %ld loopback test -----", unit);
50830138Ssam 	printf("\n\t Program I/O ...");
50930138Ssam 	for (ix=0;ix<NPAT;ix++) {
51030138Ssam 		dr->dr_data = tstpat[ix];	/* Write to Data out register */
51130294Ssam 		result = dr->dr_data & 0xFFFF;	/* Read it back */
51230138Ssam 		if (result != tstpat[ix]) {
51330138Ssam 			printf("Failed, expected : %lx --- actual : %lx",
51430294Ssam 				tstpat[ix], result);
51530138Ssam 			return;
51630138Ssam 		}
51730138Ssam 	}
51830138Ssam 	printf("OK\n\t Functions & Status Bits ...");
51930138Ssam 	dr->dr_cstat = (FCN1 | FCN3);
52030138Ssam 	result = dr->dr_cstat & 0xffff;		/* Read them back */
52130138Ssam 	if ((result & (STTC | STTA)) != (STTC |STTA)) {
52230138Ssam 		printf("Failed, expected : %lx --- actual : %lx, ISR:%lx",
52330294Ssam 			(STTA|STTC), (result & (STTA|STTC)), result);
52430138Ssam 		return;
52530138Ssam 	}
52630138Ssam 	dr->dr_cstat = FCN2;
52730138Ssam 	result = dr->dr_cstat & 0xffff;		/* Read them back */
52830138Ssam 	if ((result & STTB) != STTB) {
52930138Ssam 		printf("Failed, expected : %lx --- actual : %lx, ISR:%lx",
53030294Ssam 			STTB, (result & STTB), result);
53130138Ssam 		return;
53230138Ssam 	}
53330138Ssam 	printf("OK\n\t DMA output ...");
53430294Ssam 	if (DMAin)
53530294Ssam 		goto dmain;
53630138Ssam 	/* Initialize DMA data buffer */
53730294Ssam 	for (ix=0; ix<DMATBL; ix++)
53830294Ssam 		tstpat[ix] = 0xCCCC + ix;
53930138Ssam 	tstpat[DMATBL-1] = 0xCCCC;	/* Last word output */
54030138Ssam 	/* Setup normal DMA */
54130294Ssam 	addr = (long)vtoph((struct proc *)0, (unsigned)tstpat);
54230294Ssam 	dr->dr_walo = (addr >> 1) & 0xffff;
54330294Ssam 	dr->dr_wahi = (addr >> 17) & 0x7fff;
54430294Ssam 	/* Set DMA range count: (number of words - 1) */
54530294Ssam 	dr->dr_range = DMATBL - 1;
54630294Ssam 	/* Set address modifier code to be used for DMA access to memory */
54730294Ssam 	dr->dr_addmod = DRADDMOD;
54830138Ssam 
54930294Ssam 	/*
55030294Ssam 	 * Clear dmaf and attf to assure a clean dma start, also disable
55130294Ssam 	 * attention interrupt
55230294Ssam 	 */
55330294Ssam 	dr->dr_pulse = RDMA|RATN|RMSK;  /* Use pulse register */
55430294Ssam 	dr->dr_cstat = GO|CYCL;		  /* GO...... */
55530138Ssam 
55630138Ssam 	/* Wait for DMA complete; REDY and DMAF are true in ISR */
55730138Ssam 	wait = 0;
55830294Ssam 	while ((result=(dr->dr_cstat & (REDY|DMAF))) != (REDY|DMAF)) {
55930294Ssam 		printf("\n\tWait for DMA complete...ISR : %lx", result);
56030138Ssam 		if (++wait > 5) {
56130138Ssam 			printf("\n\t DMA output fails...timeout!!, ISR:%lx",
56230138Ssam 				result);
56330138Ssam 			return;
56430138Ssam 		}
56530138Ssam 	}
56630138Ssam 	result = dr->dr_data & 0xffff;		/* Read last word output */
56730138Ssam 	if (result != 0xCCCC) {
56830138Ssam 		printf("\n\t Fails, expected : %lx --- actual : %lx",
56930294Ssam 			0xCCCC, result);
57030138Ssam 		return;
57130138Ssam 	}
57230138Ssam 	printf("OK\n\t DMA input ...");
57330138Ssam dmain:
57430138Ssam 	dr->dr_data = 0x1111;		/* DMA input data */
57530138Ssam 	/* Setup normal DMA */
57630294Ssam 	addr = (long)vtoph((struct proc *)0, (unsigned)tstpat);
57730294Ssam 	dr->dr_walo = (addr >> 1) & 0xffff;
57830294Ssam 	dr->dr_wahi = (addr >> 17) & 0x7fff;
57930294Ssam 	dr->dr_range = DMATBL - 1;
58030294Ssam 	dr->dr_addmod = (char)DRADDMOD;
58130294Ssam 	dr->dr_cstat = FCN1;		/* Set FCN1 in ICR to DMA in*/
58230294Ssam 	if ((dra->dr_flags & DR_LOOPTST) == 0) {
58330138Ssam 		/* Use pulse reg */
58430294Ssam 		dr->dr_pulse = RDMA|RATN|RMSK|CYCL|GO;
58530138Ssam 		/* Wait for DMA complete; REDY and DMAF are true in ISR */
58630138Ssam 		wait = 0;
58730294Ssam 		while ((result=(dr->dr_cstat & (REDY|DMAF))) != (REDY|DMAF)) {
58830138Ssam 			printf("\n\tWait for DMA to complete...ISR:%lx",result);
58930138Ssam 			if (++wait > 5) {
59030138Ssam 				printf("\n\t DMA input timeout!!, ISR:%lx",
59130138Ssam 					result);
59230138Ssam 				return;
59330138Ssam 			}
59430138Ssam 		}
59530294Ssam 	} else  {
59630138Ssam 		/* Enable DMA e-o-r interrupt */
59730294Ssam 		dr->dr_pulse = IENB|RDMA|RATN|CYCL|GO;
59830138Ssam 		/* Wait for DMA complete; DR_LOOPTST is false in dra->dr_flags*/
59930138Ssam 		wait = 0;
60030138Ssam 		while (dra->dr_flags & DR_LOOPTST) {
60130138Ssam 			result = dr->dr_cstat & 0xffff;
60230294Ssam 			printf("\n\tWait for DMA e-o-r intr...ISR:%lx", result);
60330138Ssam 			if (++wait > 7) {
60430138Ssam 				printf("\n\t DMA e-o-r timeout!!, ISR:%lx",
60530138Ssam 					result);
60630138Ssam 				dra->dr_flags &= ~DR_LOOPTST;
60730138Ssam 				return;
60830138Ssam 			}
60930138Ssam 		}
61030138Ssam 		dra->dr_flags |= DR_LOOPTST;
61130138Ssam 	}
61230294Ssam 	mtpr(P1DC, tstpat);			/* Purge cache */
61330294Ssam 	mtpr(P1DC, 0x3ff+tstpat);
61430294Ssam 	for (ix=0; ix<DMATBL; ix++) {
61530138Ssam 		if (tstpat[ix] != 0x1111) {
61630294Ssam 			printf("\n\t Fails, ix:%d, expected:%x --- actual:%x",
61730294Ssam 				ix, 0x1111, tstpat[ix]);
61830138Ssam 			return;
61930138Ssam 		}
62030138Ssam 	}
62130294Ssam 	if ((dra->dr_flags & DR_LOOPTST) == 0) {
62230138Ssam 		dra->dr_flags |= DR_LOOPTST;
62330138Ssam 		printf(" OK..\n\tDMA end of range interrupt...");
62430138Ssam 		goto dmain;
62530138Ssam 	}
62630138Ssam 	printf(" OK..\n\tAttention interrupt....");
62730294Ssam 	dr->dr_pulse = IENB|RDMA;
62830294Ssam 	dr->dr_pulse = FCN2;
62930138Ssam 	/* Wait for ATTN interrupt; DR_LOOPTST is false in dra->dr_flags*/
63030138Ssam 	wait = 0;
63130138Ssam 	while (dra->dr_flags & DR_LOOPTST) {
63230138Ssam 		result = dr->dr_cstat & 0xffff;
63330138Ssam 		printf("\n\tWait for Attention intr...ISR:%lx",result);
63430138Ssam 		if (++wait > 7) {
63530138Ssam 			printf("\n\t Attention interrupt timeout!!, ISR:%lx",
63630138Ssam 				result);
63730138Ssam 			dra->dr_flags &= ~DR_LOOPTST;
63830138Ssam 			return;
63930138Ssam 		}
64030138Ssam 	}
64130138Ssam 	dra->dr_flags &= ~DR_LOOPTST;
64230138Ssam 	printf(" OK..\n\tDone...");
64330138Ssam }
64430138Ssam 
64529651Ssam /* Reset state on Unibus reset */
64630294Ssam /*ARGSUSED*/
64729651Ssam drreset(uban)
64830294Ssam 	int uban;
64929651Ssam {
65029651Ssam 
65129651Ssam }
65229651Ssam 
65329651Ssam /*
65429651Ssam  * An interrupt is caused either by an error,
65529651Ssam  * base address overflow, or transfer complete
65629651Ssam  */
65730294Ssam drintr(dr11)
65830294Ssam 	int dr11;
65929651Ssam {
66030294Ssam 	register struct dr_aux *dra = &dr_aux[dr11];
66130294Ssam 	register struct rsdevice *rsaddr = RSADDR(dr11);
66230294Ssam 	register struct buf *bp;
66330294Ssam 	register short status;
66429651Ssam 
66530294Ssam 	status = rsaddr->dr_cstat & 0xffff;	/* get board status register */
66630294Ssam 	dra->dr_istat = status;
66729651Ssam #ifdef DR_DEBUG
66830294Ssam 	if (DR11 & 2)
66930294Ssam 		printf("\ndrintr: dr11 status : %lx",status & 0xffff);
67029651Ssam #endif
67130294Ssam 	if (dra->dr_flags & DR_LOOPTST) {	/* doing loopback test */
67230294Ssam 		dra->dr_flags &= ~DR_LOOPTST;
67330294Ssam 		return;
67430294Ssam 	}
67530294Ssam 	/*
67630294Ssam 	 * Make sure this is not a stray interrupt; at least one of dmaf or attf
67730294Ssam 	 * must be set. Note that if the dr11 interrupt enable latch is reset
67830294Ssam 	 * during a hardware interrupt ack sequence, and by the we get to this
67930294Ssam 	 * point in the interrupt code it will be 0. This is done to give the
68030294Ssam 	 * programmer some control over how the two more-or-less independent
68130294Ssam 	 * interrupt sources on the board are handled.
68230294Ssam 	 * If the attention flag is set when drstrategy() is called to start a
68330294Ssam 	 * dma read or write an interrupt will be generated as soon as the
68430294Ssam 	 * strategy routine enables interrupts for dma end-of-range. This will
68530294Ssam 	 * cause execution of the interrupt routine (not necessarily bad) and
68630294Ssam 	 * will cause the interrupt enable mask to be reset (very bad since the
68730294Ssam 	 * dma end-of-range condition will not be able to generate an interrupt
68830294Ssam 	 * when it occurs) causing the dma operation to time-out (even though
68930294Ssam 	 * the dma transfer will be done successfully) or hang the process if a
69030294Ssam 	 * software time-out capability is not implemented. One way to avoid
69130294Ssam 	 * this situation is to check for a pending attention interrupt (attf
69230294Ssam 	 * set) by calling drioctl() before doing a read or a write. For the
69330294Ssam 	 * time being this driver will solve the problem by clearing the attf
69430294Ssam 	 * flag in the status register before enabling interrupts in
69530294Ssam 	 * drstrategy().
69630294Ssam 	 *
69730294Ssam 	 * **** The IKON 10084 for which this driver is written will set both
69830294Ssam 	 * attf and dmaf if dma is terminated by an attention pulse. This will
69930294Ssam 	 * cause a wakeup(&dr_aux), which will be ignored since it is not being
70030294Ssam 	 * waited on, and an iodone(bp) which is the desired action. Some other
70130294Ssam 	 * dr11 emulators, in particular the IKON 10077 for the Multibus, donot
70230294Ssam 	 * dmaf in this case. This may require some addtional code in the inter-
70330294Ssam 	 * rupt routine to ensure that en iodone(bp) is issued when dma is term-
70430294Ssam 	 * inated by attention.
70530294Ssam 	 */
70630294Ssam 	bp = dra->dr_actf;
70730294Ssam 	if ((status & (ATTF | DMAF)) == 0) {
70830294Ssam 		printf("dr%d: stray interrupt, status=%x", dr11, status);
70930294Ssam 		return;
71030294Ssam 	}
71130294Ssam 	if (status & DMAF) {		/* End-of-range interrupt */
71230294Ssam 		dra->dr_flags |= DR_DMAX;
71329651Ssam 
71429651Ssam #ifdef DR_DEBUG
71530294Ssam 		if (DR11 & 2)
71630294Ssam 		printf("\ndrintr: e-o-r interrupt,cstat:%lx,dr_flags:%lx",
71730294Ssam 			status&0xffff, dra->dr_flags & DR_ACTV);
71829651Ssam #endif
71930294Ssam 		if ((dra->dr_flags & DR_ACTV) == 0) {
72030294Ssam 			/* We are not doing DMA !! */
72130294Ssam 			bp->b_flags |= B_ERROR;
72230294Ssam 		} else {
72330294Ssam 			if (dra->dr_op == DR_READ)
72430294Ssam 				mtpr(P1DC, bp->b_un.b_addr);
72530294Ssam 			dra->dr_bycnt -= bp->b_bcount;
72630294Ssam 			if (dra->dr_bycnt >0) {
72730294Ssam 				bp->b_un.b_addr += bp->b_bcount;
72830294Ssam 				bp->b_bcount = (dra->dr_bycnt > NBPG) ? NBPG:
72929651Ssam 					dra->dr_bycnt;
73030294Ssam 				drstart(rsaddr, dra, bp);
73130294Ssam 				return;
73230294Ssam 			}
73329651Ssam 		}
73430294Ssam 		dra->dr_flags &= ~DR_ACTV;
73530294Ssam 		wakeup((caddr_t)dra);		/* Wakeup waiting in drwait() */
73630294Ssam 		rsaddr->dr_pulse = (RPER|RDMA|RATN); /* reset dma e-o-r flag */
73729651Ssam 	}
73830294Ssam 	/*
73930294Ssam 	 * Now test for attention interrupt -- It may be set in addition to
74030294Ssam 	 * the dma e-o-r interrupt. If we get one we will issue a wakeup to
74130294Ssam 	 * the drioctl() routine which is presumable waiting for one.
74230294Ssam 	 * The program may have to monitor the attention interrupt received
74330294Ssam 	 * flag in addition to doing waits for the interrupt. Futhermore,
74430294Ssam 	 * interrupts are not enabled unless dma is in progress or drioctl()
74530294Ssam 	 * has been called to wait for attention -- this may produce some
74630294Ssam 	 * strange results if attf is set on the dr11 when a read or a write
74730294Ssam 	 * is initiated, since that will enables interrupts.
74830294Ssam 	 * **** The appropriate code for this interrupt routine will probably
74930294Ssam 	 * be rather application dependent.
75030294Ssam 	 */
75130294Ssam 	if (status & ATTF) {
75230294Ssam 		dra->dr_flags |= DR_ATRX;
75330294Ssam 		dra->dr_flags &= ~DR_ATWT;
75430294Ssam 		rsaddr->dr_cstat = RATN;	/* reset attention flag */
75530294Ssam 		/*
75630294Ssam 		 * Some applications which use attention to terminate
75730294Ssam 		 * dma may also want to issue an iodone() here to
75830294Ssam 		 * wakeup physio().
75930294Ssam 		 */
76030294Ssam 		wakeup((caddr_t)&dra->dr_cmd);
76130294Ssam 	}
76229651Ssam }
76329651Ssam 
76429651Ssam unsigned
76529651Ssam drminphys(bp)
76630294Ssam 	struct buf *bp;
76729651Ssam {
76830294Ssam 
76930294Ssam 	if (bp->b_bcount > 65536)
77030294Ssam 		bp->b_bcount = 65536;
77129651Ssam }
77229651Ssam 
77329651Ssam /*
77430294Ssam  * This routine performs the device unique operations on the DR11W
77530294Ssam  * it is passed as an argument to and invoked by physio
77629651Ssam  */
77729651Ssam drstrategy (bp)
77830294Ssam 	register struct buf *bp;
77929651Ssam {
78030294Ssam 	register int s;
78130294Ssam 	int unit = RSUNIT(bp->b_dev);
78230294Ssam 	register struct rsdevice *rsaddr = RSADDR(unit);
78330294Ssam 	register struct dr_aux *dra = &dr_aux[unit];
78430294Ssam 	register int ok;
78529651Ssam #ifdef DR_DEBUG
78630294Ssam 	register char *caddr;
78730294Ssam 	long drva();
78829651Ssam #endif
78929651Ssam 
79030294Ssam 	if ((dra->dr_flags & DR_OPEN) == 0) {	/* Device not open */
79130294Ssam 		bp->b_error = ENXIO;
79230294Ssam 		bp->b_flags |= B_ERROR;
79330294Ssam 		iodone (bp);
79430294Ssam 		return;
79530294Ssam 	}
79630294Ssam 	while (dra->dr_flags & DR_ACTV)
79730294Ssam 		/* Device is active; should never be in here... */
79830294Ssam 		sleep((caddr_t)&dra->dr_flags,DRPRI);
79930294Ssam 	dra->dr_actf = bp;
80029651Ssam #ifdef DR_DEBUG
80130294Ssam 	drva(dra, bp->b_proc, bp->b_un.b_addr, bp->b_bcount);
80229651Ssam #endif
80330294Ssam 	dra->dr_oba = bp->b_un.b_addr;	/* Save original addr, count */
80430294Ssam 	dra->dr_obc = bp->b_bcount;
80530294Ssam 	dra->dr_bycnt = bp->b_bcount;	/* Save xfer count used by drintr() */
80630294Ssam 	if ((((long)bp->b_un.b_addr & 0x3fffffff) >> PGSHIFT) !=
80730294Ssam 	    ((((long)bp->b_un.b_addr & 0x3fffffff) + bp->b_bcount) >> PGSHIFT))
80830294Ssam 		bp->b_bcount = NBPG - (((long)bp->b_un.b_addr) & PGOFSET);
80930294Ssam 	dra->dr_flags |= DR_ACTV;	/* Mark active (use in intr handler) */
81030294Ssam 	s = SPL_UP();
81130294Ssam 	drstart(rsaddr,dra,bp);
81230294Ssam 	splx(s);
81330294Ssam 	ok = drwait(rsaddr,dra);
81429651Ssam #ifdef DR_DEBUG
81530294Ssam 	if (DR11 & 0x40) {
81630294Ssam 		caddr = (char *)dra->dr_oba;
81730294Ssam 		if (dra->dr_op == DR_READ)
81830294Ssam 			printf("\nAfter read: (%lx)(%lx)",
81930294Ssam 			    caddr[0]&0xff, caddr[1]&0xff);
82030294Ssam 	}
82129651Ssam #endif
82230294Ssam 	dra->dr_flags &= ~DR_ACTV;		/* Clear active flag */
82330294Ssam 	bp->b_un.b_addr = dra->dr_oba;	/* Restore original addr, count */
82430294Ssam 	bp->b_bcount = dra->dr_obc;
82530294Ssam 	if (!ok)
82630294Ssam 		bp->b_flags |= B_ERROR;
82730294Ssam 	/* Mark buffer B_DONE,so physstrat() in ml/machdep.c won't sleep */
82830294Ssam 	iodone(bp);
82930294Ssam 	wakeup((caddr_t)&dra->dr_flags);
83030294Ssam 	/*
83130294Ssam 	 * Return to the calling program (physio()). Physio() will sleep
83230294Ssam 	 * until awaken by a call to iodone() in the interupt handler --
83330294Ssam 	 * which will be called by the dispatcher when it receives dma
83430294Ssam 	 * end-of-range interrupt.
83530294Ssam 	 */
83629651Ssam }
83729651Ssam 
83830294Ssam drwait(rs, dr)
83930294Ssam 	register struct rsdevice *rs;
84030294Ssam 	register struct dr_aux *dr;
84129651Ssam {
84230294Ssam 	int s;
84329651Ssam 
84429651Ssam 	s = SPL_UP();
84530294Ssam 	while (dr->dr_flags & DR_ACTV)
84630294Ssam 		sleep((caddr_t)dr, DRPRI);
84729651Ssam 	splx(s);
84830294Ssam 	if (dr->dr_flags & DR_TMDM) {		/* DMA timed out */
84929651Ssam 		dr->dr_flags &= ~DR_TMDM;
85030294Ssam 		return (0);
85129651Ssam 	}
85230294Ssam 	if (rs->dr_cstat & (PERR|BERR|TERR)) {
85330294Ssam 		dr->dr_actf->b_flags |= B_ERROR;
85430294Ssam 		return (0);
85529651Ssam 	}
85629651Ssam 	dr->dr_flags &= ~DR_DMAX;
85730294Ssam 	return (1);
85829651Ssam }
85929651Ssam 
86030294Ssam /*
86130294Ssam  *
86230294Ssam  * The lower 8-bit of tinfo is the minor device number, the
86330294Ssam  * remaining higher 8-bit is the current timout number
86430294Ssam  */
86529651Ssam drrwtimo(tinfo)
86630294Ssam 	register u_long tinfo;
86730294Ssam {
86830294Ssam 	register long unit = tinfo & 0xff;
86929651Ssam 	register struct dr_aux *dr = &dr_aux[unit];
87029651Ssam 	register struct rsdevice *rs = dr->dr_addr;
87129651Ssam 
87230294Ssam 	/*
87330294Ssam 	 * If this is not the timeout that drwrite/drread is waiting
87430294Ssam 	 * for then we should just go away
87530294Ssam 	 */
87630294Ssam 	if ((tinfo &~ 0xff) != (dr->currenttimo << 8))
87730294Ssam 		return;
87829651Ssam 	/* Mark the device timed out */
87929651Ssam 	dr->dr_flags |= DR_TMDM;
88029651Ssam 	dr->dr_flags &= ~DR_ACTV;
88129651Ssam 	rs->dr_pulse = RMSK;			/* Inihibit interrupt */
88229651Ssam 	rs->dr_pulse = (RPER|RDMA|RATN|IENB);	/* Clear DMA logic */
88330294Ssam 	/*
88430294Ssam 	 * Some applications will not issue a master after dma timeout,
88530294Ssam 	 * since doing so sends an INIT H pulse to the external device,
88630294Ssam 	 * which may produce undesirable side-effects.
88730294Ssam 	 */
88829651Ssam 	/* Wake up process waiting in drwait() and flag the error */
88930294Ssam 	dr->dr_actf->b_flags |= B_ERROR;
89029651Ssam 	wakeup((caddr_t)dr->dr_cmd);
89129651Ssam }
89229651Ssam 
89329651Ssam /*
89430294Ssam  * Kick the driver every second
89530294Ssam  */
89629651Ssam drtimo(dev)
89730294Ssam 	dev_t dev;
89829651Ssam {
89930294Ssam 	register int unit = RSUNIT(dev);
90029651Ssam 	register struct dr_aux *dr;
90129651Ssam 
90230294Ssam 	dr = &dr_aux[unit];
90329651Ssam 	if (dr->dr_flags & DR_OPEN)
90430294Ssam 		timeout(drtimo, (caddr_t)dev, hz);
90529651Ssam 	wakeup((caddr_t)dr);	/* Wakeup any process waiting for interrupt */
90629651Ssam }
90729651Ssam 
90829651Ssam #ifdef DR_DEBUG
90930294Ssam drva(dra, p, va, bcnt)
91030294Ssam 	struct dr_aux *dra;
91130294Ssam 	struct proc *p;
91230294Ssam 	char *va;
91330294Ssam 	long bcnt;
91430294Ssam {
91530294Ssam 	register long first, last , np;
91629651Ssam 
91729651Ssam 	if (DR11 & 0x20)  {
91830294Ssam 		first = ((long)(vtoph(p, (unsigned)va))) >> 10;
91930294Ssam 		last = ((long)(vtoph(p, (unsigned)va+bcnt))) >> 10;
92029651Ssam 		np = bcnt / 0x3ff;
92129651Ssam 		printf("\ndrva: (op:%ld)(first:%ld)(last:%ld)(np:%ld)(cnt:%ld)",
92229651Ssam 			dra->dr_op,first,last,np,bcnt);
92329651Ssam 	}
92429651Ssam }
92529651Ssam #endif
92629651Ssam 
92730294Ssam drstart(rsaddr, dra, bp)
92830294Ssam 	register struct rsdevice *rsaddr;
92930294Ssam 	register struct dr_aux *dra;
93030294Ssam 	register struct buf *bp;
93130294Ssam {
93230294Ssam 	register long addr;
93330294Ssam 	u_short go;
93429651Ssam 
93529651Ssam #ifdef DR_DEBUG
93630294Ssam 	if (dra->dr_op == DR_READ && (DR11 & 8)) {
93730294Ssam 		char *caddr = (char *)bp->b_un.b_addr;
93829651Ssam 		printf("\ndrstart: READ, bcnt:%ld",bp->b_bcount);
93929651Ssam 		printf(",(%lx)(%lx)",caddr[0]&0xff,caddr[1]&0xff);
94029651Ssam 	}
94129651Ssam #endif
94230294Ssam 	/* we are doing raw IO, bp->b_un.b_addr is user's address */
94330294Ssam 	addr = (long)vtoph(bp->b_proc, (unsigned)bp->b_un.b_addr);
94430294Ssam 	/*
94530294Ssam 	 * Set DMA address into DR11 interace registers: DR11 requires that
94630294Ssam 	 * the address be right shifted 1 bit position before it is written
94730294Ssam 	 * to the board (The board will left shift it one bit position before
94830294Ssam 	 * it places the address on the bus
94930294Ssam 	 */
95030294Ssam 	rsaddr->dr_walo = (addr >> 1) & 0xffff;
95130294Ssam 	rsaddr->dr_wahi = (addr >> 17) & 0x7fff;
95230294Ssam 	/* Set DMA range count: (number of words - 1) */
95330294Ssam 	rsaddr->dr_range = (bp->b_bcount >> 1) - 1;
95430294Ssam 	/* Set address modifier code to be used for DMA access to memory */
95530294Ssam 	rsaddr->dr_addmod = DRADDMOD;
95630294Ssam 	/*
95730294Ssam 	 * Now determine whether this is a read or a write. ***** This is
95830294Ssam 	 * probably only usefull for link mode operation, since dr11 doesnot
95930294Ssam 	 * controll the direction of data transfer. The C1 control input
96030294Ssam 	 * controls whether the hardware is doing a read or a write. In link
96130294Ssam 	 * mode this is controlled by function 1 latch (looped back by the
96230294Ssam 	 * cable) and could be set the program. In the general case, the dr11
96330294Ssam 	 * doesnot know in advance what the direction of transfer is - although
96430294Ssam 	 * the program and protocol logic probably is
96530294Ssam 	 */
96629651Ssam #ifdef DR_DEBUG
96730294Ssam 	if (DR11 & 1)
96830294Ssam 		printf(
96930294Ssam "\ndrstrat: about to GO..,dr_cmd:%lx,drstat:%lx,drcnt:%ld,cdata:%lx,OP:%ld",
97030294Ssam 		    dra->dr_cmd, rsaddr->dr_cstat, rsaddr->dr_range,
97130294Ssam 		    rsaddr->dr_data, dra->dr_op);
97229651Ssam #endif
97330294Ssam 	/*
97430294Ssam 	 * Update function latches may have been done already by drioctl() if
97530294Ssam 	 * request from drioctl()
97630294Ssam 	 */
97730294Ssam 	if (dra->dr_cmd & DR_DFCN) {		/* deferred function write */
97830294Ssam 		dra->dr_cmd &= ~DR_DFCN;	/* Clear request */
97930294Ssam 		go = dra->dr_cmd & DR_FMSK;	/* mask out fcn bits */
98030294Ssam 		rsaddr->dr_cstat = go;		/* Write it to the board */
98130294Ssam 	}
98230294Ssam 	/* Clear dmaf and attf to assure a clean dma start */
98330294Ssam 	rsaddr->dr_pulse = RATN|RDMA|RPER;
98430294Ssam 	rsaddr->dr_cstat = IENB|GO|CYCL|dra->dr_op; /* GO...... */
98530294Ssam 	/*
98630294Ssam 	 * Now check for software cycle request -- usually
98730294Ssam 	 * by transmitter in link mode.
98830294Ssam 	 */
98930294Ssam 	if (dra->dr_cmd & DR_PCYL) {
99030294Ssam 		dra->dr_cmd &= ~DR_PCYL;	/* Clear request */
99130294Ssam 		rsaddr->dr_pulse = CYCL;	/* Use pulse register again */
99230294Ssam 	}
99330294Ssam 	/*
99430294Ssam 	 * Now check for deferred ACLO FCNT2 pulse request -- usually to tell
99530294Ssam 	 * the transmitter (via its attention) that we have enabled dma.
99630294Ssam 	 */
99730294Ssam 	if (dra->dr_cmd & DR_DACL) {
99830294Ssam 		dra->dr_cmd &= ~DR_DACL;	/* Clear request */
99930294Ssam 		rsaddr->dr_pulse = FCN2;	/* Use pulse register again */
100030294Ssam 	}
100129651Ssam }
100229651Ssam #endif  NDR
1003