xref: /csrg-svn/sys/tahoe/vba/ik.c (revision 30294)
1*30294Ssam /*	ik.c	1.4	86/12/15	*/
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"
2130228Ssam #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 
3130286Ssam int	ikprobe(), ikattach(), iktimer();
3230286Ssam struct	vba_device *ikinfo[NIK];
3330286Ssam long	ikstd[] = { 0 };
3430286Ssam struct	vba_driver ikdriver = { ikprobe, 0, ikattach, 0, ikstd, "ik", ikinfo };
3530222Ssam 
3630286Ssam #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  */
4330286Ssam #define IKUNIT(dev)	(minor(dev) >> 1)
4430286Ssam #define IKDIAG(dev)	(minor(dev) & 01)	/* is a diagnostic unit */
4530222Ssam 
4630286Ssam struct	ik_softc {
4730286Ssam 	uid_t	is_uid;		/* uid of open processes */
4830286Ssam 	u_short is_timeout;	/* current timeout (seconds) */
4930286Ssam 	u_short is_error;	/* internal error codes */
5030286Ssam 	u_short is_flags;
5130286Ssam #define IKF_ATTACHED	0x1	/* unit is attached (not used yet) */
5230286Ssam 	union {
5330286Ssam 		u_short w[2];
5430286Ssam 		u_long	l;
5530286Ssam 	} is_nameaddr;		/* address of last symbol lookup */
5630286Ssam 	caddr_t is_buf;		/* i/o buffer XXX */
5730222Ssam } ik_softc[NIK];
5830222Ssam 
5930286Ssam struct	buf iktab[NIK];		/* unit command queue headers */
6030286Ssam struct	buf rikbuf[NIK];	/* buffers for read/write operations */
6130286Ssam struct	buf cikbuf[NIK];	/* buffers for control operations */
6230222Ssam 
6330222Ssam /* buf overlay definitions */
6430286Ssam #define b_command	b_resid
6530222Ssam 
6630286Ssam int	ikdiotimo = PS_DIOTIMO; /* dio polling timeout */
6730286Ssam int	iktimeout = PS_TIMEOUT; /* attention/dma timeout (in hz) */
6830222Ssam 
6930222Ssam ikprobe(reg, vi)
7030286Ssam 	caddr_t reg;
7130222Ssam 	struct vba_device *vi;
7230222Ssam {
7330286Ssam 	register int br, cvec;		/* r12, r11 */
7430222Ssam 	register struct ikdevice *ik;
7530222Ssam 
76*30294Ssam #ifdef lint
77*30294Ssam 	br = 0; cvec = br; br = cvec;
78*30294Ssam 	ikintr(0);
79*30294Ssam #endif
8030286Ssam 	if (badaddr(reg, 2))
8130286Ssam 		return (0);
8230222Ssam 	ik = (struct ikdevice *)reg;
8330222Ssam 	ik->ik_vec = --vi->ui_hd->vh_lastiv;
8430286Ssam 	/*
8530286Ssam 	 * Use extended non-privileged address modifier to
8630286Ssam 	 * insure DMA to/from intermediate buffer works when
8730286Ssam 	 * buffer is not in lower 16Mb of memory (also avoids
8830286Ssam 	 * other 24-bit devices mapped into overlapping regions).
8930286Ssam 	 */
9030286Ssam 	ik->ik_mod = 0xf1;			/* address modifier */
9130286Ssam 	/*
9230286Ssam 	 * Try and reset the PS300.  Since this
9330286Ssam 	 * won't work if it's powered off, we
9430286Ssam 	 * can't use sucess/failure to decide
9530286Ssam 	 * if the device is present.
9630286Ssam 	 */
9730222Ssam 	br = 0;
9830286Ssam 	(void) psreset(ik, IKCSR_IENA);
9930286Ssam 	if (br == 0)				/* XXX */
10030222Ssam 		br = 0x18, cvec = ik->ik_vec;	/* XXX */
10130286Ssam 	return (sizeof (struct ikdevice));
10230222Ssam }
10330222Ssam 
10430222Ssam /*
10530222Ssam  * Perform a ``hard'' reset.
10630222Ssam  */
10730222Ssam psreset(ik, iena)
10830286Ssam 	register struct ikdevice *ik;
10930222Ssam {
11030222Ssam 
11130286Ssam 	ik->ik_csr = IKCSR_MCLR|iena;
11230286Ssam 	DELAY(10000);
11330286Ssam 	ik->ik_csr = IKCSR_FNC3|iena;
11430286Ssam 	if (!iena)
11530286Ssam 		return (dioread(ik) == PS_RESET);
11630286Ssam 	return (1);
11730222Ssam }
11830222Ssam 
11930222Ssam ikattach(vi)
12030286Ssam 	struct vba_device *vi;
12130222Ssam {
12230222Ssam 
12330286Ssam 	ik_softc[vi->ui_unit].is_uid = -1;
12430222Ssam }
12530222Ssam 
12630222Ssam /*
12730222Ssam  * Open a PS300 and attach.  We allow multiple
12830222Ssam  * processes with the same uid to share a unit.
12930222Ssam  */
13030222Ssam /*ARGSUSED*/
13130222Ssam ikopen(dev, flag)
13230286Ssam 	dev_t dev;
13330286Ssam 	int flag;
13430222Ssam {
13530286Ssam 	register int unit = IKUNIT(dev);
13630286Ssam 	register struct ik_softc *sc;
13730286Ssam 	struct vba_device *vi;
13830286Ssam 	struct ikdevice *ik;
13930286Ssam 	int reset;
14030222Ssam 
14130286Ssam 	if (unit >= NIK || (vi = ikinfo[unit]) == 0 || vi->ui_alive == 0)
14230286Ssam 		return (ENXIO);
14330286Ssam 	sc = &ik_softc[unit];
144*30294Ssam 	if (sc->is_uid != (uid_t)-1 && sc->is_uid != u.u_uid)
14530286Ssam 		return (EBUSY);
146*30294Ssam 	if (sc->is_uid == (uid_t)-1) {
14730222Ssam 		sc->is_buf = (caddr_t)wmemall(vmemall, PS_MAXDMA);
14830222Ssam 		if (sc->is_buf == 0)
14930222Ssam 			return (ENOMEM);
15030286Ssam 		sc->is_timeout = 0;
151*30294Ssam 		timeout(iktimer, (caddr_t)unit, hz);
15230286Ssam 		/*
15330286Ssam 		 * Perform PS300 attach for first process.
15430286Ssam 		 */
15530286Ssam 		if (!IKDIAG(dev)) {
15630286Ssam 			reset = 0;
15730286Ssam 		again:
15830286Ssam 			if (ikcommand(dev, PS_ATTACH, 1)) {
15930286Ssam 				/*
16030286Ssam 				 * If attach fails, perform a hard
16130286Ssam 				 * reset once, then retry the command.
16230286Ssam 				 */
16330286Ssam 				ik = (struct ikdevice *)ikinfo[unit]->ui_addr;
16430286Ssam 				if (!reset++ && psreset(ik, 0))
16530286Ssam 					goto again;
166*30294Ssam 				untimeout(iktimer, (caddr_t)unit);
16730222Ssam 				wmemfree(sc->is_buf, PS_MAXDMA);
16830222Ssam 				sc->is_buf = 0;
16930286Ssam 				return (EIO);
17030286Ssam 			}
17130286Ssam 		}
17230286Ssam 		sc->is_uid = u.u_uid;
17330286Ssam 	}
17430286Ssam 	return (0);
17530222Ssam }
17630222Ssam 
17730222Ssam /*ARGSUSED*/
17830222Ssam ikclose(dev, flag)
17930286Ssam 	dev_t dev;
18030286Ssam 	int flag;
18130222Ssam {
18230286Ssam 	int unit = IKUNIT(dev);
18330222Ssam 	register struct ik_softc *sc = &ik_softc[unit];
18430222Ssam 
18530286Ssam 	if (!IKDIAG(dev))
18630286Ssam 		(void) ikcommand(dev, PS_DETACH, 1);	/* auto detach */
18730286Ssam 	sc->is_uid = -1;
18830222Ssam 	if (sc->is_buf) {
18930222Ssam 		wmemfree(sc->is_buf, PS_MAXDMA);
19030222Ssam 		sc->is_buf = 0;
19130222Ssam 	}
192*30294Ssam 	untimeout(iktimer, (caddr_t)unit);
19330222Ssam }
19430222Ssam 
19530222Ssam ikread(dev, uio)
19630286Ssam 	dev_t dev;
19730286Ssam 	struct uio *uio;
19830222Ssam {
19930222Ssam 
20030286Ssam 	return (ikrw(dev, uio, B_READ));
20130222Ssam }
20230222Ssam 
20330222Ssam ikwrite(dev, uio)
20430286Ssam 	dev_t dev;
20530286Ssam 	struct uio *uio;
20630222Ssam {
20730222Ssam 
20830286Ssam 	return (ikrw(dev, uio, B_WRITE));
20930222Ssam }
21030222Ssam 
21130222Ssam /*
21230222Ssam  * Take read/write request and perform physical i/o
21330222Ssam  * transaction with PS300.  This involves constructing
21430222Ssam  * a physical i/o request vector based on the uio
21530222Ssam  * vector, performing the dma, and, finally, moving
21630222Ssam  * the data to it's final destination (because of CCI
21730222Ssam  * VERSAbus bogosities).
21830222Ssam  */
21930222Ssam ikrw(dev, uio, rw)
22030286Ssam 	dev_t dev;
22130286Ssam 	register struct uio *uio;
22230286Ssam 	int rw;
22330222Ssam {
22430286Ssam 	int error, unit = IKUNIT(dev), s, wrcmd;
22530286Ssam 	register struct buf *bp;
22630286Ssam 	register struct iovec *iov;
22730286Ssam 	register struct psalist *ap;
22830286Ssam 	struct ik_softc *sc = &ik_softc[unit];
22930222Ssam 
23030286Ssam 	if (unit >= NIK)
23130286Ssam 		return (ENXIO);
23230286Ssam 	bp = &rikbuf[unit];
23330286Ssam 	error = 0, iov = uio->uio_iov, wrcmd = PS_WRPHY;
23430286Ssam 	for (; !error && uio->uio_iovcnt; iov++, uio->uio_iovcnt--) {
23530286Ssam 		/*
23630286Ssam 		 * Hack way to set PS300 address w/o doing an lseek
23730286Ssam 		 * and specify write physical w/ refresh synchronization.
23830286Ssam 		 */
23930286Ssam 		if (iov->iov_len == 0) {
24030286Ssam 			if ((int)iov->iov_base&PSIO_SYNC)
24130286Ssam 				wrcmd = PS_WRPHY_SYNC;
24230286Ssam 			uio->uio_offset = (int)iov->iov_base & ~PSIO_SYNC;
24330286Ssam 			continue;
24430286Ssam 		}
24530286Ssam 		if (iov->iov_len > PS_MAXDMA) {
24630286Ssam 			sc->is_error = PSERROR_INVALBC, error = EINVAL;
24730286Ssam 			continue;
24830286Ssam 		}
24930286Ssam 		if ((int)uio->uio_offset&01) {
25030286Ssam 			sc->is_error = PSERROR_BADADDR, error = EINVAL;
25130286Ssam 			continue;
25230286Ssam 		}
25330286Ssam 		s = splbio();
25430286Ssam 		while (bp->b_flags&B_BUSY) {
25530286Ssam 			bp->b_flags |= B_WANTED;
25630286Ssam 			sleep((caddr_t)bp, PRIBIO+1);
25730286Ssam 		}
25830286Ssam 		splx(s);
25930286Ssam 		bp->b_flags = B_BUSY | rw;
26030286Ssam 		/*
26130286Ssam 		 * Construct address descriptor in buffer.
26230286Ssam 		 */
26330286Ssam 		ap = (struct psalist *)sc->is_buf;
26430286Ssam 		ap->nblocks = 1;
26530286Ssam 		/* work-around dr300 word swapping */
26630286Ssam 		ap->addr[0] = uio->uio_offset & 0xffff;
26730286Ssam 		ap->addr[1] = uio->uio_offset >> 16;
26830286Ssam 		ap->wc = (iov->iov_len + 1) >> 1;
26930286Ssam 		if (rw == B_WRITE) {
27030286Ssam 			error = copyin(iov->iov_base, (caddr_t)&ap[1],
271*30294Ssam 			    (unsigned)iov->iov_len);
27230286Ssam 			if (!error)
27330286Ssam 				error = ikcommand(dev, wrcmd,
27430286Ssam 				    iov->iov_len + sizeof (*ap));
27530286Ssam 		} else {
27630286Ssam 			caddr_t cp;
27730286Ssam 			int len;
27830222Ssam 
27930286Ssam 			error = ikcommand(dev, PS_RDPHY, sizeof (*ap));
28030286Ssam 			cp = (caddr_t)&ap[1], len = iov->iov_len;
28130286Ssam 			for (; len > 0; len -= NBPG, cp += NBPG)
28230286Ssam 				mtpr(P1DC, cp);
28330286Ssam 			if (!error)
28430286Ssam 				error = copyout((caddr_t)&ap[1], iov->iov_base,
285*30294Ssam 				    (unsigned)iov->iov_len);
28630286Ssam 		}
28730286Ssam 		(void) splbio();
28830286Ssam 		if (bp->b_flags&B_WANTED)
28930286Ssam 			wakeup((caddr_t)bp);
29030286Ssam 		splx(s);
29130286Ssam 		uio->uio_resid -= iov->iov_len;
29230286Ssam 		uio->uio_offset += iov->iov_len;
29330286Ssam 		bp->b_flags &= ~(B_BUSY|B_WANTED);
29430286Ssam 	}
29530286Ssam 	return (error);
29630222Ssam }
29730222Ssam 
29830222Ssam /*
29930222Ssam  * Perform a PS300 command.
30030222Ssam  */
30130222Ssam ikcommand(dev, com, count)
30230286Ssam 	dev_t dev;
30330286Ssam 	int com, count;
30430222Ssam {
30530286Ssam 	register struct buf *bp;
30630286Ssam 	register int s;
30730222Ssam 
30830286Ssam 	bp = &cikbuf[IKUNIT(dev)];
30930286Ssam 	s = splik();
31030286Ssam 	while (bp->b_flags&B_BUSY) {
31130286Ssam 		if (bp->b_flags&B_DONE)
31230286Ssam 			break;
31330286Ssam 		bp->b_flags |= B_WANTED;
31430286Ssam 		sleep((caddr_t)bp, PRIBIO);
31530286Ssam 	}
31630286Ssam 	bp->b_flags = B_BUSY|B_READ;
31730286Ssam 	splx(s);
31830286Ssam 	bp->b_dev = dev;
31930286Ssam 	bp->b_command = com;
32030286Ssam 	bp->b_bcount = count;
32130286Ssam 	ikstrategy(bp);
32230286Ssam 	biowait(bp);
32330286Ssam 	if (bp->b_flags&B_WANTED)
32430286Ssam 		wakeup((caddr_t)bp);
32530286Ssam 	bp->b_flags &= B_ERROR;
32630286Ssam 	return (geterror(bp));
32730222Ssam }
32830222Ssam 
32930222Ssam /*
33030222Ssam  * Physio strategy routine
33130222Ssam  */
33230222Ssam ikstrategy(bp)
33330286Ssam 	register struct buf *bp;
33430222Ssam {
33530286Ssam 	register struct buf *dp;
33630222Ssam 
33730286Ssam 	/*
33830286Ssam 	 * Put request at end of controller queue.
33930286Ssam 	 */
34030286Ssam 	dp = &iktab[IKUNIT(bp->b_dev)];
34130286Ssam 	bp->av_forw = NULL;
34230286Ssam 	(void) splik();
34330286Ssam 	if (dp->b_actf != NULL) {
34430286Ssam 		dp->b_actl->av_forw = bp;
34530286Ssam 		dp->b_actl = bp;
34630286Ssam 	} else
34730286Ssam 		dp->b_actf = dp->b_actl = bp;
34830286Ssam 	if (!dp->b_active)
34930286Ssam 		ikstart(dp);
35030286Ssam 	(void) spl0();
35130222Ssam }
35230222Ssam 
35330222Ssam /*
35430222Ssam  * Start the next command on the controller's queue.
35530222Ssam  */
35630222Ssam ikstart(dp)
35730286Ssam 	register struct buf *dp;
35830222Ssam {
35930286Ssam 	register struct buf *bp;
36030286Ssam 	register struct ikdevice *ik;
36130286Ssam 	register struct ik_softc *sc;
36230286Ssam 	u_short bc, csr;
36330286Ssam 	u_int addr;
36430286Ssam 	int unit;
36530222Ssam 
36630222Ssam loop:
36730286Ssam 	/*
36830286Ssam 	 * Pull a request off the controller queue
36930286Ssam 	 */
37030286Ssam 	if ((bp = dp->b_actf) == NULL) {
37130286Ssam 		dp->b_active = 0;
37230286Ssam 		return;
37330286Ssam 	}
37430286Ssam 	/*
37530286Ssam 	 * Mark controller busy and process this request.
37630286Ssam 	 */
37730286Ssam 	dp->b_active = 1;
37830286Ssam 	unit = IKUNIT(bp->b_dev);
37930286Ssam 	sc = &ik_softc[unit];
38030286Ssam 	ik = (struct ikdevice *)ikinfo[unit]->ui_addr;
381*30294Ssam 	switch ((int)bp->b_command) {
38230222Ssam 
38330286Ssam 	case PS_ATTACH:		/* logical unit attach */
38430286Ssam 	case PS_DETACH:		/* logical unit detach */
38530286Ssam 	case PS_LOOKUP:		/* name lookup */
38630286Ssam 	case PS_RDPHY:		/* physical i/o read */
38730286Ssam 	case PS_WRPHY:		/* physical i/o write */
38830286Ssam 	case PS_WRPHY_SYNC:	/* physical i/o write w/ sync */
38930286Ssam 		/*
39030286Ssam 		 * Handshake command and, optionally,
39130286Ssam 		 * byte count and byte swap flag.
39230286Ssam 		 */
393*30294Ssam 		if (sc->is_error = diowrite(ik, (u_short)bp->b_command))
39430286Ssam 			goto bad;
39530286Ssam 		if (bp->b_command < PS_DETACH) {
396*30294Ssam 			if (sc->is_error = diowrite(ik, (u_short)bp->b_bcount))
39730286Ssam 				goto bad;
398*30294Ssam 			if (sc->is_error = diowrite(ik, (u_short)0 /* !swab */))
39930286Ssam 				goto bad;
40030286Ssam 		}
40130286Ssam 		/*
40230286Ssam 		 * Set timeout and wait for an attention interrupt.
40330286Ssam 		 */
40430286Ssam 		sc->is_timeout = iktimeout;
40530286Ssam 		return;
40630222Ssam 
40730286Ssam 	case PS_DMAOUT:		/* dma data host->PS300 */
40830286Ssam 		bc = bp->b_bcount;
40930286Ssam 		csr = IKCSR_CYCLE;
41030286Ssam 		break;
41130222Ssam 
41230286Ssam 	case PS_DMAIN:		/* dma data PS300->host */
41330286Ssam 		bc = bp->b_bcount;
41430286Ssam 		csr = IKCSR_CYCLE|IKCSR_FNC1;
41530286Ssam 		break;
41630222Ssam 
41730286Ssam 	default:
41830286Ssam 		log(LOG_ERR, "ik%d: bad cmd %x\n", unit, bp->b_command);
41930286Ssam 		sc->is_error = PSERROR_BADCMD;
42030286Ssam 		goto bad;
42130286Ssam 	}
42230286Ssam 	/* initiate dma transfer */
423*30294Ssam 	addr = vtoph((struct proc *)0, (unsigned)sc->is_buf);
42430286Ssam 	ik->ik_bahi = addr >> 17;
42530286Ssam 	ik->ik_balo = (addr >> 1) & 0xffff;
42630286Ssam 	ik->ik_wc = ((bc + 1) >> 1) - 1;	/* round & convert */
42730286Ssam 	ik->ik_pulse = IKPULSE_RATTF|IKPULSE_RDMAF;
42830286Ssam 	sc->is_timeout = iktimeout;
42930286Ssam 	ik->ik_csr = IKCSR_IENA|IKCSR_GO|csr;
43030286Ssam 	return;
43130222Ssam bad:
43230286Ssam 	bp->b_flags |= B_ERROR;
43330286Ssam 	dp->b_actf = bp->av_forw;		/* remove from queue */
43430286Ssam 	biodone(bp);
43530286Ssam 	goto loop;
43630222Ssam }
43730222Ssam 
43830222Ssam #define FETCHWORD(i) { \
43930286Ssam 	v = dioread(ik); \
44030286Ssam 	if (v == -1) { \
44130286Ssam 		sc->is_error = PSERROR_NAMETIMO; \
44230286Ssam 		goto bad; \
44330286Ssam 	} \
44430286Ssam 	sc->is_nameaddr.w[i] = v; \
44530222Ssam }
44630222Ssam 
44730222Ssam /*
44830222Ssam  * Process a device interrupt.
44930222Ssam  */
45030222Ssam ikintr(ikon)
45130286Ssam 	int ikon;
45230222Ssam {
45330286Ssam 	register struct ikdevice *ik;
45430286Ssam 	register struct buf *bp, *dp;
45530286Ssam 	struct ik_softc *sc;
45630286Ssam 	register u_short data;
457*30294Ssam 	int v;
45830222Ssam 
45930286Ssam 	/* should go by controller, but for now... */
46030286Ssam 	if (ikinfo[ikon] == 0)
46130286Ssam 		return;
46230286Ssam 	ik = (struct ikdevice *)ikinfo[ikon]->ui_addr;
46330286Ssam 	/*
46430286Ssam 	 * Discard all non-attention interrupts.  The
46530286Ssam 	 * interrupts we're throwing away should all be
46630286Ssam 	 * associated with DMA completion.
46730286Ssam 	 */
46830286Ssam 	data = ik->ik_data;
46930286Ssam 	if ((ik->ik_csr&(IKCSR_ATTF|IKCSR_STATC)) != IKCSR_ATTF) {
47030286Ssam 		ik->ik_pulse = IKPULSE_RATTF|IKPULSE_RDMAF|IKPULSE_SIENA;
47130286Ssam 		return;
47230286Ssam 	}
47330286Ssam 	/*
47430286Ssam 	 * Fetch attention code immediately.
47530286Ssam 	 */
47630286Ssam 	ik->ik_csr = IKCSR_RATTF|IKCSR_RDMAF|IKCSR_FNC1;
47730286Ssam 	ik->ik_pulse = IKPULSE_FNC2;
47830286Ssam 	/*
47930286Ssam 	 * Get device and block structures, and a pointer
48030286Ssam 	 * to the vba_device for the device.  We receive an
48130286Ssam 	 * unsolicited interrupt whenever the PS300 is power
48230286Ssam 	 * cycled (so ignore it in that case).
48330286Ssam 	 */
48430286Ssam 	dp = &iktab[ikon];
48530286Ssam 	if ((bp = dp->b_actf) == NULL) {
48630286Ssam 		if (PS_CODE(data) != PS_RESET)		/* power failure */
48730286Ssam 			log(LOG_WARNING, "ik%d: spurious interrupt, code %x\n",
48830286Ssam 			    ikon, data);
48930286Ssam 		goto enable;
49030286Ssam 	}
49130286Ssam 	sc = &ik_softc[IKUNIT(bp->b_dev)];
49230286Ssam 	sc->is_timeout = 0;			/* disable timer */
49330286Ssam 	switch (PS_CODE(data)) {
49430222Ssam 
49530286Ssam 	case PS_LOOKUP:				/* name lookup */
49630286Ssam 		if (data == PS_LOOKUP) {	/* dma name */
49730286Ssam 			bp->b_command = PS_DMAOUT;
49830286Ssam 			goto opcont;
49930286Ssam 		}
50030286Ssam 		if (data == PS_DMAOK(PS_LOOKUP)) {
50130286Ssam 			/* reenable interrupt and wait for address */
50230286Ssam 			sc->is_timeout = iktimeout;
50330286Ssam 			goto enable;
50430286Ssam 		}
50530286Ssam 		/*
50630286Ssam 		 * Address should be present, extract it one
50730286Ssam 		 * word at a time from the PS300 (yech).
50830286Ssam 		 */
50930286Ssam 		if (data != PS_ADROK(PS_LOOKUP))
51030286Ssam 			goto bad;
51130286Ssam 		FETCHWORD(0);
51230286Ssam 		FETCHWORD(1);
51330286Ssam 		goto opdone;
51430222Ssam 
51530286Ssam 	case PS_WRPHY_SYNC:			/* physical i/o write w/ sync */
51630286Ssam 		if (data == PS_WRPHY_SYNC) {	/* start dma transfer */
51730286Ssam 			bp->b_command = PS_DMAOUT;
51830286Ssam 			goto opcont;
51930286Ssam 		}
52030286Ssam 		if (data != PS_DMAOK(PS_WRPHY_SYNC))
52130286Ssam 			goto bad;
52230286Ssam 		goto opdone;
52330222Ssam 
52430286Ssam 	case PS_WRPHY:				/* physical i/o write */
52530286Ssam 		if (data == PS_WRPHY) { /* start dma transfer */
52630286Ssam 			bp->b_command = PS_DMAOUT;
52730286Ssam 			goto opcont;
52830286Ssam 		}
52930286Ssam 		if (data != PS_DMAOK(PS_WRPHY))
53030286Ssam 			goto bad;
53130286Ssam 		goto opdone;
53230222Ssam 
53330286Ssam 	case PS_ATTACH:				/* attach unit */
53430286Ssam 	case PS_DETACH:				/* detach unit */
53530286Ssam 	case PS_ABORT:				/* abort code from ps300 */
53630286Ssam 		if (data != bp->b_command)
53730286Ssam 			goto bad;
53830286Ssam 		goto opdone;
53930222Ssam 
54030286Ssam 	case PS_RDPHY:				/* physical i/o read */
54130286Ssam 		if (data == PS_RDPHY) {		/* dma address list */
54230286Ssam 			bp->b_command = PS_DMAOUT;
54330286Ssam 			goto opcont;
54430286Ssam 		}
54530286Ssam 		if (data == PS_ADROK(PS_RDPHY)) {
54630286Ssam 			/* collect read byte count and start dma */
54730286Ssam 			bp->b_bcount = dioread(ik);
54830286Ssam 			if (bp->b_bcount == -1)
54930286Ssam 				goto bad;
55030286Ssam 			bp->b_command = PS_DMAIN;
55130286Ssam 			goto opcont;
55230286Ssam 		}
55330286Ssam 		if (data == PS_DMAOK(PS_RDPHY))
55430286Ssam 			goto opdone;
55530286Ssam 		goto bad;
55630286Ssam 	}
55730222Ssam bad:
55830286Ssam 	sc->is_error = data;
55930286Ssam 	bp->b_flags |= B_ERROR;
56030222Ssam opdone:
56130286Ssam 	dp->b_actf = bp->av_forw;		/* remove from queue */
56230286Ssam 	biodone(bp);
56330222Ssam opcont:
56430286Ssam 	ikstart(dp);
56530222Ssam enable:
56630286Ssam 	ik->ik_pulse = IKPULSE_SIENA;		/* explicitly reenable */
56730222Ssam }
56830222Ssam 
56930222Ssam /*
57030222Ssam  * Watchdog timer.
57130222Ssam  */
57230222Ssam iktimer(unit)
57330286Ssam 	int unit;
57430222Ssam {
57530286Ssam 	register struct ik_softc *sc = &ik_softc[unit];
57630222Ssam 
57730286Ssam 	if (sc->is_timeout && --sc->is_timeout == 0) {
57830286Ssam 		register struct buf *dp, *bp;
57930286Ssam 		int s;
58030222Ssam 
58130286Ssam 		log(LOG_ERR, "ik%d: timeout\n", unit);
58230286Ssam 		s = splik();
58330286Ssam 		/* should abort current command */
58430286Ssam 		dp = &iktab[unit];
58530286Ssam 		if (bp = dp->b_actf) {
58630286Ssam 			sc->is_error = PSERROR_CMDTIMO;
58730286Ssam 			bp->b_flags |= B_ERROR;
58830286Ssam 			dp->b_actf = bp->av_forw;	/* remove from queue */
58930286Ssam 			biodone(bp);
59030286Ssam 			ikstart(dp);
59130286Ssam 		}
59230286Ssam 		splx(s);
59330286Ssam 	}
594*30294Ssam 	timeout(iktimer, (caddr_t)unit, hz);
59530222Ssam }
59630222Ssam 
59730222Ssam /*
59830222Ssam  * Handshake read from DR300.
59930222Ssam  */
60030222Ssam dioread(ik)
60130286Ssam 	register struct ikdevice *ik;
60230222Ssam {
603*30294Ssam 	register int t;
60430286Ssam 	u_short data;
60530222Ssam 
606*30294Ssam 	for (t = ikdiotimo; t > 0; t--)
60730286Ssam 		if ((ik->ik_csr&(IKCSR_ATTF|IKCSR_STATC)) == IKCSR_ATTF) {
60830286Ssam 			data = ik->ik_data;
60930286Ssam 			ik->ik_csr = IKCSR_RATTF|IKCSR_RDMAF|IKCSR_FNC1;
61030286Ssam 			ik->ik_pulse = IKPULSE_FNC2;
61130286Ssam 			return (data);
61230286Ssam 		}
61330286Ssam 	return (-1);
61430222Ssam }
61530222Ssam 
61630222Ssam /*
61730222Ssam  * Handshake write to DR300.
61830222Ssam  *
61930222Ssam  * Interrupts are enabled before completing the work
62030222Ssam  * so the caller should either be at splik or be
62130222Ssam  * prepared to take the interrupt immediately.
62230222Ssam  */
62330222Ssam diowrite(ik, v)
62430286Ssam 	register struct ikdevice *ik;
62530286Ssam 	u_short v;
62630222Ssam {
627*30294Ssam 	register int t;
62830286Ssam 	register u_short csr;
62930222Ssam 
63030222Ssam top:
63130286Ssam 	/*
63230286Ssam 	 * Deposit data and generate dr300 attention
63330286Ssam 	 */
63430286Ssam 	ik->ik_data = v;
63530286Ssam 	ik->ik_csr = IKCSR_RDMAF|IKCSR_RATTF;
63630286Ssam 	ik->ik_pulse = IKPULSE_FNC2;
637*30294Ssam 	for (t = ikdiotimo; t > 0; t--) {
63830286Ssam 		csr = ik->ik_csr;
63930286Ssam #define IKCSR_DONE	(IKCSR_STATA|IKCSR_STATC)
64030286Ssam 		if ((csr&IKCSR_DONE) == IKCSR_DONE) {
64130286Ssam 			/*
64230286Ssam 			 * Done, complete handshake by notifying dr300.
64330286Ssam 			 */
64430286Ssam 			ik->ik_csr = IKCSR_IENA;	/* ~IKCSR_FNC1 */
64530286Ssam 			ik->ik_pulse = IKPULSE_FNC2;
64630286Ssam 			return (0);
64730286Ssam 		}
64830286Ssam 		/* beware of potential deadlock with dioread */
64930286Ssam 		if ((csr&(IKCSR_ATTF|IKCSR_STATC)) == IKCSR_ATTF)
65030286Ssam 			goto top;
65130286Ssam 	}
65230286Ssam 	ik->ik_csr = IKCSR_IENA;
65330286Ssam 	return (PSERROR_DIOTIMO);
65430222Ssam }
65530222Ssam 
65630222Ssam /*ARGSUSED*/
65730222Ssam ikioctl(dev, cmd, data, flag)
65830286Ssam 	dev_t dev;
65930286Ssam 	int cmd;
66030286Ssam 	caddr_t data;
66130286Ssam 	int flag;
66230222Ssam {
66330286Ssam 	int error = 0, unit = IKUNIT(dev), s;
66430286Ssam 	register struct ik_softc *sc = &ik_softc[unit];
66530222Ssam 
66630286Ssam 	switch (cmd) {
66730222Ssam 
66830286Ssam 	case PSIOGETERROR:		/* get error code for last operation */
66930286Ssam 		*(int *)data = sc->is_error;
67030286Ssam 		break;
67130222Ssam 
67230286Ssam 	case PSIOLOOKUP: {		/* PS300 name lookup */
67330286Ssam 		register struct pslookup *lp = (struct pslookup *)data;
67430286Ssam 		register struct buf *bp;
67530222Ssam 
67630286Ssam 		if (lp->pl_len > PS_MAXNAMELEN)
67730286Ssam 			return (EINVAL);
67830286Ssam 		bp = &rikbuf[unit];
67930286Ssam 		s = splbio();
68030286Ssam 		while (bp->b_flags&B_BUSY) {
68130286Ssam 			bp->b_flags |= B_WANTED;
68230286Ssam 			sleep((caddr_t)bp, PRIBIO+1);
68330286Ssam 		}
68430286Ssam 		splx(s);
68530286Ssam 		bp->b_flags = B_BUSY | B_WRITE;
686*30294Ssam 		error = copyin(lp->pl_name, sc->is_buf, (unsigned)lp->pl_len);
68730286Ssam 		if (error == 0) {
68830286Ssam 			if (lp->pl_len&1)
68930286Ssam 				sc->is_buf[lp->pl_len] = '\0';
69030286Ssam 			error = ikcommand(dev, PS_LOOKUP, lp->pl_len);
69130286Ssam 		}
69230286Ssam 		s = splbio();
69330286Ssam 		if (bp->b_flags&B_WANTED)
69430286Ssam 			wakeup((caddr_t)bp);
69530286Ssam 		splx(s);
69630286Ssam 		bp->b_flags &= ~(B_BUSY|B_WANTED);
69730286Ssam 		lp->pl_addr = sc->is_nameaddr.l;
69830286Ssam 		break;
69930286Ssam 	}
70030286Ssam 	default:
70130286Ssam 		return (ENOTTY);
70230286Ssam 	}
70330286Ssam 	return (error);
70430222Ssam }
70530222Ssam #endif
706