1*30222Ssam /* ik.c 1.1 86/11/29 */ 2*30222Ssam 3*30222Ssam #include "ik.h" 4*30222Ssam #if NIK > 0 5*30222Ssam /* 6*30222Ssam * PS300/IKON DR-11W Device Driver. 7*30222Ssam */ 8*30222Ssam #include "param.h" 9*30222Ssam #include "buf.h" 10*30222Ssam #include "cmap.h" 11*30222Ssam #include "conf.h" 12*30222Ssam #include "dir.h" 13*30222Ssam #include "dkstat.h" 14*30222Ssam #include "map.h" 15*30222Ssam #include "systm.h" 16*30222Ssam #include "user.h" 17*30222Ssam #include "vmmac.h" 18*30222Ssam #include "proc.h" 19*30222Ssam #include "uio.h" 20*30222Ssam #include "kernel.h" 21*30222Ssam 22*30222Ssam #include "../tahoe/mtpr.h" 23*30222Ssam #include "../tahoe/pte.h" 24*30222Ssam 25*30222Ssam #include "../tahoevba/vbavar.h" 26*30222Ssam #include "../tahoevba/ikreg.h" 27*30222Ssam #include "../tahoevba/psreg.h" 28*30222Ssam #include "../tahoevba/psproto.h" 29*30222Ssam 30*30222Ssam int ikprobe(), ikattach(), iktimer(); 31*30222Ssam struct vba_device *ikinfo[NIK]; 32*30222Ssam long ikstd[] = { 0 }; 33*30222Ssam struct vba_driver ikdriver = { ikprobe, 0, ikattach, 0, ikstd, "ik", ikinfo }; 34*30222Ssam 35*30222Ssam #define splik() spl4() 36*30222Ssam /* 37*30222Ssam * Devices are organized in pairs with the odd valued 38*30222Ssam * device being used for ``diagnostic'' purposes. That 39*30222Ssam * is diagnostic devices don't get auto-attach'd and 40*30222Ssam * detach'd on open-close. 41*30222Ssam */ 42*30222Ssam #define IKUNIT(dev) (minor(dev) >> 1) 43*30222Ssam #define IKDIAG(dev) (minor(dev) & 01) /* is a diagnostic unit */ 44*30222Ssam 45*30222Ssam struct ik_softc { 46*30222Ssam uid_t is_uid; /* uid of open processes */ 47*30222Ssam u_short is_timeout; /* current timeout (seconds) */ 48*30222Ssam u_short is_error; /* internal error codes */ 49*30222Ssam u_short is_flags; 50*30222Ssam #define IKF_ATTACHED 0x1 /* unit is attached (not used yet) */ 51*30222Ssam union { 52*30222Ssam u_short w[2]; 53*30222Ssam u_long l; 54*30222Ssam } is_nameaddr; /* address of last symbol lookup */ 55*30222Ssam caddr_t is_buf; /* i/o buffer XXX */ 56*30222Ssam } ik_softc[NIK]; 57*30222Ssam 58*30222Ssam struct buf iktab[NIK]; /* unit command queue headers */ 59*30222Ssam struct buf rikbuf[NIK]; /* buffers for read/write operations */ 60*30222Ssam struct buf cikbuf[NIK]; /* buffers for control operations */ 61*30222Ssam 62*30222Ssam /* buf overlay definitions */ 63*30222Ssam #define b_command b_resid 64*30222Ssam 65*30222Ssam int ikdiotimo = PS_DIOTIMO; /* dio polling timeout */ 66*30222Ssam int iktimeout = PS_TIMEOUT; /* attention/dma timeout (in hz) */ 67*30222Ssam 68*30222Ssam ikprobe(reg, vi) 69*30222Ssam caddr_t reg; 70*30222Ssam struct vba_device *vi; 71*30222Ssam { 72*30222Ssam register int br, cvec; /* r12, r11 */ 73*30222Ssam register struct ikdevice *ik; 74*30222Ssam 75*30222Ssam if (badaddr(reg, 2)) 76*30222Ssam return (0); 77*30222Ssam ik = (struct ikdevice *)reg; 78*30222Ssam ik->ik_vec = --vi->ui_hd->vh_lastiv; 79*30222Ssam /* 80*30222Ssam * Try and reset the PS300. Since this 81*30222Ssam * won't work if it's powered off, we 82*30222Ssam * can't use sucess/failure to decide 83*30222Ssam * if the device is present. 84*30222Ssam */ 85*30222Ssam br = 0; 86*30222Ssam if (!psreset(ik, IKCSR_IENA) || br == 0) 87*30222Ssam br = 0x18, cvec = ik->ik_vec; /* XXX */ 88*30222Ssam return (sizeof (struct ikdevice)); 89*30222Ssam } 90*30222Ssam 91*30222Ssam /* 92*30222Ssam * Perform a ``hard'' reset. 93*30222Ssam */ 94*30222Ssam psreset(ik, iena) 95*30222Ssam register struct ikdevice *ik; 96*30222Ssam { 97*30222Ssam 98*30222Ssam ik->ik_csr = IKCSR_MCLR|iena; 99*30222Ssam DELAY(10000); 100*30222Ssam ik->ik_csr = IKCSR_FNC3; 101*30222Ssam return (dioread(ik) == PS_RESET); 102*30222Ssam } 103*30222Ssam 104*30222Ssam ikattach(vi) 105*30222Ssam struct vba_device *vi; 106*30222Ssam { 107*30222Ssam register struct ikdevice *ik; 108*30222Ssam 109*30222Ssam ikinfo[vi->ui_unit] = vi; 110*30222Ssam ik = (struct ikdevice *)vi->ui_addr; 111*30222Ssam ik->ik_vec = IKVEC_BASE + vi->ui_unit; /* interrupt vector */ 112*30222Ssam ik->ik_mod = IKMOD_STD; /* address modifier */ 113*30222Ssam ik_softc[vi->ui_unit].is_uid = -1; 114*30222Ssam } 115*30222Ssam 116*30222Ssam /* 117*30222Ssam * Open a PS300 and attach. We allow multiple 118*30222Ssam * processes with the same uid to share a unit. 119*30222Ssam */ 120*30222Ssam /*ARGSUSED*/ 121*30222Ssam ikopen(dev, flag) 122*30222Ssam dev_t dev; 123*30222Ssam int flag; 124*30222Ssam { 125*30222Ssam register int unit = IKUNIT(dev); 126*30222Ssam register struct ik_softc *sc; 127*30222Ssam struct vba_device *vi; 128*30222Ssam struct ikdevice *ik; 129*30222Ssam int reset; 130*30222Ssam 131*30222Ssam if (unit >= NIK || (vi = ikinfo[unit]) == 0 || vi->ui_alive == 0) 132*30222Ssam return (ENXIO); 133*30222Ssam sc = &ik_softc[unit]; 134*30222Ssam if (sc->is_uid != -1 && sc->is_uid != u.u_uid) 135*30222Ssam return (EBUSY); 136*30222Ssam if (sc->is_uid == -1) { 137*30222Ssam sc->is_buf = (caddr_t)wmemall(vmemall, PS_MAXDMA); 138*30222Ssam if (sc->is_buf == 0) 139*30222Ssam return (ENOMEM); 140*30222Ssam sc->is_timeout = 0; 141*30222Ssam timeout(iktimer, unit, hz); 142*30222Ssam /* 143*30222Ssam * Perform PS300 attach for first process. 144*30222Ssam */ 145*30222Ssam if (!IKDIAG(dev)) { 146*30222Ssam reset = 0; 147*30222Ssam again: 148*30222Ssam if (ikcommand(dev, PS_ATTACH, 1)) { 149*30222Ssam /* 150*30222Ssam * If attach fails, perform a hard 151*30222Ssam * reset once, then retry the command. 152*30222Ssam */ 153*30222Ssam ik = (struct ikdevice *)ikinfo[unit]->ui_addr; 154*30222Ssam if (!reset++ && psreset(ik, 0)) 155*30222Ssam goto again; 156*30222Ssam untimeout(iktimer, unit); 157*30222Ssam wmemfree(sc->is_buf, PS_MAXDMA); 158*30222Ssam sc->is_buf = 0; 159*30222Ssam return (EIO); 160*30222Ssam } 161*30222Ssam } 162*30222Ssam sc->is_uid = u.u_uid; 163*30222Ssam } 164*30222Ssam return (0); 165*30222Ssam } 166*30222Ssam 167*30222Ssam /*ARGSUSED*/ 168*30222Ssam ikclose(dev, flag) 169*30222Ssam dev_t dev; 170*30222Ssam int flag; 171*30222Ssam { 172*30222Ssam int unit = IKUNIT(dev); 173*30222Ssam register struct ik_softc *sc = &ik_softc[unit]; 174*30222Ssam 175*30222Ssam if (!IKDIAG(dev)) 176*30222Ssam (void) ikcommand(dev, PS_DETACH, 1); /* auto detach */ 177*30222Ssam sc->is_uid = -1; 178*30222Ssam if (sc->is_buf) { 179*30222Ssam wmemfree(sc->is_buf, PS_MAXDMA); 180*30222Ssam sc->is_buf = 0; 181*30222Ssam } 182*30222Ssam untimeout(iktimer, unit); 183*30222Ssam } 184*30222Ssam 185*30222Ssam ikread(dev, uio) 186*30222Ssam dev_t dev; 187*30222Ssam struct uio *uio; 188*30222Ssam { 189*30222Ssam 190*30222Ssam return (ikrw(dev, uio, B_READ)); 191*30222Ssam } 192*30222Ssam 193*30222Ssam ikwrite(dev, uio) 194*30222Ssam dev_t dev; 195*30222Ssam struct uio *uio; 196*30222Ssam { 197*30222Ssam 198*30222Ssam return (ikrw(dev, uio, B_WRITE)); 199*30222Ssam } 200*30222Ssam 201*30222Ssam /* 202*30222Ssam * Take read/write request and perform physical i/o 203*30222Ssam * transaction with PS300. This involves constructing 204*30222Ssam * a physical i/o request vector based on the uio 205*30222Ssam * vector, performing the dma, and, finally, moving 206*30222Ssam * the data to it's final destination (because of CCI 207*30222Ssam * VERSAbus bogosities). 208*30222Ssam */ 209*30222Ssam ikrw(dev, uio, rw) 210*30222Ssam dev_t dev; 211*30222Ssam register struct uio *uio; 212*30222Ssam int rw; 213*30222Ssam { 214*30222Ssam int error, unit = IKUNIT(dev), s, wrcmd; 215*30222Ssam register struct buf *bp; 216*30222Ssam register struct iovec *iov; 217*30222Ssam register struct psalist *ap; 218*30222Ssam struct ik_softc *sc = &ik_softc[unit]; 219*30222Ssam 220*30222Ssam if (unit >= NIK) 221*30222Ssam return (ENXIO); 222*30222Ssam bp = &rikbuf[unit]; 223*30222Ssam error = 0, iov = uio->uio_iov, wrcmd = PS_WRPHY; 224*30222Ssam for (; !error && uio->uio_iovcnt; iov++, uio->uio_iovcnt--) { 225*30222Ssam /* 226*30222Ssam * Hack way to set PS300 address w/o doing an lseek 227*30222Ssam * and specify write physical w/ refresh synchronization. 228*30222Ssam */ 229*30222Ssam if (iov->iov_len == 0) { 230*30222Ssam if ((int)iov->iov_base&PSIO_SYNC) 231*30222Ssam wrcmd = PS_WRPHY_SYNC; 232*30222Ssam uio->uio_offset = (int)iov->iov_base & ~PSIO_SYNC; 233*30222Ssam continue; 234*30222Ssam } 235*30222Ssam if (iov->iov_len > PS_MAXDMA) { 236*30222Ssam sc->is_error = PSERROR_INVALBC, error = EINVAL; 237*30222Ssam continue; 238*30222Ssam } 239*30222Ssam if ((int)uio->uio_offset&01) { 240*30222Ssam sc->is_error = PSERROR_BADADDR, error = EINVAL; 241*30222Ssam continue; 242*30222Ssam } 243*30222Ssam s = splbio(); 244*30222Ssam while (bp->b_flags&B_BUSY) { 245*30222Ssam bp->b_flags |= B_WANTED; 246*30222Ssam sleep((caddr_t)bp, PRIBIO+1); 247*30222Ssam } 248*30222Ssam splx(s); 249*30222Ssam bp->b_flags = B_BUSY | rw; 250*30222Ssam /* 251*30222Ssam * Construct address descriptor in buffer. 252*30222Ssam */ 253*30222Ssam ap = (struct psalist *)sc->is_buf; 254*30222Ssam ap->nblocks = 1; 255*30222Ssam /* work-around dr300 word swapping */ 256*30222Ssam ap->addr[0] = uio->uio_offset & 0xffff; 257*30222Ssam ap->addr[1] = uio->uio_offset >> 16; 258*30222Ssam ap->wc = (iov->iov_len + 1) >> 1; 259*30222Ssam if (rw == B_WRITE) { 260*30222Ssam error = copyin(iov->iov_base, (caddr_t)&ap[1], 261*30222Ssam iov->iov_len); 262*30222Ssam if (!error) 263*30222Ssam error = ikcommand(dev, wrcmd, 264*30222Ssam iov->iov_len + sizeof (*ap)); 265*30222Ssam } else { 266*30222Ssam caddr_t cp; 267*30222Ssam int len; 268*30222Ssam 269*30222Ssam error = ikcommand(dev, PS_RDPHY, sizeof (*ap)); 270*30222Ssam cp = (caddr_t)&ap[1], len = iov->iov_len; 271*30222Ssam for (; len > 0; len -= NBPG, cp += NBPG) 272*30222Ssam mtpr(cp, P1DC); 273*30222Ssam if (!error) 274*30222Ssam error = copyout((caddr_t)&ap[1], iov->iov_base, 275*30222Ssam iov->iov_len); 276*30222Ssam } 277*30222Ssam (void) splbio(); 278*30222Ssam if (bp->b_flags&B_WANTED) 279*30222Ssam wakeup((caddr_t)bp); 280*30222Ssam splx(s); 281*30222Ssam uio->uio_resid -= iov->iov_len; 282*30222Ssam uio->uio_offset += iov->iov_len; 283*30222Ssam bp->b_flags &= ~(B_BUSY|B_WANTED); 284*30222Ssam } 285*30222Ssam return (error); 286*30222Ssam } 287*30222Ssam 288*30222Ssam /* 289*30222Ssam * Perform a PS300 command. 290*30222Ssam */ 291*30222Ssam ikcommand(dev, com, count) 292*30222Ssam dev_t dev; 293*30222Ssam int com, count; 294*30222Ssam { 295*30222Ssam register struct buf *bp; 296*30222Ssam register int s; 297*30222Ssam 298*30222Ssam bp = &cikbuf[IKUNIT(dev)]; 299*30222Ssam s = splik(); 300*30222Ssam while (bp->b_flags&B_BUSY) { 301*30222Ssam if (bp->b_flags&B_DONE) 302*30222Ssam break; 303*30222Ssam bp->b_flags |= B_WANTED; 304*30222Ssam sleep((caddr_t)bp, PRIBIO); 305*30222Ssam } 306*30222Ssam bp->b_flags = B_BUSY|B_READ; 307*30222Ssam splx(s); 308*30222Ssam bp->b_dev = dev; 309*30222Ssam bp->b_command = com; 310*30222Ssam bp->b_bcount = count; 311*30222Ssam ikstrategy(bp); 312*30222Ssam biowait(bp); 313*30222Ssam if (bp->b_flags&B_WANTED) 314*30222Ssam wakeup((caddr_t)bp); 315*30222Ssam bp->b_flags &= B_ERROR; 316*30222Ssam return (geterror(bp)); 317*30222Ssam } 318*30222Ssam 319*30222Ssam /* 320*30222Ssam * Physio strategy routine 321*30222Ssam */ 322*30222Ssam ikstrategy(bp) 323*30222Ssam register struct buf *bp; 324*30222Ssam { 325*30222Ssam register struct buf *dp; 326*30222Ssam 327*30222Ssam /* 328*30222Ssam * Put request at end of controller queue. 329*30222Ssam */ 330*30222Ssam dp = &iktab[IKUNIT(bp->b_dev)]; 331*30222Ssam bp->av_forw = NULL; 332*30222Ssam (void) splik(); 333*30222Ssam if (dp->b_actf != NULL) { 334*30222Ssam dp->b_actl->av_forw = bp; 335*30222Ssam dp->b_actl = bp; 336*30222Ssam } else 337*30222Ssam dp->b_actf = dp->b_actl = bp; 338*30222Ssam if (!dp->b_active) 339*30222Ssam ikstart(dp); 340*30222Ssam (void) spl0(); 341*30222Ssam } 342*30222Ssam 343*30222Ssam /* 344*30222Ssam * Start the next command on the controller's queue. 345*30222Ssam */ 346*30222Ssam ikstart(dp) 347*30222Ssam register struct buf *dp; 348*30222Ssam { 349*30222Ssam register struct buf *bp; 350*30222Ssam register struct ikdevice *ik; 351*30222Ssam register struct ik_softc *sc; 352*30222Ssam register struct psalist *ap; 353*30222Ssam u_short bc, csr; 354*30222Ssam u_int addr; 355*30222Ssam int unit; 356*30222Ssam 357*30222Ssam loop: 358*30222Ssam /* 359*30222Ssam * Pull a request off the controller queue 360*30222Ssam */ 361*30222Ssam if ((bp = dp->b_actf) == NULL) { 362*30222Ssam dp->b_active = 0; 363*30222Ssam return; 364*30222Ssam } 365*30222Ssam /* 366*30222Ssam * Mark controller busy and process this request. 367*30222Ssam */ 368*30222Ssam dp->b_active = 1; 369*30222Ssam unit = IKUNIT(bp->b_dev); 370*30222Ssam sc = &ik_softc[unit]; 371*30222Ssam ik = (struct ikdevice *)ikinfo[unit]->ui_addr; 372*30222Ssam switch (bp->b_command) { 373*30222Ssam 374*30222Ssam case PS_ATTACH: /* logical unit attach */ 375*30222Ssam case PS_DETACH: /* logical unit detach */ 376*30222Ssam case PS_LOOKUP: /* name lookup */ 377*30222Ssam case PS_RDPHY: /* physical i/o read */ 378*30222Ssam case PS_WRPHY: /* physical i/o write */ 379*30222Ssam case PS_WRPHY_SYNC: /* physical i/o write w/ sync */ 380*30222Ssam /* 381*30222Ssam * Handshake command and, optionally, 382*30222Ssam * byte count and byte swap flag. 383*30222Ssam */ 384*30222Ssam if (sc->is_error = diowrite(ik, bp->b_command)) 385*30222Ssam goto bad; 386*30222Ssam if (bp->b_command < PS_DETACH) { 387*30222Ssam if (sc->is_error = diowrite(ik, bp->b_bcount)) 388*30222Ssam goto bad; 389*30222Ssam if (sc->is_error = diowrite(ik, 0 /* !swab */)) 390*30222Ssam goto bad; 391*30222Ssam } 392*30222Ssam /* 393*30222Ssam * Set timeout and wait for an attention interrupt. 394*30222Ssam */ 395*30222Ssam sc->is_timeout = iktimeout; 396*30222Ssam return; 397*30222Ssam 398*30222Ssam case PS_DMAOUT: /* dma data host->PS300 */ 399*30222Ssam bc = bp->b_bcount; 400*30222Ssam csr = IKCSR_CYCLE; 401*30222Ssam break; 402*30222Ssam 403*30222Ssam case PS_DMAIN: /* dma data PS300->host */ 404*30222Ssam bc = bp->b_bcount; 405*30222Ssam csr = IKCSR_CYCLE|IKCSR_FNC1; 406*30222Ssam break; 407*30222Ssam 408*30222Ssam default: 409*30222Ssam log(LOG_ERR, "ik%d: bad cmd %x\n", unit, bp->b_command); 410*30222Ssam sc->is_error = PSERROR_BADCMD; 411*30222Ssam goto bad; 412*30222Ssam } 413*30222Ssam /* initiate dma transfer */ 414*30222Ssam addr = vtoph((struct proc *)0, sc->is_buf); 415*30222Ssam ik->ik_bahi = addr >> 17; 416*30222Ssam ik->ik_balo = (addr >> 1) & 0xffff; 417*30222Ssam ik->ik_wc = ((bc + 1) >> 1) - 1; /* round & convert */ 418*30222Ssam ik->ik_pulse = IKPULSE_RATTF|IKPULSE_RDMAF; 419*30222Ssam sc->is_timeout = iktimeout; 420*30222Ssam ik->ik_csr = IKCSR_IENA|IKCSR_GO|csr; 421*30222Ssam return; 422*30222Ssam bad: 423*30222Ssam bp->b_flags |= B_ERROR; 424*30222Ssam dp->b_actf = bp->av_forw; /* remove from queue */ 425*30222Ssam biodone(bp); 426*30222Ssam goto loop; 427*30222Ssam } 428*30222Ssam 429*30222Ssam #define FETCHWORD(i) { \ 430*30222Ssam int v; \ 431*30222Ssam \ 432*30222Ssam v = dioread(ik); \ 433*30222Ssam if (v == -1) { \ 434*30222Ssam sc->is_error = PSERROR_NAMETIMO; \ 435*30222Ssam goto bad; \ 436*30222Ssam } \ 437*30222Ssam sc->is_nameaddr.w[i] = v; \ 438*30222Ssam } 439*30222Ssam 440*30222Ssam /* 441*30222Ssam * Process a device interrupt. 442*30222Ssam */ 443*30222Ssam ikintr(ikon) 444*30222Ssam int ikon; 445*30222Ssam { 446*30222Ssam register struct ikdevice *ik; 447*30222Ssam register struct buf *bp, *dp; 448*30222Ssam struct ik_softc *sc; 449*30222Ssam register u_short data; 450*30222Ssam u_short i, v; 451*30222Ssam 452*30222Ssam /* should go by controller, but for now... */ 453*30222Ssam if (ikinfo[ikon] == 0) 454*30222Ssam return; 455*30222Ssam ik = (struct ikdevice *)ikinfo[ikon]->ui_addr; 456*30222Ssam /* 457*30222Ssam * Discard all non-attention interrupts. The 458*30222Ssam * interrupts we're throwing away should all be 459*30222Ssam * associated with DMA completion. 460*30222Ssam */ 461*30222Ssam data = ik->ik_data; 462*30222Ssam if ((ik->ik_csr&(IKCSR_ATTF|IKCSR_STATC)) != IKCSR_ATTF) { 463*30222Ssam ik->ik_pulse = IKPULSE_RATTF|IKPULSE_RDMAF|IKPULSE_SIENA; 464*30222Ssam return; 465*30222Ssam } 466*30222Ssam /* 467*30222Ssam * Fetch attention code immediately. 468*30222Ssam */ 469*30222Ssam ik->ik_csr = IKCSR_RATTF|IKCSR_RDMAF|IKCSR_FNC1; 470*30222Ssam ik->ik_pulse = IKPULSE_FNC2; 471*30222Ssam /* 472*30222Ssam * Get device and block structures, and a pointer 473*30222Ssam * to the vba_device for the device. We receive an 474*30222Ssam * unsolicited interrupt whenever the PS300 is power 475*30222Ssam * cycled (so ignore it in that case). 476*30222Ssam */ 477*30222Ssam dp = &iktab[ikon]; 478*30222Ssam if ((bp = dp->b_actf) == NULL) { 479*30222Ssam if (PS_CODE(data) != PS_RESET) /* power failure */ 480*30222Ssam log(LOG_WARNING, "ik%d: spurious interrupt, code %x\n", 481*30222Ssam ikon, data); 482*30222Ssam goto enable; 483*30222Ssam } 484*30222Ssam sc = &ik_softc[IKUNIT(bp->b_dev)]; 485*30222Ssam sc->is_timeout = 0; /* disable timer */ 486*30222Ssam switch (PS_CODE(data)) { 487*30222Ssam 488*30222Ssam case PS_LOOKUP: /* name lookup */ 489*30222Ssam if (data == PS_LOOKUP) { /* dma name */ 490*30222Ssam bp->b_command = PS_DMAOUT; 491*30222Ssam goto opcont; 492*30222Ssam } 493*30222Ssam if (data == PS_DMAOK(PS_LOOKUP)) { 494*30222Ssam /* reenable interrupt and wait for address */ 495*30222Ssam sc->is_timeout = iktimeout; 496*30222Ssam goto enable; 497*30222Ssam } 498*30222Ssam /* 499*30222Ssam * Address should be present, extract it one 500*30222Ssam * word at a time from the PS300 (yech). 501*30222Ssam */ 502*30222Ssam if (data != PS_ADROK(PS_LOOKUP)) 503*30222Ssam goto bad; 504*30222Ssam FETCHWORD(0); 505*30222Ssam FETCHWORD(1); 506*30222Ssam goto opdone; 507*30222Ssam 508*30222Ssam case PS_WRPHY_SYNC: /* physical i/o write w/ sync */ 509*30222Ssam if (data == PS_WRPHY_SYNC) { /* start dma transfer */ 510*30222Ssam bp->b_command = PS_DMAOUT; 511*30222Ssam goto opcont; 512*30222Ssam } 513*30222Ssam if (data != PS_DMAOK(PS_WRPHY_SYNC)) 514*30222Ssam goto bad; 515*30222Ssam goto opdone; 516*30222Ssam 517*30222Ssam case PS_WRPHY: /* physical i/o write */ 518*30222Ssam if (data == PS_WRPHY) { /* start dma transfer */ 519*30222Ssam bp->b_command = PS_DMAOUT; 520*30222Ssam goto opcont; 521*30222Ssam } 522*30222Ssam if (data != PS_DMAOK(PS_WRPHY)) 523*30222Ssam goto bad; 524*30222Ssam goto opdone; 525*30222Ssam 526*30222Ssam case PS_ATTACH: /* attach unit */ 527*30222Ssam case PS_DETACH: /* detach unit */ 528*30222Ssam case PS_ABORT: /* abort code from ps300 */ 529*30222Ssam if (data != bp->b_command) 530*30222Ssam goto bad; 531*30222Ssam goto opdone; 532*30222Ssam 533*30222Ssam case PS_RDPHY: /* physical i/o read */ 534*30222Ssam if (data == PS_RDPHY) { /* dma address list */ 535*30222Ssam bp->b_command = PS_DMAOUT; 536*30222Ssam goto opcont; 537*30222Ssam } 538*30222Ssam if (data == PS_ADROK(PS_RDPHY)) { 539*30222Ssam /* collect read byte count and start dma */ 540*30222Ssam bp->b_bcount = dioread(ik); 541*30222Ssam if (bp->b_bcount == -1) 542*30222Ssam goto bad; 543*30222Ssam bp->b_command = PS_DMAIN; 544*30222Ssam goto opcont; 545*30222Ssam } 546*30222Ssam if (data == PS_DMAOK(PS_RDPHY)) 547*30222Ssam goto opdone; 548*30222Ssam goto bad; 549*30222Ssam } 550*30222Ssam bad: 551*30222Ssam sc->is_error = data; 552*30222Ssam bp->b_flags |= B_ERROR; 553*30222Ssam opdone: 554*30222Ssam dp->b_actf = bp->av_forw; /* remove from queue */ 555*30222Ssam biodone(bp); 556*30222Ssam opcont: 557*30222Ssam ikstart(dp); 558*30222Ssam enable: 559*30222Ssam ik->ik_pulse = IKPULSE_SIENA; /* explicitly reenable */ 560*30222Ssam } 561*30222Ssam 562*30222Ssam /* 563*30222Ssam * Watchdog timer. 564*30222Ssam */ 565*30222Ssam iktimer(unit) 566*30222Ssam int unit; 567*30222Ssam { 568*30222Ssam register struct ik_softc *sc = &ik_softc[unit]; 569*30222Ssam 570*30222Ssam if (sc->is_timeout && --sc->is_timeout == 0) { 571*30222Ssam register struct buf *dp, *bp; 572*30222Ssam int s; 573*30222Ssam 574*30222Ssam log(LOG_ERROR, "ik%d: timeout\n", unit); 575*30222Ssam s = splik(); 576*30222Ssam /* should abort current command */ 577*30222Ssam dp = &iktab[unit]; 578*30222Ssam if (bp = dp->b_actf) { 579*30222Ssam sc->is_error = PSERROR_CMDTIMO; 580*30222Ssam bp->b_flags |= B_ERROR; 581*30222Ssam dp->b_actf = bp->av_forw; /* remove from queue */ 582*30222Ssam biodone(bp); 583*30222Ssam ikstart(dp); 584*30222Ssam } 585*30222Ssam splx(s); 586*30222Ssam } 587*30222Ssam timeout(iktimer, unit, hz); 588*30222Ssam } 589*30222Ssam 590*30222Ssam /* 591*30222Ssam * Handshake read from DR300. 592*30222Ssam */ 593*30222Ssam dioread(ik) 594*30222Ssam register struct ikdevice *ik; 595*30222Ssam { 596*30222Ssam register int timeout; 597*30222Ssam u_short data; 598*30222Ssam 599*30222Ssam for (timeout = ikdiotimo; timeout > 0; timeout--) 600*30222Ssam if ((ik->ik_csr&(IKCSR_ATTF|IKCSR_STATC)) == IKCSR_ATTF) { 601*30222Ssam data = ik->ik_data; 602*30222Ssam ik->ik_csr = IKCSR_RATTF|IKCSR_RDMAF|IKCSR_FNC1; 603*30222Ssam ik->ik_pulse = IKPULSE_FNC2; 604*30222Ssam return (data); 605*30222Ssam } 606*30222Ssam return (-1); 607*30222Ssam } 608*30222Ssam 609*30222Ssam /* 610*30222Ssam * Handshake write to DR300. 611*30222Ssam * 612*30222Ssam * Interrupts are enabled before completing the work 613*30222Ssam * so the caller should either be at splik or be 614*30222Ssam * prepared to take the interrupt immediately. 615*30222Ssam */ 616*30222Ssam diowrite(ik, v) 617*30222Ssam register struct ikdevice *ik; 618*30222Ssam u_short v; 619*30222Ssam { 620*30222Ssam register int timeout; 621*30222Ssam register u_short csr; 622*30222Ssam 623*30222Ssam top: 624*30222Ssam /* 625*30222Ssam * Deposit data and generate dr300 attention 626*30222Ssam */ 627*30222Ssam ik->ik_data = v; 628*30222Ssam ik->ik_csr = IKCSR_RDMAF|IKCSR_RATTF; 629*30222Ssam ik->ik_pulse = IKPULSE_FNC2; 630*30222Ssam for (timeout = ikdiotimo; timeout > 0; timeout--) { 631*30222Ssam csr = ik->ik_csr; 632*30222Ssam #define IKCSR_DONE (IKCSR_STATA|IKCSR_STATC) 633*30222Ssam if ((csr&IKCSR_DONE) == IKCSR_DONE) { 634*30222Ssam /* 635*30222Ssam * Done, complete handshake by notifying dr300. 636*30222Ssam */ 637*30222Ssam ik->ik_csr = IKCSR_IENA; /* ~IKCSR_FNC1 */ 638*30222Ssam ik->ik_pulse = IKPULSE_FNC2; 639*30222Ssam return (0); 640*30222Ssam } 641*30222Ssam /* beware of potential deadlock with dioread */ 642*30222Ssam if ((csr&(IKCSR_ATTF|IKCSR_STATC)) == IKCSR_ATTF) 643*30222Ssam goto top; 644*30222Ssam } 645*30222Ssam ik->ik_csr = IKCSR_IENA; 646*30222Ssam return (PSERROR_DIOTIMO); 647*30222Ssam } 648*30222Ssam 649*30222Ssam /*ARGSUSED*/ 650*30222Ssam ikioctl(dev, cmd, data, flag) 651*30222Ssam dev_t dev; 652*30222Ssam int cmd; 653*30222Ssam caddr_t data; 654*30222Ssam int flag; 655*30222Ssam { 656*30222Ssam int error = 0, unit = IKUNIT(dev), s; 657*30222Ssam register struct ik_softc *sc = &ik_softc[unit]; 658*30222Ssam 659*30222Ssam switch (cmd) { 660*30222Ssam 661*30222Ssam case PSIOGETERROR: /* get error code for last operation */ 662*30222Ssam *(int *)data = sc->is_error; 663*30222Ssam break; 664*30222Ssam 665*30222Ssam case PSIOLOOKUP: { /* PS300 name lookup */ 666*30222Ssam register struct pslookup *lp = (struct pslookup *)data; 667*30222Ssam register struct buf *bp; 668*30222Ssam 669*30222Ssam if (lp->pl_len > PS_MAXNAMELEN) 670*30222Ssam return (EINVAL); 671*30222Ssam bp = &rikbuf[unit]; 672*30222Ssam s = splbio(); 673*30222Ssam while (bp->b_flags&B_BUSY) { 674*30222Ssam bp->b_flags |= B_WANTED; 675*30222Ssam sleep((caddr_t)bp, PRIBIO+1); 676*30222Ssam } 677*30222Ssam splx(s); 678*30222Ssam bp->b_flags = B_BUSY | B_WRITE; 679*30222Ssam error = copyin(lp->pl_name, sc->is_buf, lp->pl_len); 680*30222Ssam if (error == 0) { 681*30222Ssam if (lp->pl_len&1) 682*30222Ssam sc->is_buf[lp->pl_len] = '\0'; 683*30222Ssam error = ikcommand(dev, PS_LOOKUP, lp->pl_len); 684*30222Ssam } 685*30222Ssam s = splbio(); 686*30222Ssam if (bp->b_flags&B_WANTED) 687*30222Ssam wakeup((caddr_t)bp); 688*30222Ssam splx(s); 689*30222Ssam bp->b_flags &= ~(B_BUSY|B_WANTED); 690*30222Ssam lp->pl_addr = sc->is_nameaddr.l; 691*30222Ssam break; 692*30222Ssam } 693*30222Ssam default: 694*30222Ssam return (ENOTTY); 695*30222Ssam } 696*30222Ssam return (error); 697*30222Ssam } 698*30222Ssam #endif 699