134506Skarels /* 2*35514Sbostic * Copyright (c) 1986 The Regents of the University of California. 3*35514Sbostic * All rights reserved. 4*35514Sbostic * 5*35514Sbostic * Redistribution and use in source and binary forms are permitted 6*35514Sbostic * provided that the above copyright notice and this paragraph are 7*35514Sbostic * duplicated in all such forms and that any documentation, 8*35514Sbostic * advertising materials, and other materials related to such 9*35514Sbostic * distribution and use acknowledge that the software was developed 10*35514Sbostic * by the University of California, Berkeley. The name of the 11*35514Sbostic * University may not be used to endorse or promote products derived 12*35514Sbostic * from this software without specific prior written permission. 13*35514Sbostic * THIS SOFTWARE IS PROVIDED ``AS IS'' AND WITHOUT ANY EXPRESS OR 14*35514Sbostic * IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED 15*35514Sbostic * WARRANTIES OF MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE. 16*35514Sbostic * 17*35514Sbostic * @(#)ik.c 7.2 (Berkeley) 09/16/88 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 "dir.h" 3030222Ssam #include "dkstat.h" 3130222Ssam #include "map.h" 3230222Ssam #include "systm.h" 3330222Ssam #include "user.h" 3430222Ssam #include "vmmac.h" 3530222Ssam #include "proc.h" 3630222Ssam #include "uio.h" 3730222Ssam #include "kernel.h" 3830228Ssam #include "syslog.h" 3930222Ssam 4030222Ssam #include "../tahoe/mtpr.h" 4130222Ssam #include "../tahoe/pte.h" 4230222Ssam 4330222Ssam #include "../tahoevba/vbavar.h" 4430222Ssam #include "../tahoevba/ikreg.h" 4530222Ssam #include "../tahoevba/psreg.h" 4630222Ssam #include "../tahoevba/psproto.h" 4730222Ssam 4830286Ssam int ikprobe(), ikattach(), iktimer(); 4930286Ssam struct vba_device *ikinfo[NIK]; 5030286Ssam long ikstd[] = { 0 }; 5130286Ssam struct vba_driver ikdriver = { ikprobe, 0, ikattach, 0, ikstd, "ik", ikinfo }; 5230222Ssam 5330286Ssam #define splik() spl4() 5430222Ssam /* 5530222Ssam * Devices are organized in pairs with the odd valued 5630222Ssam * device being used for ``diagnostic'' purposes. That 5730222Ssam * is diagnostic devices don't get auto-attach'd and 5830222Ssam * detach'd on open-close. 5930222Ssam */ 6030286Ssam #define IKUNIT(dev) (minor(dev) >> 1) 6130286Ssam #define IKDIAG(dev) (minor(dev) & 01) /* is a diagnostic unit */ 6230222Ssam 6330286Ssam struct ik_softc { 6430286Ssam uid_t is_uid; /* uid of open processes */ 6530286Ssam u_short is_timeout; /* current timeout (seconds) */ 6630286Ssam u_short is_error; /* internal error codes */ 6730286Ssam u_short is_flags; 6830286Ssam #define IKF_ATTACHED 0x1 /* unit is attached (not used yet) */ 6930286Ssam union { 7030286Ssam u_short w[2]; 7130286Ssam u_long l; 7230286Ssam } is_nameaddr; /* address of last symbol lookup */ 7330344Ssam caddr_t is_buf[PS_MAXDMA];/* i/o buffer XXX */ 7430222Ssam } ik_softc[NIK]; 7530222Ssam 7630286Ssam struct buf iktab[NIK]; /* unit command queue headers */ 7730286Ssam struct buf rikbuf[NIK]; /* buffers for read/write operations */ 7830286Ssam struct buf cikbuf[NIK]; /* buffers for control operations */ 7930222Ssam 8030222Ssam /* buf overlay definitions */ 8130286Ssam #define b_command b_resid 8230222Ssam 8330286Ssam int ikdiotimo = PS_DIOTIMO; /* dio polling timeout */ 8430286Ssam int iktimeout = PS_TIMEOUT; /* attention/dma timeout (in hz) */ 8530222Ssam 8630222Ssam ikprobe(reg, vi) 8730286Ssam caddr_t reg; 8830222Ssam struct vba_device *vi; 8930222Ssam { 9030286Ssam register int br, cvec; /* r12, r11 */ 9130222Ssam register struct ikdevice *ik; 9230222Ssam 9330294Ssam #ifdef lint 9430294Ssam br = 0; cvec = br; br = cvec; 9530294Ssam ikintr(0); 9630294Ssam #endif 9730286Ssam if (badaddr(reg, 2)) 9830286Ssam return (0); 9930222Ssam ik = (struct ikdevice *)reg; 10030222Ssam ik->ik_vec = --vi->ui_hd->vh_lastiv; 10130286Ssam /* 10230344Ssam * Use extended non-privileged address modifier 10330344Ssam * to avoid address overlap with 24-bit devices. 10430286Ssam */ 10530286Ssam ik->ik_mod = 0xf1; /* address modifier */ 10630286Ssam /* 10730286Ssam * Try and reset the PS300. Since this 10830286Ssam * won't work if it's powered off, we 10930286Ssam * can't use sucess/failure to decide 11030286Ssam * if the device is present. 11130286Ssam */ 11230222Ssam br = 0; 11330286Ssam (void) psreset(ik, IKCSR_IENA); 11430286Ssam if (br == 0) /* XXX */ 11530222Ssam br = 0x18, cvec = ik->ik_vec; /* XXX */ 11630286Ssam return (sizeof (struct ikdevice)); 11730222Ssam } 11830222Ssam 11930222Ssam /* 12030222Ssam * Perform a ``hard'' reset. 12130222Ssam */ 12230222Ssam psreset(ik, iena) 12330286Ssam register struct ikdevice *ik; 12430222Ssam { 12530222Ssam 12630286Ssam ik->ik_csr = IKCSR_MCLR|iena; 12730286Ssam DELAY(10000); 12830286Ssam ik->ik_csr = IKCSR_FNC3|iena; 12930286Ssam if (!iena) 13030286Ssam return (dioread(ik) == PS_RESET); 13130286Ssam return (1); 13230222Ssam } 13330222Ssam 13430222Ssam ikattach(vi) 13530286Ssam struct vba_device *vi; 13630222Ssam { 13730222Ssam 13830286Ssam ik_softc[vi->ui_unit].is_uid = -1; 13930222Ssam } 14030222Ssam 14130222Ssam /* 14230222Ssam * Open a PS300 and attach. We allow multiple 14330222Ssam * processes with the same uid to share a unit. 14430222Ssam */ 14530222Ssam /*ARGSUSED*/ 14630222Ssam ikopen(dev, flag) 14730286Ssam dev_t dev; 14830286Ssam int flag; 14930222Ssam { 15030286Ssam register int unit = IKUNIT(dev); 15130286Ssam register struct ik_softc *sc; 15230286Ssam struct vba_device *vi; 15330286Ssam struct ikdevice *ik; 15430286Ssam int reset; 15530222Ssam 15630286Ssam if (unit >= NIK || (vi = ikinfo[unit]) == 0 || vi->ui_alive == 0) 15730286Ssam return (ENXIO); 15830286Ssam sc = &ik_softc[unit]; 15930294Ssam if (sc->is_uid != (uid_t)-1 && sc->is_uid != u.u_uid) 16030286Ssam return (EBUSY); 16130294Ssam if (sc->is_uid == (uid_t)-1) { 16230286Ssam sc->is_timeout = 0; 16330294Ssam timeout(iktimer, (caddr_t)unit, hz); 16430286Ssam /* 16530286Ssam * Perform PS300 attach for first process. 16630286Ssam */ 16730286Ssam if (!IKDIAG(dev)) { 16830286Ssam reset = 0; 16930286Ssam again: 17030286Ssam if (ikcommand(dev, PS_ATTACH, 1)) { 17130286Ssam /* 17230286Ssam * If attach fails, perform a hard 17330286Ssam * reset once, then retry the command. 17430286Ssam */ 17530286Ssam ik = (struct ikdevice *)ikinfo[unit]->ui_addr; 17630286Ssam if (!reset++ && psreset(ik, 0)) 17730286Ssam goto again; 17830294Ssam untimeout(iktimer, (caddr_t)unit); 17930286Ssam return (EIO); 18030286Ssam } 18130286Ssam } 18230286Ssam sc->is_uid = u.u_uid; 18330286Ssam } 18430286Ssam return (0); 18530222Ssam } 18630222Ssam 18730222Ssam /*ARGSUSED*/ 18830222Ssam ikclose(dev, flag) 18930286Ssam dev_t dev; 19030286Ssam int flag; 19130222Ssam { 19230286Ssam int unit = IKUNIT(dev); 19330222Ssam register struct ik_softc *sc = &ik_softc[unit]; 19430222Ssam 19530286Ssam if (!IKDIAG(dev)) 19630286Ssam (void) ikcommand(dev, PS_DETACH, 1); /* auto detach */ 19730286Ssam sc->is_uid = -1; 19830294Ssam untimeout(iktimer, (caddr_t)unit); 19930222Ssam } 20030222Ssam 20130222Ssam ikread(dev, uio) 20230286Ssam dev_t dev; 20330286Ssam struct uio *uio; 20430222Ssam { 20530222Ssam 20630286Ssam return (ikrw(dev, uio, B_READ)); 20730222Ssam } 20830222Ssam 20930222Ssam ikwrite(dev, uio) 21030286Ssam dev_t dev; 21130286Ssam struct uio *uio; 21230222Ssam { 21330222Ssam 21430286Ssam return (ikrw(dev, uio, B_WRITE)); 21530222Ssam } 21630222Ssam 21730222Ssam /* 21830222Ssam * Take read/write request and perform physical i/o 21930222Ssam * transaction with PS300. This involves constructing 22030222Ssam * a physical i/o request vector based on the uio 22130222Ssam * vector, performing the dma, and, finally, moving 22230222Ssam * the data to it's final destination (because of CCI 22330222Ssam * VERSAbus bogosities). 22430222Ssam */ 22530222Ssam ikrw(dev, uio, rw) 22630286Ssam dev_t dev; 22730286Ssam register struct uio *uio; 22830286Ssam int rw; 22930222Ssam { 23030286Ssam int error, unit = IKUNIT(dev), s, wrcmd; 23130286Ssam register struct buf *bp; 23230286Ssam register struct iovec *iov; 23330286Ssam register struct psalist *ap; 23430286Ssam struct ik_softc *sc = &ik_softc[unit]; 23530222Ssam 23630286Ssam if (unit >= NIK) 23730286Ssam return (ENXIO); 23830286Ssam bp = &rikbuf[unit]; 23930286Ssam error = 0, iov = uio->uio_iov, wrcmd = PS_WRPHY; 24030286Ssam for (; !error && uio->uio_iovcnt; iov++, uio->uio_iovcnt--) { 24130286Ssam /* 24230286Ssam * Hack way to set PS300 address w/o doing an lseek 24330286Ssam * and specify write physical w/ refresh synchronization. 24430286Ssam */ 24530286Ssam if (iov->iov_len == 0) { 24630286Ssam if ((int)iov->iov_base&PSIO_SYNC) 24730286Ssam wrcmd = PS_WRPHY_SYNC; 24830286Ssam uio->uio_offset = (int)iov->iov_base & ~PSIO_SYNC; 24930286Ssam continue; 25030286Ssam } 25130286Ssam if (iov->iov_len > PS_MAXDMA) { 25230286Ssam sc->is_error = PSERROR_INVALBC, error = EINVAL; 25330286Ssam continue; 25430286Ssam } 25530286Ssam if ((int)uio->uio_offset&01) { 25630286Ssam sc->is_error = PSERROR_BADADDR, error = EINVAL; 25730286Ssam continue; 25830286Ssam } 25930286Ssam s = splbio(); 26030286Ssam while (bp->b_flags&B_BUSY) { 26130286Ssam bp->b_flags |= B_WANTED; 26230286Ssam sleep((caddr_t)bp, PRIBIO+1); 26330286Ssam } 26430286Ssam splx(s); 26530286Ssam bp->b_flags = B_BUSY | rw; 26630286Ssam /* 26730286Ssam * Construct address descriptor in buffer. 26830286Ssam */ 26930286Ssam ap = (struct psalist *)sc->is_buf; 27030286Ssam ap->nblocks = 1; 27130286Ssam /* work-around dr300 word swapping */ 27230286Ssam ap->addr[0] = uio->uio_offset & 0xffff; 27330286Ssam ap->addr[1] = uio->uio_offset >> 16; 27430286Ssam ap->wc = (iov->iov_len + 1) >> 1; 27530286Ssam if (rw == B_WRITE) { 27630286Ssam error = copyin(iov->iov_base, (caddr_t)&ap[1], 27730294Ssam (unsigned)iov->iov_len); 27830286Ssam if (!error) 27930286Ssam error = ikcommand(dev, wrcmd, 28030286Ssam iov->iov_len + sizeof (*ap)); 28130286Ssam } else { 28230286Ssam caddr_t cp; 28330286Ssam int len; 28430222Ssam 28530286Ssam error = ikcommand(dev, PS_RDPHY, sizeof (*ap)); 28630286Ssam cp = (caddr_t)&ap[1], len = iov->iov_len; 28730286Ssam for (; len > 0; len -= NBPG, cp += NBPG) 28830286Ssam mtpr(P1DC, cp); 28930286Ssam if (!error) 29030286Ssam error = copyout((caddr_t)&ap[1], iov->iov_base, 29130294Ssam (unsigned)iov->iov_len); 29230286Ssam } 29330286Ssam (void) splbio(); 29430286Ssam if (bp->b_flags&B_WANTED) 29530286Ssam wakeup((caddr_t)bp); 29630286Ssam splx(s); 29730286Ssam uio->uio_resid -= iov->iov_len; 29830286Ssam uio->uio_offset += iov->iov_len; 29930286Ssam bp->b_flags &= ~(B_BUSY|B_WANTED); 30030286Ssam } 30130286Ssam return (error); 30230222Ssam } 30330222Ssam 30430222Ssam /* 30530222Ssam * Perform a PS300 command. 30630222Ssam */ 30730222Ssam ikcommand(dev, com, count) 30830286Ssam dev_t dev; 30930286Ssam int com, count; 31030222Ssam { 31130286Ssam register struct buf *bp; 31230286Ssam register int s; 31330222Ssam 31430286Ssam bp = &cikbuf[IKUNIT(dev)]; 31530286Ssam s = splik(); 31630286Ssam while (bp->b_flags&B_BUSY) { 31730286Ssam if (bp->b_flags&B_DONE) 31830286Ssam break; 31930286Ssam bp->b_flags |= B_WANTED; 32030286Ssam sleep((caddr_t)bp, PRIBIO); 32130286Ssam } 32230286Ssam bp->b_flags = B_BUSY|B_READ; 32330286Ssam splx(s); 32430286Ssam bp->b_dev = dev; 32530286Ssam bp->b_command = com; 32630286Ssam bp->b_bcount = count; 32730286Ssam ikstrategy(bp); 32830286Ssam biowait(bp); 32930286Ssam if (bp->b_flags&B_WANTED) 33030286Ssam wakeup((caddr_t)bp); 33130286Ssam bp->b_flags &= B_ERROR; 33230286Ssam return (geterror(bp)); 33330222Ssam } 33430222Ssam 33530222Ssam /* 33630222Ssam * Physio strategy routine 33730222Ssam */ 33830222Ssam ikstrategy(bp) 33930286Ssam register struct buf *bp; 34030222Ssam { 34130286Ssam register struct buf *dp; 34230222Ssam 34330286Ssam /* 34430286Ssam * Put request at end of controller queue. 34530286Ssam */ 34630286Ssam dp = &iktab[IKUNIT(bp->b_dev)]; 34730286Ssam bp->av_forw = NULL; 34830286Ssam (void) splik(); 34930286Ssam if (dp->b_actf != NULL) { 35030286Ssam dp->b_actl->av_forw = bp; 35130286Ssam dp->b_actl = bp; 35230286Ssam } else 35330286Ssam dp->b_actf = dp->b_actl = bp; 35430286Ssam if (!dp->b_active) 35530286Ssam ikstart(dp); 35630286Ssam (void) spl0(); 35730222Ssam } 35830222Ssam 35930222Ssam /* 36030222Ssam * Start the next command on the controller's queue. 36130222Ssam */ 36230222Ssam ikstart(dp) 36330286Ssam register struct buf *dp; 36430222Ssam { 36530286Ssam register struct buf *bp; 36630286Ssam register struct ikdevice *ik; 36730286Ssam register struct ik_softc *sc; 36830286Ssam u_short bc, csr; 36930286Ssam u_int addr; 37030286Ssam int unit; 37130222Ssam 37230222Ssam loop: 37330286Ssam /* 37430286Ssam * Pull a request off the controller queue 37530286Ssam */ 37630286Ssam if ((bp = dp->b_actf) == NULL) { 37730286Ssam dp->b_active = 0; 37830286Ssam return; 37930286Ssam } 38030286Ssam /* 38130286Ssam * Mark controller busy and process this request. 38230286Ssam */ 38330286Ssam dp->b_active = 1; 38430286Ssam unit = IKUNIT(bp->b_dev); 38530286Ssam sc = &ik_softc[unit]; 38630286Ssam ik = (struct ikdevice *)ikinfo[unit]->ui_addr; 38730294Ssam switch ((int)bp->b_command) { 38830222Ssam 38930286Ssam case PS_ATTACH: /* logical unit attach */ 39030286Ssam case PS_DETACH: /* logical unit detach */ 39130286Ssam case PS_LOOKUP: /* name lookup */ 39230286Ssam case PS_RDPHY: /* physical i/o read */ 39330286Ssam case PS_WRPHY: /* physical i/o write */ 39430286Ssam case PS_WRPHY_SYNC: /* physical i/o write w/ sync */ 39530286Ssam /* 39630286Ssam * Handshake command and, optionally, 39730286Ssam * byte count and byte swap flag. 39830286Ssam */ 39930294Ssam if (sc->is_error = diowrite(ik, (u_short)bp->b_command)) 40030286Ssam goto bad; 40130286Ssam if (bp->b_command < PS_DETACH) { 40230294Ssam if (sc->is_error = diowrite(ik, (u_short)bp->b_bcount)) 40330286Ssam goto bad; 40430294Ssam if (sc->is_error = diowrite(ik, (u_short)0 /* !swab */)) 40530286Ssam goto bad; 40630286Ssam } 40730286Ssam /* 40830286Ssam * Set timeout and wait for an attention interrupt. 40930286Ssam */ 41030286Ssam sc->is_timeout = iktimeout; 41130286Ssam return; 41230222Ssam 41330286Ssam case PS_DMAOUT: /* dma data host->PS300 */ 41430286Ssam bc = bp->b_bcount; 41530286Ssam csr = IKCSR_CYCLE; 41630286Ssam break; 41730222Ssam 41830286Ssam case PS_DMAIN: /* dma data PS300->host */ 41930286Ssam bc = bp->b_bcount; 42030286Ssam csr = IKCSR_CYCLE|IKCSR_FNC1; 42130286Ssam break; 42230222Ssam 42330286Ssam default: 42430286Ssam log(LOG_ERR, "ik%d: bad cmd %x\n", unit, bp->b_command); 42530286Ssam sc->is_error = PSERROR_BADCMD; 42630286Ssam goto bad; 42730286Ssam } 42830286Ssam /* initiate dma transfer */ 42930294Ssam addr = vtoph((struct proc *)0, (unsigned)sc->is_buf); 43030286Ssam ik->ik_bahi = addr >> 17; 43130286Ssam ik->ik_balo = (addr >> 1) & 0xffff; 43230286Ssam ik->ik_wc = ((bc + 1) >> 1) - 1; /* round & convert */ 43330286Ssam ik->ik_pulse = IKPULSE_RATTF|IKPULSE_RDMAF; 43430286Ssam sc->is_timeout = iktimeout; 43530286Ssam ik->ik_csr = IKCSR_IENA|IKCSR_GO|csr; 43630286Ssam return; 43730222Ssam bad: 43830286Ssam bp->b_flags |= B_ERROR; 43930286Ssam dp->b_actf = bp->av_forw; /* remove from queue */ 44030286Ssam biodone(bp); 44130286Ssam goto loop; 44230222Ssam } 44330222Ssam 44430222Ssam #define FETCHWORD(i) { \ 44530286Ssam v = dioread(ik); \ 44630286Ssam if (v == -1) { \ 44730286Ssam sc->is_error = PSERROR_NAMETIMO; \ 44830286Ssam goto bad; \ 44930286Ssam } \ 45030286Ssam sc->is_nameaddr.w[i] = v; \ 45130222Ssam } 45230222Ssam 45330222Ssam /* 45430222Ssam * Process a device interrupt. 45530222Ssam */ 45630222Ssam ikintr(ikon) 45730286Ssam int ikon; 45830222Ssam { 45930286Ssam register struct ikdevice *ik; 46030286Ssam register struct buf *bp, *dp; 46130286Ssam struct ik_softc *sc; 46230286Ssam register u_short data; 46330294Ssam int v; 46430222Ssam 46530286Ssam /* should go by controller, but for now... */ 46630286Ssam if (ikinfo[ikon] == 0) 46730286Ssam return; 46830286Ssam ik = (struct ikdevice *)ikinfo[ikon]->ui_addr; 46930286Ssam /* 47030286Ssam * Discard all non-attention interrupts. The 47130286Ssam * interrupts we're throwing away should all be 47230286Ssam * associated with DMA completion. 47330286Ssam */ 47430286Ssam data = ik->ik_data; 47530286Ssam if ((ik->ik_csr&(IKCSR_ATTF|IKCSR_STATC)) != IKCSR_ATTF) { 47630286Ssam ik->ik_pulse = IKPULSE_RATTF|IKPULSE_RDMAF|IKPULSE_SIENA; 47730286Ssam return; 47830286Ssam } 47930286Ssam /* 48030286Ssam * Fetch attention code immediately. 48130286Ssam */ 48230286Ssam ik->ik_csr = IKCSR_RATTF|IKCSR_RDMAF|IKCSR_FNC1; 48330286Ssam ik->ik_pulse = IKPULSE_FNC2; 48430286Ssam /* 48530286Ssam * Get device and block structures, and a pointer 48630286Ssam * to the vba_device for the device. We receive an 48730286Ssam * unsolicited interrupt whenever the PS300 is power 48830286Ssam * cycled (so ignore it in that case). 48930286Ssam */ 49030286Ssam dp = &iktab[ikon]; 49130286Ssam if ((bp = dp->b_actf) == NULL) { 49230286Ssam if (PS_CODE(data) != PS_RESET) /* power failure */ 49330286Ssam log(LOG_WARNING, "ik%d: spurious interrupt, code %x\n", 49430286Ssam ikon, data); 49530286Ssam goto enable; 49630286Ssam } 49730286Ssam sc = &ik_softc[IKUNIT(bp->b_dev)]; 49830286Ssam sc->is_timeout = 0; /* disable timer */ 49930286Ssam switch (PS_CODE(data)) { 50030222Ssam 50130286Ssam case PS_LOOKUP: /* name lookup */ 50230286Ssam if (data == PS_LOOKUP) { /* dma name */ 50330286Ssam bp->b_command = PS_DMAOUT; 50430286Ssam goto opcont; 50530286Ssam } 50630286Ssam if (data == PS_DMAOK(PS_LOOKUP)) { 50730286Ssam /* reenable interrupt and wait for address */ 50830286Ssam sc->is_timeout = iktimeout; 50930286Ssam goto enable; 51030286Ssam } 51130286Ssam /* 51230286Ssam * Address should be present, extract it one 51330286Ssam * word at a time from the PS300 (yech). 51430286Ssam */ 51530286Ssam if (data != PS_ADROK(PS_LOOKUP)) 51630286Ssam goto bad; 51730286Ssam FETCHWORD(0); 51830286Ssam FETCHWORD(1); 51930286Ssam goto opdone; 52030222Ssam 52130286Ssam case PS_WRPHY_SYNC: /* physical i/o write w/ sync */ 52230286Ssam if (data == PS_WRPHY_SYNC) { /* start dma transfer */ 52330286Ssam bp->b_command = PS_DMAOUT; 52430286Ssam goto opcont; 52530286Ssam } 52630286Ssam if (data != PS_DMAOK(PS_WRPHY_SYNC)) 52730286Ssam goto bad; 52830286Ssam goto opdone; 52930222Ssam 53030286Ssam case PS_WRPHY: /* physical i/o write */ 53130286Ssam if (data == PS_WRPHY) { /* start dma transfer */ 53230286Ssam bp->b_command = PS_DMAOUT; 53330286Ssam goto opcont; 53430286Ssam } 53530286Ssam if (data != PS_DMAOK(PS_WRPHY)) 53630286Ssam goto bad; 53730286Ssam goto opdone; 53830222Ssam 53930286Ssam case PS_ATTACH: /* attach unit */ 54030286Ssam case PS_DETACH: /* detach unit */ 54130286Ssam case PS_ABORT: /* abort code from ps300 */ 54230286Ssam if (data != bp->b_command) 54330286Ssam goto bad; 54430286Ssam goto opdone; 54530222Ssam 54630286Ssam case PS_RDPHY: /* physical i/o read */ 54730286Ssam if (data == PS_RDPHY) { /* dma address list */ 54830286Ssam bp->b_command = PS_DMAOUT; 54930286Ssam goto opcont; 55030286Ssam } 55130286Ssam if (data == PS_ADROK(PS_RDPHY)) { 55230286Ssam /* collect read byte count and start dma */ 55330286Ssam bp->b_bcount = dioread(ik); 55430286Ssam if (bp->b_bcount == -1) 55530286Ssam goto bad; 55630286Ssam bp->b_command = PS_DMAIN; 55730286Ssam goto opcont; 55830286Ssam } 55930286Ssam if (data == PS_DMAOK(PS_RDPHY)) 56030286Ssam goto opdone; 56130286Ssam goto bad; 56230286Ssam } 56330222Ssam bad: 56430286Ssam sc->is_error = data; 56530286Ssam bp->b_flags |= B_ERROR; 56630222Ssam opdone: 56730286Ssam dp->b_actf = bp->av_forw; /* remove from queue */ 56830286Ssam biodone(bp); 56930222Ssam opcont: 57030286Ssam ikstart(dp); 57130222Ssam enable: 57230286Ssam ik->ik_pulse = IKPULSE_SIENA; /* explicitly reenable */ 57330222Ssam } 57430222Ssam 57530222Ssam /* 57630222Ssam * Watchdog timer. 57730222Ssam */ 57830222Ssam iktimer(unit) 57930286Ssam int unit; 58030222Ssam { 58130286Ssam register struct ik_softc *sc = &ik_softc[unit]; 58230222Ssam 58330286Ssam if (sc->is_timeout && --sc->is_timeout == 0) { 58430286Ssam register struct buf *dp, *bp; 58530286Ssam int s; 58630222Ssam 58730286Ssam log(LOG_ERR, "ik%d: timeout\n", unit); 58830286Ssam s = splik(); 58930286Ssam /* should abort current command */ 59030286Ssam dp = &iktab[unit]; 59130286Ssam if (bp = dp->b_actf) { 59230286Ssam sc->is_error = PSERROR_CMDTIMO; 59330286Ssam bp->b_flags |= B_ERROR; 59430286Ssam dp->b_actf = bp->av_forw; /* remove from queue */ 59530286Ssam biodone(bp); 59630286Ssam ikstart(dp); 59730286Ssam } 59830286Ssam splx(s); 59930286Ssam } 60030294Ssam timeout(iktimer, (caddr_t)unit, hz); 60130222Ssam } 60230222Ssam 60330222Ssam /* 60430222Ssam * Handshake read from DR300. 60530222Ssam */ 60630222Ssam dioread(ik) 60730286Ssam register struct ikdevice *ik; 60830222Ssam { 60930294Ssam register int t; 61030286Ssam u_short data; 61130222Ssam 61230294Ssam for (t = ikdiotimo; t > 0; t--) 61330286Ssam if ((ik->ik_csr&(IKCSR_ATTF|IKCSR_STATC)) == IKCSR_ATTF) { 61430286Ssam data = ik->ik_data; 61530286Ssam ik->ik_csr = IKCSR_RATTF|IKCSR_RDMAF|IKCSR_FNC1; 61630286Ssam ik->ik_pulse = IKPULSE_FNC2; 61730286Ssam return (data); 61830286Ssam } 61930286Ssam return (-1); 62030222Ssam } 62130222Ssam 62230222Ssam /* 62330222Ssam * Handshake write to DR300. 62430222Ssam * 62530222Ssam * Interrupts are enabled before completing the work 62630222Ssam * so the caller should either be at splik or be 62730222Ssam * prepared to take the interrupt immediately. 62830222Ssam */ 62930222Ssam diowrite(ik, v) 63030286Ssam register struct ikdevice *ik; 63130286Ssam u_short v; 63230222Ssam { 63330294Ssam register int t; 63430286Ssam register u_short csr; 63530222Ssam 63630222Ssam top: 63730286Ssam /* 63830286Ssam * Deposit data and generate dr300 attention 63930286Ssam */ 64030286Ssam ik->ik_data = v; 64130286Ssam ik->ik_csr = IKCSR_RDMAF|IKCSR_RATTF; 64230286Ssam ik->ik_pulse = IKPULSE_FNC2; 64330294Ssam for (t = ikdiotimo; t > 0; t--) { 64430286Ssam csr = ik->ik_csr; 64530286Ssam #define IKCSR_DONE (IKCSR_STATA|IKCSR_STATC) 64630286Ssam if ((csr&IKCSR_DONE) == IKCSR_DONE) { 64730286Ssam /* 64830286Ssam * Done, complete handshake by notifying dr300. 64930286Ssam */ 65030286Ssam ik->ik_csr = IKCSR_IENA; /* ~IKCSR_FNC1 */ 65130286Ssam ik->ik_pulse = IKPULSE_FNC2; 65230286Ssam return (0); 65330286Ssam } 65430286Ssam /* beware of potential deadlock with dioread */ 65530286Ssam if ((csr&(IKCSR_ATTF|IKCSR_STATC)) == IKCSR_ATTF) 65630286Ssam goto top; 65730286Ssam } 65830286Ssam ik->ik_csr = IKCSR_IENA; 65930286Ssam return (PSERROR_DIOTIMO); 66030222Ssam } 66130222Ssam 66230222Ssam /*ARGSUSED*/ 66330222Ssam ikioctl(dev, cmd, data, flag) 66430286Ssam dev_t dev; 66530286Ssam int cmd; 66630286Ssam caddr_t data; 66730286Ssam int flag; 66830222Ssam { 66930286Ssam int error = 0, unit = IKUNIT(dev), s; 67030286Ssam register struct ik_softc *sc = &ik_softc[unit]; 67130222Ssam 67230286Ssam switch (cmd) { 67330222Ssam 67430286Ssam case PSIOGETERROR: /* get error code for last operation */ 67530286Ssam *(int *)data = sc->is_error; 67630286Ssam break; 67730222Ssam 67830286Ssam case PSIOLOOKUP: { /* PS300 name lookup */ 67930286Ssam register struct pslookup *lp = (struct pslookup *)data; 68030286Ssam register struct buf *bp; 68130222Ssam 68230286Ssam if (lp->pl_len > PS_MAXNAMELEN) 68330286Ssam return (EINVAL); 68430286Ssam bp = &rikbuf[unit]; 68530286Ssam s = splbio(); 68630286Ssam while (bp->b_flags&B_BUSY) { 68730286Ssam bp->b_flags |= B_WANTED; 68830286Ssam sleep((caddr_t)bp, PRIBIO+1); 68930286Ssam } 69030286Ssam splx(s); 69130286Ssam bp->b_flags = B_BUSY | B_WRITE; 69234506Skarels error = copyin(lp->pl_name, (caddr_t)sc->is_buf, 69334506Skarels (unsigned)lp->pl_len); 69430286Ssam if (error == 0) { 69530286Ssam if (lp->pl_len&1) 69630286Ssam sc->is_buf[lp->pl_len] = '\0'; 69730286Ssam error = ikcommand(dev, PS_LOOKUP, lp->pl_len); 69830286Ssam } 69930286Ssam s = splbio(); 70030286Ssam if (bp->b_flags&B_WANTED) 70130286Ssam wakeup((caddr_t)bp); 70230286Ssam splx(s); 70330286Ssam bp->b_flags &= ~(B_BUSY|B_WANTED); 70430286Ssam lp->pl_addr = sc->is_nameaddr.l; 70530286Ssam break; 70630286Ssam } 70730286Ssam default: 70830286Ssam return (ENOTTY); 70930286Ssam } 71030286Ssam return (error); 71130222Ssam } 71230222Ssam #endif 713