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