134406Skarels /*
235514Sbostic * Copyright (c) 1988 The Regents of the University of California.
335514Sbostic * All rights reserved.
435514Sbostic *
535514Sbostic * This code is derived from software contributed to Berkeley by
635514Sbostic * Computer Consoles Inc.
735514Sbostic *
844534Sbostic * %sccs.include.redist.c%
935514Sbostic *
10*45798Sbostic * @(#)dr.c 7.9 (Berkeley) 12/16/90
1134406Skarels */
1229651Ssam
1329651Ssam #include "dr.h"
1429651Ssam #if NDR > 0
1530294Ssam /*
1630294Ssam * DRV11-W DMA interface driver.
1730294Ssam *
1830227Ssam * UNTESTED WITH 4.3
1929651Ssam */
20*45798Sbostic #include "../include/mtpr.h"
21*45798Sbostic #include "../include/pte.h"
2229651Ssam
23*45798Sbostic #include "sys/param.h"
24*45798Sbostic #include "sys/conf.h"
25*45798Sbostic #include "sys/user.h"
26*45798Sbostic #include "sys/proc.h"
27*45798Sbostic #include "sys/map.h"
28*45798Sbostic #include "sys/ioctl.h"
29*45798Sbostic #include "sys/buf.h"
30*45798Sbostic #include "sys/vm.h"
31*45798Sbostic #include "sys/kernel.h"
3229651Ssam
33*45798Sbostic #include "../vba/vbavar.h"
34*45798Sbostic #include "../vba/drreg.h"
3529651Ssam
3629651Ssam #define YES 1
3729651Ssam #define NO 0
3829651Ssam
3929651Ssam struct vba_device *drinfo[NDR];
4029651Ssam struct dr_aux dr_aux[NDR];
4129651Ssam
4229651Ssam unsigned drminphys();
4330294Ssam int drprobe(), drintr(), drattach(), drtimo(), drrwtimo();
4430294Ssam int drstrategy();
4530294Ssam extern struct vba_device *drinfo[];
4630294Ssam static long drstd[] = { 0 };
4729651Ssam struct vba_driver drdriver =
4830294Ssam { drprobe, 0, drattach, 0, drstd, "rs", drinfo };
4929651Ssam
5029651Ssam #define RSUNIT(dev) (minor(dev) & 7)
5129651Ssam #define SPL_UP spl5
5229651Ssam
5329651Ssam /* -------- Per-unit data -------- */
5429651Ssam
5529651Ssam extern struct dr_aux dr_aux[];
5629651Ssam
5729651Ssam #ifdef DR_DEBUG
5830294Ssam long DR11 = 0;
5929651Ssam #endif
6029651Ssam
drprobe(reg,vi)6129651Ssam drprobe(reg, vi)
6230294Ssam caddr_t reg;
6330294Ssam struct vba_device *vi;
6429651Ssam {
6530294Ssam register int br, cvec; /* must be r12, r11 */
6630294Ssam struct rsdevice *dr;
6729651Ssam
6830294Ssam #ifdef lint
6930294Ssam br = 0; cvec = br; br = cvec;
7030294Ssam drintr(0);
7129651Ssam #endif
7230294Ssam if (badaddr(reg, 2))
7330294Ssam return (0);
7430294Ssam dr = (struct rsdevice *)reg;
7530294Ssam dr->dr_intvect = --vi->ui_hd->vh_lastiv;
7629651Ssam #ifdef DR_DEBUG
7730294Ssam printf("dprobe: Set interrupt vector %lx and init\n",dr->dr_intvec);
7829651Ssam #endif
7930294Ssam /* generate interrupt here for autoconfig */
8030294Ssam dr->dr_cstat = MCLR; /* init board and device */
8129651Ssam #ifdef DR_DEBUG
8230294Ssam printf("drprobe: Initial status %lx\n", dr->dr_cstat);
8329651Ssam #endif
8430294Ssam br = 0x18, cvec = dr->dr_intvect; /* XXX */
8530294Ssam return (sizeof (struct rsdevice)); /* DR11 exist */
8629651Ssam }
8729651Ssam
8829651Ssam /* ARGSUSED */
8929651Ssam drattach(ui)
9030294Ssam struct vba_device *ui;
9129651Ssam {
9230294Ssam register struct dr_aux *rsd;
9329651Ssam
9430294Ssam rsd = &dr_aux[ui->ui_unit];
9530294Ssam rsd->dr_flags = DR_PRES; /* This dr11 is present */
9630294Ssam rsd->dr_addr = (struct rsdevice *)ui->ui_addr; /* Save addr of this dr11 */
9730294Ssam rsd->dr_istat = 0;
9830294Ssam rsd->dr_bycnt = 0;
9930294Ssam rsd->dr_cmd = 0;
10030294Ssam rsd->currenttimo = 0;
10129651Ssam }
10229651Ssam
10330294Ssam /*ARGSUSED*/
dropen(dev,flag)10430294Ssam dropen(dev, flag)
10530294Ssam dev_t dev;
10630294Ssam int flag;
10729651Ssam {
10830294Ssam register int unit = RSUNIT(dev);
10930294Ssam register struct rsdevice *dr;
11030294Ssam register struct dr_aux *rsd;
11129651Ssam
11230294Ssam if (drinfo[unit] == 0 || !drinfo[unit]->ui_alive)
11330294Ssam return (ENXIO);
11430294Ssam dr = RSADDR(unit);
11530294Ssam rsd = &dr_aux[unit];
11630294Ssam if (rsd->dr_flags & DR_OPEN) {
11729651Ssam #ifdef DR_DEBUG
11830294Ssam printf("\ndropen: dr11 unit %ld already open",unit);
11929651Ssam #endif
12030294Ssam return (ENXIO); /* DR11 already open */
12130294Ssam }
12230294Ssam rsd->dr_flags |= DR_OPEN; /* Mark it OPEN */
12330294Ssam rsd->dr_istat = 0; /* Clear status of previous interrupt */
12430294Ssam rsd->rtimoticks = hz; /* Set read no stall timout to 1 sec */
12530294Ssam rsd->wtimoticks = hz*60; /* Set write no stall timout to 1 min */
12630294Ssam dr->dr_cstat = DR_ZERO; /* Clear function & latches */
12730294Ssam dr->dr_pulse = (RDMA | RATN); /* clear leftover attn & e-o-r flags */
12830294Ssam drtimo(dev); /* start the self kicker */
12930294Ssam return (0);
13029651Ssam }
13129651Ssam
drclose(dev)13229651Ssam drclose (dev)
13330294Ssam dev_t dev;
13429651Ssam {
13530294Ssam register int unit = RSUNIT(dev);
13630294Ssam register struct dr_aux *dra;
13730294Ssam register struct rsdevice *rs;
13830294Ssam register short s;
13929651Ssam
14030294Ssam dra = &dr_aux[unit];
14130294Ssam if ((dra->dr_flags & DR_OPEN) == 0) {
14229651Ssam #ifdef DR_DEBUG
14330294Ssam printf("\ndrclose: DR11 device %ld not open",unit);
14429651Ssam #endif
14530294Ssam return;
14630294Ssam }
14730294Ssam dra->dr_flags &= ~(DR_OPEN|DR_ACTV);
14830294Ssam rs = dra->dr_addr;
14930294Ssam s = SPL_UP();
15030294Ssam rs->dr_cstat = DR_ZERO;
15130294Ssam if (dra->dr_buf.b_flags & B_BUSY) {
15230294Ssam dra->dr_buf.b_flags &= ~B_BUSY;
15330294Ssam wakeup((caddr_t)&dra->dr_buf.b_flags);
15430294Ssam }
15530294Ssam splx(s);
15640735Skarels return (0);
15729651Ssam }
15829651Ssam
15929651Ssam
16029651Ssam /* drread() works exactly like drwrite() except that the
16129651Ssam B_READ flag is used when physio() is called
16229651Ssam */
drread(dev,uio)16329651Ssam drread (dev, uio)
16430294Ssam dev_t dev;
16530294Ssam struct uio *uio;
16629651Ssam { register struct dr_aux *dra;
16729651Ssam register struct buf *bp;
16830294Ssam register int spl, err;
16930294Ssam register int unit = RSUNIT(dev);
17029651Ssam
17130294Ssam if (uio->uio_iov->iov_len <= 0 || /* Negative count */
17230294Ssam uio->uio_iov->iov_len & 1 || /* odd count */
17330294Ssam (int)uio->uio_iov->iov_base & 1) /* odd destination address */
17430294Ssam return (EINVAL);
17529651Ssam #ifdef DR_DEBUG
17630294Ssam if (DR11 & 8)
17730294Ssam printf("\ndrread: (len:%ld)(base:%lx)",
17830294Ssam uio->uio_iov->iov_len,(int)uio->uio_iov->iov_base);
17929651Ssam #endif
18030294Ssam dra = &dr_aux[RSUNIT(dev)];
18130294Ssam dra->dr_op = DR_READ;
18230294Ssam bp = &dra->dr_buf;
18330294Ssam bp->b_resid = 0;
18430294Ssam if (dra->dr_flags & DR_NORSTALL) {
18530294Ssam /*
18630294Ssam * We are in no stall mode, start the timer,
18730294Ssam * raise IPL so nothing can stop us once the
18830294Ssam * timer's running
18930294Ssam */
19030294Ssam spl = SPL_UP();
19130294Ssam timeout(drrwtimo, (caddr_t)((dra->currenttimo<<8) | unit),
19230294Ssam (int)dra->rtimoticks);
19330294Ssam err = physio(drstrategy, bp, dev,B_READ, drminphys, uio);
19430294Ssam splx(spl);
19530294Ssam if (err)
19630294Ssam return (err);
19730294Ssam dra->currenttimo++; /* Update current timeout number */
19830294Ssam /* Did we timeout */
19943384Smckusick if (dra->dr_flags & DR_TMDM)
20030294Ssam dra->dr_flags &= ~DR_TMDM; /* Clear timeout flag */
20130294Ssam return (err);
20229651Ssam }
20330294Ssam return (physio(drstrategy, bp, dev,B_READ, drminphys, uio));
20429651Ssam }
20529651Ssam
drwrite(dev,uio)20630294Ssam drwrite(dev, uio)
20730294Ssam dev_t dev;
20830294Ssam struct uio *uio;
20929651Ssam { register struct dr_aux *dra;
21029651Ssam register struct buf *bp;
21130294Ssam register int unit = RSUNIT(dev);
21230294Ssam int spl, err;
21329651Ssam
21430294Ssam if (uio->uio_iov->iov_len <= 0 || uio->uio_iov->iov_len & 1 ||
21530294Ssam (int)uio->uio_iov->iov_base & 1)
21630294Ssam return (EINVAL);
21729651Ssam #ifdef DR_DEBUG
21830294Ssam if (DR11 & 4)
21930294Ssam printf("\ndrwrite: (len:%ld)(base:%lx)",
22030294Ssam uio->uio_iov->iov_len,(int)uio->uio_iov->iov_base);
22129651Ssam #endif
22230294Ssam dra = &dr_aux[RSUNIT(dev)];
22330294Ssam dra->dr_op = DR_WRITE;
22430294Ssam bp = &dra->dr_buf;
22530294Ssam bp->b_resid = 0;
22630294Ssam if (dra->dr_flags & DR_NOWSTALL) {
22730294Ssam /*
22830294Ssam * We are in no stall mode, start the timer,
22930294Ssam * raise IPL so nothing can stop us once the
23030294Ssam * timer's running
23130294Ssam */
23230294Ssam spl = SPL_UP();
23330294Ssam timeout(drrwtimo,(caddr_t)((dra->currenttimo<<8) | unit),
23430294Ssam (int)dra->wtimoticks);
23530294Ssam err = physio (drstrategy, bp, dev,B_WRITE, drminphys, uio);
23630294Ssam splx(spl);
23730294Ssam if (err)
23830294Ssam return (err);
23930294Ssam dra->currenttimo++; /* Update current timeout number */
24030294Ssam /* Did we timeout */
24143384Smckusick if (dra->dr_flags & DR_TMDM)
24230294Ssam dra->dr_flags &= ~DR_TMDM; /* Clear timeout flag */
24330294Ssam return (err);
24429651Ssam }
24530294Ssam return (physio(drstrategy, bp, dev,B_WRITE, drminphys, uio));
24629651Ssam }
24729651Ssam
24830294Ssam /*
24930294Ssam * Routine used by calling program to issue commands to dr11 driver and
25030294Ssam * through it to the device.
25130294Ssam * It is also used to read status from the device and driver and to wait
25230294Ssam * for attention interrupts.
25330294Ssam * Status is returned in an 8 elements unsigned short integer array, the
25430294Ssam * first two elements of the array are also used to pass arguments to
25530294Ssam * drioctl() if required.
25630294Ssam * The function bits to be written to the dr11 are included in the cmd
25730294Ssam * argument. Even if they are not being written to the dr11 in a particular
25830294Ssam * drioctl() call, they will update the copy of cmd that is stored in the
25930294Ssam * driver. When drstrategy() is called, this updated copy is used if a
26030294Ssam * deferred function bit write has been specified. The "side effect" of
26130294Ssam * calls to the drioctl() requires that the last call prior to a read or
26230294Ssam * write has an appropriate copy of the function bits in cmd if they are
26330294Ssam * to be used in drstrategy().
26430294Ssam * When used as command value, the contents of data[0] is the command
26530294Ssam * parameter.
26630294Ssam */
drioctl(dev,cmd,data)26730294Ssam drioctl(dev, cmd, data)
26830294Ssam dev_t dev;
26930294Ssam int cmd;
27030294Ssam long *data;
27129651Ssam {
27230294Ssam register int unit = RSUNIT(dev);
27330294Ssam register struct dr_aux *dra;
27430294Ssam register struct rsdevice *rsaddr = RSADDR(unit);
27537545Smckusick int s, error = 0;
27630294Ssam u_short status;
27730294Ssam long temp;
27829651Ssam
27929651Ssam #ifdef DR_DEBUG
28030294Ssam if (DR11 & 0x10)
28130294Ssam printf("\ndrioctl: (dev:%lx)(cmd:%lx)(data:%lx)(data[0]:%lx)",
28230294Ssam dev,cmd,data,data[0]);
28329651Ssam #endif
28430294Ssam dra = &dr_aux[unit];
28530294Ssam dra->dr_cmd = 0; /* Fresh copy; clear all previous flags */
28630294Ssam switch (cmd) {
28729651Ssam
28830294Ssam case DRWAIT: /* Wait for attention interrupt */
28929651Ssam #ifdef DR_DEBUG
29030294Ssam printf("\ndrioctl: wait for attention interrupt");
29129651Ssam #endif
29230294Ssam s = SPL_UP();
29330294Ssam /*
29430294Ssam * If the attention flag in dr_flags is set, it probably
29530294Ssam * means that an attention has arrived by the time a
29630294Ssam * previous DMA end-of-range interrupt was serviced. If
29730294Ssam * ATRX is set, we will return with out sleeping, since
29830294Ssam * we have received an attention since the last call to
29930294Ssam * wait on attention. This may not be appropriate for
30030294Ssam * some applications.
30130294Ssam */
30230294Ssam if ((dra->dr_flags & DR_ATRX) == 0) {
30330294Ssam dra->dr_flags |= DR_ATWT; /* Set waiting flag */
30430294Ssam /*
30530294Ssam * Enable interrupt; use pulse reg.
30630294Ssam * so function bits are not changed
30730294Ssam */
30830294Ssam rsaddr->dr_pulse = IENB;
30940735Skarels error = tsleep((caddr_t)&dra->dr_cmd, DRPRI | PCATCH,
31040735Skarels devio, 0);
31130294Ssam }
31230294Ssam splx(s);
31330294Ssam break;
31429651Ssam
31530294Ssam case DRPIOW: /* Write to p-i/o register */
31630294Ssam rsaddr->dr_data = data[0];
31730294Ssam break;
31829651Ssam
31930294Ssam case DRPACL: /* Send pulse to device */
32030294Ssam rsaddr->dr_pulse = FCN2;
32130294Ssam break;
32229651Ssam
32330294Ssam case DRDACL: /* Defer alco pulse until go */
32430294Ssam dra->dr_cmd |= DR_DACL;
32530294Ssam break;
32629651Ssam
32730294Ssam case DRPCYL: /* Set cycle with next go */
32830294Ssam dra->dr_cmd |= DR_PCYL;
32930294Ssam break;
33029651Ssam
33130294Ssam case DRDFCN: /* Update function with next go */
33230294Ssam dra->dr_cmd |= DR_DFCN;
33330294Ssam break;
33429651Ssam
33530294Ssam case DRRATN: /* Reset attention flag */
33630294Ssam rsaddr->dr_pulse = RATN;
33730294Ssam break;
33829651Ssam
33930294Ssam case DRRDMA: /* Reset DMA e-o-r flag */
34030294Ssam rsaddr->dr_pulse = RDMA;
34130294Ssam break;
34229651Ssam
34330294Ssam case DRSFCN: /* Set function bits */
34430294Ssam temp = data[0] & DR_FMSK;
34530294Ssam /*
34630294Ssam * This has a very important side effect -- It clears
34730294Ssam * the interrupt enable flag. That is fine for this driver,
34830294Ssam * but if it is desired to leave interrupt enable at all
34930294Ssam * times, it will be necessary to read the status register
35030294Ssam * first to get IENB, or carry a software flag that indicates
35130294Ssam * whether interrupts are set, and or this into the control
35230294Ssam * register value being written.
35330294Ssam */
35430294Ssam rsaddr->dr_cstat = temp;
35530294Ssam break;
35629651Ssam
35730294Ssam case DRRPER: /* Clear parity flag */
35830294Ssam rsaddr->dr_pulse = RPER;
35930294Ssam break;
36029651Ssam
36130294Ssam case DRSETRSTALL: /* Set read stall mode. */
36230294Ssam dra->dr_flags &= (~DR_NORSTALL);
36330294Ssam break;
36429651Ssam
36530294Ssam case DRSETNORSTALL: /* Set no stall read mode. */
36630294Ssam dra->dr_flags |= DR_NORSTALL;
36730294Ssam break;
36829651Ssam
36930294Ssam case DRGETRSTALL: /* Returns true if in read stall mode */
37030294Ssam data[0] = (dra->dr_flags & DR_NORSTALL)? 0 : 1;
37130294Ssam break;
37229651Ssam
37330294Ssam case DRSETRTIMEOUT: /* Set read stall timeout (1/10 secs) */
37443384Smckusick if (data[0] < 1)
37543384Smckusick error = EINVAL;
37630294Ssam dra->rtimoticks = (data[0] * hz )/10;
37730294Ssam break;
37829651Ssam
37930294Ssam case DRGETRTIMEOUT: /* Return read stall timeout */
38030294Ssam data[0] = ((dra->rtimoticks)*10)/hz;
38130294Ssam break;
38229651Ssam
38330294Ssam case DRSETWSTALL: /* Set write stall mode. */
38430294Ssam dra->dr_flags &= (~DR_NOWSTALL);
38530294Ssam break;
38629651Ssam
38730294Ssam case DRSETNOWSTALL: /* Set write stall mode. */
38830294Ssam dra->dr_flags |= DR_NOWSTALL;
38930294Ssam break;
39029651Ssam
39130294Ssam case DRGETWSTALL: /* Return true if in write stall mode */
39230294Ssam data[0] = (dra->dr_flags & DR_NOWSTALL)? 0 : 1;
39330294Ssam break;
39429651Ssam
39530294Ssam case DRSETWTIMEOUT: /* Set write stall timeout (1/10's) */
39643384Smckusick if (data[0] < 1)
39743384Smckusick error = EINVAL;
39830294Ssam dra->wtimoticks = (data[0] * hz )/10;
39930294Ssam break;
40029651Ssam
40130294Ssam case DRGETWTIMEOUT: /* Return write stall timeout */
40230294Ssam data[0] = ((dra->wtimoticks)*10)/hz;
40330294Ssam break;
40429651Ssam
40530294Ssam case DRWRITEREADY: /* Return true if can write data */
40630294Ssam data[0] = (rsaddr->dr_cstat & STTA)? 1 : 0;
40730294Ssam break;
40829651Ssam
40930294Ssam case DRREADREADY: /* Return true if data to be read */
41030294Ssam data[0] = (rsaddr->dr_cstat & STTB)? 1 : 0;
41130294Ssam break;
41229651Ssam
41330294Ssam case DRBUSY: /* Return true if device busy */
41430294Ssam /*
41530294Ssam * Internally this is the DR11-W
41630294Ssam * STAT C bit, but there is a bug in the Omega 500/FIFO
41730294Ssam * interface board that it cannot drive this signal low
41830294Ssam * for certain DR11-W ctlr such as the Ikon. We use the
41930294Ssam * REDY signal of the CSR on the Ikon DR11-W instead.
42030294Ssam */
42130294Ssam #ifdef notdef
42230294Ssam data[0] = (rsaddr->dr_cstat & STTC)? 1 : 0;
42330294Ssam #else
42430294Ssam data[0] = ((rsaddr->dr_cstat & REDY)? 0 : 1);
42530294Ssam #endif
42630294Ssam break;
42729651Ssam
42830294Ssam case DRRESET: /* Reset device */
42930294Ssam /* Reset DMA ATN RPER flag */
43030294Ssam rsaddr->dr_pulse = (MCLR|RDMA|RATN|RPER);
43130294Ssam DELAY(0x1f000);
43240735Skarels while ((rsaddr->dr_cstat & REDY) == 0 && error == 0)
43340735Skarels /* Wakeup by drtimo() */
43440735Skarels error = tsleep((caddr_t)dra, DRPRI | PCATCH, devio, 0);
43530294Ssam dra->dr_istat = 0;
43630294Ssam dra->dr_cmd = 0;
43730294Ssam dra->currenttimo = 0;
43830294Ssam break;
43929651Ssam
44030294Ssam case DR11STAT: { /* Copy back dr11 status to user */
44130294Ssam register struct dr11io *dr = (struct dr11io *)data;
44230294Ssam dr->arg[0] = dra->dr_flags;
44330294Ssam dr->arg[1] = rsaddr->dr_cstat;
44430294Ssam dr->arg[2] = dra->dr_istat; /* Status at last interrupt */
44530294Ssam dr->arg[3] = rsaddr->dr_data; /* P-i/o input data */
44630294Ssam status = (u_short)((rsaddr->dr_addmod << 8) & 0xff00);
44730294Ssam dr->arg[4] = status | (u_short)(rsaddr->dr_intvect & 0xff);
44830294Ssam dr->arg[5] = rsaddr->dr_range;
44930294Ssam dr->arg[6] = rsaddr->dr_rahi;
45030294Ssam dr->arg[7] = rsaddr->dr_ralo;
45130294Ssam break;
45230294Ssam }
45330294Ssam case DR11LOOP: /* Perform loopback test */
45430294Ssam /*
45530294Ssam * NB: MUST HAVE LOOPBACK CABLE ATTACHED --
45630294Ssam * Test results are printed on system console
45730294Ssam */
45837545Smckusick if (error = suser(u.u_cred, &u.u_acflag))
45937545Smckusick break;
46037545Smckusick dr11loop(rsaddr, dra, unit);
46130294Ssam break;
46229651Ssam
46330294Ssam default:
46430294Ssam return (EINVAL);
46529651Ssam }
46629651Ssam #ifdef DR_DEBUG
46730294Ssam if (DR11 & 0x10)
46830294Ssam printf("**** (data[0]:%lx)",data[0]);
46929651Ssam #endif
47037545Smckusick return (error);
47129651Ssam }
47229651Ssam
47330294Ssam #define NPAT 2
47430294Ssam #define DMATBL 20
47530294Ssam u_short tstpat[DMATBL] = { 0xAAAA, 0x5555};
47630294Ssam long DMAin = 0;
47730138Ssam
47830294Ssam /*
47930294Ssam * Perform loopback test -- MUST HAVE LOOPBACK CABLE ATTACHED
48030294Ssam * Test results are printed on system console
48130294Ssam */
48230294Ssam dr11loop(dr, dra, unit)
48330294Ssam struct rsdevice *dr;
48430294Ssam struct dr_aux *dra;
48530294Ssam int unit;
48630294Ssam {
48730294Ssam register long result, ix;
48830294Ssam long addr, wait;
48930138Ssam
49030138Ssam dr->dr_cstat = MCLR; /* Clear board & device, disable intr */
49130294Ssam printf("\n\t ----- DR11 unit %ld loopback test -----", unit);
49230138Ssam printf("\n\t Program I/O ...");
49330138Ssam for (ix=0;ix<NPAT;ix++) {
49430138Ssam dr->dr_data = tstpat[ix]; /* Write to Data out register */
49530294Ssam result = dr->dr_data & 0xFFFF; /* Read it back */
49630138Ssam if (result != tstpat[ix]) {
49730138Ssam printf("Failed, expected : %lx --- actual : %lx",
49830294Ssam tstpat[ix], result);
49930138Ssam return;
50030138Ssam }
50130138Ssam }
50230138Ssam printf("OK\n\t Functions & Status Bits ...");
50330138Ssam dr->dr_cstat = (FCN1 | FCN3);
50430138Ssam result = dr->dr_cstat & 0xffff; /* Read them back */
50530138Ssam if ((result & (STTC | STTA)) != (STTC |STTA)) {
50630138Ssam printf("Failed, expected : %lx --- actual : %lx, ISR:%lx",
50730294Ssam (STTA|STTC), (result & (STTA|STTC)), result);
50830138Ssam return;
50930138Ssam }
51030138Ssam dr->dr_cstat = FCN2;
51130138Ssam result = dr->dr_cstat & 0xffff; /* Read them back */
51230138Ssam if ((result & STTB) != STTB) {
51330138Ssam printf("Failed, expected : %lx --- actual : %lx, ISR:%lx",
51430294Ssam STTB, (result & STTB), result);
51530138Ssam return;
51630138Ssam }
51730138Ssam printf("OK\n\t DMA output ...");
51830294Ssam if (DMAin)
51930294Ssam goto dmain;
52030138Ssam /* Initialize DMA data buffer */
52130294Ssam for (ix=0; ix<DMATBL; ix++)
52230294Ssam tstpat[ix] = 0xCCCC + ix;
52330138Ssam tstpat[DMATBL-1] = 0xCCCC; /* Last word output */
52430138Ssam /* Setup normal DMA */
52530294Ssam addr = (long)vtoph((struct proc *)0, (unsigned)tstpat);
52630294Ssam dr->dr_walo = (addr >> 1) & 0xffff;
52730294Ssam dr->dr_wahi = (addr >> 17) & 0x7fff;
52830294Ssam /* Set DMA range count: (number of words - 1) */
52930294Ssam dr->dr_range = DMATBL - 1;
53030294Ssam /* Set address modifier code to be used for DMA access to memory */
53130294Ssam dr->dr_addmod = DRADDMOD;
53230138Ssam
53330294Ssam /*
53430294Ssam * Clear dmaf and attf to assure a clean dma start, also disable
53530294Ssam * attention interrupt
53630294Ssam */
53730294Ssam dr->dr_pulse = RDMA|RATN|RMSK; /* Use pulse register */
53830294Ssam dr->dr_cstat = GO|CYCL; /* GO...... */
53930138Ssam
54030138Ssam /* Wait for DMA complete; REDY and DMAF are true in ISR */
54130138Ssam wait = 0;
54230294Ssam while ((result=(dr->dr_cstat & (REDY|DMAF))) != (REDY|DMAF)) {
54330294Ssam printf("\n\tWait for DMA complete...ISR : %lx", result);
54430138Ssam if (++wait > 5) {
54530138Ssam printf("\n\t DMA output fails...timeout!!, ISR:%lx",
54630138Ssam result);
54730138Ssam return;
54830138Ssam }
54930138Ssam }
55030138Ssam result = dr->dr_data & 0xffff; /* Read last word output */
55130138Ssam if (result != 0xCCCC) {
55230138Ssam printf("\n\t Fails, expected : %lx --- actual : %lx",
55330294Ssam 0xCCCC, result);
55430138Ssam return;
55530138Ssam }
55630138Ssam printf("OK\n\t DMA input ...");
55730138Ssam dmain:
55830138Ssam dr->dr_data = 0x1111; /* DMA input data */
55930138Ssam /* Setup normal DMA */
56030294Ssam addr = (long)vtoph((struct proc *)0, (unsigned)tstpat);
56130294Ssam dr->dr_walo = (addr >> 1) & 0xffff;
56230294Ssam dr->dr_wahi = (addr >> 17) & 0x7fff;
56330294Ssam dr->dr_range = DMATBL - 1;
56430294Ssam dr->dr_addmod = (char)DRADDMOD;
56530294Ssam dr->dr_cstat = FCN1; /* Set FCN1 in ICR to DMA in*/
56630294Ssam if ((dra->dr_flags & DR_LOOPTST) == 0) {
56730138Ssam /* Use pulse reg */
56830294Ssam dr->dr_pulse = RDMA|RATN|RMSK|CYCL|GO;
56930138Ssam /* Wait for DMA complete; REDY and DMAF are true in ISR */
57030138Ssam wait = 0;
57130294Ssam while ((result=(dr->dr_cstat & (REDY|DMAF))) != (REDY|DMAF)) {
57230138Ssam printf("\n\tWait for DMA to complete...ISR:%lx",result);
57330138Ssam if (++wait > 5) {
57430138Ssam printf("\n\t DMA input timeout!!, ISR:%lx",
57530138Ssam result);
57630138Ssam return;
57730138Ssam }
57830138Ssam }
57930294Ssam } else {
58030138Ssam /* Enable DMA e-o-r interrupt */
58130294Ssam dr->dr_pulse = IENB|RDMA|RATN|CYCL|GO;
58230138Ssam /* Wait for DMA complete; DR_LOOPTST is false in dra->dr_flags*/
58330138Ssam wait = 0;
58430138Ssam while (dra->dr_flags & DR_LOOPTST) {
58530138Ssam result = dr->dr_cstat & 0xffff;
58630294Ssam printf("\n\tWait for DMA e-o-r intr...ISR:%lx", result);
58730138Ssam if (++wait > 7) {
58830138Ssam printf("\n\t DMA e-o-r timeout!!, ISR:%lx",
58930138Ssam result);
59030138Ssam dra->dr_flags &= ~DR_LOOPTST;
59130138Ssam return;
59230138Ssam }
59330138Ssam }
59430138Ssam dra->dr_flags |= DR_LOOPTST;
59530138Ssam }
59630294Ssam mtpr(P1DC, tstpat); /* Purge cache */
59730294Ssam mtpr(P1DC, 0x3ff+tstpat);
59830294Ssam for (ix=0; ix<DMATBL; ix++) {
59930138Ssam if (tstpat[ix] != 0x1111) {
60030294Ssam printf("\n\t Fails, ix:%d, expected:%x --- actual:%x",
60130294Ssam ix, 0x1111, tstpat[ix]);
60230138Ssam return;
60330138Ssam }
60430138Ssam }
60530294Ssam if ((dra->dr_flags & DR_LOOPTST) == 0) {
60630138Ssam dra->dr_flags |= DR_LOOPTST;
60730138Ssam printf(" OK..\n\tDMA end of range interrupt...");
60830138Ssam goto dmain;
60930138Ssam }
61030138Ssam printf(" OK..\n\tAttention interrupt....");
61130294Ssam dr->dr_pulse = IENB|RDMA;
61230294Ssam dr->dr_pulse = FCN2;
61330138Ssam /* Wait for ATTN interrupt; DR_LOOPTST is false in dra->dr_flags*/
61430138Ssam wait = 0;
61530138Ssam while (dra->dr_flags & DR_LOOPTST) {
61630138Ssam result = dr->dr_cstat & 0xffff;
61730138Ssam printf("\n\tWait for Attention intr...ISR:%lx",result);
61830138Ssam if (++wait > 7) {
61930138Ssam printf("\n\t Attention interrupt timeout!!, ISR:%lx",
62030138Ssam result);
62130138Ssam dra->dr_flags &= ~DR_LOOPTST;
62230138Ssam return;
62330138Ssam }
62430138Ssam }
62530138Ssam dra->dr_flags &= ~DR_LOOPTST;
62630138Ssam printf(" OK..\n\tDone...");
62730138Ssam }
62830138Ssam
62929651Ssam /* Reset state on Unibus reset */
63030294Ssam /*ARGSUSED*/
drreset(uban)63129651Ssam drreset(uban)
63230294Ssam int uban;
63329651Ssam {
63429651Ssam
63529651Ssam }
63629651Ssam
63729651Ssam /*
63829651Ssam * An interrupt is caused either by an error,
63929651Ssam * base address overflow, or transfer complete
64029651Ssam */
drintr(dr11)64130294Ssam drintr(dr11)
64230294Ssam int dr11;
64329651Ssam {
64430294Ssam register struct dr_aux *dra = &dr_aux[dr11];
64530294Ssam register struct rsdevice *rsaddr = RSADDR(dr11);
64630294Ssam register struct buf *bp;
64730294Ssam register short status;
64829651Ssam
64930294Ssam status = rsaddr->dr_cstat & 0xffff; /* get board status register */
65030294Ssam dra->dr_istat = status;
65129651Ssam #ifdef DR_DEBUG
65230294Ssam if (DR11 & 2)
65330294Ssam printf("\ndrintr: dr11 status : %lx",status & 0xffff);
65429651Ssam #endif
65530294Ssam if (dra->dr_flags & DR_LOOPTST) { /* doing loopback test */
65630294Ssam dra->dr_flags &= ~DR_LOOPTST;
65730294Ssam return;
65830294Ssam }
65930294Ssam /*
66030294Ssam * Make sure this is not a stray interrupt; at least one of dmaf or attf
66130294Ssam * must be set. Note that if the dr11 interrupt enable latch is reset
66230294Ssam * during a hardware interrupt ack sequence, and by the we get to this
66330294Ssam * point in the interrupt code it will be 0. This is done to give the
66430294Ssam * programmer some control over how the two more-or-less independent
66530294Ssam * interrupt sources on the board are handled.
66630294Ssam * If the attention flag is set when drstrategy() is called to start a
66730294Ssam * dma read or write an interrupt will be generated as soon as the
66830294Ssam * strategy routine enables interrupts for dma end-of-range. This will
66930294Ssam * cause execution of the interrupt routine (not necessarily bad) and
67030294Ssam * will cause the interrupt enable mask to be reset (very bad since the
67130294Ssam * dma end-of-range condition will not be able to generate an interrupt
67230294Ssam * when it occurs) causing the dma operation to time-out (even though
67330294Ssam * the dma transfer will be done successfully) or hang the process if a
67430294Ssam * software time-out capability is not implemented. One way to avoid
67530294Ssam * this situation is to check for a pending attention interrupt (attf
67630294Ssam * set) by calling drioctl() before doing a read or a write. For the
67730294Ssam * time being this driver will solve the problem by clearing the attf
67830294Ssam * flag in the status register before enabling interrupts in
67930294Ssam * drstrategy().
68030294Ssam *
68130294Ssam * **** The IKON 10084 for which this driver is written will set both
68230294Ssam * attf and dmaf if dma is terminated by an attention pulse. This will
68330294Ssam * cause a wakeup(&dr_aux), which will be ignored since it is not being
68430294Ssam * waited on, and an iodone(bp) which is the desired action. Some other
68530294Ssam * dr11 emulators, in particular the IKON 10077 for the Multibus, donot
68630294Ssam * dmaf in this case. This may require some addtional code in the inter-
68730294Ssam * rupt routine to ensure that en iodone(bp) is issued when dma is term-
68830294Ssam * inated by attention.
68930294Ssam */
69030294Ssam bp = dra->dr_actf;
69130294Ssam if ((status & (ATTF | DMAF)) == 0) {
69230294Ssam printf("dr%d: stray interrupt, status=%x", dr11, status);
69330294Ssam return;
69430294Ssam }
69530294Ssam if (status & DMAF) { /* End-of-range interrupt */
69630294Ssam dra->dr_flags |= DR_DMAX;
69729651Ssam
69829651Ssam #ifdef DR_DEBUG
69930294Ssam if (DR11 & 2)
70030294Ssam printf("\ndrintr: e-o-r interrupt,cstat:%lx,dr_flags:%lx",
70130294Ssam status&0xffff, dra->dr_flags & DR_ACTV);
70229651Ssam #endif
70330294Ssam if ((dra->dr_flags & DR_ACTV) == 0) {
70430294Ssam /* We are not doing DMA !! */
70530294Ssam bp->b_flags |= B_ERROR;
70630294Ssam } else {
70730294Ssam if (dra->dr_op == DR_READ)
70830294Ssam mtpr(P1DC, bp->b_un.b_addr);
70930294Ssam dra->dr_bycnt -= bp->b_bcount;
71030294Ssam if (dra->dr_bycnt >0) {
71130294Ssam bp->b_un.b_addr += bp->b_bcount;
71230294Ssam bp->b_bcount = (dra->dr_bycnt > NBPG) ? NBPG:
71329651Ssam dra->dr_bycnt;
71430294Ssam drstart(rsaddr, dra, bp);
71530294Ssam return;
71630294Ssam }
71729651Ssam }
71830294Ssam dra->dr_flags &= ~DR_ACTV;
71930294Ssam wakeup((caddr_t)dra); /* Wakeup waiting in drwait() */
72030294Ssam rsaddr->dr_pulse = (RPER|RDMA|RATN); /* reset dma e-o-r flag */
72129651Ssam }
72230294Ssam /*
72330294Ssam * Now test for attention interrupt -- It may be set in addition to
72430294Ssam * the dma e-o-r interrupt. If we get one we will issue a wakeup to
72530294Ssam * the drioctl() routine which is presumable waiting for one.
72630294Ssam * The program may have to monitor the attention interrupt received
72730294Ssam * flag in addition to doing waits for the interrupt. Futhermore,
72830294Ssam * interrupts are not enabled unless dma is in progress or drioctl()
72930294Ssam * has been called to wait for attention -- this may produce some
73030294Ssam * strange results if attf is set on the dr11 when a read or a write
73130294Ssam * is initiated, since that will enables interrupts.
73230294Ssam * **** The appropriate code for this interrupt routine will probably
73330294Ssam * be rather application dependent.
73430294Ssam */
73530294Ssam if (status & ATTF) {
73630294Ssam dra->dr_flags |= DR_ATRX;
73730294Ssam dra->dr_flags &= ~DR_ATWT;
73830294Ssam rsaddr->dr_cstat = RATN; /* reset attention flag */
73930294Ssam /*
74030294Ssam * Some applications which use attention to terminate
74130294Ssam * dma may also want to issue an iodone() here to
74230294Ssam * wakeup physio().
74330294Ssam */
74430294Ssam wakeup((caddr_t)&dra->dr_cmd);
74530294Ssam }
74629651Ssam }
74729651Ssam
74829651Ssam unsigned
drminphys(bp)74929651Ssam drminphys(bp)
75030294Ssam struct buf *bp;
75129651Ssam {
75230294Ssam
75330294Ssam if (bp->b_bcount > 65536)
75430294Ssam bp->b_bcount = 65536;
75529651Ssam }
75629651Ssam
75729651Ssam /*
75830294Ssam * This routine performs the device unique operations on the DR11W
75930294Ssam * it is passed as an argument to and invoked by physio
76029651Ssam */
drstrategy(bp)76129651Ssam drstrategy (bp)
76230294Ssam register struct buf *bp;
76329651Ssam {
76430294Ssam register int s;
76530294Ssam int unit = RSUNIT(bp->b_dev);
76630294Ssam register struct rsdevice *rsaddr = RSADDR(unit);
76730294Ssam register struct dr_aux *dra = &dr_aux[unit];
76830294Ssam register int ok;
76929651Ssam #ifdef DR_DEBUG
77030294Ssam register char *caddr;
77130294Ssam long drva();
77229651Ssam #endif
77329651Ssam
77430294Ssam if ((dra->dr_flags & DR_OPEN) == 0) { /* Device not open */
77530294Ssam bp->b_error = ENXIO;
77630294Ssam bp->b_flags |= B_ERROR;
77730294Ssam iodone (bp);
77830294Ssam return;
77930294Ssam }
78030294Ssam while (dra->dr_flags & DR_ACTV)
78130294Ssam /* Device is active; should never be in here... */
78240735Skarels (void) tsleep((caddr_t)&dra->dr_flags, DRPRI, devio, 0);
78330294Ssam dra->dr_actf = bp;
78429651Ssam #ifdef DR_DEBUG
78530294Ssam drva(dra, bp->b_proc, bp->b_un.b_addr, bp->b_bcount);
78629651Ssam #endif
78730294Ssam dra->dr_oba = bp->b_un.b_addr; /* Save original addr, count */
78830294Ssam dra->dr_obc = bp->b_bcount;
78930294Ssam dra->dr_bycnt = bp->b_bcount; /* Save xfer count used by drintr() */
79030294Ssam if ((((long)bp->b_un.b_addr & 0x3fffffff) >> PGSHIFT) !=
79130294Ssam ((((long)bp->b_un.b_addr & 0x3fffffff) + bp->b_bcount) >> PGSHIFT))
79230294Ssam bp->b_bcount = NBPG - (((long)bp->b_un.b_addr) & PGOFSET);
79330294Ssam dra->dr_flags |= DR_ACTV; /* Mark active (use in intr handler) */
79430294Ssam s = SPL_UP();
79530294Ssam drstart(rsaddr,dra,bp);
79630294Ssam splx(s);
79730294Ssam ok = drwait(rsaddr,dra);
79829651Ssam #ifdef DR_DEBUG
79930294Ssam if (DR11 & 0x40) {
80030294Ssam caddr = (char *)dra->dr_oba;
80130294Ssam if (dra->dr_op == DR_READ)
80230294Ssam printf("\nAfter read: (%lx)(%lx)",
80330294Ssam caddr[0]&0xff, caddr[1]&0xff);
80430294Ssam }
80529651Ssam #endif
80630294Ssam dra->dr_flags &= ~DR_ACTV; /* Clear active flag */
80730294Ssam bp->b_un.b_addr = dra->dr_oba; /* Restore original addr, count */
80830294Ssam bp->b_bcount = dra->dr_obc;
80930294Ssam if (!ok)
81030294Ssam bp->b_flags |= B_ERROR;
81130294Ssam /* Mark buffer B_DONE,so physstrat() in ml/machdep.c won't sleep */
81230294Ssam iodone(bp);
81330294Ssam wakeup((caddr_t)&dra->dr_flags);
81430294Ssam /*
81530294Ssam * Return to the calling program (physio()). Physio() will sleep
81630294Ssam * until awaken by a call to iodone() in the interupt handler --
81730294Ssam * which will be called by the dispatcher when it receives dma
81830294Ssam * end-of-range interrupt.
81930294Ssam */
82029651Ssam }
82129651Ssam
drwait(rs,dr)82230294Ssam drwait(rs, dr)
82330294Ssam register struct rsdevice *rs;
82430294Ssam register struct dr_aux *dr;
82529651Ssam {
82630294Ssam int s;
82729651Ssam
82829651Ssam s = SPL_UP();
82930294Ssam while (dr->dr_flags & DR_ACTV)
83040735Skarels (void) tsleep((caddr_t)dr, DRPRI, devio, 0);
83129651Ssam splx(s);
83230294Ssam if (dr->dr_flags & DR_TMDM) { /* DMA timed out */
83329651Ssam dr->dr_flags &= ~DR_TMDM;
83430294Ssam return (0);
83529651Ssam }
83630294Ssam if (rs->dr_cstat & (PERR|BERR|TERR)) {
83730294Ssam dr->dr_actf->b_flags |= B_ERROR;
83830294Ssam return (0);
83929651Ssam }
84029651Ssam dr->dr_flags &= ~DR_DMAX;
84130294Ssam return (1);
84229651Ssam }
84329651Ssam
84430294Ssam /*
84530294Ssam *
84630294Ssam * The lower 8-bit of tinfo is the minor device number, the
84730294Ssam * remaining higher 8-bit is the current timout number
84830294Ssam */
drrwtimo(tinfo)84929651Ssam drrwtimo(tinfo)
85030294Ssam register u_long tinfo;
85130294Ssam {
85230294Ssam register long unit = tinfo & 0xff;
85329651Ssam register struct dr_aux *dr = &dr_aux[unit];
85429651Ssam register struct rsdevice *rs = dr->dr_addr;
85529651Ssam
85630294Ssam /*
85730294Ssam * If this is not the timeout that drwrite/drread is waiting
85830294Ssam * for then we should just go away
85930294Ssam */
86030294Ssam if ((tinfo &~ 0xff) != (dr->currenttimo << 8))
86130294Ssam return;
86229651Ssam /* Mark the device timed out */
86329651Ssam dr->dr_flags |= DR_TMDM;
86429651Ssam dr->dr_flags &= ~DR_ACTV;
86529651Ssam rs->dr_pulse = RMSK; /* Inihibit interrupt */
86629651Ssam rs->dr_pulse = (RPER|RDMA|RATN|IENB); /* Clear DMA logic */
86730294Ssam /*
86830294Ssam * Some applications will not issue a master after dma timeout,
86930294Ssam * since doing so sends an INIT H pulse to the external device,
87030294Ssam * which may produce undesirable side-effects.
87130294Ssam */
87229651Ssam /* Wake up process waiting in drwait() and flag the error */
87330294Ssam dr->dr_actf->b_flags |= B_ERROR;
87429651Ssam wakeup((caddr_t)dr->dr_cmd);
87529651Ssam }
87629651Ssam
87729651Ssam /*
87830294Ssam * Kick the driver every second
87930294Ssam */
drtimo(dev)88029651Ssam drtimo(dev)
88130294Ssam dev_t dev;
88229651Ssam {
88330294Ssam register int unit = RSUNIT(dev);
88429651Ssam register struct dr_aux *dr;
88529651Ssam
88630294Ssam dr = &dr_aux[unit];
88729651Ssam if (dr->dr_flags & DR_OPEN)
88830294Ssam timeout(drtimo, (caddr_t)dev, hz);
88929651Ssam wakeup((caddr_t)dr); /* Wakeup any process waiting for interrupt */
89029651Ssam }
89129651Ssam
89229651Ssam #ifdef DR_DEBUG
89330294Ssam drva(dra, p, va, bcnt)
89430294Ssam struct dr_aux *dra;
89530294Ssam struct proc *p;
89630294Ssam char *va;
89730294Ssam long bcnt;
89830294Ssam {
89930294Ssam register long first, last , np;
90029651Ssam
90129651Ssam if (DR11 & 0x20) {
90230294Ssam first = ((long)(vtoph(p, (unsigned)va))) >> 10;
90330294Ssam last = ((long)(vtoph(p, (unsigned)va+bcnt))) >> 10;
90429651Ssam np = bcnt / 0x3ff;
90529651Ssam printf("\ndrva: (op:%ld)(first:%ld)(last:%ld)(np:%ld)(cnt:%ld)",
90629651Ssam dra->dr_op,first,last,np,bcnt);
90729651Ssam }
90829651Ssam }
90929651Ssam #endif
91029651Ssam
drstart(rsaddr,dra,bp)91130294Ssam drstart(rsaddr, dra, bp)
91230294Ssam register struct rsdevice *rsaddr;
91330294Ssam register struct dr_aux *dra;
91430294Ssam register struct buf *bp;
91530294Ssam {
91630294Ssam register long addr;
91730294Ssam u_short go;
91829651Ssam
91929651Ssam #ifdef DR_DEBUG
92030294Ssam if (dra->dr_op == DR_READ && (DR11 & 8)) {
92130294Ssam char *caddr = (char *)bp->b_un.b_addr;
92229651Ssam printf("\ndrstart: READ, bcnt:%ld",bp->b_bcount);
92329651Ssam printf(",(%lx)(%lx)",caddr[0]&0xff,caddr[1]&0xff);
92429651Ssam }
92529651Ssam #endif
92630294Ssam /* we are doing raw IO, bp->b_un.b_addr is user's address */
92730294Ssam addr = (long)vtoph(bp->b_proc, (unsigned)bp->b_un.b_addr);
92830294Ssam /*
92930294Ssam * Set DMA address into DR11 interace registers: DR11 requires that
93030294Ssam * the address be right shifted 1 bit position before it is written
93130294Ssam * to the board (The board will left shift it one bit position before
93230294Ssam * it places the address on the bus
93330294Ssam */
93430294Ssam rsaddr->dr_walo = (addr >> 1) & 0xffff;
93530294Ssam rsaddr->dr_wahi = (addr >> 17) & 0x7fff;
93630294Ssam /* Set DMA range count: (number of words - 1) */
93730294Ssam rsaddr->dr_range = (bp->b_bcount >> 1) - 1;
93830294Ssam /* Set address modifier code to be used for DMA access to memory */
93930294Ssam rsaddr->dr_addmod = DRADDMOD;
94030294Ssam /*
94130294Ssam * Now determine whether this is a read or a write. ***** This is
94230294Ssam * probably only usefull for link mode operation, since dr11 doesnot
94330294Ssam * controll the direction of data transfer. The C1 control input
94430294Ssam * controls whether the hardware is doing a read or a write. In link
94530294Ssam * mode this is controlled by function 1 latch (looped back by the
94630294Ssam * cable) and could be set the program. In the general case, the dr11
94730294Ssam * doesnot know in advance what the direction of transfer is - although
94830294Ssam * the program and protocol logic probably is
94930294Ssam */
95029651Ssam #ifdef DR_DEBUG
95130294Ssam if (DR11 & 1)
95230294Ssam printf(
95330294Ssam "\ndrstrat: about to GO..,dr_cmd:%lx,drstat:%lx,drcnt:%ld,cdata:%lx,OP:%ld",
95430294Ssam dra->dr_cmd, rsaddr->dr_cstat, rsaddr->dr_range,
95530294Ssam rsaddr->dr_data, dra->dr_op);
95629651Ssam #endif
95730294Ssam /*
95830294Ssam * Update function latches may have been done already by drioctl() if
95930294Ssam * request from drioctl()
96030294Ssam */
96130294Ssam if (dra->dr_cmd & DR_DFCN) { /* deferred function write */
96230294Ssam dra->dr_cmd &= ~DR_DFCN; /* Clear request */
96330294Ssam go = dra->dr_cmd & DR_FMSK; /* mask out fcn bits */
96430294Ssam rsaddr->dr_cstat = go; /* Write it to the board */
96530294Ssam }
96630294Ssam /* Clear dmaf and attf to assure a clean dma start */
96730294Ssam rsaddr->dr_pulse = RATN|RDMA|RPER;
96830294Ssam rsaddr->dr_cstat = IENB|GO|CYCL|dra->dr_op; /* GO...... */
96930294Ssam /*
97030294Ssam * Now check for software cycle request -- usually
97130294Ssam * by transmitter in link mode.
97230294Ssam */
97330294Ssam if (dra->dr_cmd & DR_PCYL) {
97430294Ssam dra->dr_cmd &= ~DR_PCYL; /* Clear request */
97530294Ssam rsaddr->dr_pulse = CYCL; /* Use pulse register again */
97630294Ssam }
97730294Ssam /*
97830294Ssam * Now check for deferred ACLO FCNT2 pulse request -- usually to tell
97930294Ssam * the transmitter (via its attention) that we have enabled dma.
98030294Ssam */
98130294Ssam if (dra->dr_cmd & DR_DACL) {
98230294Ssam dra->dr_cmd &= ~DR_DACL; /* Clear request */
98330294Ssam rsaddr->dr_pulse = FCN2; /* Use pulse register again */
98430294Ssam }
98529651Ssam }
98629651Ssam #endif NDR
987