134506Skarels /* 235514Sbostic * Copyright (c) 1986 The Regents of the University of California. 335514Sbostic * All rights reserved. 435514Sbostic * 535514Sbostic * Redistribution and use in source and binary forms are permitted 635514Sbostic * provided that the above copyright notice and this paragraph are 735514Sbostic * duplicated in all such forms and that any documentation, 835514Sbostic * advertising materials, and other materials related to such 935514Sbostic * distribution and use acknowledge that the software was developed 1035514Sbostic * by the University of California, Berkeley. The name of the 1135514Sbostic * University may not be used to endorse or promote products derived 1235514Sbostic * from this software without specific prior written permission. 1335514Sbostic * THIS SOFTWARE IS PROVIDED ``AS IS'' AND WITHOUT ANY EXPRESS OR 1435514Sbostic * IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED 1535514Sbostic * WARRANTIES OF MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE. 1635514Sbostic * 17*37772Smckusick * @(#)ik.c 7.4 (Berkeley) 05/09/89 1834506Skarels */ 1930222Ssam 2030222Ssam #include "ik.h" 2130222Ssam #if NIK > 0 2230222Ssam /* 2330222Ssam * PS300/IKON DR-11W Device Driver. 2430222Ssam */ 2530222Ssam #include "param.h" 2630222Ssam #include "buf.h" 2730222Ssam #include "cmap.h" 2830222Ssam #include "conf.h" 2930222Ssam #include "dkstat.h" 3030222Ssam #include "map.h" 3130222Ssam #include "systm.h" 3230222Ssam #include "user.h" 3330222Ssam #include "vmmac.h" 3430222Ssam #include "proc.h" 3530222Ssam #include "kernel.h" 3630228Ssam #include "syslog.h" 3730222Ssam 3830222Ssam #include "../tahoe/mtpr.h" 3930222Ssam #include "../tahoe/pte.h" 4030222Ssam 4130222Ssam #include "../tahoevba/vbavar.h" 4230222Ssam #include "../tahoevba/ikreg.h" 4330222Ssam #include "../tahoevba/psreg.h" 4430222Ssam #include "../tahoevba/psproto.h" 4530222Ssam 4630286Ssam int ikprobe(), ikattach(), iktimer(); 4730286Ssam struct vba_device *ikinfo[NIK]; 4830286Ssam long ikstd[] = { 0 }; 4930286Ssam struct vba_driver ikdriver = { ikprobe, 0, ikattach, 0, ikstd, "ik", ikinfo }; 5030222Ssam 5130286Ssam #define splik() spl4() 5230222Ssam /* 5330222Ssam * Devices are organized in pairs with the odd valued 5430222Ssam * device being used for ``diagnostic'' purposes. That 5530222Ssam * is diagnostic devices don't get auto-attach'd and 5630222Ssam * detach'd on open-close. 5730222Ssam */ 5830286Ssam #define IKUNIT(dev) (minor(dev) >> 1) 5930286Ssam #define IKDIAG(dev) (minor(dev) & 01) /* is a diagnostic unit */ 6030222Ssam 6130286Ssam struct ik_softc { 6230286Ssam uid_t is_uid; /* uid of open processes */ 6330286Ssam u_short is_timeout; /* current timeout (seconds) */ 6430286Ssam u_short is_error; /* internal error codes */ 6530286Ssam u_short is_flags; 6630286Ssam #define IKF_ATTACHED 0x1 /* unit is attached (not used yet) */ 6730286Ssam union { 6830286Ssam u_short w[2]; 6930286Ssam u_long l; 7030286Ssam } is_nameaddr; /* address of last symbol lookup */ 7130344Ssam caddr_t is_buf[PS_MAXDMA];/* i/o buffer XXX */ 7230222Ssam } ik_softc[NIK]; 7330222Ssam 7430286Ssam struct buf iktab[NIK]; /* unit command queue headers */ 7530286Ssam struct buf rikbuf[NIK]; /* buffers for read/write operations */ 7630286Ssam struct buf cikbuf[NIK]; /* buffers for control operations */ 7730222Ssam 7830222Ssam /* buf overlay definitions */ 7930286Ssam #define b_command b_resid 8030222Ssam 8130286Ssam int ikdiotimo = PS_DIOTIMO; /* dio polling timeout */ 8230286Ssam int iktimeout = PS_TIMEOUT; /* attention/dma timeout (in hz) */ 8330222Ssam 8430222Ssam ikprobe(reg, vi) 8530286Ssam caddr_t reg; 8630222Ssam struct vba_device *vi; 8730222Ssam { 8830286Ssam register int br, cvec; /* r12, r11 */ 8930222Ssam register struct ikdevice *ik; 9030222Ssam 9130294Ssam #ifdef lint 9230294Ssam br = 0; cvec = br; br = cvec; 9330294Ssam ikintr(0); 9430294Ssam #endif 9530286Ssam if (badaddr(reg, 2)) 9630286Ssam return (0); 9730222Ssam ik = (struct ikdevice *)reg; 9830222Ssam ik->ik_vec = --vi->ui_hd->vh_lastiv; 9930286Ssam /* 10030344Ssam * Use extended non-privileged address modifier 10130344Ssam * to avoid address overlap with 24-bit devices. 10230286Ssam */ 10330286Ssam ik->ik_mod = 0xf1; /* address modifier */ 10430286Ssam /* 10530286Ssam * Try and reset the PS300. Since this 10630286Ssam * won't work if it's powered off, we 10730286Ssam * can't use sucess/failure to decide 10830286Ssam * if the device is present. 10930286Ssam */ 11030222Ssam br = 0; 11130286Ssam (void) psreset(ik, IKCSR_IENA); 11230286Ssam if (br == 0) /* XXX */ 11330222Ssam br = 0x18, cvec = ik->ik_vec; /* XXX */ 11430286Ssam return (sizeof (struct ikdevice)); 11530222Ssam } 11630222Ssam 11730222Ssam /* 11830222Ssam * Perform a ``hard'' reset. 11930222Ssam */ 12030222Ssam psreset(ik, iena) 12130286Ssam register struct ikdevice *ik; 12230222Ssam { 12330222Ssam 12430286Ssam ik->ik_csr = IKCSR_MCLR|iena; 12530286Ssam DELAY(10000); 12630286Ssam ik->ik_csr = IKCSR_FNC3|iena; 12730286Ssam if (!iena) 12830286Ssam return (dioread(ik) == PS_RESET); 12930286Ssam return (1); 13030222Ssam } 13130222Ssam 13230222Ssam ikattach(vi) 13330286Ssam struct vba_device *vi; 13430222Ssam { 13530222Ssam 13630286Ssam ik_softc[vi->ui_unit].is_uid = -1; 13730222Ssam } 13830222Ssam 13930222Ssam /* 14030222Ssam * Open a PS300 and attach. We allow multiple 14130222Ssam * processes with the same uid to share a unit. 14230222Ssam */ 14330222Ssam /*ARGSUSED*/ 14430222Ssam ikopen(dev, flag) 14530286Ssam dev_t dev; 14630286Ssam int flag; 14730222Ssam { 14830286Ssam register int unit = IKUNIT(dev); 14930286Ssam register struct ik_softc *sc; 15030286Ssam struct vba_device *vi; 15130286Ssam struct ikdevice *ik; 15230286Ssam int reset; 15330222Ssam 15430286Ssam if (unit >= NIK || (vi = ikinfo[unit]) == 0 || vi->ui_alive == 0) 15530286Ssam return (ENXIO); 15630286Ssam sc = &ik_softc[unit]; 15730294Ssam if (sc->is_uid != (uid_t)-1 && sc->is_uid != u.u_uid) 15830286Ssam return (EBUSY); 15930294Ssam if (sc->is_uid == (uid_t)-1) { 16030286Ssam sc->is_timeout = 0; 16130294Ssam timeout(iktimer, (caddr_t)unit, hz); 16230286Ssam /* 16330286Ssam * Perform PS300 attach for first process. 16430286Ssam */ 16530286Ssam if (!IKDIAG(dev)) { 16630286Ssam reset = 0; 16730286Ssam again: 16830286Ssam if (ikcommand(dev, PS_ATTACH, 1)) { 16930286Ssam /* 17030286Ssam * If attach fails, perform a hard 17130286Ssam * reset once, then retry the command. 17230286Ssam */ 17330286Ssam ik = (struct ikdevice *)ikinfo[unit]->ui_addr; 17430286Ssam if (!reset++ && psreset(ik, 0)) 17530286Ssam goto again; 17630294Ssam untimeout(iktimer, (caddr_t)unit); 17730286Ssam return (EIO); 17830286Ssam } 17930286Ssam } 18030286Ssam sc->is_uid = u.u_uid; 18130286Ssam } 18230286Ssam return (0); 18330222Ssam } 18430222Ssam 18530222Ssam /*ARGSUSED*/ 18630222Ssam ikclose(dev, flag) 18730286Ssam dev_t dev; 18830286Ssam int flag; 18930222Ssam { 19030286Ssam int unit = IKUNIT(dev); 19130222Ssam register struct ik_softc *sc = &ik_softc[unit]; 19230222Ssam 19330286Ssam if (!IKDIAG(dev)) 19430286Ssam (void) ikcommand(dev, PS_DETACH, 1); /* auto detach */ 19530286Ssam sc->is_uid = -1; 19630294Ssam untimeout(iktimer, (caddr_t)unit); 19730222Ssam } 19830222Ssam 19930222Ssam ikread(dev, uio) 20030286Ssam dev_t dev; 20130286Ssam struct uio *uio; 20230222Ssam { 20330222Ssam 20430286Ssam return (ikrw(dev, uio, B_READ)); 20530222Ssam } 20630222Ssam 20730222Ssam ikwrite(dev, uio) 20830286Ssam dev_t dev; 20930286Ssam struct uio *uio; 21030222Ssam { 21130222Ssam 21230286Ssam return (ikrw(dev, uio, B_WRITE)); 21330222Ssam } 21430222Ssam 21530222Ssam /* 21630222Ssam * Take read/write request and perform physical i/o 21730222Ssam * transaction with PS300. This involves constructing 21830222Ssam * a physical i/o request vector based on the uio 21930222Ssam * vector, performing the dma, and, finally, moving 22030222Ssam * the data to it's final destination (because of CCI 22130222Ssam * VERSAbus bogosities). 22230222Ssam */ 22330222Ssam ikrw(dev, uio, rw) 22430286Ssam dev_t dev; 22530286Ssam register struct uio *uio; 22630286Ssam int rw; 22730222Ssam { 22830286Ssam int error, unit = IKUNIT(dev), s, wrcmd; 22930286Ssam register struct buf *bp; 23030286Ssam register struct iovec *iov; 23130286Ssam register struct psalist *ap; 23230286Ssam struct ik_softc *sc = &ik_softc[unit]; 23330222Ssam 23430286Ssam if (unit >= NIK) 23530286Ssam return (ENXIO); 23630286Ssam bp = &rikbuf[unit]; 23730286Ssam error = 0, iov = uio->uio_iov, wrcmd = PS_WRPHY; 23830286Ssam for (; !error && uio->uio_iovcnt; iov++, uio->uio_iovcnt--) { 23930286Ssam /* 24030286Ssam * Hack way to set PS300 address w/o doing an lseek 24130286Ssam * and specify write physical w/ refresh synchronization. 24230286Ssam */ 24330286Ssam if (iov->iov_len == 0) { 24430286Ssam if ((int)iov->iov_base&PSIO_SYNC) 24530286Ssam wrcmd = PS_WRPHY_SYNC; 24630286Ssam uio->uio_offset = (int)iov->iov_base & ~PSIO_SYNC; 24730286Ssam continue; 24830286Ssam } 24930286Ssam if (iov->iov_len > PS_MAXDMA) { 25030286Ssam sc->is_error = PSERROR_INVALBC, error = EINVAL; 25130286Ssam continue; 25230286Ssam } 25330286Ssam if ((int)uio->uio_offset&01) { 25430286Ssam sc->is_error = PSERROR_BADADDR, error = EINVAL; 25530286Ssam continue; 25630286Ssam } 25730286Ssam s = splbio(); 25830286Ssam while (bp->b_flags&B_BUSY) { 25930286Ssam bp->b_flags |= B_WANTED; 26030286Ssam sleep((caddr_t)bp, PRIBIO+1); 26130286Ssam } 26230286Ssam splx(s); 26330286Ssam bp->b_flags = B_BUSY | rw; 26430286Ssam /* 26530286Ssam * Construct address descriptor in buffer. 26630286Ssam */ 26730286Ssam ap = (struct psalist *)sc->is_buf; 26830286Ssam ap->nblocks = 1; 26930286Ssam /* work-around dr300 word swapping */ 27030286Ssam ap->addr[0] = uio->uio_offset & 0xffff; 27130286Ssam ap->addr[1] = uio->uio_offset >> 16; 27230286Ssam ap->wc = (iov->iov_len + 1) >> 1; 27330286Ssam if (rw == B_WRITE) { 27430286Ssam error = copyin(iov->iov_base, (caddr_t)&ap[1], 27530294Ssam (unsigned)iov->iov_len); 27630286Ssam if (!error) 27730286Ssam error = ikcommand(dev, wrcmd, 27830286Ssam iov->iov_len + sizeof (*ap)); 27930286Ssam } else { 28030286Ssam caddr_t cp; 28130286Ssam int len; 28230222Ssam 28330286Ssam error = ikcommand(dev, PS_RDPHY, sizeof (*ap)); 28430286Ssam cp = (caddr_t)&ap[1], len = iov->iov_len; 28530286Ssam for (; len > 0; len -= NBPG, cp += NBPG) 28630286Ssam mtpr(P1DC, cp); 28730286Ssam if (!error) 28830286Ssam error = copyout((caddr_t)&ap[1], iov->iov_base, 28930294Ssam (unsigned)iov->iov_len); 29030286Ssam } 29130286Ssam (void) splbio(); 29230286Ssam if (bp->b_flags&B_WANTED) 29330286Ssam wakeup((caddr_t)bp); 29430286Ssam splx(s); 29530286Ssam uio->uio_resid -= iov->iov_len; 29630286Ssam uio->uio_offset += iov->iov_len; 29730286Ssam bp->b_flags &= ~(B_BUSY|B_WANTED); 29830286Ssam } 29930286Ssam return (error); 30030222Ssam } 30130222Ssam 30230222Ssam /* 30330222Ssam * Perform a PS300 command. 30430222Ssam */ 30530222Ssam ikcommand(dev, com, count) 30630286Ssam dev_t dev; 30730286Ssam int com, count; 30830222Ssam { 30930286Ssam register struct buf *bp; 31030286Ssam register int s; 311*37772Smckusick int error; 31230222Ssam 31330286Ssam bp = &cikbuf[IKUNIT(dev)]; 31430286Ssam s = splik(); 31530286Ssam while (bp->b_flags&B_BUSY) { 31630286Ssam if (bp->b_flags&B_DONE) 31730286Ssam break; 31830286Ssam bp->b_flags |= B_WANTED; 31930286Ssam sleep((caddr_t)bp, PRIBIO); 32030286Ssam } 32130286Ssam bp->b_flags = B_BUSY|B_READ; 32230286Ssam splx(s); 32330286Ssam bp->b_dev = dev; 32430286Ssam bp->b_command = com; 32530286Ssam bp->b_bcount = count; 32630286Ssam ikstrategy(bp); 327*37772Smckusick error = biowait(bp); 32830286Ssam if (bp->b_flags&B_WANTED) 32930286Ssam wakeup((caddr_t)bp); 33030286Ssam bp->b_flags &= B_ERROR; 331*37772Smckusick return (error); 33230222Ssam } 33330222Ssam 33430222Ssam /* 33530222Ssam * Physio strategy routine 33630222Ssam */ 33730222Ssam ikstrategy(bp) 33830286Ssam register struct buf *bp; 33930222Ssam { 34030286Ssam register struct buf *dp; 34130222Ssam 34230286Ssam /* 34330286Ssam * Put request at end of controller queue. 34430286Ssam */ 34530286Ssam dp = &iktab[IKUNIT(bp->b_dev)]; 34630286Ssam bp->av_forw = NULL; 34730286Ssam (void) splik(); 34830286Ssam if (dp->b_actf != NULL) { 34930286Ssam dp->b_actl->av_forw = bp; 35030286Ssam dp->b_actl = bp; 35130286Ssam } else 35230286Ssam dp->b_actf = dp->b_actl = bp; 35330286Ssam if (!dp->b_active) 35430286Ssam ikstart(dp); 35530286Ssam (void) spl0(); 35630222Ssam } 35730222Ssam 35830222Ssam /* 35930222Ssam * Start the next command on the controller's queue. 36030222Ssam */ 36130222Ssam ikstart(dp) 36230286Ssam register struct buf *dp; 36330222Ssam { 36430286Ssam register struct buf *bp; 36530286Ssam register struct ikdevice *ik; 36630286Ssam register struct ik_softc *sc; 36730286Ssam u_short bc, csr; 36830286Ssam u_int addr; 36930286Ssam int unit; 37030222Ssam 37130222Ssam loop: 37230286Ssam /* 37330286Ssam * Pull a request off the controller queue 37430286Ssam */ 37530286Ssam if ((bp = dp->b_actf) == NULL) { 37630286Ssam dp->b_active = 0; 37730286Ssam return; 37830286Ssam } 37930286Ssam /* 38030286Ssam * Mark controller busy and process this request. 38130286Ssam */ 38230286Ssam dp->b_active = 1; 38330286Ssam unit = IKUNIT(bp->b_dev); 38430286Ssam sc = &ik_softc[unit]; 38530286Ssam ik = (struct ikdevice *)ikinfo[unit]->ui_addr; 38630294Ssam switch ((int)bp->b_command) { 38730222Ssam 38830286Ssam case PS_ATTACH: /* logical unit attach */ 38930286Ssam case PS_DETACH: /* logical unit detach */ 39030286Ssam case PS_LOOKUP: /* name lookup */ 39130286Ssam case PS_RDPHY: /* physical i/o read */ 39230286Ssam case PS_WRPHY: /* physical i/o write */ 39330286Ssam case PS_WRPHY_SYNC: /* physical i/o write w/ sync */ 39430286Ssam /* 39530286Ssam * Handshake command and, optionally, 39630286Ssam * byte count and byte swap flag. 39730286Ssam */ 39830294Ssam if (sc->is_error = diowrite(ik, (u_short)bp->b_command)) 39930286Ssam goto bad; 40030286Ssam if (bp->b_command < PS_DETACH) { 40130294Ssam if (sc->is_error = diowrite(ik, (u_short)bp->b_bcount)) 40230286Ssam goto bad; 40330294Ssam if (sc->is_error = diowrite(ik, (u_short)0 /* !swab */)) 40430286Ssam goto bad; 40530286Ssam } 40630286Ssam /* 40730286Ssam * Set timeout and wait for an attention interrupt. 40830286Ssam */ 40930286Ssam sc->is_timeout = iktimeout; 41030286Ssam return; 41130222Ssam 41230286Ssam case PS_DMAOUT: /* dma data host->PS300 */ 41330286Ssam bc = bp->b_bcount; 41430286Ssam csr = IKCSR_CYCLE; 41530286Ssam break; 41630222Ssam 41730286Ssam case PS_DMAIN: /* dma data PS300->host */ 41830286Ssam bc = bp->b_bcount; 41930286Ssam csr = IKCSR_CYCLE|IKCSR_FNC1; 42030286Ssam break; 42130222Ssam 42230286Ssam default: 42330286Ssam log(LOG_ERR, "ik%d: bad cmd %x\n", unit, bp->b_command); 42430286Ssam sc->is_error = PSERROR_BADCMD; 42530286Ssam goto bad; 42630286Ssam } 42730286Ssam /* initiate dma transfer */ 42830294Ssam addr = vtoph((struct proc *)0, (unsigned)sc->is_buf); 42930286Ssam ik->ik_bahi = addr >> 17; 43030286Ssam ik->ik_balo = (addr >> 1) & 0xffff; 43130286Ssam ik->ik_wc = ((bc + 1) >> 1) - 1; /* round & convert */ 43230286Ssam ik->ik_pulse = IKPULSE_RATTF|IKPULSE_RDMAF; 43330286Ssam sc->is_timeout = iktimeout; 43430286Ssam ik->ik_csr = IKCSR_IENA|IKCSR_GO|csr; 43530286Ssam return; 43630222Ssam bad: 43730286Ssam bp->b_flags |= B_ERROR; 43830286Ssam dp->b_actf = bp->av_forw; /* remove from queue */ 43930286Ssam biodone(bp); 44030286Ssam goto loop; 44130222Ssam } 44230222Ssam 44330222Ssam #define FETCHWORD(i) { \ 44430286Ssam v = dioread(ik); \ 44530286Ssam if (v == -1) { \ 44630286Ssam sc->is_error = PSERROR_NAMETIMO; \ 44730286Ssam goto bad; \ 44830286Ssam } \ 44930286Ssam sc->is_nameaddr.w[i] = v; \ 45030222Ssam } 45130222Ssam 45230222Ssam /* 45330222Ssam * Process a device interrupt. 45430222Ssam */ 45530222Ssam ikintr(ikon) 45630286Ssam int ikon; 45730222Ssam { 45830286Ssam register struct ikdevice *ik; 45930286Ssam register struct buf *bp, *dp; 46030286Ssam struct ik_softc *sc; 46130286Ssam register u_short data; 46230294Ssam int v; 46330222Ssam 46430286Ssam /* should go by controller, but for now... */ 46530286Ssam if (ikinfo[ikon] == 0) 46630286Ssam return; 46730286Ssam ik = (struct ikdevice *)ikinfo[ikon]->ui_addr; 46830286Ssam /* 46930286Ssam * Discard all non-attention interrupts. The 47030286Ssam * interrupts we're throwing away should all be 47130286Ssam * associated with DMA completion. 47230286Ssam */ 47330286Ssam data = ik->ik_data; 47430286Ssam if ((ik->ik_csr&(IKCSR_ATTF|IKCSR_STATC)) != IKCSR_ATTF) { 47530286Ssam ik->ik_pulse = IKPULSE_RATTF|IKPULSE_RDMAF|IKPULSE_SIENA; 47630286Ssam return; 47730286Ssam } 47830286Ssam /* 47930286Ssam * Fetch attention code immediately. 48030286Ssam */ 48130286Ssam ik->ik_csr = IKCSR_RATTF|IKCSR_RDMAF|IKCSR_FNC1; 48230286Ssam ik->ik_pulse = IKPULSE_FNC2; 48330286Ssam /* 48430286Ssam * Get device and block structures, and a pointer 48530286Ssam * to the vba_device for the device. We receive an 48630286Ssam * unsolicited interrupt whenever the PS300 is power 48730286Ssam * cycled (so ignore it in that case). 48830286Ssam */ 48930286Ssam dp = &iktab[ikon]; 49030286Ssam if ((bp = dp->b_actf) == NULL) { 49130286Ssam if (PS_CODE(data) != PS_RESET) /* power failure */ 49230286Ssam log(LOG_WARNING, "ik%d: spurious interrupt, code %x\n", 49330286Ssam ikon, data); 49430286Ssam goto enable; 49530286Ssam } 49630286Ssam sc = &ik_softc[IKUNIT(bp->b_dev)]; 49730286Ssam sc->is_timeout = 0; /* disable timer */ 49830286Ssam switch (PS_CODE(data)) { 49930222Ssam 50030286Ssam case PS_LOOKUP: /* name lookup */ 50130286Ssam if (data == PS_LOOKUP) { /* dma name */ 50230286Ssam bp->b_command = PS_DMAOUT; 50330286Ssam goto opcont; 50430286Ssam } 50530286Ssam if (data == PS_DMAOK(PS_LOOKUP)) { 50630286Ssam /* reenable interrupt and wait for address */ 50730286Ssam sc->is_timeout = iktimeout; 50830286Ssam goto enable; 50930286Ssam } 51030286Ssam /* 51130286Ssam * Address should be present, extract it one 51230286Ssam * word at a time from the PS300 (yech). 51330286Ssam */ 51430286Ssam if (data != PS_ADROK(PS_LOOKUP)) 51530286Ssam goto bad; 51630286Ssam FETCHWORD(0); 51730286Ssam FETCHWORD(1); 51830286Ssam goto opdone; 51930222Ssam 52030286Ssam case PS_WRPHY_SYNC: /* physical i/o write w/ sync */ 52130286Ssam if (data == PS_WRPHY_SYNC) { /* start dma transfer */ 52230286Ssam bp->b_command = PS_DMAOUT; 52330286Ssam goto opcont; 52430286Ssam } 52530286Ssam if (data != PS_DMAOK(PS_WRPHY_SYNC)) 52630286Ssam goto bad; 52730286Ssam goto opdone; 52830222Ssam 52930286Ssam case PS_WRPHY: /* physical i/o write */ 53030286Ssam if (data == PS_WRPHY) { /* start dma transfer */ 53130286Ssam bp->b_command = PS_DMAOUT; 53230286Ssam goto opcont; 53330286Ssam } 53430286Ssam if (data != PS_DMAOK(PS_WRPHY)) 53530286Ssam goto bad; 53630286Ssam goto opdone; 53730222Ssam 53830286Ssam case PS_ATTACH: /* attach unit */ 53930286Ssam case PS_DETACH: /* detach unit */ 54030286Ssam case PS_ABORT: /* abort code from ps300 */ 54130286Ssam if (data != bp->b_command) 54230286Ssam goto bad; 54330286Ssam goto opdone; 54430222Ssam 54530286Ssam case PS_RDPHY: /* physical i/o read */ 54630286Ssam if (data == PS_RDPHY) { /* dma address list */ 54730286Ssam bp->b_command = PS_DMAOUT; 54830286Ssam goto opcont; 54930286Ssam } 55030286Ssam if (data == PS_ADROK(PS_RDPHY)) { 55130286Ssam /* collect read byte count and start dma */ 55230286Ssam bp->b_bcount = dioread(ik); 55330286Ssam if (bp->b_bcount == -1) 55430286Ssam goto bad; 55530286Ssam bp->b_command = PS_DMAIN; 55630286Ssam goto opcont; 55730286Ssam } 55830286Ssam if (data == PS_DMAOK(PS_RDPHY)) 55930286Ssam goto opdone; 56030286Ssam goto bad; 56130286Ssam } 56230222Ssam bad: 56330286Ssam sc->is_error = data; 56430286Ssam bp->b_flags |= B_ERROR; 56530222Ssam opdone: 56630286Ssam dp->b_actf = bp->av_forw; /* remove from queue */ 56730286Ssam biodone(bp); 56830222Ssam opcont: 56930286Ssam ikstart(dp); 57030222Ssam enable: 57130286Ssam ik->ik_pulse = IKPULSE_SIENA; /* explicitly reenable */ 57230222Ssam } 57330222Ssam 57430222Ssam /* 57530222Ssam * Watchdog timer. 57630222Ssam */ 57730222Ssam iktimer(unit) 57830286Ssam int unit; 57930222Ssam { 58030286Ssam register struct ik_softc *sc = &ik_softc[unit]; 58130222Ssam 58230286Ssam if (sc->is_timeout && --sc->is_timeout == 0) { 58330286Ssam register struct buf *dp, *bp; 58430286Ssam int s; 58530222Ssam 58630286Ssam log(LOG_ERR, "ik%d: timeout\n", unit); 58730286Ssam s = splik(); 58830286Ssam /* should abort current command */ 58930286Ssam dp = &iktab[unit]; 59030286Ssam if (bp = dp->b_actf) { 59130286Ssam sc->is_error = PSERROR_CMDTIMO; 59230286Ssam bp->b_flags |= B_ERROR; 59330286Ssam dp->b_actf = bp->av_forw; /* remove from queue */ 59430286Ssam biodone(bp); 59530286Ssam ikstart(dp); 59630286Ssam } 59730286Ssam splx(s); 59830286Ssam } 59930294Ssam timeout(iktimer, (caddr_t)unit, hz); 60030222Ssam } 60130222Ssam 60230222Ssam /* 60330222Ssam * Handshake read from DR300. 60430222Ssam */ 60530222Ssam dioread(ik) 60630286Ssam register struct ikdevice *ik; 60730222Ssam { 60830294Ssam register int t; 60930286Ssam u_short data; 61030222Ssam 61130294Ssam for (t = ikdiotimo; t > 0; t--) 61230286Ssam if ((ik->ik_csr&(IKCSR_ATTF|IKCSR_STATC)) == IKCSR_ATTF) { 61330286Ssam data = ik->ik_data; 61430286Ssam ik->ik_csr = IKCSR_RATTF|IKCSR_RDMAF|IKCSR_FNC1; 61530286Ssam ik->ik_pulse = IKPULSE_FNC2; 61630286Ssam return (data); 61730286Ssam } 61830286Ssam return (-1); 61930222Ssam } 62030222Ssam 62130222Ssam /* 62230222Ssam * Handshake write to DR300. 62330222Ssam * 62430222Ssam * Interrupts are enabled before completing the work 62530222Ssam * so the caller should either be at splik or be 62630222Ssam * prepared to take the interrupt immediately. 62730222Ssam */ 62830222Ssam diowrite(ik, v) 62930286Ssam register struct ikdevice *ik; 63030286Ssam u_short v; 63130222Ssam { 63230294Ssam register int t; 63330286Ssam register u_short csr; 63430222Ssam 63530222Ssam top: 63630286Ssam /* 63730286Ssam * Deposit data and generate dr300 attention 63830286Ssam */ 63930286Ssam ik->ik_data = v; 64030286Ssam ik->ik_csr = IKCSR_RDMAF|IKCSR_RATTF; 64130286Ssam ik->ik_pulse = IKPULSE_FNC2; 64230294Ssam for (t = ikdiotimo; t > 0; t--) { 64330286Ssam csr = ik->ik_csr; 64430286Ssam #define IKCSR_DONE (IKCSR_STATA|IKCSR_STATC) 64530286Ssam if ((csr&IKCSR_DONE) == IKCSR_DONE) { 64630286Ssam /* 64730286Ssam * Done, complete handshake by notifying dr300. 64830286Ssam */ 64930286Ssam ik->ik_csr = IKCSR_IENA; /* ~IKCSR_FNC1 */ 65030286Ssam ik->ik_pulse = IKPULSE_FNC2; 65130286Ssam return (0); 65230286Ssam } 65330286Ssam /* beware of potential deadlock with dioread */ 65430286Ssam if ((csr&(IKCSR_ATTF|IKCSR_STATC)) == IKCSR_ATTF) 65530286Ssam goto top; 65630286Ssam } 65730286Ssam ik->ik_csr = IKCSR_IENA; 65830286Ssam return (PSERROR_DIOTIMO); 65930222Ssam } 66030222Ssam 66130222Ssam /*ARGSUSED*/ 66230222Ssam ikioctl(dev, cmd, data, flag) 66330286Ssam dev_t dev; 66430286Ssam int cmd; 66530286Ssam caddr_t data; 66630286Ssam int flag; 66730222Ssam { 66830286Ssam int error = 0, unit = IKUNIT(dev), s; 66930286Ssam register struct ik_softc *sc = &ik_softc[unit]; 67030222Ssam 67130286Ssam switch (cmd) { 67230222Ssam 67330286Ssam case PSIOGETERROR: /* get error code for last operation */ 67430286Ssam *(int *)data = sc->is_error; 67530286Ssam break; 67630222Ssam 67730286Ssam case PSIOLOOKUP: { /* PS300 name lookup */ 67830286Ssam register struct pslookup *lp = (struct pslookup *)data; 67930286Ssam register struct buf *bp; 68030222Ssam 68130286Ssam if (lp->pl_len > PS_MAXNAMELEN) 68230286Ssam return (EINVAL); 68330286Ssam bp = &rikbuf[unit]; 68430286Ssam s = splbio(); 68530286Ssam while (bp->b_flags&B_BUSY) { 68630286Ssam bp->b_flags |= B_WANTED; 68730286Ssam sleep((caddr_t)bp, PRIBIO+1); 68830286Ssam } 68930286Ssam splx(s); 69030286Ssam bp->b_flags = B_BUSY | B_WRITE; 69134506Skarels error = copyin(lp->pl_name, (caddr_t)sc->is_buf, 69234506Skarels (unsigned)lp->pl_len); 69330286Ssam if (error == 0) { 69430286Ssam if (lp->pl_len&1) 69530286Ssam sc->is_buf[lp->pl_len] = '\0'; 69630286Ssam error = ikcommand(dev, PS_LOOKUP, lp->pl_len); 69730286Ssam } 69830286Ssam s = splbio(); 69930286Ssam if (bp->b_flags&B_WANTED) 70030286Ssam wakeup((caddr_t)bp); 70130286Ssam splx(s); 70230286Ssam bp->b_flags &= ~(B_BUSY|B_WANTED); 70330286Ssam lp->pl_addr = sc->is_nameaddr.l; 70430286Ssam break; 70530286Ssam } 70630286Ssam default: 70730286Ssam return (ENOTTY); 70830286Ssam } 70930286Ssam return (error); 71030222Ssam } 71130222Ssam #endif 712