1*29651Ssam /* dr.c 1.1 86/07/20 */ 2*29651Ssam 3*29651Ssam #include "dr.h" 4*29651Ssam #if NDR > 0 5*29651Ssam 6*29651Ssam /* DRV11-W DMA interface driver. 7*29651Ssam */ 8*29651Ssam 9*29651Ssam #include "../machine/mtpr.h" 10*29651Ssam #include "../machine/pte.h" 11*29651Ssam 12*29651Ssam #include "param.h" 13*29651Ssam #include "conf.h" 14*29651Ssam #include "dir.h" 15*29651Ssam #include "user.h" 16*29651Ssam #include "proc.h" 17*29651Ssam #include "map.h" 18*29651Ssam #include "ioctl.h" 19*29651Ssam #include "buf.h" 20*29651Ssam #include "vm.h" 21*29651Ssam #include "uio.h" 22*29651Ssam 23*29651Ssam #include "../tahoevba/vbavar.h" 24*29651Ssam #include "../tahoevba/drreg.h" 25*29651Ssam 26*29651Ssam #define YES 1 27*29651Ssam #define NO 0 28*29651Ssam 29*29651Ssam struct vba_device *drinfo[NDR]; 30*29651Ssam struct dr_aux dr_aux[NDR]; 31*29651Ssam 32*29651Ssam caddr_t vtoph(); 33*29651Ssam unsigned drminphys(); 34*29651Ssam int drprobe(), drintr(), drattach(), drtime(), drrwtimo(); 35*29651Ssam int drstrategy(); 36*29651Ssam extern struct vba_device *drinfo[]; 37*29651Ssam static long drstd[] = { 0 }; 38*29651Ssam struct vba_driver drdriver = 39*29651Ssam { drprobe, 0, drattach, 0, drstd, "rs", drinfo }; 40*29651Ssam extern long hz; 41*29651Ssam 42*29651Ssam #define RSUNIT(dev) (minor(dev) & 7) 43*29651Ssam #define SPL_UP spl5 44*29651Ssam 45*29651Ssam /* -------- Per-unit data -------- */ 46*29651Ssam 47*29651Ssam extern struct dr_aux dr_aux[]; 48*29651Ssam 49*29651Ssam struct rs_data { 50*29651Ssam struct buf rs_buf; 51*29651Ssam int rs_ubainfo; 52*29651Ssam short rs_debug; 53*29651Ssam short rs_busy; 54*29651Ssam short rs_tout; 55*29651Ssam short rs_uid; 56*29651Ssam short rs_isopen; 57*29651Ssam short rs_func; 58*29651Ssam } rs_data[NDR]; 59*29651Ssam 60*29651Ssam 61*29651Ssam #ifdef DR_DEBUG 62*29651Ssam long DR11 = 0; 63*29651Ssam #endif 64*29651Ssam 65*29651Ssam drprobe(reg, vi) 66*29651Ssam caddr_t reg; 67*29651Ssam struct vba_device *vi; 68*29651Ssam { 69*29651Ssam register int br, cvec; /* must be r12, r11 */ 70*29651Ssam register struct rsdevice *dr; 71*29651Ssam register ushort status; 72*29651Ssam 73*29651Ssam dr = (struct rsdevice *)reg; 74*29651Ssam #ifdef notdef 75*29651Ssam dr->dr_intvec = --vi->ui_hd->vh_lastiv; 76*29651Ssam #else 77*29651Ssam dr->dr_intvec = DRINTV+vi->ui_unit; 78*29651Ssam #endif 79*29651Ssam #ifdef DR_DEBUG 80*29651Ssam printf("dprobe: Set interrupt vector %lx and init\n",dr->dr_intvec); 81*29651Ssam #endif 82*29651Ssam /* generate interrupt here for autoconfig */ 83*29651Ssam dr->dr_cstat = MCLR; /* init board and device */ 84*29651Ssam status = dr->dr_cstat; /* read initial status */ 85*29651Ssam #ifdef DR_DEBUG 86*29651Ssam printf("drprobe: Initial status %lx\n",status & 0xffff); 87*29651Ssam #endif 88*29651Ssam br = 0x18, cvec = dr->dr_intvec; /* XXX */ 89*29651Ssam return (sizeof (struct rsdevice)); /* DR11 exist */ 90*29651Ssam } 91*29651Ssam 92*29651Ssam /* ARGSUSED */ 93*29651Ssam drattach(ui) 94*29651Ssam struct vba_device *ui; 95*29651Ssam { 96*29651Ssam register struct dr_aux *rsd; 97*29651Ssam 98*29651Ssam rsd = &dr_aux[ui->ui_unit]; 99*29651Ssam rsd->dr_flags = DR_PRES; /* This dr11 is present */ 100*29651Ssam rsd->dr_addr = (struct rsdevice *)ui->ui_addr; /* Save addr of this dr11 */ 101*29651Ssam rsd->dr_istat = 0; 102*29651Ssam rsd->dr_bycnt = 0; 103*29651Ssam rsd->dr_cmd = 0; 104*29651Ssam rsd->currenttimo = 0; 105*29651Ssam return; 106*29651Ssam } 107*29651Ssam 108*29651Ssam dropen (dev, flag) 109*29651Ssam dev_t dev; 110*29651Ssam int flag; 111*29651Ssam { 112*29651Ssam register int unit = RSUNIT(dev); 113*29651Ssam register struct rsdevice *dr; 114*29651Ssam register struct dr_aux *rsd; 115*29651Ssam 116*29651Ssam if ((drinfo[unit] == 0) || (!drinfo[unit]->ui_alive)) 117*29651Ssam return ENXIO; 118*29651Ssam 119*29651Ssam dr = RSADDR(unit); 120*29651Ssam rsd = &dr_aux[unit]; 121*29651Ssam if (rsd->dr_flags & DR_OPEN) { 122*29651Ssam #ifdef DR_DEBUG 123*29651Ssam printf("\ndropen: dr11 unit %ld already open",unit); 124*29651Ssam #endif 125*29651Ssam return ENXIO; /* DR11 already open */ 126*29651Ssam } 127*29651Ssam rsd->dr_flags |= DR_OPEN; /* Mark it OPEN */ 128*29651Ssam rsd->dr_istat = 0; /* Clear status of previous interrupt */ 129*29651Ssam rsd->rtimoticks = hz; /* Set read no stall timout to 1 sec */ 130*29651Ssam rsd->wtimoticks = hz*60; /* Set write no stall timout to 1 min */ 131*29651Ssam dr->dr_cstat = DR_ZERO; /* Clear function & latches */ 132*29651Ssam dr->dr_pulse = (RDMA | RATN); /* clear leftover attn & e-o-r flags */ 133*29651Ssam drtimo(dev); /* start the self kicker */ 134*29651Ssam return 0; 135*29651Ssam } 136*29651Ssam 137*29651Ssam drclose (dev) 138*29651Ssam dev_t dev; 139*29651Ssam { 140*29651Ssam register int unit = RSUNIT(dev); 141*29651Ssam register struct dr_aux *dra; 142*29651Ssam register struct rsdevice *rs; 143*29651Ssam register short s; 144*29651Ssam 145*29651Ssam dra = &dr_aux[unit]; 146*29651Ssam if (!(dra->dr_flags & DR_OPEN)) { 147*29651Ssam #ifdef DR_DEBUG 148*29651Ssam printf("\ndrclose: DR11 device %ld not open",unit); 149*29651Ssam #endif 150*29651Ssam return; 151*29651Ssam } 152*29651Ssam dra->dr_flags &= ~(DR_OPEN|DR_ACTV); 153*29651Ssam rs = dra->dr_addr; 154*29651Ssam s=SPL_UP(); 155*29651Ssam rs->dr_cstat = DR_ZERO; 156*29651Ssam if (dra->dr_buf.b_flags & B_BUSY) { 157*29651Ssam dra->dr_buf.b_flags &= ~B_BUSY; 158*29651Ssam wakeup(&dra->dr_buf.b_flags); 159*29651Ssam } 160*29651Ssam splx(s); 161*29651Ssam return; 162*29651Ssam } 163*29651Ssam 164*29651Ssam 165*29651Ssam /* drread() works exactly like drwrite() except that the 166*29651Ssam B_READ flag is used when physio() is called 167*29651Ssam */ 168*29651Ssam drread (dev, uio) 169*29651Ssam dev_t dev; 170*29651Ssam struct uio *uio; 171*29651Ssam { register struct dr_aux *dra; 172*29651Ssam register struct buf *bp; 173*29651Ssam register long spl, err; 174*29651Ssam register int unit = RSUNIT(dev); 175*29651Ssam 176*29651Ssam if ( uio->uio_iov->iov_len <= 0 /* Negative count */ 177*29651Ssam || uio->uio_iov->iov_len & 1 /* odd count */ 178*29651Ssam || (int)uio->uio_iov->iov_base & 1 /* odd destination address */ 179*29651Ssam ) 180*29651Ssam return EINVAL; 181*29651Ssam 182*29651Ssam #ifdef DR_DEBUG 183*29651Ssam if (DR11 & 8) { 184*29651Ssam printf("\ndrread: (len:%ld)(base:%lx)", 185*29651Ssam uio->uio_iov->iov_len,(int)uio->uio_iov->iov_base); 186*29651Ssam } 187*29651Ssam #endif 188*29651Ssam 189*29651Ssam dra = &dr_aux[RSUNIT(dev)]; 190*29651Ssam dra->dr_op = DR_READ; 191*29651Ssam bp = &dra->dr_buf; 192*29651Ssam bp->b_resid = 0; 193*29651Ssam if (dra->dr_flags & DR_NORSTALL) { 194*29651Ssam /* We are in no stall mode, start the timer, raise IPL so nothing 195*29651Ssam can stop us once the timer's running */ 196*29651Ssam spl = SPL_UP(); 197*29651Ssam timeout(drrwtimo,(caddr_t)((dra->currenttimo<<8) | unit), 198*29651Ssam dra->rtimoticks); 199*29651Ssam err = physio (drstrategy, bp, dev,B_READ, drminphys, uio); 200*29651Ssam splx(spl); 201*29651Ssam if (err) 202*29651Ssam return(err); 203*29651Ssam dra->currenttimo++; /* Update current timeout number */ 204*29651Ssam /* Did we timeout */ 205*29651Ssam if (dra->dr_flags & DR_TMDM) { 206*29651Ssam dra->dr_flags &= ~DR_TMDM; /* Clear timeout flag */ 207*29651Ssam u.u_error = 0; /* Made the error ourself, ignore it */ 208*29651Ssam } 209*29651Ssam } 210*29651Ssam else { 211*29651Ssam return physio (drstrategy, bp, dev,B_READ, drminphys, uio); 212*29651Ssam } 213*29651Ssam } 214*29651Ssam 215*29651Ssam drwrite (dev, uio) 216*29651Ssam dev_t dev; 217*29651Ssam struct uio *uio; 218*29651Ssam { register struct dr_aux *dra; 219*29651Ssam register struct buf *bp; 220*29651Ssam register int unit = RSUNIT(dev); 221*29651Ssam register long spl, err; 222*29651Ssam 223*29651Ssam if ( uio->uio_iov->iov_len <= 0 224*29651Ssam || uio->uio_iov->iov_len & 1 225*29651Ssam || (int)uio->uio_iov->iov_base & 1 226*29651Ssam ) 227*29651Ssam return EINVAL; 228*29651Ssam 229*29651Ssam #ifdef DR_DEBUG 230*29651Ssam if (DR11 & 4) { 231*29651Ssam printf("\ndrwrite: (len:%ld)(base:%lx)", 232*29651Ssam uio->uio_iov->iov_len,(int)uio->uio_iov->iov_base); 233*29651Ssam } 234*29651Ssam #endif 235*29651Ssam 236*29651Ssam dra = &dr_aux[RSUNIT(dev)]; 237*29651Ssam dra->dr_op = DR_WRITE; 238*29651Ssam bp = &dra->dr_buf; 239*29651Ssam bp->b_resid = 0; 240*29651Ssam if (dra->dr_flags & DR_NOWSTALL) { 241*29651Ssam /* We are in no stall mode, start the timer, raise IPL so nothing 242*29651Ssam can stop us once the timer's running */ 243*29651Ssam spl = SPL_UP(); 244*29651Ssam timeout(drrwtimo,(caddr_t)((dra->currenttimo<<8) | unit), 245*29651Ssam dra->wtimoticks); 246*29651Ssam err = physio (drstrategy, bp, dev,B_WRITE, drminphys, uio); 247*29651Ssam splx(spl); 248*29651Ssam if (err) 249*29651Ssam return(err); 250*29651Ssam dra->currenttimo++; /* Update current timeout number */ 251*29651Ssam /* Did we timeout */ 252*29651Ssam if (dra->dr_flags & DR_TMDM) { 253*29651Ssam dra->dr_flags &= ~DR_TMDM; /* Clear timeout flag */ 254*29651Ssam u.u_error = 0; /* Made the error ourself, ignore it */ 255*29651Ssam } 256*29651Ssam } 257*29651Ssam else { 258*29651Ssam return physio (drstrategy, bp, dev,B_WRITE, drminphys, uio); 259*29651Ssam } 260*29651Ssam } 261*29651Ssam 262*29651Ssam /* Routine used by calling program to issue commands to dr11 driver and 263*29651Ssam through it to the device. 264*29651Ssam It is also used to read status from the device and driver and to wait 265*29651Ssam for attention interrupts. 266*29651Ssam Status is returned in an 8 elements unsigned short integer array, the 267*29651Ssam first two elements of the array are also used to pass arguments to 268*29651Ssam drioctl() if required. 269*29651Ssam The function bits to be written to the dr11 are included in the cmd 270*29651Ssam argument. Even if they are not being written to the dr11 in a particular 271*29651Ssam drioctl() call, they will update the copy of cmd that is stored in the 272*29651Ssam driver. When drstrategy() is called, this updated copy is used if a 273*29651Ssam deferred function bit write has been specified. The "side effect" of 274*29651Ssam calls to the drioctl() requires that the last call prior to a read or 275*29651Ssam write has an appropriate copy of the function bits in cmd if they are 276*29651Ssam to be used in drstrategy(). 277*29651Ssam When used as command value, the contents of data[0] is the command 278*29651Ssam parameter. 279*29651Ssam */ 280*29651Ssam 281*29651Ssam drioctl(dev, cmd, data, flag) 282*29651Ssam dev_t dev; 283*29651Ssam int cmd; 284*29651Ssam long *data; 285*29651Ssam int flag; 286*29651Ssam { 287*29651Ssam register int unit = RSUNIT(dev); 288*29651Ssam register struct dr_aux *dra; 289*29651Ssam register struct rsdevice *rsaddr = RSADDR(unit); 290*29651Ssam struct dr11io dio; 291*29651Ssam ushort s, errcode, status; 292*29651Ssam long temp; 293*29651Ssam 294*29651Ssam #ifdef DR_DEBUG 295*29651Ssam if (DR11 & 0x10) 296*29651Ssam printf("\ndrioctl: (dev:%lx)(cmd:%lx)(data:%lx)(data[0]:%lx)", 297*29651Ssam dev,cmd,data,data[0]); 298*29651Ssam #endif 299*29651Ssam 300*29651Ssam dra = &dr_aux[unit]; 301*29651Ssam dra->dr_cmd = 0; /* Fresh copy; clear all previous flags */ 302*29651Ssam 303*29651Ssam switch (cmd) { 304*29651Ssam 305*29651Ssam case DRWAIT: 306*29651Ssam /* Wait for attention interrupt */ 307*29651Ssam #ifdef DR_DEBUG 308*29651Ssam printf("\ndrioctl: wait for attention interrupt"); 309*29651Ssam #endif 310*29651Ssam s = SPL_UP(); 311*29651Ssam /* If the attention flag in dr_flags is set, it probably means that 312*29651Ssam an attention has arrived by the time a previous DMA end-of-range 313*29651Ssam interrupt was serviced. If ATRX is set, we will return with out 314*29651Ssam sleeping, since we have received an attention since the last call 315*29651Ssam to wait on attention. 316*29651Ssam This may not be appropriate for some applications. 317*29651Ssam */ 318*29651Ssam if (!(dra->dr_flags & DR_ATRX)) { 319*29651Ssam dra->dr_flags |= DR_ATWT; /* Set waiting flag */ 320*29651Ssam rsaddr->dr_pulse = IENB; /* Enable interrupt; use pulse 321*29651Ssam reg. so function bits are 322*29651Ssam not changed */ 323*29651Ssam sleep((caddr_t)&dra->dr_cmd,DRPRI); 324*29651Ssam } 325*29651Ssam splx(s); 326*29651Ssam break; 327*29651Ssam 328*29651Ssam case DRPIOW: 329*29651Ssam /* Write to p-i/o register */ 330*29651Ssam rsaddr->dr_data = data[0]; 331*29651Ssam break; 332*29651Ssam 333*29651Ssam case DRPACL: 334*29651Ssam /* Send pulse to device */ 335*29651Ssam rsaddr->dr_pulse = FCN2; 336*29651Ssam break; 337*29651Ssam 338*29651Ssam case DRDACL: 339*29651Ssam /* Defer alco pulse until go */ 340*29651Ssam dra->dr_cmd |= DR_DACL; 341*29651Ssam break; 342*29651Ssam 343*29651Ssam case DRPCYL: 344*29651Ssam /* Set cycle with next go */ 345*29651Ssam dra->dr_cmd |= DR_PCYL; 346*29651Ssam break; 347*29651Ssam 348*29651Ssam case DRDFCN: 349*29651Ssam /* Do not update function bits until next go issued */ 350*29651Ssam dra->dr_cmd |= DR_DFCN; 351*29651Ssam break; 352*29651Ssam 353*29651Ssam case DRRATN: 354*29651Ssam /* Reset attention flag -- use with extreme caution */ 355*29651Ssam rsaddr->dr_pulse = RATN; 356*29651Ssam break; 357*29651Ssam 358*29651Ssam case DRRDMA: 359*29651Ssam /* Reset DMA e-o-r flag -- should never used */ 360*29651Ssam rsaddr->dr_pulse = RDMA; 361*29651Ssam break; 362*29651Ssam 363*29651Ssam case DRSFCN: 364*29651Ssam /* Set function bits */ 365*29651Ssam temp = data[0] & DR_FMSK; 366*29651Ssam rsaddr->dr_cstat = temp; /* Write to control register */ 367*29651Ssam /* This has a very important side effect -- It clears the interrupt 368*29651Ssam enable flag. That is fine for this driver, but if it is desired 369*29651Ssam to leave interrupt enable at all times, it will be necessary to 370*29651Ssam to read the status register first to get IENB, or carry a software 371*29651Ssam flag that indicates whether interrupts are set, and or this into 372*29651Ssam the controll register value being written. 373*29651Ssam */ 374*29651Ssam break; 375*29651Ssam 376*29651Ssam case DRRPER: 377*29651Ssam /* Clear parity flag */ 378*29651Ssam rsaddr->dr_pulse = RPER; 379*29651Ssam break; 380*29651Ssam 381*29651Ssam case DRSETRSTALL: 382*29651Ssam /* Set read stall mode. */ 383*29651Ssam dra->dr_flags &= (~DR_NORSTALL); 384*29651Ssam break; 385*29651Ssam 386*29651Ssam case DRSETNORSTALL: 387*29651Ssam /* Set no stall read mode. */ 388*29651Ssam dra->dr_flags |= DR_NORSTALL; 389*29651Ssam break; 390*29651Ssam 391*29651Ssam case DRGETRSTALL: 392*29651Ssam /* Returns true if in read stall mode. */ 393*29651Ssam data[0] = (dra->dr_flags & DR_NORSTALL)? 0 : 1; 394*29651Ssam break; 395*29651Ssam 396*29651Ssam case DRSETRTIMEOUT: 397*29651Ssam /* Set the number of ticks before a no stall read times out. 398*29651Ssam The argument is given in tenths of a second. */ 399*29651Ssam if (data[0] < 1) { 400*29651Ssam u.u_error = EINVAL; 401*29651Ssam temp = 1; 402*29651Ssam } 403*29651Ssam dra->rtimoticks = (data[0] * hz )/10; 404*29651Ssam break; 405*29651Ssam 406*29651Ssam case DRGETRTIMEOUT: 407*29651Ssam /* Returns the number of tenths of seconds before 408*29651Ssam a no stall read times out. */ 409*29651Ssam /* The argument is given in tenths of a second. */ 410*29651Ssam data[0] = ((dra->rtimoticks)*10)/hz; 411*29651Ssam break; 412*29651Ssam 413*29651Ssam case DRSETWSTALL: 414*29651Ssam /* Set write stall mode. */ 415*29651Ssam dra->dr_flags &= (~DR_NOWSTALL); 416*29651Ssam break; 417*29651Ssam 418*29651Ssam case DRSETNOWSTALL: 419*29651Ssam /* Set write stall mode. */ 420*29651Ssam dra->dr_flags |= DR_NOWSTALL; 421*29651Ssam break; 422*29651Ssam 423*29651Ssam case DRGETWSTALL: 424*29651Ssam /* Returns true if in write stall mode. */ 425*29651Ssam data[0] = (dra->dr_flags & DR_NOWSTALL)? 0 : 1; 426*29651Ssam break; 427*29651Ssam 428*29651Ssam case DRSETWTIMEOUT: 429*29651Ssam /* Set the number of ticks before a no stall write times out. 430*29651Ssam The argument is given in tenths of a second. */ 431*29651Ssam if (data[0] < 1) { 432*29651Ssam u.u_error = EINVAL; 433*29651Ssam temp = 1; 434*29651Ssam } 435*29651Ssam dra->wtimoticks = (data[0] * hz )/10; 436*29651Ssam break; 437*29651Ssam 438*29651Ssam case DRGETWTIMEOUT: 439*29651Ssam /* Returns the number of tenths of seconds before 440*29651Ssam a no stall write times out. */ 441*29651Ssam /* The argument is given in tenths of a second. */ 442*29651Ssam data[0] = ((dra->wtimoticks)*10)/hz; 443*29651Ssam break; 444*29651Ssam 445*29651Ssam case DRWRITEREADY: 446*29651Ssam /* Returns a value of 1 if the device can accept 447*29651Ssam data, 0 otherwise. Internally this is the 448*29651Ssam DR11-W STAT A bit. */ 449*29651Ssam 450*29651Ssam data[0] = (rsaddr->dr_cstat & STTA)? 1 : 0; 451*29651Ssam break; 452*29651Ssam 453*29651Ssam case DRREADREADY: 454*29651Ssam /* Returns a value of 1 if the device has data 455*29651Ssam for host to be read, 0 otherwise. Internally 456*29651Ssam this is the DR11-W STAT B bit. */ 457*29651Ssam data[0] = (rsaddr->dr_cstat & STTB)? 1 : 0; 458*29651Ssam break; 459*29651Ssam 460*29651Ssam case DRBUSY: 461*29651Ssam /* Returns a value of 1 if the device is busy, 462*29651Ssam 0 otherwise. Internally this is the DR11-W 463*29651Ssam STAT C bit, but there is a bug in the Omega 500/FIFO interface 464*29651Ssam board that it cannot drive this signal low for certain DR11-W 465*29651Ssam ctlr such as the Ikon. We use the REDY signal of the CSR on 466*29651Ssam the Ikon DR11-W instead. 467*29651Ssam 468*29651Ssam data[0] = (rsaddr->dr_cstat & STTC)? 1 : 0; 469*29651Ssam */ 470*29651Ssam 471*29651Ssam data[0] = ((rsaddr->dr_cstat & REDY)? 0 : 1); 472*29651Ssam break; 473*29651Ssam 474*29651Ssam case DRRESET: 475*29651Ssam rsaddr->dr_pulse = (MCLR|RDMA|RATN|RPER);/* Reset DMA ATN RPER flag */ 476*29651Ssam DELAY(0x1f000); 477*29651Ssam while (!(rsaddr->dr_cstat & REDY)) { 478*29651Ssam sleep((caddr_t)dra, DRPRI); /* Wakeup by drtimo() */ 479*29651Ssam } 480*29651Ssam dra->dr_istat = 0; 481*29651Ssam dra->dr_cmd = 0; 482*29651Ssam dra->currenttimo = 0; 483*29651Ssam break; 484*29651Ssam 485*29651Ssam default: 486*29651Ssam printf("\ndrioctl: Invalid ioctl cmd : %lx",cmd); 487*29651Ssam return EINVAL; 488*29651Ssam } 489*29651Ssam 490*29651Ssam #ifdef DR_DEBUG 491*29651Ssam if (DR11 & 0x10) 492*29651Ssam printf("**** (data[0]:%lx)",data[0]); 493*29651Ssam #endif 494*29651Ssam return 0; 495*29651Ssam } 496*29651Ssam 497*29651Ssam /* Reset state on Unibus reset */ 498*29651Ssam drreset(uban) 499*29651Ssam int uban; 500*29651Ssam { 501*29651Ssam register int i; 502*29651Ssam register struct vba_device *ui; 503*29651Ssam register struct dr_aux *dra; 504*29651Ssam 505*29651Ssam for (i = 0; i < NDR; i++, dra++) { 506*29651Ssam if ( (ui = drinfo[i]) == 0 507*29651Ssam || !ui->ui_alive 508*29651Ssam || ui->ui_vbanum != uban 509*29651Ssam ) 510*29651Ssam continue; 511*29651Ssam printf("\ndrreset: %ld",i); 512*29651Ssam /* Do something; reset board */ 513*29651Ssam } 514*29651Ssam return; 515*29651Ssam } 516*29651Ssam 517*29651Ssam /* 518*29651Ssam * An interrupt is caused either by an error, 519*29651Ssam * base address overflow, or transfer complete 520*29651Ssam */ 521*29651Ssam drintr (unit) 522*29651Ssam register long unit; 523*29651Ssam { 524*29651Ssam register struct dr_aux *dra = &dr_aux[unit]; 525*29651Ssam register struct rsdevice *rsaddr = RSADDR(unit); 526*29651Ssam register struct buf *bp; 527*29651Ssam register short status, csrtmp; 528*29651Ssam 529*29651Ssam status = rsaddr->dr_cstat & 0xffff; /* get board status register */ 530*29651Ssam dra->dr_istat = status; 531*29651Ssam 532*29651Ssam #ifdef DR_DEBUG 533*29651Ssam if (DR11 & 2) 534*29651Ssam printf("\ndrintr: dr11 status : %lx",status & 0xffff); 535*29651Ssam #endif 536*29651Ssam 537*29651Ssam if (dra->dr_flags & DR_LOOPTST) { 538*29651Ssam /* Controller is doing loopback test */ 539*29651Ssam dra->dr_flags &= ~DR_LOOPTST; 540*29651Ssam return; 541*29651Ssam } 542*29651Ssam 543*29651Ssam /* Make sure this is not a stray interrupt; at least one of dmaf or attf 544*29651Ssam must be set. Note that if the dr11 interrupt enable latch is reset 545*29651Ssam during a hardware interrupt ack sequence, and by the we get to this 546*29651Ssam point in the interrupt code it will be 0. This is done to give the 547*29651Ssam programmer some control over how the two more-or-less independent 548*29651Ssam interrupt sources on the board are handled. 549*29651Ssam If the attention flag is set when drstrategy() is called to start a 550*29651Ssam dma read or write an interrupt will be generated as soon as the 551*29651Ssam strategy routine enables interrupts for dma end-of-range. This will 552*29651Ssam cause execution of the interrupt routine (not necessarily bad) and 553*29651Ssam will cause the interrupt enable mask to be reset (very bad since the 554*29651Ssam dma end-of-range condition will not be able to generate an interrupt 555*29651Ssam when it occurs) causing the dma operation to time-out (even though 556*29651Ssam the dma transfer will be done successfully) or hang the process if a 557*29651Ssam software time-out capability is not implemented. One way to avoid 558*29651Ssam this situation is to check for a pending attention interrupt (attf 559*29651Ssam set) by calling drioctl() before doing a read or a write. For the 560*29651Ssam time being this driver will solve the problem by clearing the attf 561*29651Ssam flag in the status register before enabling interrupts in drstrategy(). 562*29651Ssam 563*29651Ssam **** The IKON 10084 for which this driver is written will set both 564*29651Ssam attf and dmaf if dma is terminated by an attention pulse. This will 565*29651Ssam cause a wakeup(&dr_aux), which will be ignored since it is not being 566*29651Ssam waited on, and an iodone(bp) which is the desired action. Some other 567*29651Ssam dr11 emulators, in particular the IKON 10077 for the Multibus, donot 568*29651Ssam dmaf in this case. This may require some addtional code in the inter- 569*29651Ssam rupt routine to ensure that en iodone(bp) is issued when dma is term- 570*29651Ssam inated by attention. 571*29651Ssam */ 572*29651Ssam 573*29651Ssam bp = dra->dr_actf; 574*29651Ssam if (!(status & (ATTF | DMAF))) { 575*29651Ssam printf("\ndrintr: Stray interrupt, dr11 status : %lx",status); 576*29651Ssam return; 577*29651Ssam } 578*29651Ssam if (status & DMAF) { 579*29651Ssam /* End-of-range interrupt */ 580*29651Ssam dra->dr_flags |= DR_DMAX; 581*29651Ssam 582*29651Ssam #ifdef DR_DEBUG 583*29651Ssam if (DR11 & 2) 584*29651Ssam printf("\ndrintr: e-o-r interrupt,cstat:%lx,dr_flags:%lx", 585*29651Ssam status&0xffff,dra->dr_flags & DR_ACTV); 586*29651Ssam #endif 587*29651Ssam if (!(dra->dr_flags & DR_ACTV)) { 588*29651Ssam /* We are not doing DMA !! */ 589*29651Ssam bp->b_flags |= B_ERROR; 590*29651Ssam } 591*29651Ssam else { 592*29651Ssam if (dra->dr_op == DR_READ) mtpr(bp->b_un.b_addr,P1DC); 593*29651Ssam dra->dr_bycnt -= bp->b_bcount; 594*29651Ssam if (dra->dr_bycnt >0) { 595*29651Ssam bp->b_un.b_addr += bp->b_bcount; 596*29651Ssam bp->b_bcount = (dra->dr_bycnt > NBPG) ? NBPG: 597*29651Ssam dra->dr_bycnt; 598*29651Ssam drstart(rsaddr,dra,bp); 599*29651Ssam return; 600*29651Ssam } 601*29651Ssam } 602*29651Ssam dra->dr_flags &= ~DR_ACTV; 603*29651Ssam wakeup(dra); /* Wakeup proc waiting in drwait() */ 604*29651Ssam rsaddr->dr_pulse = (RPER|RDMA|RATN); /* reset dma e-o-r flag */ 605*29651Ssam } 606*29651Ssam 607*29651Ssam /* Now test for attention interrupt -- It may be set in addition to 608*29651Ssam the dma e-o-r interrupt. If we get one we will issue a wakeup to 609*29651Ssam the drioctl() routine which is presumable waiting for one. 610*29651Ssam The program may have to monitor the attention interrupt received 611*29651Ssam flag in addition to doing waits for the interrupt. Futhermore, 612*29651Ssam interrupts are not enabled unless dma is in progress or drioctl() 613*29651Ssam has been called to wait for attention -- this may produce some 614*29651Ssam strange results if attf is set on the dr11 when a read or a write 615*29651Ssam is initiated, since that will enables interrupts. 616*29651Ssam **** The appropriate code for this interrupt routine will probably 617*29651Ssam be rather application dependent. 618*29651Ssam */ 619*29651Ssam 620*29651Ssam if (status & ATTF) { 621*29651Ssam dra->dr_flags |= DR_ATRX; 622*29651Ssam dra->dr_flags &= ~DR_ATWT; 623*29651Ssam rsaddr->dr_cstat = RATN; /* reset attention flag */ 624*29651Ssam wakeup((caddr_t)&dra->dr_cmd); 625*29651Ssam /* Some applications which use attention to terminate dma may also 626*29651Ssam want to issue an iodone() here to wakeup physio(). 627*29651Ssam */ 628*29651Ssam } 629*29651Ssam return; 630*29651Ssam } 631*29651Ssam 632*29651Ssam unsigned 633*29651Ssam drminphys(bp) 634*29651Ssam struct buf *bp; 635*29651Ssam { 636*29651Ssam if (bp->b_bcount > 65536) 637*29651Ssam bp->b_bcount = 65536; 638*29651Ssam } 639*29651Ssam 640*29651Ssam /* 641*29651Ssam * This routine performs the device unique operations on the DR11W 642*29651Ssam * it is passed as an argument to and invoked by physio 643*29651Ssam */ 644*29651Ssam drstrategy (bp) 645*29651Ssam register struct buf *bp; 646*29651Ssam { 647*29651Ssam register int s; 648*29651Ssam int unit = RSUNIT(bp->b_dev); 649*29651Ssam register struct rsdevice *rsaddr = RSADDR(unit); 650*29651Ssam register struct dr_aux *dra = &dr_aux[unit]; 651*29651Ssam register short go = 0; 652*29651Ssam register long baddr, ok; 653*29651Ssam #ifdef DR_DEBUG 654*29651Ssam register char *caddr; 655*29651Ssam long drva(); 656*29651Ssam #endif 657*29651Ssam 658*29651Ssam 659*29651Ssam if (!(dra->dr_flags & DR_OPEN)) { 660*29651Ssam /* Device not open */ 661*29651Ssam bp->b_error = ENXIO; 662*29651Ssam bp->b_flags |= B_ERROR; 663*29651Ssam iodone (bp); 664*29651Ssam return; 665*29651Ssam } 666*29651Ssam 667*29651Ssam while (dra->dr_flags & DR_ACTV) { 668*29651Ssam /* Device is active; should never be in here... */ 669*29651Ssam sleep((caddr_t)&dra->dr_flags,DRPRI); 670*29651Ssam } 671*29651Ssam 672*29651Ssam dra->dr_actf = bp; 673*29651Ssam 674*29651Ssam #ifdef DR_DEBUG 675*29651Ssam drva(dra,bp->b_proc,bp->b_un.b_addr,bp->b_bcount); 676*29651Ssam #endif 677*29651Ssam 678*29651Ssam dra->dr_oba = bp->b_un.b_addr; /* Save original addr, count */ 679*29651Ssam dra->dr_obc = bp->b_bcount; 680*29651Ssam dra->dr_bycnt = bp->b_bcount; /* Save xfer count used by drintr() */ 681*29651Ssam 682*29651Ssam if ((((long)bp->b_un.b_addr & 0x3fffffff) >> PGSHIFT) != 683*29651Ssam ((((long)bp->b_un.b_addr & 0x3fffffff) + bp->b_bcount) >> PGSHIFT)) { 684*29651Ssam bp->b_bcount = NBPG - (((long)bp->b_un.b_addr) & PGOFSET); 685*29651Ssam } 686*29651Ssam 687*29651Ssam dra->dr_flags |= DR_ACTV; /* Mark it active (use in intr handler) */ 688*29651Ssam s = SPL_UP(); 689*29651Ssam drstart(rsaddr,dra,bp); 690*29651Ssam splx(s); 691*29651Ssam 692*29651Ssam ok = drwait(rsaddr,dra); 693*29651Ssam #ifdef DR_DEBUG 694*29651Ssam if (DR11 & 0x40) { 695*29651Ssam caddr = (char *)dra->dr_oba; 696*29651Ssam if (dra->dr_op == DR_READ) 697*29651Ssam printf("\nAfter read: (%lx)(%lx)",caddr[0]&0xff,caddr[1]&0xff); 698*29651Ssam } 699*29651Ssam #endif 700*29651Ssam dra->dr_flags &= ~DR_ACTV; /* Clear active flag */ 701*29651Ssam bp->b_un.b_addr = dra->dr_oba; /* Restore original addr, count */ 702*29651Ssam bp->b_bcount = dra->dr_obc; 703*29651Ssam 704*29651Ssam if (!ok) bp->b_flags |= B_ERROR; 705*29651Ssam iodone(bp); /* Mark buffer B_DONE,so physstrat() 706*29651Ssam in ml/machdep.c won't sleep */ 707*29651Ssam wakeup((caddr_t)&dra->dr_flags); 708*29651Ssam 709*29651Ssam /* Return to the calling program (physio()). Physio() will sleep 710*29651Ssam until awaken by a call to iodone() in the interupt handler -- 711*29651Ssam which will be called by the dispatcher when it receives dma 712*29651Ssam end-of-range interrupt. 713*29651Ssam */ 714*29651Ssam return; 715*29651Ssam } 716*29651Ssam 717*29651Ssam drwait(rs,dr) 718*29651Ssam register struct rsdevice *rs; 719*29651Ssam register struct dr_aux *dr; 720*29651Ssam { 721*29651Ssam register long status, s; 722*29651Ssam 723*29651Ssam s = SPL_UP(); 724*29651Ssam while (dr->dr_flags & DR_ACTV) 725*29651Ssam sleep((caddr_t)dr,DRPRI); 726*29651Ssam splx(s); 727*29651Ssam 728*29651Ssam if (dr->dr_flags & DR_TMDM) { 729*29651Ssam /* DMA timed out */ 730*29651Ssam dr->dr_flags &= ~DR_TMDM; 731*29651Ssam return(0); 732*29651Ssam } 733*29651Ssam else { 734*29651Ssam if (rs->dr_cstat & (PERR|BERR|TERR)) { 735*29651Ssam (dr->dr_actf)->b_flags |= B_ERROR; 736*29651Ssam return(0); 737*29651Ssam } 738*29651Ssam } 739*29651Ssam dr->dr_flags &= ~DR_DMAX; 740*29651Ssam return(1); 741*29651Ssam } 742*29651Ssam 743*29651Ssam 744*29651Ssam drrwtimo(tinfo) 745*29651Ssam register unsigned long tinfo; 746*29651Ssam /* 747*29651Ssam * The lower 8-bit of tinfo is the minor device number, the 748*29651Ssam * remaining higher 8-bit is the current timout number 749*29651Ssam */ 750*29651Ssam { register long unit = tinfo & 0xff; 751*29651Ssam register struct dr_aux *dr = &dr_aux[unit]; 752*29651Ssam register struct rsdevice *rs = dr->dr_addr; 753*29651Ssam 754*29651Ssam /* If this is not the timeout that drwrite/drread is waiting 755*29651Ssam for then we should just go away */ 756*29651Ssam if ((tinfo & (~0xff)) != (dr->currenttimo << 8)) return; 757*29651Ssam 758*29651Ssam /* Mark the device timed out */ 759*29651Ssam dr->dr_flags |= DR_TMDM; 760*29651Ssam dr->dr_flags &= ~DR_ACTV; 761*29651Ssam rs->dr_pulse = RMSK; /* Inihibit interrupt */ 762*29651Ssam rs->dr_pulse = (RPER|RDMA|RATN|IENB); /* Clear DMA logic */ 763*29651Ssam 764*29651Ssam /* Some applications will not issue a master after dma timeout, 765*29651Ssam since doing so sends an INIT H pulse to the external device, 766*29651Ssam which may produce undesirable side-effects. */ 767*29651Ssam 768*29651Ssam /* Wake up process waiting in drwait() and flag the error */ 769*29651Ssam (dr->dr_actf)->b_flags |= B_ERROR; 770*29651Ssam wakeup((caddr_t)dr->dr_cmd); 771*29651Ssam } 772*29651Ssam 773*29651Ssam 774*29651Ssam /* 775*29651Ssam * Kick the driver every second 776*29651Ssam */ 777*29651Ssam drtimo(dev) 778*29651Ssam dev_t dev; 779*29651Ssam { 780*29651Ssam register int unit = RSUNIT(dev); 781*29651Ssam register struct dr_aux *dr; 782*29651Ssam 783*29651Ssam dr = &dr_aux[unit]; 784*29651Ssam if (dr->dr_flags & DR_OPEN) 785*29651Ssam timeout(drtimo,(caddr_t)dev,hz); 786*29651Ssam wakeup((caddr_t)dr); /* Wakeup any process waiting for interrupt */ 787*29651Ssam } 788*29651Ssam 789*29651Ssam 790*29651Ssam #ifdef DR_DEBUG 791*29651Ssam 792*29651Ssam drva(dra,p,va,bcnt) 793*29651Ssam struct dr_aux *dra; 794*29651Ssam struct proc *p; 795*29651Ssam char *va; 796*29651Ssam long bcnt; 797*29651Ssam { register long first, last , np; 798*29651Ssam 799*29651Ssam if (DR11 & 0x20) { 800*29651Ssam first = ((long)(vtoph(p,va))) >> 10; 801*29651Ssam last = ((long)(vtoph(p,va+bcnt))) >> 10; 802*29651Ssam np = bcnt / 0x3ff; 803*29651Ssam printf("\ndrva: (op:%ld)(first:%ld)(last:%ld)(np:%ld)(cnt:%ld)", 804*29651Ssam dra->dr_op,first,last,np,bcnt); 805*29651Ssam } 806*29651Ssam } 807*29651Ssam #endif 808*29651Ssam 809*29651Ssam 810*29651Ssam drstart(rsaddr,dra,bp) 811*29651Ssam register struct rsdevice *rsaddr; 812*29651Ssam register struct dr_aux *dra; 813*29651Ssam register struct buf *bp; 814*29651Ssam { register long baddr; 815*29651Ssam ushort go; 816*29651Ssam register char *caddr; 817*29651Ssam 818*29651Ssam #ifdef DR_DEBUG 819*29651Ssam if ((dra->dr_op == DR_READ) && (DR11 & 8)) { 820*29651Ssam printf("\ndrstart: READ, bcnt:%ld",bp->b_bcount); 821*29651Ssam caddr = (char *)bp->b_un.b_addr; 822*29651Ssam printf(",(%lx)(%lx)",caddr[0]&0xff,caddr[1]&0xff); 823*29651Ssam } 824*29651Ssam #endif 825*29651Ssam /* we are doing raw IO, bp->b_un.b_addr is user's address */ 826*29651Ssam baddr = (long)vtoph(bp->b_proc,(caddr_t)bp->b_un.b_addr); 827*29651Ssam 828*29651Ssam /* Set DMA address into DR11 interace registers: DR11 requires that 829*29651Ssam the address be right shifted 1 bit position before it is written 830*29651Ssam to the board (The board will left shift it one bit position before 831*29651Ssam it places the address on the bus 832*29651Ssam */ 833*29651Ssam rsaddr->dr_walo = (ushort)((baddr >> 1) & 0xffff); 834*29651Ssam rsaddr->dr_wahi = (ushort)((baddr >> 17) & 0x7fff); 835*29651Ssam 836*29651Ssam /* Set DMA range count: (number of words - 1) */ 837*29651Ssam rsaddr->dr_range = (ushort)((bp->b_bcount >> 1) - 1); 838*29651Ssam 839*29651Ssam /* Set address modifier code to be used for DMA access to memory */ 840*29651Ssam rsaddr->dr_addmod = (char)DRADDMOD; 841*29651Ssam 842*29651Ssam /* Now determine whether this is a read or a write. ***** This is 843*29651Ssam probably only usefull for link mode operation, since dr11 doesnot 844*29651Ssam controll the direction of data transfer. The C1 control input 845*29651Ssam controls whether the hardware is doing a read or a write. In link 846*29651Ssam mode this is controlled by function 1 latch (looped back by the 847*29651Ssam cable) and could be set the program. In the general case, the dr11 848*29651Ssam doesnot know in advance what the direction of transfer is - although 849*29651Ssam the program and protocol logic probably is 850*29651Ssam */ 851*29651Ssam 852*29651Ssam #ifdef DR_DEBUG 853*29651Ssam if (DR11 & 1) 854*29651Ssam printf("\ndrstrat: about to GO..,dr_cmd:%lx,drstat:%lx,drcnt:%ld,cdata:%lx,OP:%ld", 855*29651Ssam dra->dr_cmd,rsaddr->dr_cstat,rsaddr->dr_range,rsaddr->dr_data,dra->dr_op); 856*29651Ssam #endif 857*29651Ssam 858*29651Ssam /* Update function latches may have been done already by drioctl() if 859*29651Ssam request from drioctl() 860*29651Ssam */ 861*29651Ssam if (dra->dr_cmd & DR_DFCN) { 862*29651Ssam /* deferred function write */ 863*29651Ssam dra->dr_cmd &= ~DR_DFCN; /* Clear request */ 864*29651Ssam go = dra->dr_cmd & DR_FMSK; /* mask out fcn bits */ 865*29651Ssam rsaddr->dr_cstat = go; /* Write it to the board */ 866*29651Ssam } 867*29651Ssam 868*29651Ssam /* Clear dmaf and attf to assure a clean dma start */ 869*29651Ssam rsaddr->dr_pulse = (ushort)(RATN|RDMA|RPER); 870*29651Ssam rsaddr->dr_cstat = (ushort)(IENB|GO|CYCL|dra->dr_op); /* GO...... */ 871*29651Ssam 872*29651Ssam /* Now check for software cycle request -- usually by transmitter in 873*29651Ssam link mode. 874*29651Ssam */ 875*29651Ssam if (dra->dr_cmd & DR_PCYL) { 876*29651Ssam dra->dr_cmd &= ~DR_PCYL; /* Clear request */ 877*29651Ssam rsaddr->dr_pulse = CYCL; /* Use pulse register again */ 878*29651Ssam } 879*29651Ssam 880*29651Ssam /* Now check for deferred ACLO FCNT2 pulse request -- usually to tell 881*29651Ssam the transmitter (via its attention) that we have enabled dma. 882*29651Ssam */ 883*29651Ssam if (dra->dr_cmd & DR_DACL) { 884*29651Ssam dra->dr_cmd &= ~DR_DACL; /* Clear request */ 885*29651Ssam rsaddr->dr_pulse = FCN2; /* Use pulse register again */ 886*29651Ssam } 887*29651Ssam } 888*29651Ssam 889*29651Ssam #endif NDR 890