xref: /csrg-svn/sys/tahoe/vba/dr.c (revision 30138)
1*30138Ssam /*	dr.c	1.2	86/11/23	*/
229651Ssam 
329651Ssam #include "dr.h"
429651Ssam #if NDR > 0
529651Ssam 
629651Ssam /*      DRV11-W DMA interface driver.
729651Ssam  */
829651Ssam 
929651Ssam #include "../machine/mtpr.h"
1029651Ssam #include "../machine/pte.h"
1129651Ssam 
1229651Ssam #include "param.h"
1329651Ssam #include "conf.h"
1429651Ssam #include "dir.h"
1529651Ssam #include "user.h"
1629651Ssam #include "proc.h"
1729651Ssam #include "map.h"
1829651Ssam #include "ioctl.h"
1929651Ssam #include "buf.h"
2029651Ssam #include "vm.h"
2129651Ssam #include "uio.h"
2229651Ssam 
2329651Ssam #include "../tahoevba/vbavar.h"
2429651Ssam #include "../tahoevba/drreg.h"
2529651Ssam 
2629651Ssam #define YES 1
2729651Ssam #define NO  0
2829651Ssam 
2929651Ssam struct  vba_device  *drinfo[NDR];
3029651Ssam struct  dr_aux dr_aux[NDR];
3129651Ssam 
3229651Ssam caddr_t vtoph();
3329651Ssam unsigned drminphys();
3429651Ssam int     drprobe(), drintr(), drattach(), drtime(), drrwtimo();
3529651Ssam int     drstrategy();
3629651Ssam extern struct  vba_device  *drinfo[];
3729651Ssam static long drstd[] = { 0 };
3829651Ssam struct  vba_driver drdriver =
3929651Ssam 	{ drprobe, 0, drattach, 0, drstd, "rs", drinfo };
4029651Ssam extern long hz;
4129651Ssam 
4229651Ssam #define RSUNIT(dev) (minor(dev) & 7)
4329651Ssam #define SPL_UP spl5
4429651Ssam 
4529651Ssam /* -------- Per-unit data -------- */
4629651Ssam 
4729651Ssam extern struct dr_aux dr_aux[];
4829651Ssam 
4929651Ssam struct rs_data {
5029651Ssam     struct buf  rs_buf;
5129651Ssam     int         rs_ubainfo;
5229651Ssam     short       rs_debug;
5329651Ssam     short       rs_busy;
5429651Ssam     short       rs_tout;
5529651Ssam     short       rs_uid;
5629651Ssam     short       rs_isopen;
5729651Ssam     short       rs_func;
5829651Ssam } rs_data[NDR];
5929651Ssam 
6029651Ssam 
6129651Ssam #ifdef DR_DEBUG
6229651Ssam long DR11 = 0;
6329651Ssam #endif
6429651Ssam 
6529651Ssam drprobe(reg, vi)
6629651Ssam     caddr_t reg;
6729651Ssam     struct vba_device *vi;
6829651Ssam {
6929651Ssam     register int br, cvec;		/* must be r12, r11 */
7029651Ssam     register struct rsdevice *dr;
7129651Ssam     register ushort status;
7229651Ssam 
7329651Ssam     dr = (struct rsdevice *)reg;
7429651Ssam #ifdef notdef
7529651Ssam     dr->dr_intvec = --vi->ui_hd->vh_lastiv;
7629651Ssam #else
7729651Ssam     dr->dr_intvec = DRINTV+vi->ui_unit;
7829651Ssam #endif
7929651Ssam #ifdef DR_DEBUG
8029651Ssam     printf("dprobe: Set interrupt vector %lx and init\n",dr->dr_intvec);
8129651Ssam #endif
8229651Ssam     /* generate interrupt here for autoconfig */
8329651Ssam     dr->dr_cstat = MCLR;		/* init board and device */
8429651Ssam     status = dr->dr_cstat;		/* read initial status */
8529651Ssam #ifdef DR_DEBUG
8629651Ssam     printf("drprobe: Initial status %lx\n",status & 0xffff);
8729651Ssam #endif
8829651Ssam     br = 0x18, cvec = dr->dr_intvec;	/* XXX */
8929651Ssam     return (sizeof (struct rsdevice));		/* DR11 exist */
9029651Ssam }
9129651Ssam 
9229651Ssam /* ARGSUSED */
9329651Ssam drattach(ui)
9429651Ssam struct vba_device *ui;
9529651Ssam {
9629651Ssam     register struct dr_aux *rsd;
9729651Ssam 
9829651Ssam     rsd = &dr_aux[ui->ui_unit];
9929651Ssam     rsd->dr_flags = DR_PRES;		/* This dr11 is present */
10029651Ssam     rsd->dr_addr = (struct rsdevice *)ui->ui_addr; /* Save addr of this dr11 */
10129651Ssam     rsd->dr_istat = 0;
10229651Ssam     rsd->dr_bycnt = 0;
10329651Ssam     rsd->dr_cmd = 0;
10429651Ssam     rsd->currenttimo = 0;
10529651Ssam     return;
10629651Ssam }
10729651Ssam 
10829651Ssam dropen (dev, flag)
10929651Ssam dev_t dev;
11029651Ssam int flag;
11129651Ssam {
11229651Ssam     register int unit = RSUNIT(dev);
11329651Ssam     register struct rsdevice *dr;
11429651Ssam     register struct dr_aux *rsd;
11529651Ssam 
11629651Ssam     if ((drinfo[unit] == 0) || (!drinfo[unit]->ui_alive))
11729651Ssam 	return ENXIO;
11829651Ssam 
11929651Ssam     dr = RSADDR(unit);
12029651Ssam     rsd = &dr_aux[unit];
12129651Ssam     if (rsd->dr_flags & DR_OPEN) {
12229651Ssam #ifdef DR_DEBUG
12329651Ssam 	printf("\ndropen: dr11 unit %ld already open",unit);
12429651Ssam #endif
12529651Ssam 	return ENXIO;      		/* DR11 already open */
12629651Ssam     }
12729651Ssam     rsd->dr_flags |= DR_OPEN;		/* Mark it OPEN */
12829651Ssam     rsd->dr_istat = 0;			/* Clear status of previous interrupt */
12929651Ssam     rsd->rtimoticks = hz;		/* Set read no stall timout to 1 sec */
13029651Ssam     rsd->wtimoticks = hz*60;		/* Set write no stall timout to 1 min */
13129651Ssam     dr->dr_cstat = DR_ZERO;		/* Clear function & latches */
13229651Ssam     dr->dr_pulse = (RDMA | RATN);	/* clear leftover attn & e-o-r flags */
13329651Ssam     drtimo(dev);			/* start the self kicker */
13429651Ssam     return 0;
13529651Ssam }
13629651Ssam 
13729651Ssam drclose (dev)
13829651Ssam dev_t dev;
13929651Ssam {
14029651Ssam     register int unit = RSUNIT(dev);
14129651Ssam     register struct dr_aux *dra;
14229651Ssam     register struct rsdevice *rs;
14329651Ssam     register short s;
14429651Ssam 
14529651Ssam     dra = &dr_aux[unit];
14629651Ssam     if (!(dra->dr_flags & DR_OPEN)) {
14729651Ssam #ifdef DR_DEBUG
14829651Ssam 	printf("\ndrclose: DR11 device %ld not open",unit);
14929651Ssam #endif
15029651Ssam 	return;
15129651Ssam     }
15229651Ssam     dra->dr_flags &= ~(DR_OPEN|DR_ACTV);
15329651Ssam     rs = dra->dr_addr;
15429651Ssam     s=SPL_UP();
15529651Ssam     rs->dr_cstat = DR_ZERO;
15629651Ssam     if (dra->dr_buf.b_flags & B_BUSY) {
15729651Ssam     	dra->dr_buf.b_flags &= ~B_BUSY;
15829651Ssam 	wakeup(&dra->dr_buf.b_flags);
15929651Ssam     }
16029651Ssam     splx(s);
16129651Ssam     return;
16229651Ssam }
16329651Ssam 
16429651Ssam 
16529651Ssam /*	drread() works exactly like drwrite() except that the
16629651Ssam 	B_READ flag is used when physio() is called
16729651Ssam */
16829651Ssam drread (dev, uio)
16929651Ssam dev_t dev;
17029651Ssam struct uio *uio;
17129651Ssam {	register struct dr_aux *dra;
17229651Ssam 	register struct buf *bp;
17329651Ssam 	register long spl, err;
17429651Ssam     	register int unit = RSUNIT(dev);
17529651Ssam 
17629651Ssam     if (   uio->uio_iov->iov_len <= 0		/* Negative count */
17729651Ssam 	|| uio->uio_iov->iov_len & 1		/* odd count */
17829651Ssam 	|| (int)uio->uio_iov->iov_base & 1	/* odd destination address */
17929651Ssam        )
18029651Ssam 	return EINVAL;
18129651Ssam 
18229651Ssam #ifdef DR_DEBUG
18329651Ssam     if (DR11 & 8) {
18429651Ssam 	printf("\ndrread: (len:%ld)(base:%lx)",
18529651Ssam     		uio->uio_iov->iov_len,(int)uio->uio_iov->iov_base);
18629651Ssam     }
18729651Ssam #endif
18829651Ssam 
18929651Ssam     dra = &dr_aux[RSUNIT(dev)];
19029651Ssam     dra->dr_op = DR_READ;
19129651Ssam     bp =  &dra->dr_buf;
19229651Ssam     bp->b_resid = 0;
19329651Ssam     if (dra->dr_flags & DR_NORSTALL) {
19429651Ssam 	/* We are in no stall mode, start the timer, raise IPL so nothing
19529651Ssam 	   can stop us once the timer's running */
19629651Ssam 	spl = SPL_UP();
19729651Ssam 	timeout(drrwtimo,(caddr_t)((dra->currenttimo<<8) | unit),
19829651Ssam 				dra->rtimoticks);
19929651Ssam     	err = physio (drstrategy, bp, dev,B_READ, drminphys, uio);
20029651Ssam 	splx(spl);
20129651Ssam 	if (err)
20229651Ssam 		return(err);
20329651Ssam 	dra->currenttimo++;		/* Update current timeout number */
20429651Ssam 	/* Did we timeout */
20529651Ssam 	if (dra->dr_flags & DR_TMDM) {
20629651Ssam 		dra->dr_flags &= ~DR_TMDM;	/* Clear timeout flag */
20729651Ssam 		u.u_error = 0;		/* Made the error ourself, ignore it */
20829651Ssam 	}
20929651Ssam     }
21029651Ssam     else {
21129651Ssam     	return physio (drstrategy, bp, dev,B_READ, drminphys, uio);
21229651Ssam     }
21329651Ssam }
21429651Ssam 
21529651Ssam drwrite (dev, uio)
21629651Ssam dev_t dev;
21729651Ssam struct uio *uio;
21829651Ssam {	register struct dr_aux *dra;
21929651Ssam 	register struct buf *bp;
22029651Ssam     	register int unit = RSUNIT(dev);
22129651Ssam 	register long spl, err;
22229651Ssam 
22329651Ssam     if (   uio->uio_iov->iov_len <= 0
22429651Ssam 	|| uio->uio_iov->iov_len & 1
22529651Ssam 	|| (int)uio->uio_iov->iov_base & 1
22629651Ssam        )
22729651Ssam 	return EINVAL;
22829651Ssam 
22929651Ssam #ifdef DR_DEBUG
23029651Ssam     if (DR11 & 4) {
23129651Ssam 	printf("\ndrwrite: (len:%ld)(base:%lx)",
23229651Ssam     		uio->uio_iov->iov_len,(int)uio->uio_iov->iov_base);
23329651Ssam     }
23429651Ssam #endif
23529651Ssam 
23629651Ssam     dra = &dr_aux[RSUNIT(dev)];
23729651Ssam     dra->dr_op = DR_WRITE;
23829651Ssam     bp =  &dra->dr_buf;
23929651Ssam     bp->b_resid = 0;
24029651Ssam     if (dra->dr_flags & DR_NOWSTALL) {
24129651Ssam 	/* We are in no stall mode, start the timer, raise IPL so nothing
24229651Ssam 	   can stop us once the timer's running */
24329651Ssam 	spl = SPL_UP();
24429651Ssam 	timeout(drrwtimo,(caddr_t)((dra->currenttimo<<8) | unit),
24529651Ssam 				dra->wtimoticks);
24629651Ssam     	err = physio (drstrategy, bp, dev,B_WRITE, drminphys, uio);
24729651Ssam 	splx(spl);
24829651Ssam 	if (err)
24929651Ssam 		return(err);
25029651Ssam 	dra->currenttimo++;		/* Update current timeout number */
25129651Ssam 	/* Did we timeout */
25229651Ssam 	if (dra->dr_flags & DR_TMDM) {
25329651Ssam 		dra->dr_flags &= ~DR_TMDM;	/* Clear timeout flag */
25429651Ssam 		u.u_error = 0;		/* Made the error ourself, ignore it */
25529651Ssam 	}
25629651Ssam     }
25729651Ssam     else {
25829651Ssam     	return physio (drstrategy, bp, dev,B_WRITE, drminphys, uio);
25929651Ssam     }
26029651Ssam }
26129651Ssam 
26229651Ssam /*  Routine used by calling program to issue commands to dr11 driver and
26329651Ssam     through it to the device.
26429651Ssam     It is also used to read status from the device and driver and to wait
26529651Ssam     for attention interrupts.
26629651Ssam     Status is returned in an 8 elements unsigned short integer array, the
26729651Ssam     first two elements of the array are also used to pass arguments to
26829651Ssam     drioctl() if required.
26929651Ssam     The function bits to be written to the dr11 are included in the cmd
27029651Ssam     argument. Even if they are not being written to the dr11 in a particular
27129651Ssam     drioctl() call, they will update the copy of cmd that is stored in the
27229651Ssam     driver. When drstrategy() is called, this updated copy is used if a
27329651Ssam     deferred function bit write has been specified. The "side effect" of
27429651Ssam     calls to the drioctl() requires that the last call prior to a read or
27529651Ssam     write has an appropriate copy of the function bits in cmd if they are
27629651Ssam     to be used in drstrategy().
27729651Ssam     When used as command value, the contents of data[0] is the command
27829651Ssam     parameter.
27929651Ssam */
28029651Ssam 
28129651Ssam drioctl(dev, cmd, data, flag)
28229651Ssam dev_t dev;
28329651Ssam int cmd;
28429651Ssam long *data;
28529651Ssam int flag;
28629651Ssam {
28729651Ssam     register int unit = RSUNIT(dev);
28829651Ssam     register struct dr_aux *dra;
28929651Ssam     register struct rsdevice *rsaddr = RSADDR(unit);
29029651Ssam     struct dr11io dio;
29129651Ssam     ushort s, errcode, status;
29229651Ssam     long temp;
29329651Ssam 
29429651Ssam #ifdef DR_DEBUG
29529651Ssam     if (DR11 & 0x10)
29629651Ssam     printf("\ndrioctl: (dev:%lx)(cmd:%lx)(data:%lx)(data[0]:%lx)",
29729651Ssam 	dev,cmd,data,data[0]);
29829651Ssam #endif
29929651Ssam 
30029651Ssam     dra = &dr_aux[unit];
30129651Ssam     dra->dr_cmd = 0;		/* Fresh copy; clear all previous flags */
30229651Ssam 
30329651Ssam     switch (cmd) {
30429651Ssam 
30529651Ssam     case DRWAIT:
30629651Ssam 	/* Wait for attention interrupt */
30729651Ssam #ifdef DR_DEBUG
30829651Ssam 	printf("\ndrioctl: wait for attention interrupt");
30929651Ssam #endif
31029651Ssam 	s = SPL_UP();
31129651Ssam 	/* If the attention flag in dr_flags is set, it probably means that
31229651Ssam 	   an attention has arrived by the time a previous DMA end-of-range
31329651Ssam 	   interrupt was serviced. If ATRX is set, we will return with out
31429651Ssam 	   sleeping, since we have received an attention since the last call
31529651Ssam 	   to wait on attention.
31629651Ssam 	   This may not be appropriate for some applications.
31729651Ssam 	*/
31829651Ssam 	if (!(dra->dr_flags & DR_ATRX)) {
31929651Ssam 		dra->dr_flags |= DR_ATWT;	/* Set waiting flag */
32029651Ssam 		rsaddr->dr_pulse = IENB;	/* Enable interrupt; use pulse
32129651Ssam 						   reg. so function bits are
32229651Ssam 						   not changed */
32329651Ssam 		sleep((caddr_t)&dra->dr_cmd,DRPRI);
32429651Ssam 	}
32529651Ssam 	splx(s);
32629651Ssam 	break;
32729651Ssam 
32829651Ssam     case DRPIOW:
32929651Ssam 	/* Write to p-i/o register */
33029651Ssam 	rsaddr->dr_data = data[0];
33129651Ssam 	break;
33229651Ssam 
33329651Ssam     case DRPACL:
33429651Ssam 	/* Send pulse to device */
33529651Ssam 	rsaddr->dr_pulse = FCN2;
33629651Ssam 	break;
33729651Ssam 
33829651Ssam     case DRDACL:
33929651Ssam 	/* Defer alco pulse until go */
34029651Ssam 	dra->dr_cmd |= DR_DACL;
34129651Ssam 	break;
34229651Ssam 
34329651Ssam     case DRPCYL:
34429651Ssam 	/* Set cycle with next go */
34529651Ssam 	dra->dr_cmd |= DR_PCYL;
34629651Ssam 	break;
34729651Ssam 
34829651Ssam     case DRDFCN:
34929651Ssam 	/* Do not update function bits until next go issued */
35029651Ssam 	dra->dr_cmd |= DR_DFCN;
35129651Ssam 	break;
35229651Ssam 
35329651Ssam     case DRRATN:
35429651Ssam 	/* Reset attention flag -- use with extreme caution */
35529651Ssam 	rsaddr->dr_pulse = RATN;
35629651Ssam 	break;
35729651Ssam 
35829651Ssam     case DRRDMA:
35929651Ssam 	/* Reset DMA e-o-r flag -- should never used */
36029651Ssam 	rsaddr->dr_pulse = RDMA;
36129651Ssam 	break;
36229651Ssam 
36329651Ssam     case DRSFCN:
36429651Ssam 	/* Set function bits */
36529651Ssam 	temp = data[0] & DR_FMSK;
36629651Ssam 	rsaddr->dr_cstat = temp;	/* Write to control register */
36729651Ssam 	/* This has a very important side effect -- It clears the interrupt
36829651Ssam 	   enable flag. That is fine for this driver, but if it is desired
36929651Ssam 	   to leave interrupt enable at all times, it will be necessary to
37029651Ssam 	   to read the status register first to get IENB, or carry a software
37129651Ssam 	   flag that indicates whether interrupts are set, and or this into
37229651Ssam 	   the controll register value being written.
37329651Ssam 	*/
37429651Ssam 	break;
37529651Ssam 
37629651Ssam     case DRRPER:
37729651Ssam 	/* Clear parity flag */
37829651Ssam 	rsaddr->dr_pulse = RPER;
37929651Ssam 	break;
38029651Ssam 
38129651Ssam     case DRSETRSTALL:
38229651Ssam 	/* Set read stall mode. */
38329651Ssam 	dra->dr_flags &= (~DR_NORSTALL);
38429651Ssam 	break;
38529651Ssam 
38629651Ssam     case DRSETNORSTALL:
38729651Ssam 	/* Set no stall read  mode. */
38829651Ssam 	dra->dr_flags |= DR_NORSTALL;
38929651Ssam 	break;
39029651Ssam 
39129651Ssam     case DRGETRSTALL:
39229651Ssam 	/* Returns true if in read stall mode. */
39329651Ssam 	data[0]  = (dra->dr_flags & DR_NORSTALL)? 0 : 1;
39429651Ssam 	break;
39529651Ssam 
39629651Ssam     case DRSETRTIMEOUT:
39729651Ssam 	/* Set the number of ticks before a no stall read times out.
39829651Ssam 	   The argument is given in tenths of a second. */
39929651Ssam 	if (data[0] < 1) {
40029651Ssam 		u.u_error = EINVAL;
40129651Ssam 		temp = 1;
40229651Ssam 	}
40329651Ssam 	dra->rtimoticks = (data[0] * hz )/10;
40429651Ssam 	break;
40529651Ssam 
40629651Ssam     case DRGETRTIMEOUT:
40729651Ssam 	/* Returns the number of tenths of seconds before
40829651Ssam 	   a no stall read times out. */
40929651Ssam 	/* The argument is given in tenths of a second. */
41029651Ssam 	data[0] = ((dra->rtimoticks)*10)/hz;
41129651Ssam 	break;
41229651Ssam 
41329651Ssam     case DRSETWSTALL:
41429651Ssam 	/* Set write stall mode. */
41529651Ssam 	dra->dr_flags &= (~DR_NOWSTALL);
41629651Ssam 	break;
41729651Ssam 
41829651Ssam     case DRSETNOWSTALL:
41929651Ssam 	/* Set write stall mode. */
42029651Ssam 	dra->dr_flags |= DR_NOWSTALL;
42129651Ssam 	break;
42229651Ssam 
42329651Ssam     case DRGETWSTALL:
42429651Ssam 	/* Returns true if in write stall mode. */
42529651Ssam 	data[0] = (dra->dr_flags & DR_NOWSTALL)? 0 : 1;
42629651Ssam 	break;
42729651Ssam 
42829651Ssam     case DRSETWTIMEOUT:
42929651Ssam 	/* Set the number of ticks before a no stall write times out.
43029651Ssam 	   The argument is given in tenths of a second. */
43129651Ssam 	if (data[0] < 1) {
43229651Ssam 		u.u_error = EINVAL;
43329651Ssam 		temp = 1;
43429651Ssam 	}
43529651Ssam 	dra->wtimoticks = (data[0] * hz )/10;
43629651Ssam 	break;
43729651Ssam 
43829651Ssam     case DRGETWTIMEOUT:
43929651Ssam 	/* Returns the number of tenths of seconds before
44029651Ssam 	   a no stall write times out. */
44129651Ssam 	/* The argument is given in tenths of a second. */
44229651Ssam 	data[0] = ((dra->wtimoticks)*10)/hz;
44329651Ssam 	break;
44429651Ssam 
44529651Ssam     case DRWRITEREADY:
44629651Ssam 	/* Returns a value of 1 if the device can accept
44729651Ssam 	   data, 0 otherwise. Internally this is the
44829651Ssam 	   DR11-W STAT A bit. */
44929651Ssam 
45029651Ssam 	data[0] = (rsaddr->dr_cstat & STTA)? 1 : 0;
45129651Ssam 	break;
45229651Ssam 
45329651Ssam     case DRREADREADY:
45429651Ssam 	/* Returns a value of 1 if the device has data
45529651Ssam 	   for host to be read, 0 otherwise. Internally
45629651Ssam 	   this is the DR11-W STAT B bit. */
45729651Ssam 	data[0] = (rsaddr->dr_cstat & STTB)? 1 : 0;
45829651Ssam 	break;
45929651Ssam 
46029651Ssam     case DRBUSY:
46129651Ssam 	/* Returns a value of 1 if the device is busy,
46229651Ssam 	   0 otherwise. Internally this is the DR11-W
46329651Ssam 	   STAT C bit, but there is a bug in the Omega 500/FIFO interface
46429651Ssam 	   board that it cannot drive this signal low for certain DR11-W
46529651Ssam 	   ctlr such as the Ikon. We use the REDY signal of the CSR on
46629651Ssam 	   the Ikon DR11-W instead.
46729651Ssam 
46829651Ssam 	data[0] = (rsaddr->dr_cstat & STTC)? 1 : 0;
46929651Ssam 	*/
47029651Ssam 
47129651Ssam 	data[0] = ((rsaddr->dr_cstat & REDY)? 0 : 1);
47229651Ssam 	break;
47329651Ssam 
47429651Ssam     case DRRESET:
47529651Ssam 	rsaddr->dr_pulse = (MCLR|RDMA|RATN|RPER);/* Reset DMA ATN RPER flag */
47629651Ssam 	DELAY(0x1f000);
47729651Ssam 	while (!(rsaddr->dr_cstat & REDY)) {
47829651Ssam 		sleep((caddr_t)dra, DRPRI);	/* Wakeup by drtimo() */
47929651Ssam 	}
48029651Ssam     	dra->dr_istat = 0;
48129651Ssam     	dra->dr_cmd = 0;
48229651Ssam     	dra->currenttimo = 0;
48329651Ssam 	break;
48429651Ssam 
485*30138Ssam     case DR11STAT:
486*30138Ssam     	/* Copy back dr11 status to user */
487*30138Ssam     	data->arg[0] = dra->dr_flags;
488*30138Ssam     	data->arg[1] = rsaddr->dr_cstat;
489*30138Ssam     	data->arg[2] = dra->dr_istat;	/* Status reg. at last interrupt */
490*30138Ssam     	data->arg[3] = rsaddr->dr_data;	/* P-i/o input data */
491*30138Ssam     	status = (ushort)((rsaddr->dr_addmod << 8) & 0xff00);
492*30138Ssam     	data->arg[4] = status | (ushort)(rsaddr->dr_intvect & 0xff);
493*30138Ssam     	data->arg[5] = rsaddr->dr_range;
494*30138Ssam     	data->arg[6] = rsaddr->dr_rahi;
495*30138Ssam     	data->arg[7] = rsaddr->dr_ralo;
496*30138Ssam 	break;
497*30138Ssam     case DR11LOOP:
498*30138Ssam 	/* Perform loopback test -- MUST HAVE LOOPBACK CABLE ATTACHED --
499*30138Ssam 	   Test results are printed on system console */
500*30138Ssam 	if (suser())
501*30138Ssam 		dr11loop(rsaddr,dra,unit);
502*30138Ssam 	break;
503*30138Ssam 
50429651Ssam     default:
50529651Ssam 	printf("\ndrioctl: Invalid ioctl cmd : %lx",cmd);
50629651Ssam 	return EINVAL;
50729651Ssam     }
50829651Ssam 
50929651Ssam #ifdef DR_DEBUG
51029651Ssam     if (DR11 & 0x10)
51129651Ssam     	printf("**** (data[0]:%lx)",data[0]);
51229651Ssam #endif
51329651Ssam     return 0;
51429651Ssam }
51529651Ssam 
516*30138Ssam #define NPAT 2
517*30138Ssam #define DMATBL 20
518*30138Ssam ushort tstpat[DMATBL] = { 0xAAAA, 0x5555};
519*30138Ssam long DMAin = 0;
520*30138Ssam 
521*30138Ssam dr11loop(dr,dra,unit)
522*30138Ssam struct rsdevice *dr;
523*30138Ssam struct dr_aux *dra;
524*30138Ssam long unit;
525*30138Ssam {	register long result, ix;
526*30138Ssam 	long baddr, wait;
527*30138Ssam 
528*30138Ssam 	dr->dr_cstat = MCLR;		/* Clear board & device, disable intr */
529*30138Ssam 
530*30138Ssam 	/* Perform loopback test -- MUST HAVE LOOPBACK CABLE ATTACHED --
531*30138Ssam 	   Test results are printed on system console */
532*30138Ssam 	printf("\n\t ----- DR11 unit %ld loopback test -----",unit);
533*30138Ssam 
534*30138Ssam 	printf("\n\t Program I/O ...");
535*30138Ssam 	for (ix=0;ix<NPAT;ix++) {
536*30138Ssam 		dr->dr_data = tstpat[ix];	/* Write to Data out register */
537*30138Ssam 		result = (dr->dr_data & 0xFFFF);	/* Read it back */
538*30138Ssam 		if (result != tstpat[ix]) {
539*30138Ssam 			printf("Failed, expected : %lx --- actual : %lx",
540*30138Ssam 				tstpat[ix],result);
541*30138Ssam 			return;
542*30138Ssam 		}
543*30138Ssam 	}
544*30138Ssam 
545*30138Ssam 	printf("OK\n\t Functions & Status Bits ...");
546*30138Ssam 	dr->dr_cstat = (FCN1 | FCN3);
547*30138Ssam 	result = dr->dr_cstat & 0xffff;		/* Read them back */
548*30138Ssam 	if ((result & (STTC | STTA)) != (STTC |STTA)) {
549*30138Ssam 		printf("Failed, expected : %lx --- actual : %lx, ISR:%lx",
550*30138Ssam 			(STTA|STTC),(result & (STTA|STTC)), result);
551*30138Ssam 		return;
552*30138Ssam 	}
553*30138Ssam 	dr->dr_cstat = FCN2;
554*30138Ssam 	result = dr->dr_cstat & 0xffff;		/* Read them back */
555*30138Ssam 	if ((result & STTB) != STTB) {
556*30138Ssam 		printf("Failed, expected : %lx --- actual : %lx, ISR:%lx",
557*30138Ssam 			STTB,(result & STTB), result);
558*30138Ssam 		return;
559*30138Ssam 	}
560*30138Ssam 
561*30138Ssam 	printf("OK\n\t DMA output ...");
562*30138Ssam 
563*30138Ssam 	if (DMAin) goto dmain;
564*30138Ssam 
565*30138Ssam 	/* Initialize DMA data buffer */
566*30138Ssam 	for(ix=0;ix<DMATBL;ix++) tstpat[ix] = 0xCCCC + ix;
567*30138Ssam 	tstpat[DMATBL-1] = 0xCCCC;	/* Last word output */
568*30138Ssam 
569*30138Ssam 	/* Setup normal DMA */
570*30138Ssam 	baddr = (long)vtoph(0,tstpat);		/* Virtual --> physical */
571*30138Ssam     	dr->dr_walo = (ushort)((baddr >> 1) & 0xffff);
572*30138Ssam     	dr->dr_wahi = (ushort)((baddr >> 17) & 0x7fff);
573*30138Ssam 
574*30138Ssam     	/* Set DMA range count: (number of words - 1) */
575*30138Ssam     	dr->dr_range = (ushort)(DMATBL - 1);
576*30138Ssam 
577*30138Ssam     	/* Set  address modifier code to be used for DMA access to memory */
578*30138Ssam     	dr->dr_addmod = (char)DRADDMOD;
579*30138Ssam 
580*30138Ssam     	/* Clear dmaf and attf to assure a clean dma start, also disable
581*30138Ssam 	   attention interrupt
582*30138Ssam 	*/
583*30138Ssam     	dr->dr_pulse = (ushort)(RDMA|RATN|RMSK);  /* Use pulse register */
584*30138Ssam     	dr->dr_cstat = (GO|CYCL);		  /* GO...... */
585*30138Ssam 
586*30138Ssam 	/* Wait for DMA complete; REDY and DMAF are true in ISR */
587*30138Ssam 	wait = 0;
588*30138Ssam 	while ((result=(dr->dr_cstat & (REDY | DMAF))) != (REDY|DMAF)) {
589*30138Ssam 		printf("\n\tWait for DMA complete...ISR : %lx",result);
590*30138Ssam 		if (++wait > 5) {
591*30138Ssam 			printf("\n\t DMA output fails...timeout!!, ISR:%lx",
592*30138Ssam 				result);
593*30138Ssam 			return;
594*30138Ssam 		}
595*30138Ssam 	}
596*30138Ssam 
597*30138Ssam 	result = dr->dr_data & 0xffff;		/* Read last word output */
598*30138Ssam 	if (result != 0xCCCC) {
599*30138Ssam 		printf("\n\t Fails, expected : %lx --- actual : %lx",
600*30138Ssam 			0xCCCC,result);
601*30138Ssam 		return;
602*30138Ssam 	}
603*30138Ssam 
604*30138Ssam 	printf("OK\n\t DMA input ...");
605*30138Ssam 
606*30138Ssam dmain:
607*30138Ssam 	dr->dr_data = 0x1111;		/* DMA input data */
608*30138Ssam 	/* Setup normal DMA */
609*30138Ssam 	baddr = (long)vtoph(0,tstpat);		/* Virtual --> physical */
610*30138Ssam     	dr->dr_walo = (ushort)((baddr >> 1) & 0xffff);
611*30138Ssam     	dr->dr_wahi = (ushort)((baddr >> 17) & 0x7fff);
612*30138Ssam 
613*30138Ssam     	/* Set DMA range count: (number of words - 1) */
614*30138Ssam     	dr->dr_range = (ushort)(DMATBL - 1);
615*30138Ssam 
616*30138Ssam     	/* Set  address modifier code to be used for DMA access to memory */
617*30138Ssam     	dr->dr_addmod = (char)DRADDMOD;
618*30138Ssam 	/* Set FCN1 in ICR to DMA in*/
619*30138Ssam 	dr->dr_cstat = FCN1;
620*30138Ssam 
621*30138Ssam 	if (!(dra->dr_flags & DR_LOOPTST)) {
622*30138Ssam 		/* Use pulse reg */
623*30138Ssam     		dr->dr_pulse = (ushort)(RDMA|RATN|RMSK|CYCL|GO);
624*30138Ssam 		/* Wait for DMA complete; REDY and DMAF are true in ISR */
625*30138Ssam 		wait = 0;
626*30138Ssam 		while ((result=(dr->dr_cstat & (REDY | DMAF)))
627*30138Ssam 						!= (REDY|DMAF)) {
628*30138Ssam 			printf("\n\tWait for DMA to complete...ISR:%lx",result);
629*30138Ssam 			if (++wait > 5) {
630*30138Ssam 				printf("\n\t DMA input timeout!!, ISR:%lx",
631*30138Ssam 					result);
632*30138Ssam 				return;
633*30138Ssam 			}
634*30138Ssam 		}
635*30138Ssam 	}
636*30138Ssam 	else  {
637*30138Ssam 		/* Enable DMA e-o-r interrupt */
638*30138Ssam     		dr->dr_pulse = (ushort)(IENB|RDMA|RATN|CYCL|GO);
639*30138Ssam 		/* Wait for DMA complete; DR_LOOPTST is false in dra->dr_flags*/
640*30138Ssam 		wait = 0;
641*30138Ssam 		while (dra->dr_flags & DR_LOOPTST) {
642*30138Ssam 			result = dr->dr_cstat & 0xffff;
643*30138Ssam 			printf("\n\tWait for DMA e-o-r intr...ISR:%lx",result);
644*30138Ssam 			if (++wait > 7) {
645*30138Ssam 				printf("\n\t DMA e-o-r timeout!!, ISR:%lx",
646*30138Ssam 					result);
647*30138Ssam 				dra->dr_flags &= ~DR_LOOPTST;
648*30138Ssam 				return;
649*30138Ssam 			}
650*30138Ssam 		}
651*30138Ssam 		dra->dr_flags |= DR_LOOPTST;
652*30138Ssam 	}
653*30138Ssam 
654*30138Ssam 	mtpr(tstpat,P1DC);			/* Purge cache */
655*30138Ssam 	mtpr((0x3ff+(long)tstpat),P1DC);
656*30138Ssam 	for(ix=0;ix<DMATBL;ix++) {
657*30138Ssam 		if (tstpat[ix] != 0x1111) {
658*30138Ssam 			printf("\n\t Fails, ix:%ld,expected : %lx --- actual : %lx",
659*30138Ssam 				ix,0x1111,tstpat[ix]);
660*30138Ssam 			return;
661*30138Ssam 		}
662*30138Ssam 	}
663*30138Ssam 	if (!(dra->dr_flags & DR_LOOPTST)) {
664*30138Ssam 		dra->dr_flags |= DR_LOOPTST;
665*30138Ssam 		printf(" OK..\n\tDMA end of range interrupt...");
666*30138Ssam 		goto dmain;
667*30138Ssam 	}
668*30138Ssam 
669*30138Ssam 
670*30138Ssam 	printf(" OK..\n\tAttention interrupt....");
671*30138Ssam 	/* Pulse FCN2 in pulse register with IENB */
672*30138Ssam     	dr->dr_pulse = (ushort)(IENB|RDMA);
673*30138Ssam     	dr->dr_pulse = (ushort)FCN2;
674*30138Ssam 
675*30138Ssam 	/* Wait for ATTN interrupt; DR_LOOPTST is false in dra->dr_flags*/
676*30138Ssam 	wait = 0;
677*30138Ssam 	while (dra->dr_flags & DR_LOOPTST) {
678*30138Ssam 		result = dr->dr_cstat & 0xffff;
679*30138Ssam 		printf("\n\tWait for Attention intr...ISR:%lx",result);
680*30138Ssam 		if (++wait > 7) {
681*30138Ssam 			printf("\n\t Attention interrupt timeout!!, ISR:%lx",
682*30138Ssam 				result);
683*30138Ssam 			dra->dr_flags &= ~DR_LOOPTST;
684*30138Ssam 			return;
685*30138Ssam 		}
686*30138Ssam 	}
687*30138Ssam 	dra->dr_flags &= ~DR_LOOPTST;
688*30138Ssam 	printf(" OK..\n\tDone...");
689*30138Ssam }
690*30138Ssam 
69129651Ssam /* Reset state on Unibus reset */
69229651Ssam drreset(uban)
69329651Ssam int uban;
69429651Ssam {
69529651Ssam     register int i;
69629651Ssam     register struct vba_device *ui;
69729651Ssam     register struct dr_aux *dra;
69829651Ssam 
69929651Ssam     for (i = 0; i < NDR; i++, dra++) {
70029651Ssam 	if (   (ui = drinfo[i]) == 0
70129651Ssam 	    || !ui->ui_alive
70229651Ssam 	    || ui->ui_vbanum != uban
70329651Ssam 	   )
70429651Ssam 	    continue;
70529651Ssam 	printf("\ndrreset: %ld",i);
70629651Ssam 	/* Do something; reset board */
70729651Ssam     }
70829651Ssam     return;
70929651Ssam }
71029651Ssam 
71129651Ssam /*
71229651Ssam  * An interrupt is caused either by an error,
71329651Ssam  * base address overflow, or transfer complete
71429651Ssam  */
71529651Ssam drintr (unit)
71629651Ssam register long unit;
71729651Ssam {
71829651Ssam     register struct dr_aux *dra = &dr_aux[unit];
71929651Ssam     register struct rsdevice *rsaddr = RSADDR(unit);
72029651Ssam     register struct buf *bp;
72129651Ssam     register short status, csrtmp;
72229651Ssam 
72329651Ssam     status = rsaddr->dr_cstat & 0xffff;		/* get board status register */
72429651Ssam     dra->dr_istat = status;
72529651Ssam 
72629651Ssam #ifdef DR_DEBUG
72729651Ssam     if (DR11 & 2)
72829651Ssam     	printf("\ndrintr: dr11 status : %lx",status & 0xffff);
72929651Ssam #endif
73029651Ssam 
73129651Ssam     if (dra->dr_flags & DR_LOOPTST) {
73229651Ssam 	/* Controller is doing loopback test */
73329651Ssam     	dra->dr_flags &= ~DR_LOOPTST;
73429651Ssam 	return;
73529651Ssam     }
73629651Ssam 
73729651Ssam     /* Make sure this is not a stray interrupt; at least one of dmaf or attf
73829651Ssam        must be set. Note that if the dr11 interrupt enable latch is reset
73929651Ssam        during a hardware interrupt ack sequence, and by the we get to this
74029651Ssam        point in the interrupt code it will be 0. This is done to give the
74129651Ssam        programmer some control over how the two more-or-less independent
74229651Ssam        interrupt sources on the board are handled.
74329651Ssam        If the attention flag is set when drstrategy() is called to start a
74429651Ssam        dma read or write an interrupt will be generated as soon as the
74529651Ssam        strategy routine enables interrupts for dma end-of-range. This will
74629651Ssam        cause execution of the interrupt routine (not necessarily bad) and
74729651Ssam        will cause the interrupt enable mask to be reset (very bad since the
74829651Ssam        dma end-of-range condition will not be able to generate an interrupt
74929651Ssam        when it occurs) causing the dma operation to time-out (even though
75029651Ssam        the dma transfer will be done successfully) or hang the process if a
75129651Ssam        software time-out capability is not implemented. One way to avoid
75229651Ssam        this situation is to check for a pending attention interrupt (attf
75329651Ssam        set) by calling drioctl() before doing a read or a write. For the
75429651Ssam        time being this driver will solve the problem by clearing the attf
75529651Ssam        flag in the status register before enabling interrupts in drstrategy().
75629651Ssam 
75729651Ssam        **** The IKON 10084 for which this driver is written will set both
75829651Ssam        attf and dmaf if dma is terminated by an attention pulse. This will
75929651Ssam        cause a wakeup(&dr_aux), which will be ignored since it is not being
76029651Ssam        waited on, and an iodone(bp) which is the desired action. Some other
76129651Ssam        dr11 emulators, in particular the IKON 10077 for the Multibus, donot
76229651Ssam        dmaf in this case. This may require some addtional code in the inter-
76329651Ssam        rupt routine to ensure that en iodone(bp) is issued when dma is term-
76429651Ssam        inated by attention.
76529651Ssam     */
76629651Ssam 
76729651Ssam     bp = dra->dr_actf;
76829651Ssam     if (!(status & (ATTF | DMAF))) {
76929651Ssam 	printf("\ndrintr: Stray interrupt, dr11 status : %lx",status);
77029651Ssam 	return;
77129651Ssam     }
77229651Ssam     if (status & DMAF) {
77329651Ssam 	/* End-of-range interrupt */
77429651Ssam 	dra->dr_flags |= DR_DMAX;
77529651Ssam 
77629651Ssam #ifdef DR_DEBUG
77729651Ssam     if (DR11 & 2)
77829651Ssam 	printf("\ndrintr: e-o-r interrupt,cstat:%lx,dr_flags:%lx",
77929651Ssam 		status&0xffff,dra->dr_flags & DR_ACTV);
78029651Ssam #endif
78129651Ssam 	if (!(dra->dr_flags & DR_ACTV)) {
78229651Ssam 		/* We are not doing DMA !! */
78329651Ssam 		bp->b_flags |= B_ERROR;
78429651Ssam 	}
78529651Ssam 	else {
78629651Ssam 		if (dra->dr_op == DR_READ) mtpr(bp->b_un.b_addr,P1DC);
78729651Ssam 		dra->dr_bycnt -= bp->b_bcount;
78829651Ssam 		if (dra->dr_bycnt >0) {
78929651Ssam 			bp->b_un.b_addr += bp->b_bcount;
79029651Ssam 			bp->b_bcount = (dra->dr_bycnt > NBPG) ? NBPG:
79129651Ssam 					dra->dr_bycnt;
79229651Ssam 			drstart(rsaddr,dra,bp);
79329651Ssam 			return;
79429651Ssam 		}
79529651Ssam 	}
79629651Ssam 	dra->dr_flags &= ~DR_ACTV;
79729651Ssam 	wakeup(dra);			/* Wakeup proc waiting in drwait() */
79829651Ssam 	rsaddr->dr_pulse = (RPER|RDMA|RATN);	/* reset dma e-o-r flag */
79929651Ssam     }
80029651Ssam 
80129651Ssam     /* Now test for attention interrupt -- It may be set in addition to
80229651Ssam        the dma e-o-r interrupt. If we get one we will issue a wakeup to
80329651Ssam        the drioctl() routine which is presumable waiting for one.
80429651Ssam        The program may have to monitor the attention interrupt received
80529651Ssam        flag in addition to doing waits for the interrupt. Futhermore,
80629651Ssam        interrupts are not enabled unless dma is in progress or drioctl()
80729651Ssam        has been called to wait for attention -- this may produce some
80829651Ssam        strange results if attf is set on the dr11 when a read or a write
80929651Ssam        is initiated, since that will enables interrupts.
81029651Ssam        **** The appropriate code for this interrupt routine will probably
81129651Ssam        be rather application dependent.
81229651Ssam     */
81329651Ssam 
81429651Ssam     if (status & ATTF) {
81529651Ssam 	dra->dr_flags |= DR_ATRX;
81629651Ssam 	dra->dr_flags &= ~DR_ATWT;
81729651Ssam 	rsaddr->dr_cstat = RATN;	/* reset attention flag */
81829651Ssam 	wakeup((caddr_t)&dra->dr_cmd);
81929651Ssam 	/* Some applications which use attention to terminate dma may also
82029651Ssam 	   want to issue an iodone() here to wakeup physio().
82129651Ssam  	*/
82229651Ssam     }
82329651Ssam     return;
82429651Ssam }
82529651Ssam 
82629651Ssam unsigned
82729651Ssam drminphys(bp)
82829651Ssam struct buf *bp;
82929651Ssam {
83029651Ssam     if (bp->b_bcount > 65536)
83129651Ssam 	bp->b_bcount = 65536;
83229651Ssam }
83329651Ssam 
83429651Ssam /*
83529651Ssam  *  This routine performs the device unique operations on the DR11W
83629651Ssam  *  it is passed as an argument to and invoked by physio
83729651Ssam  */
83829651Ssam drstrategy (bp)
83929651Ssam register struct buf *bp;
84029651Ssam {
84129651Ssam     register int s;
84229651Ssam     int unit = RSUNIT(bp->b_dev);
84329651Ssam     register struct rsdevice *rsaddr = RSADDR(unit);
84429651Ssam     register struct dr_aux *dra = &dr_aux[unit];
84529651Ssam     register short go = 0;
84629651Ssam     register long baddr, ok;
84729651Ssam #ifdef DR_DEBUG
84829651Ssam     register char *caddr;
84929651Ssam     long drva();
85029651Ssam #endif
85129651Ssam 
85229651Ssam 
85329651Ssam     if (!(dra->dr_flags & DR_OPEN)) {
85429651Ssam 	/* Device not open */
85529651Ssam 	bp->b_error = ENXIO;
85629651Ssam 	bp->b_flags |= B_ERROR;
85729651Ssam 	iodone (bp);
85829651Ssam 	return;
85929651Ssam     }
86029651Ssam 
86129651Ssam     while (dra->dr_flags & DR_ACTV) {
86229651Ssam 	/* Device is active; should never be in here... */
86329651Ssam 	sleep((caddr_t)&dra->dr_flags,DRPRI);
86429651Ssam     }
86529651Ssam 
86629651Ssam     dra->dr_actf = bp;
86729651Ssam 
86829651Ssam #ifdef DR_DEBUG
86929651Ssam     drva(dra,bp->b_proc,bp->b_un.b_addr,bp->b_bcount);
87029651Ssam #endif
87129651Ssam 
87229651Ssam     dra->dr_oba = bp->b_un.b_addr;	/* Save original addr, count */
87329651Ssam     dra->dr_obc = bp->b_bcount;
87429651Ssam     dra->dr_bycnt = bp->b_bcount;	/* Save xfer count used by drintr() */
87529651Ssam 
87629651Ssam     if ((((long)bp->b_un.b_addr & 0x3fffffff) >> PGSHIFT) !=
87729651Ssam 	((((long)bp->b_un.b_addr & 0x3fffffff) + bp->b_bcount) >> PGSHIFT)) {
87829651Ssam     	bp->b_bcount = NBPG - (((long)bp->b_un.b_addr) & PGOFSET);
87929651Ssam     }
88029651Ssam 
88129651Ssam     dra->dr_flags |= DR_ACTV;	/* Mark it active (use in intr handler) */
88229651Ssam     s = SPL_UP();
88329651Ssam     drstart(rsaddr,dra,bp);
88429651Ssam     splx(s);
88529651Ssam 
88629651Ssam     ok = drwait(rsaddr,dra);
88729651Ssam #ifdef DR_DEBUG
88829651Ssam     if (DR11 & 0x40) {
88929651Ssam 	caddr = (char *)dra->dr_oba;
89029651Ssam     	if (dra->dr_op == DR_READ)
89129651Ssam 		printf("\nAfter read: (%lx)(%lx)",caddr[0]&0xff,caddr[1]&0xff);
89229651Ssam     }
89329651Ssam #endif
89429651Ssam     dra->dr_flags &= ~DR_ACTV;		/* Clear active flag */
89529651Ssam     bp->b_un.b_addr = dra->dr_oba;	/* Restore original addr, count */
89629651Ssam     bp->b_bcount = dra->dr_obc;
89729651Ssam 
89829651Ssam     if (!ok) bp->b_flags |= B_ERROR;
89929651Ssam     iodone(bp);				/* Mark buffer B_DONE,so physstrat()
90029651Ssam 					   in ml/machdep.c won't sleep */
90129651Ssam     wakeup((caddr_t)&dra->dr_flags);
90229651Ssam 
90329651Ssam     /* Return to the calling program (physio()). Physio() will sleep
90429651Ssam        until awaken by a call to iodone() in the interupt handler --
90529651Ssam        which will be called by the dispatcher when it receives dma
90629651Ssam        end-of-range interrupt.
90729651Ssam     */
90829651Ssam     return;
90929651Ssam }
91029651Ssam 
91129651Ssam drwait(rs,dr)
91229651Ssam register struct rsdevice *rs;
91329651Ssam register struct dr_aux *dr;
91429651Ssam {
91529651Ssam 	register long status, s;
91629651Ssam 
91729651Ssam 	s = SPL_UP();
91829651Ssam     	while (dr->dr_flags & DR_ACTV)
91929651Ssam 		sleep((caddr_t)dr,DRPRI);
92029651Ssam 	splx(s);
92129651Ssam 
92229651Ssam 	if (dr->dr_flags & DR_TMDM) {
92329651Ssam 		/* DMA timed out */
92429651Ssam 		dr->dr_flags &= ~DR_TMDM;
92529651Ssam 		return(0);
92629651Ssam 	}
92729651Ssam 	else {
92829651Ssam 		if (rs->dr_cstat & (PERR|BERR|TERR)) {
92929651Ssam 			(dr->dr_actf)->b_flags |= B_ERROR;
93029651Ssam 			return(0);
93129651Ssam 		}
93229651Ssam 	}
93329651Ssam 	dr->dr_flags &= ~DR_DMAX;
93429651Ssam 	return(1);
93529651Ssam }
93629651Ssam 
93729651Ssam 
93829651Ssam drrwtimo(tinfo)
93929651Ssam register unsigned long tinfo;
94029651Ssam /*
94129651Ssam  * 	The lower 8-bit of tinfo is the minor device number, the
94229651Ssam  *	remaining higher 8-bit is the current timout number
94329651Ssam */
94429651Ssam {	register long unit = tinfo & 0xff;
94529651Ssam 	register struct dr_aux *dr = &dr_aux[unit];
94629651Ssam 	register struct rsdevice *rs = dr->dr_addr;
94729651Ssam 
94829651Ssam 	/* If this is not the timeout that drwrite/drread is waiting
94929651Ssam 	   for then we should just go away */
95029651Ssam 	if ((tinfo & (~0xff)) != (dr->currenttimo << 8)) return;
95129651Ssam 
95229651Ssam 	/* Mark the device timed out */
95329651Ssam 	dr->dr_flags |= DR_TMDM;
95429651Ssam 	dr->dr_flags &= ~DR_ACTV;
95529651Ssam 	rs->dr_pulse = RMSK;			/* Inihibit interrupt */
95629651Ssam 	rs->dr_pulse = (RPER|RDMA|RATN|IENB);	/* Clear DMA logic */
95729651Ssam 
95829651Ssam 	/* Some applications will not issue a master after dma timeout,
95929651Ssam 	   since doing so sends an INIT H pulse to the external device,
96029651Ssam 	   which may produce undesirable side-effects.  */
96129651Ssam 
96229651Ssam 	/* Wake up process waiting in drwait() and flag the error */
96329651Ssam 	(dr->dr_actf)->b_flags |= B_ERROR;
96429651Ssam 	wakeup((caddr_t)dr->dr_cmd);
96529651Ssam }
96629651Ssam 
96729651Ssam 
96829651Ssam /*
96929651Ssam  *	Kick the driver every second
97029651Ssam */
97129651Ssam drtimo(dev)
97229651Ssam dev_t dev;
97329651Ssam {
97429651Ssam     	register int unit = RSUNIT(dev);
97529651Ssam 	register struct dr_aux *dr;
97629651Ssam 
97729651Ssam     	dr = &dr_aux[unit];
97829651Ssam 	if (dr->dr_flags & DR_OPEN)
97929651Ssam 		timeout(drtimo,(caddr_t)dev,hz);
98029651Ssam 	wakeup((caddr_t)dr);	/* Wakeup any process waiting for interrupt */
98129651Ssam }
98229651Ssam 
98329651Ssam 
98429651Ssam #ifdef DR_DEBUG
98529651Ssam 
98629651Ssam drva(dra,p,va,bcnt)
98729651Ssam struct dr_aux *dra;
98829651Ssam struct proc *p;
98929651Ssam char *va;
99029651Ssam long bcnt;
99129651Ssam {	register long first, last , np;
99229651Ssam 
99329651Ssam 	if (DR11 & 0x20)  {
99429651Ssam 		first = ((long)(vtoph(p,va))) >> 10;
99529651Ssam 		last = ((long)(vtoph(p,va+bcnt))) >> 10;
99629651Ssam 		np = bcnt / 0x3ff;
99729651Ssam 		printf("\ndrva: (op:%ld)(first:%ld)(last:%ld)(np:%ld)(cnt:%ld)",
99829651Ssam 			dra->dr_op,first,last,np,bcnt);
99929651Ssam 	}
100029651Ssam }
100129651Ssam #endif
100229651Ssam 
100329651Ssam 
100429651Ssam drstart(rsaddr,dra,bp)
100529651Ssam register struct rsdevice *rsaddr;
100629651Ssam register struct dr_aux *dra;
100729651Ssam register struct buf *bp;
100829651Ssam {	register long baddr;
100929651Ssam 	ushort go;
101029651Ssam 	register char *caddr;
101129651Ssam 
101229651Ssam #ifdef DR_DEBUG
101329651Ssam 	if ((dra->dr_op == DR_READ) && (DR11 & 8)) {
101429651Ssam 		printf("\ndrstart: READ, bcnt:%ld",bp->b_bcount);
101529651Ssam     		caddr = (char *)bp->b_un.b_addr;
101629651Ssam 		printf(",(%lx)(%lx)",caddr[0]&0xff,caddr[1]&0xff);
101729651Ssam 	}
101829651Ssam #endif
101929651Ssam     /* we are doing raw IO, bp->b_un.b_addr is user's address */
102029651Ssam     baddr = (long)vtoph(bp->b_proc,(caddr_t)bp->b_un.b_addr);
102129651Ssam 
102229651Ssam     /* Set DMA address into DR11 interace registers: DR11 requires that
102329651Ssam        the address be right shifted 1 bit position before it is written
102429651Ssam        to the board (The board will left shift it one bit position before
102529651Ssam        it places the address on the bus
102629651Ssam     */
102729651Ssam     rsaddr->dr_walo = (ushort)((baddr >> 1) & 0xffff);
102829651Ssam     rsaddr->dr_wahi = (ushort)((baddr >> 17) & 0x7fff);
102929651Ssam 
103029651Ssam     /* Set DMA range count: (number of words - 1) */
103129651Ssam     rsaddr->dr_range = (ushort)((bp->b_bcount >> 1) - 1);
103229651Ssam 
103329651Ssam     /* Set address modifier code to be used for DMA access to memory */
103429651Ssam     rsaddr->dr_addmod = (char)DRADDMOD;
103529651Ssam 
103629651Ssam     /* Now determine whether this is a read or a write. ***** This is
103729651Ssam        probably only usefull for link mode operation, since dr11 doesnot
103829651Ssam        controll the direction of data transfer. The C1 control input
103929651Ssam        controls whether the hardware is doing a read or a write. In link
104029651Ssam        mode this is controlled by function 1 latch (looped back by the
104129651Ssam        cable) and could be set the program. In the general case, the dr11
104229651Ssam        doesnot know in advance what the direction of transfer is - although
104329651Ssam        the program and protocol logic probably is
104429651Ssam     */
104529651Ssam 
104629651Ssam #ifdef DR_DEBUG
104729651Ssam    if (DR11 & 1)
104829651Ssam     printf("\ndrstrat: about to GO..,dr_cmd:%lx,drstat:%lx,drcnt:%ld,cdata:%lx,OP:%ld",
104929651Ssam 	dra->dr_cmd,rsaddr->dr_cstat,rsaddr->dr_range,rsaddr->dr_data,dra->dr_op);
105029651Ssam #endif
105129651Ssam 
105229651Ssam     /* Update function latches may have been done already by drioctl() if
105329651Ssam        request from drioctl()
105429651Ssam     */
105529651Ssam     if (dra->dr_cmd & DR_DFCN) {
105629651Ssam 	/* deferred function write */
105729651Ssam     	dra->dr_cmd &= ~DR_DFCN;	/* Clear request */
105829651Ssam 	go = dra->dr_cmd & DR_FMSK;	/* mask out fcn bits */
105929651Ssam 	rsaddr->dr_cstat = go;		/* Write it to the board */
106029651Ssam     }
106129651Ssam 
106229651Ssam     /* Clear dmaf and attf to assure a clean dma start */
106329651Ssam     rsaddr->dr_pulse = (ushort)(RATN|RDMA|RPER);
106429651Ssam     rsaddr->dr_cstat = (ushort)(IENB|GO|CYCL|dra->dr_op); /* GO...... */
106529651Ssam 
106629651Ssam     /* Now check for software cycle request -- usually by transmitter in
106729651Ssam        link mode.
106829651Ssam     */
106929651Ssam     if (dra->dr_cmd & DR_PCYL) {
107029651Ssam     	dra->dr_cmd &= ~DR_PCYL;	/* Clear request */
107129651Ssam 	rsaddr->dr_pulse = CYCL;	/* Use pulse register again */
107229651Ssam     }
107329651Ssam 
107429651Ssam     /* Now check for deferred ACLO FCNT2 pulse request -- usually to tell
107529651Ssam        the transmitter (via its attention) that we have enabled dma.
107629651Ssam     */
107729651Ssam     if (dra->dr_cmd & DR_DACL) {
107829651Ssam     	dra->dr_cmd &= ~DR_DACL;	/* Clear request */
107929651Ssam 	rsaddr->dr_pulse = FCN2;	/* Use pulse register again */
108029651Ssam     }
108129651Ssam }
108229651Ssam 
108329651Ssam #endif  NDR
1084