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