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