1*30228Ssam /* ik.c 1.2 86/11/29 */ 230222Ssam 330222Ssam #include "ik.h" 430222Ssam #if NIK > 0 530222Ssam /* 630222Ssam * PS300/IKON DR-11W Device Driver. 730222Ssam */ 830222Ssam #include "param.h" 930222Ssam #include "buf.h" 1030222Ssam #include "cmap.h" 1130222Ssam #include "conf.h" 1230222Ssam #include "dir.h" 1330222Ssam #include "dkstat.h" 1430222Ssam #include "map.h" 1530222Ssam #include "systm.h" 1630222Ssam #include "user.h" 1730222Ssam #include "vmmac.h" 1830222Ssam #include "proc.h" 1930222Ssam #include "uio.h" 2030222Ssam #include "kernel.h" 21*30228Ssam #include "syslog.h" 2230222Ssam 2330222Ssam #include "../tahoe/mtpr.h" 2430222Ssam #include "../tahoe/pte.h" 2530222Ssam 2630222Ssam #include "../tahoevba/vbavar.h" 2730222Ssam #include "../tahoevba/ikreg.h" 2830222Ssam #include "../tahoevba/psreg.h" 2930222Ssam #include "../tahoevba/psproto.h" 3030222Ssam 3130222Ssam int ikprobe(), ikattach(), iktimer(); 3230222Ssam struct vba_device *ikinfo[NIK]; 3330222Ssam long ikstd[] = { 0 }; 3430222Ssam struct vba_driver ikdriver = { ikprobe, 0, ikattach, 0, ikstd, "ik", ikinfo }; 3530222Ssam 3630222Ssam #define splik() spl4() 3730222Ssam /* 3830222Ssam * Devices are organized in pairs with the odd valued 3930222Ssam * device being used for ``diagnostic'' purposes. That 4030222Ssam * is diagnostic devices don't get auto-attach'd and 4130222Ssam * detach'd on open-close. 4230222Ssam */ 4330222Ssam #define IKUNIT(dev) (minor(dev) >> 1) 4430222Ssam #define IKDIAG(dev) (minor(dev) & 01) /* is a diagnostic unit */ 4530222Ssam 4630222Ssam struct ik_softc { 4730222Ssam uid_t is_uid; /* uid of open processes */ 4830222Ssam u_short is_timeout; /* current timeout (seconds) */ 4930222Ssam u_short is_error; /* internal error codes */ 5030222Ssam u_short is_flags; 5130222Ssam #define IKF_ATTACHED 0x1 /* unit is attached (not used yet) */ 5230222Ssam union { 5330222Ssam u_short w[2]; 5430222Ssam u_long l; 5530222Ssam } is_nameaddr; /* address of last symbol lookup */ 5630222Ssam caddr_t is_buf; /* i/o buffer XXX */ 5730222Ssam } ik_softc[NIK]; 5830222Ssam 5930222Ssam struct buf iktab[NIK]; /* unit command queue headers */ 6030222Ssam struct buf rikbuf[NIK]; /* buffers for read/write operations */ 6130222Ssam struct buf cikbuf[NIK]; /* buffers for control operations */ 6230222Ssam 6330222Ssam /* buf overlay definitions */ 6430222Ssam #define b_command b_resid 6530222Ssam 6630222Ssam int ikdiotimo = PS_DIOTIMO; /* dio polling timeout */ 6730222Ssam int iktimeout = PS_TIMEOUT; /* attention/dma timeout (in hz) */ 6830222Ssam 6930222Ssam ikprobe(reg, vi) 7030222Ssam caddr_t reg; 7130222Ssam struct vba_device *vi; 7230222Ssam { 7330222Ssam register int br, cvec; /* r12, r11 */ 7430222Ssam register struct ikdevice *ik; 7530222Ssam 7630222Ssam if (badaddr(reg, 2)) 7730222Ssam return (0); 7830222Ssam ik = (struct ikdevice *)reg; 7930222Ssam ik->ik_vec = --vi->ui_hd->vh_lastiv; 8030222Ssam /* 8130222Ssam * Try and reset the PS300. Since this 8230222Ssam * won't work if it's powered off, we 8330222Ssam * can't use sucess/failure to decide 8430222Ssam * if the device is present. 8530222Ssam */ 8630222Ssam br = 0; 8730222Ssam if (!psreset(ik, IKCSR_IENA) || br == 0) 8830222Ssam br = 0x18, cvec = ik->ik_vec; /* XXX */ 8930222Ssam return (sizeof (struct ikdevice)); 9030222Ssam } 9130222Ssam 9230222Ssam /* 9330222Ssam * Perform a ``hard'' reset. 9430222Ssam */ 9530222Ssam psreset(ik, iena) 9630222Ssam register struct ikdevice *ik; 9730222Ssam { 9830222Ssam 9930222Ssam ik->ik_csr = IKCSR_MCLR|iena; 10030222Ssam DELAY(10000); 10130222Ssam ik->ik_csr = IKCSR_FNC3; 10230222Ssam return (dioread(ik) == PS_RESET); 10330222Ssam } 10430222Ssam 10530222Ssam ikattach(vi) 10630222Ssam struct vba_device *vi; 10730222Ssam { 10830222Ssam register struct ikdevice *ik; 10930222Ssam 11030222Ssam ikinfo[vi->ui_unit] = vi; 11130222Ssam ik = (struct ikdevice *)vi->ui_addr; 11230222Ssam ik->ik_vec = IKVEC_BASE + vi->ui_unit; /* interrupt vector */ 11330222Ssam ik->ik_mod = IKMOD_STD; /* address modifier */ 11430222Ssam ik_softc[vi->ui_unit].is_uid = -1; 11530222Ssam } 11630222Ssam 11730222Ssam /* 11830222Ssam * Open a PS300 and attach. We allow multiple 11930222Ssam * processes with the same uid to share a unit. 12030222Ssam */ 12130222Ssam /*ARGSUSED*/ 12230222Ssam ikopen(dev, flag) 12330222Ssam dev_t dev; 12430222Ssam int flag; 12530222Ssam { 12630222Ssam register int unit = IKUNIT(dev); 12730222Ssam register struct ik_softc *sc; 12830222Ssam struct vba_device *vi; 12930222Ssam struct ikdevice *ik; 13030222Ssam int reset; 13130222Ssam 13230222Ssam if (unit >= NIK || (vi = ikinfo[unit]) == 0 || vi->ui_alive == 0) 13330222Ssam return (ENXIO); 13430222Ssam sc = &ik_softc[unit]; 13530222Ssam if (sc->is_uid != -1 && sc->is_uid != u.u_uid) 13630222Ssam return (EBUSY); 13730222Ssam if (sc->is_uid == -1) { 13830222Ssam sc->is_buf = (caddr_t)wmemall(vmemall, PS_MAXDMA); 13930222Ssam if (sc->is_buf == 0) 14030222Ssam return (ENOMEM); 14130222Ssam sc->is_timeout = 0; 14230222Ssam timeout(iktimer, unit, hz); 14330222Ssam /* 14430222Ssam * Perform PS300 attach for first process. 14530222Ssam */ 14630222Ssam if (!IKDIAG(dev)) { 14730222Ssam reset = 0; 14830222Ssam again: 14930222Ssam if (ikcommand(dev, PS_ATTACH, 1)) { 15030222Ssam /* 15130222Ssam * If attach fails, perform a hard 15230222Ssam * reset once, then retry the command. 15330222Ssam */ 15430222Ssam ik = (struct ikdevice *)ikinfo[unit]->ui_addr; 15530222Ssam if (!reset++ && psreset(ik, 0)) 15630222Ssam goto again; 15730222Ssam untimeout(iktimer, unit); 15830222Ssam wmemfree(sc->is_buf, PS_MAXDMA); 15930222Ssam sc->is_buf = 0; 16030222Ssam return (EIO); 16130222Ssam } 16230222Ssam } 16330222Ssam sc->is_uid = u.u_uid; 16430222Ssam } 16530222Ssam return (0); 16630222Ssam } 16730222Ssam 16830222Ssam /*ARGSUSED*/ 16930222Ssam ikclose(dev, flag) 17030222Ssam dev_t dev; 17130222Ssam int flag; 17230222Ssam { 17330222Ssam int unit = IKUNIT(dev); 17430222Ssam register struct ik_softc *sc = &ik_softc[unit]; 17530222Ssam 17630222Ssam if (!IKDIAG(dev)) 17730222Ssam (void) ikcommand(dev, PS_DETACH, 1); /* auto detach */ 17830222Ssam sc->is_uid = -1; 17930222Ssam if (sc->is_buf) { 18030222Ssam wmemfree(sc->is_buf, PS_MAXDMA); 18130222Ssam sc->is_buf = 0; 18230222Ssam } 18330222Ssam untimeout(iktimer, unit); 18430222Ssam } 18530222Ssam 18630222Ssam ikread(dev, uio) 18730222Ssam dev_t dev; 18830222Ssam struct uio *uio; 18930222Ssam { 19030222Ssam 19130222Ssam return (ikrw(dev, uio, B_READ)); 19230222Ssam } 19330222Ssam 19430222Ssam ikwrite(dev, uio) 19530222Ssam dev_t dev; 19630222Ssam struct uio *uio; 19730222Ssam { 19830222Ssam 19930222Ssam return (ikrw(dev, uio, B_WRITE)); 20030222Ssam } 20130222Ssam 20230222Ssam /* 20330222Ssam * Take read/write request and perform physical i/o 20430222Ssam * transaction with PS300. This involves constructing 20530222Ssam * a physical i/o request vector based on the uio 20630222Ssam * vector, performing the dma, and, finally, moving 20730222Ssam * the data to it's final destination (because of CCI 20830222Ssam * VERSAbus bogosities). 20930222Ssam */ 21030222Ssam ikrw(dev, uio, rw) 21130222Ssam dev_t dev; 21230222Ssam register struct uio *uio; 21330222Ssam int rw; 21430222Ssam { 21530222Ssam int error, unit = IKUNIT(dev), s, wrcmd; 21630222Ssam register struct buf *bp; 21730222Ssam register struct iovec *iov; 21830222Ssam register struct psalist *ap; 21930222Ssam struct ik_softc *sc = &ik_softc[unit]; 22030222Ssam 22130222Ssam if (unit >= NIK) 22230222Ssam return (ENXIO); 22330222Ssam bp = &rikbuf[unit]; 22430222Ssam error = 0, iov = uio->uio_iov, wrcmd = PS_WRPHY; 22530222Ssam for (; !error && uio->uio_iovcnt; iov++, uio->uio_iovcnt--) { 22630222Ssam /* 22730222Ssam * Hack way to set PS300 address w/o doing an lseek 22830222Ssam * and specify write physical w/ refresh synchronization. 22930222Ssam */ 23030222Ssam if (iov->iov_len == 0) { 23130222Ssam if ((int)iov->iov_base&PSIO_SYNC) 23230222Ssam wrcmd = PS_WRPHY_SYNC; 23330222Ssam uio->uio_offset = (int)iov->iov_base & ~PSIO_SYNC; 23430222Ssam continue; 23530222Ssam } 23630222Ssam if (iov->iov_len > PS_MAXDMA) { 23730222Ssam sc->is_error = PSERROR_INVALBC, error = EINVAL; 23830222Ssam continue; 23930222Ssam } 24030222Ssam if ((int)uio->uio_offset&01) { 24130222Ssam sc->is_error = PSERROR_BADADDR, error = EINVAL; 24230222Ssam continue; 24330222Ssam } 24430222Ssam s = splbio(); 24530222Ssam while (bp->b_flags&B_BUSY) { 24630222Ssam bp->b_flags |= B_WANTED; 24730222Ssam sleep((caddr_t)bp, PRIBIO+1); 24830222Ssam } 24930222Ssam splx(s); 25030222Ssam bp->b_flags = B_BUSY | rw; 25130222Ssam /* 25230222Ssam * Construct address descriptor in buffer. 25330222Ssam */ 25430222Ssam ap = (struct psalist *)sc->is_buf; 25530222Ssam ap->nblocks = 1; 25630222Ssam /* work-around dr300 word swapping */ 25730222Ssam ap->addr[0] = uio->uio_offset & 0xffff; 25830222Ssam ap->addr[1] = uio->uio_offset >> 16; 25930222Ssam ap->wc = (iov->iov_len + 1) >> 1; 26030222Ssam if (rw == B_WRITE) { 26130222Ssam error = copyin(iov->iov_base, (caddr_t)&ap[1], 26230222Ssam iov->iov_len); 26330222Ssam if (!error) 26430222Ssam error = ikcommand(dev, wrcmd, 26530222Ssam iov->iov_len + sizeof (*ap)); 26630222Ssam } else { 26730222Ssam caddr_t cp; 26830222Ssam int len; 26930222Ssam 27030222Ssam error = ikcommand(dev, PS_RDPHY, sizeof (*ap)); 27130222Ssam cp = (caddr_t)&ap[1], len = iov->iov_len; 27230222Ssam for (; len > 0; len -= NBPG, cp += NBPG) 27330222Ssam mtpr(cp, P1DC); 27430222Ssam if (!error) 27530222Ssam error = copyout((caddr_t)&ap[1], iov->iov_base, 27630222Ssam iov->iov_len); 27730222Ssam } 27830222Ssam (void) splbio(); 27930222Ssam if (bp->b_flags&B_WANTED) 28030222Ssam wakeup((caddr_t)bp); 28130222Ssam splx(s); 28230222Ssam uio->uio_resid -= iov->iov_len; 28330222Ssam uio->uio_offset += iov->iov_len; 28430222Ssam bp->b_flags &= ~(B_BUSY|B_WANTED); 28530222Ssam } 28630222Ssam return (error); 28730222Ssam } 28830222Ssam 28930222Ssam /* 29030222Ssam * Perform a PS300 command. 29130222Ssam */ 29230222Ssam ikcommand(dev, com, count) 29330222Ssam dev_t dev; 29430222Ssam int com, count; 29530222Ssam { 29630222Ssam register struct buf *bp; 29730222Ssam register int s; 29830222Ssam 29930222Ssam bp = &cikbuf[IKUNIT(dev)]; 30030222Ssam s = splik(); 30130222Ssam while (bp->b_flags&B_BUSY) { 30230222Ssam if (bp->b_flags&B_DONE) 30330222Ssam break; 30430222Ssam bp->b_flags |= B_WANTED; 30530222Ssam sleep((caddr_t)bp, PRIBIO); 30630222Ssam } 30730222Ssam bp->b_flags = B_BUSY|B_READ; 30830222Ssam splx(s); 30930222Ssam bp->b_dev = dev; 31030222Ssam bp->b_command = com; 31130222Ssam bp->b_bcount = count; 31230222Ssam ikstrategy(bp); 31330222Ssam biowait(bp); 31430222Ssam if (bp->b_flags&B_WANTED) 31530222Ssam wakeup((caddr_t)bp); 31630222Ssam bp->b_flags &= B_ERROR; 31730222Ssam return (geterror(bp)); 31830222Ssam } 31930222Ssam 32030222Ssam /* 32130222Ssam * Physio strategy routine 32230222Ssam */ 32330222Ssam ikstrategy(bp) 32430222Ssam register struct buf *bp; 32530222Ssam { 32630222Ssam register struct buf *dp; 32730222Ssam 32830222Ssam /* 32930222Ssam * Put request at end of controller queue. 33030222Ssam */ 33130222Ssam dp = &iktab[IKUNIT(bp->b_dev)]; 33230222Ssam bp->av_forw = NULL; 33330222Ssam (void) splik(); 33430222Ssam if (dp->b_actf != NULL) { 33530222Ssam dp->b_actl->av_forw = bp; 33630222Ssam dp->b_actl = bp; 33730222Ssam } else 33830222Ssam dp->b_actf = dp->b_actl = bp; 33930222Ssam if (!dp->b_active) 34030222Ssam ikstart(dp); 34130222Ssam (void) spl0(); 34230222Ssam } 34330222Ssam 34430222Ssam /* 34530222Ssam * Start the next command on the controller's queue. 34630222Ssam */ 34730222Ssam ikstart(dp) 34830222Ssam register struct buf *dp; 34930222Ssam { 35030222Ssam register struct buf *bp; 35130222Ssam register struct ikdevice *ik; 35230222Ssam register struct ik_softc *sc; 35330222Ssam register struct psalist *ap; 35430222Ssam u_short bc, csr; 35530222Ssam u_int addr; 35630222Ssam int unit; 35730222Ssam 35830222Ssam loop: 35930222Ssam /* 36030222Ssam * Pull a request off the controller queue 36130222Ssam */ 36230222Ssam if ((bp = dp->b_actf) == NULL) { 36330222Ssam dp->b_active = 0; 36430222Ssam return; 36530222Ssam } 36630222Ssam /* 36730222Ssam * Mark controller busy and process this request. 36830222Ssam */ 36930222Ssam dp->b_active = 1; 37030222Ssam unit = IKUNIT(bp->b_dev); 37130222Ssam sc = &ik_softc[unit]; 37230222Ssam ik = (struct ikdevice *)ikinfo[unit]->ui_addr; 37330222Ssam switch (bp->b_command) { 37430222Ssam 37530222Ssam case PS_ATTACH: /* logical unit attach */ 37630222Ssam case PS_DETACH: /* logical unit detach */ 37730222Ssam case PS_LOOKUP: /* name lookup */ 37830222Ssam case PS_RDPHY: /* physical i/o read */ 37930222Ssam case PS_WRPHY: /* physical i/o write */ 38030222Ssam case PS_WRPHY_SYNC: /* physical i/o write w/ sync */ 38130222Ssam /* 38230222Ssam * Handshake command and, optionally, 38330222Ssam * byte count and byte swap flag. 38430222Ssam */ 38530222Ssam if (sc->is_error = diowrite(ik, bp->b_command)) 38630222Ssam goto bad; 38730222Ssam if (bp->b_command < PS_DETACH) { 38830222Ssam if (sc->is_error = diowrite(ik, bp->b_bcount)) 38930222Ssam goto bad; 39030222Ssam if (sc->is_error = diowrite(ik, 0 /* !swab */)) 39130222Ssam goto bad; 39230222Ssam } 39330222Ssam /* 39430222Ssam * Set timeout and wait for an attention interrupt. 39530222Ssam */ 39630222Ssam sc->is_timeout = iktimeout; 39730222Ssam return; 39830222Ssam 39930222Ssam case PS_DMAOUT: /* dma data host->PS300 */ 40030222Ssam bc = bp->b_bcount; 40130222Ssam csr = IKCSR_CYCLE; 40230222Ssam break; 40330222Ssam 40430222Ssam case PS_DMAIN: /* dma data PS300->host */ 40530222Ssam bc = bp->b_bcount; 40630222Ssam csr = IKCSR_CYCLE|IKCSR_FNC1; 40730222Ssam break; 40830222Ssam 40930222Ssam default: 41030222Ssam log(LOG_ERR, "ik%d: bad cmd %x\n", unit, bp->b_command); 41130222Ssam sc->is_error = PSERROR_BADCMD; 41230222Ssam goto bad; 41330222Ssam } 41430222Ssam /* initiate dma transfer */ 41530222Ssam addr = vtoph((struct proc *)0, sc->is_buf); 41630222Ssam ik->ik_bahi = addr >> 17; 41730222Ssam ik->ik_balo = (addr >> 1) & 0xffff; 41830222Ssam ik->ik_wc = ((bc + 1) >> 1) - 1; /* round & convert */ 41930222Ssam ik->ik_pulse = IKPULSE_RATTF|IKPULSE_RDMAF; 42030222Ssam sc->is_timeout = iktimeout; 42130222Ssam ik->ik_csr = IKCSR_IENA|IKCSR_GO|csr; 42230222Ssam return; 42330222Ssam bad: 42430222Ssam bp->b_flags |= B_ERROR; 42530222Ssam dp->b_actf = bp->av_forw; /* remove from queue */ 42630222Ssam biodone(bp); 42730222Ssam goto loop; 42830222Ssam } 42930222Ssam 43030222Ssam #define FETCHWORD(i) { \ 43130222Ssam int v; \ 43230222Ssam \ 43330222Ssam v = dioread(ik); \ 43430222Ssam if (v == -1) { \ 43530222Ssam sc->is_error = PSERROR_NAMETIMO; \ 43630222Ssam goto bad; \ 43730222Ssam } \ 43830222Ssam sc->is_nameaddr.w[i] = v; \ 43930222Ssam } 44030222Ssam 44130222Ssam /* 44230222Ssam * Process a device interrupt. 44330222Ssam */ 44430222Ssam ikintr(ikon) 44530222Ssam int ikon; 44630222Ssam { 44730222Ssam register struct ikdevice *ik; 44830222Ssam register struct buf *bp, *dp; 44930222Ssam struct ik_softc *sc; 45030222Ssam register u_short data; 45130222Ssam u_short i, v; 45230222Ssam 45330222Ssam /* should go by controller, but for now... */ 45430222Ssam if (ikinfo[ikon] == 0) 45530222Ssam return; 45630222Ssam ik = (struct ikdevice *)ikinfo[ikon]->ui_addr; 45730222Ssam /* 45830222Ssam * Discard all non-attention interrupts. The 45930222Ssam * interrupts we're throwing away should all be 46030222Ssam * associated with DMA completion. 46130222Ssam */ 46230222Ssam data = ik->ik_data; 46330222Ssam if ((ik->ik_csr&(IKCSR_ATTF|IKCSR_STATC)) != IKCSR_ATTF) { 46430222Ssam ik->ik_pulse = IKPULSE_RATTF|IKPULSE_RDMAF|IKPULSE_SIENA; 46530222Ssam return; 46630222Ssam } 46730222Ssam /* 46830222Ssam * Fetch attention code immediately. 46930222Ssam */ 47030222Ssam ik->ik_csr = IKCSR_RATTF|IKCSR_RDMAF|IKCSR_FNC1; 47130222Ssam ik->ik_pulse = IKPULSE_FNC2; 47230222Ssam /* 47330222Ssam * Get device and block structures, and a pointer 47430222Ssam * to the vba_device for the device. We receive an 47530222Ssam * unsolicited interrupt whenever the PS300 is power 47630222Ssam * cycled (so ignore it in that case). 47730222Ssam */ 47830222Ssam dp = &iktab[ikon]; 47930222Ssam if ((bp = dp->b_actf) == NULL) { 48030222Ssam if (PS_CODE(data) != PS_RESET) /* power failure */ 48130222Ssam log(LOG_WARNING, "ik%d: spurious interrupt, code %x\n", 48230222Ssam ikon, data); 48330222Ssam goto enable; 48430222Ssam } 48530222Ssam sc = &ik_softc[IKUNIT(bp->b_dev)]; 48630222Ssam sc->is_timeout = 0; /* disable timer */ 48730222Ssam switch (PS_CODE(data)) { 48830222Ssam 48930222Ssam case PS_LOOKUP: /* name lookup */ 49030222Ssam if (data == PS_LOOKUP) { /* dma name */ 49130222Ssam bp->b_command = PS_DMAOUT; 49230222Ssam goto opcont; 49330222Ssam } 49430222Ssam if (data == PS_DMAOK(PS_LOOKUP)) { 49530222Ssam /* reenable interrupt and wait for address */ 49630222Ssam sc->is_timeout = iktimeout; 49730222Ssam goto enable; 49830222Ssam } 49930222Ssam /* 50030222Ssam * Address should be present, extract it one 50130222Ssam * word at a time from the PS300 (yech). 50230222Ssam */ 50330222Ssam if (data != PS_ADROK(PS_LOOKUP)) 50430222Ssam goto bad; 50530222Ssam FETCHWORD(0); 50630222Ssam FETCHWORD(1); 50730222Ssam goto opdone; 50830222Ssam 50930222Ssam case PS_WRPHY_SYNC: /* physical i/o write w/ sync */ 51030222Ssam if (data == PS_WRPHY_SYNC) { /* start dma transfer */ 51130222Ssam bp->b_command = PS_DMAOUT; 51230222Ssam goto opcont; 51330222Ssam } 51430222Ssam if (data != PS_DMAOK(PS_WRPHY_SYNC)) 51530222Ssam goto bad; 51630222Ssam goto opdone; 51730222Ssam 51830222Ssam case PS_WRPHY: /* physical i/o write */ 51930222Ssam if (data == PS_WRPHY) { /* start dma transfer */ 52030222Ssam bp->b_command = PS_DMAOUT; 52130222Ssam goto opcont; 52230222Ssam } 52330222Ssam if (data != PS_DMAOK(PS_WRPHY)) 52430222Ssam goto bad; 52530222Ssam goto opdone; 52630222Ssam 52730222Ssam case PS_ATTACH: /* attach unit */ 52830222Ssam case PS_DETACH: /* detach unit */ 52930222Ssam case PS_ABORT: /* abort code from ps300 */ 53030222Ssam if (data != bp->b_command) 53130222Ssam goto bad; 53230222Ssam goto opdone; 53330222Ssam 53430222Ssam case PS_RDPHY: /* physical i/o read */ 53530222Ssam if (data == PS_RDPHY) { /* dma address list */ 53630222Ssam bp->b_command = PS_DMAOUT; 53730222Ssam goto opcont; 53830222Ssam } 53930222Ssam if (data == PS_ADROK(PS_RDPHY)) { 54030222Ssam /* collect read byte count and start dma */ 54130222Ssam bp->b_bcount = dioread(ik); 54230222Ssam if (bp->b_bcount == -1) 54330222Ssam goto bad; 54430222Ssam bp->b_command = PS_DMAIN; 54530222Ssam goto opcont; 54630222Ssam } 54730222Ssam if (data == PS_DMAOK(PS_RDPHY)) 54830222Ssam goto opdone; 54930222Ssam goto bad; 55030222Ssam } 55130222Ssam bad: 55230222Ssam sc->is_error = data; 55330222Ssam bp->b_flags |= B_ERROR; 55430222Ssam opdone: 55530222Ssam dp->b_actf = bp->av_forw; /* remove from queue */ 55630222Ssam biodone(bp); 55730222Ssam opcont: 55830222Ssam ikstart(dp); 55930222Ssam enable: 56030222Ssam ik->ik_pulse = IKPULSE_SIENA; /* explicitly reenable */ 56130222Ssam } 56230222Ssam 56330222Ssam /* 56430222Ssam * Watchdog timer. 56530222Ssam */ 56630222Ssam iktimer(unit) 56730222Ssam int unit; 56830222Ssam { 56930222Ssam register struct ik_softc *sc = &ik_softc[unit]; 57030222Ssam 57130222Ssam if (sc->is_timeout && --sc->is_timeout == 0) { 57230222Ssam register struct buf *dp, *bp; 57330222Ssam int s; 57430222Ssam 575*30228Ssam log(LOG_ERR, "ik%d: timeout\n", unit); 57630222Ssam s = splik(); 57730222Ssam /* should abort current command */ 57830222Ssam dp = &iktab[unit]; 57930222Ssam if (bp = dp->b_actf) { 58030222Ssam sc->is_error = PSERROR_CMDTIMO; 58130222Ssam bp->b_flags |= B_ERROR; 58230222Ssam dp->b_actf = bp->av_forw; /* remove from queue */ 58330222Ssam biodone(bp); 58430222Ssam ikstart(dp); 58530222Ssam } 58630222Ssam splx(s); 58730222Ssam } 58830222Ssam timeout(iktimer, unit, hz); 58930222Ssam } 59030222Ssam 59130222Ssam /* 59230222Ssam * Handshake read from DR300. 59330222Ssam */ 59430222Ssam dioread(ik) 59530222Ssam register struct ikdevice *ik; 59630222Ssam { 59730222Ssam register int timeout; 59830222Ssam u_short data; 59930222Ssam 60030222Ssam for (timeout = ikdiotimo; timeout > 0; timeout--) 60130222Ssam if ((ik->ik_csr&(IKCSR_ATTF|IKCSR_STATC)) == IKCSR_ATTF) { 60230222Ssam data = ik->ik_data; 60330222Ssam ik->ik_csr = IKCSR_RATTF|IKCSR_RDMAF|IKCSR_FNC1; 60430222Ssam ik->ik_pulse = IKPULSE_FNC2; 60530222Ssam return (data); 60630222Ssam } 60730222Ssam return (-1); 60830222Ssam } 60930222Ssam 61030222Ssam /* 61130222Ssam * Handshake write to DR300. 61230222Ssam * 61330222Ssam * Interrupts are enabled before completing the work 61430222Ssam * so the caller should either be at splik or be 61530222Ssam * prepared to take the interrupt immediately. 61630222Ssam */ 61730222Ssam diowrite(ik, v) 61830222Ssam register struct ikdevice *ik; 61930222Ssam u_short v; 62030222Ssam { 62130222Ssam register int timeout; 62230222Ssam register u_short csr; 62330222Ssam 62430222Ssam top: 62530222Ssam /* 62630222Ssam * Deposit data and generate dr300 attention 62730222Ssam */ 62830222Ssam ik->ik_data = v; 62930222Ssam ik->ik_csr = IKCSR_RDMAF|IKCSR_RATTF; 63030222Ssam ik->ik_pulse = IKPULSE_FNC2; 63130222Ssam for (timeout = ikdiotimo; timeout > 0; timeout--) { 63230222Ssam csr = ik->ik_csr; 63330222Ssam #define IKCSR_DONE (IKCSR_STATA|IKCSR_STATC) 63430222Ssam if ((csr&IKCSR_DONE) == IKCSR_DONE) { 63530222Ssam /* 63630222Ssam * Done, complete handshake by notifying dr300. 63730222Ssam */ 63830222Ssam ik->ik_csr = IKCSR_IENA; /* ~IKCSR_FNC1 */ 63930222Ssam ik->ik_pulse = IKPULSE_FNC2; 64030222Ssam return (0); 64130222Ssam } 64230222Ssam /* beware of potential deadlock with dioread */ 64330222Ssam if ((csr&(IKCSR_ATTF|IKCSR_STATC)) == IKCSR_ATTF) 64430222Ssam goto top; 64530222Ssam } 64630222Ssam ik->ik_csr = IKCSR_IENA; 64730222Ssam return (PSERROR_DIOTIMO); 64830222Ssam } 64930222Ssam 65030222Ssam /*ARGSUSED*/ 65130222Ssam ikioctl(dev, cmd, data, flag) 65230222Ssam dev_t dev; 65330222Ssam int cmd; 65430222Ssam caddr_t data; 65530222Ssam int flag; 65630222Ssam { 65730222Ssam int error = 0, unit = IKUNIT(dev), s; 65830222Ssam register struct ik_softc *sc = &ik_softc[unit]; 65930222Ssam 66030222Ssam switch (cmd) { 66130222Ssam 66230222Ssam case PSIOGETERROR: /* get error code for last operation */ 66330222Ssam *(int *)data = sc->is_error; 66430222Ssam break; 66530222Ssam 66630222Ssam case PSIOLOOKUP: { /* PS300 name lookup */ 66730222Ssam register struct pslookup *lp = (struct pslookup *)data; 66830222Ssam register struct buf *bp; 66930222Ssam 67030222Ssam if (lp->pl_len > PS_MAXNAMELEN) 67130222Ssam return (EINVAL); 67230222Ssam bp = &rikbuf[unit]; 67330222Ssam s = splbio(); 67430222Ssam while (bp->b_flags&B_BUSY) { 67530222Ssam bp->b_flags |= B_WANTED; 67630222Ssam sleep((caddr_t)bp, PRIBIO+1); 67730222Ssam } 67830222Ssam splx(s); 67930222Ssam bp->b_flags = B_BUSY | B_WRITE; 68030222Ssam error = copyin(lp->pl_name, sc->is_buf, lp->pl_len); 68130222Ssam if (error == 0) { 68230222Ssam if (lp->pl_len&1) 68330222Ssam sc->is_buf[lp->pl_len] = '\0'; 68430222Ssam error = ikcommand(dev, PS_LOOKUP, lp->pl_len); 68530222Ssam } 68630222Ssam s = splbio(); 68730222Ssam if (bp->b_flags&B_WANTED) 68830222Ssam wakeup((caddr_t)bp); 68930222Ssam splx(s); 69030222Ssam bp->b_flags &= ~(B_BUSY|B_WANTED); 69130222Ssam lp->pl_addr = sc->is_nameaddr.l; 69230222Ssam break; 69330222Ssam } 69430222Ssam default: 69530222Ssam return (ENOTTY); 69630222Ssam } 69730222Ssam return (error); 69830222Ssam } 69930222Ssam #endif 700