xref: /csrg-svn/sys/tahoe/vba/ik.c (revision 30286)
1*30286Ssam /*	ik.c	1.3	86/12/11	*/
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 
31*30286Ssam int	ikprobe(), ikattach(), iktimer();
32*30286Ssam struct	vba_device *ikinfo[NIK];
33*30286Ssam long	ikstd[] = { 0 };
34*30286Ssam struct	vba_driver ikdriver = { ikprobe, 0, ikattach, 0, ikstd, "ik", ikinfo };
3530222Ssam 
36*30286Ssam #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  */
43*30286Ssam #define IKUNIT(dev)	(minor(dev) >> 1)
44*30286Ssam #define IKDIAG(dev)	(minor(dev) & 01)	/* is a diagnostic unit */
4530222Ssam 
46*30286Ssam struct	ik_softc {
47*30286Ssam 	uid_t	is_uid;		/* uid of open processes */
48*30286Ssam 	u_short is_timeout;	/* current timeout (seconds) */
49*30286Ssam 	u_short is_error;	/* internal error codes */
50*30286Ssam 	u_short is_flags;
51*30286Ssam #define IKF_ATTACHED	0x1	/* unit is attached (not used yet) */
52*30286Ssam 	union {
53*30286Ssam 		u_short w[2];
54*30286Ssam 		u_long	l;
55*30286Ssam 	} is_nameaddr;		/* address of last symbol lookup */
56*30286Ssam 	caddr_t is_buf;		/* i/o buffer XXX */
5730222Ssam } ik_softc[NIK];
5830222Ssam 
59*30286Ssam struct	buf iktab[NIK];		/* unit command queue headers */
60*30286Ssam struct	buf rikbuf[NIK];	/* buffers for read/write operations */
61*30286Ssam struct	buf cikbuf[NIK];	/* buffers for control operations */
6230222Ssam 
6330222Ssam /* buf overlay definitions */
64*30286Ssam #define b_command	b_resid
6530222Ssam 
66*30286Ssam int	ikdiotimo = PS_DIOTIMO; /* dio polling timeout */
67*30286Ssam int	iktimeout = PS_TIMEOUT; /* attention/dma timeout (in hz) */
6830222Ssam 
6930222Ssam ikprobe(reg, vi)
70*30286Ssam 	caddr_t reg;
7130222Ssam 	struct vba_device *vi;
7230222Ssam {
73*30286Ssam 	register int br, cvec;		/* r12, r11 */
7430222Ssam 	register struct ikdevice *ik;
7530222Ssam 
76*30286Ssam 	if (badaddr(reg, 2))
77*30286Ssam 		return (0);
7830222Ssam 	ik = (struct ikdevice *)reg;
7930222Ssam 	ik->ik_vec = --vi->ui_hd->vh_lastiv;
80*30286Ssam 	/*
81*30286Ssam 	 * Use extended non-privileged address modifier to
82*30286Ssam 	 * insure DMA to/from intermediate buffer works when
83*30286Ssam 	 * buffer is not in lower 16Mb of memory (also avoids
84*30286Ssam 	 * other 24-bit devices mapped into overlapping regions).
85*30286Ssam 	 */
86*30286Ssam 	ik->ik_mod = 0xf1;			/* address modifier */
87*30286Ssam 	/*
88*30286Ssam 	 * Try and reset the PS300.  Since this
89*30286Ssam 	 * won't work if it's powered off, we
90*30286Ssam 	 * can't use sucess/failure to decide
91*30286Ssam 	 * if the device is present.
92*30286Ssam 	 */
9330222Ssam 	br = 0;
94*30286Ssam 	(void) psreset(ik, IKCSR_IENA);
95*30286Ssam 	if (br == 0)				/* XXX */
9630222Ssam 		br = 0x18, cvec = ik->ik_vec;	/* XXX */
97*30286Ssam 	return (sizeof (struct ikdevice));
9830222Ssam }
9930222Ssam 
10030222Ssam /*
10130222Ssam  * Perform a ``hard'' reset.
10230222Ssam  */
10330222Ssam psreset(ik, iena)
104*30286Ssam 	register struct ikdevice *ik;
10530222Ssam {
10630222Ssam 
107*30286Ssam 	ik->ik_csr = IKCSR_MCLR|iena;
108*30286Ssam 	DELAY(10000);
109*30286Ssam 	ik->ik_csr = IKCSR_FNC3|iena;
110*30286Ssam 	if (!iena)
111*30286Ssam 		return (dioread(ik) == PS_RESET);
112*30286Ssam 	return (1);
11330222Ssam }
11430222Ssam 
11530222Ssam ikattach(vi)
116*30286Ssam 	struct vba_device *vi;
11730222Ssam {
11830222Ssam 
119*30286Ssam 	ik_softc[vi->ui_unit].is_uid = -1;
12030222Ssam }
12130222Ssam 
12230222Ssam /*
12330222Ssam  * Open a PS300 and attach.  We allow multiple
12430222Ssam  * processes with the same uid to share a unit.
12530222Ssam  */
12630222Ssam /*ARGSUSED*/
12730222Ssam ikopen(dev, flag)
128*30286Ssam 	dev_t dev;
129*30286Ssam 	int flag;
13030222Ssam {
131*30286Ssam 	register int unit = IKUNIT(dev);
132*30286Ssam 	register struct ik_softc *sc;
133*30286Ssam 	struct vba_device *vi;
134*30286Ssam 	struct ikdevice *ik;
135*30286Ssam 	int reset;
13630222Ssam 
137*30286Ssam 	if (unit >= NIK || (vi = ikinfo[unit]) == 0 || vi->ui_alive == 0)
138*30286Ssam 		return (ENXIO);
139*30286Ssam 	sc = &ik_softc[unit];
140*30286Ssam 	if (sc->is_uid != -1 && sc->is_uid != u.u_uid)
141*30286Ssam 		return (EBUSY);
142*30286Ssam 	if (sc->is_uid == -1) {
14330222Ssam 		sc->is_buf = (caddr_t)wmemall(vmemall, PS_MAXDMA);
14430222Ssam 		if (sc->is_buf == 0)
14530222Ssam 			return (ENOMEM);
146*30286Ssam 		sc->is_timeout = 0;
147*30286Ssam 		timeout(iktimer, unit, hz);
148*30286Ssam 		/*
149*30286Ssam 		 * Perform PS300 attach for first process.
150*30286Ssam 		 */
151*30286Ssam 		if (!IKDIAG(dev)) {
152*30286Ssam 			reset = 0;
153*30286Ssam 		again:
154*30286Ssam 			if (ikcommand(dev, PS_ATTACH, 1)) {
155*30286Ssam 				/*
156*30286Ssam 				 * If attach fails, perform a hard
157*30286Ssam 				 * reset once, then retry the command.
158*30286Ssam 				 */
159*30286Ssam 				ik = (struct ikdevice *)ikinfo[unit]->ui_addr;
160*30286Ssam 				if (!reset++ && psreset(ik, 0))
161*30286Ssam 					goto again;
162*30286Ssam 				untimeout(iktimer, unit);
16330222Ssam 				wmemfree(sc->is_buf, PS_MAXDMA);
16430222Ssam 				sc->is_buf = 0;
165*30286Ssam 				return (EIO);
166*30286Ssam 			}
167*30286Ssam 		}
168*30286Ssam 		sc->is_uid = u.u_uid;
169*30286Ssam 	}
170*30286Ssam 	return (0);
17130222Ssam }
17230222Ssam 
17330222Ssam /*ARGSUSED*/
17430222Ssam ikclose(dev, flag)
175*30286Ssam 	dev_t dev;
176*30286Ssam 	int flag;
17730222Ssam {
178*30286Ssam 	int unit = IKUNIT(dev);
17930222Ssam 	register struct ik_softc *sc = &ik_softc[unit];
18030222Ssam 
181*30286Ssam 	if (!IKDIAG(dev))
182*30286Ssam 		(void) ikcommand(dev, PS_DETACH, 1);	/* auto detach */
183*30286Ssam 	sc->is_uid = -1;
18430222Ssam 	if (sc->is_buf) {
18530222Ssam 		wmemfree(sc->is_buf, PS_MAXDMA);
18630222Ssam 		sc->is_buf = 0;
18730222Ssam 	}
188*30286Ssam 	untimeout(iktimer, unit);
18930222Ssam }
19030222Ssam 
19130222Ssam ikread(dev, uio)
192*30286Ssam 	dev_t dev;
193*30286Ssam 	struct uio *uio;
19430222Ssam {
19530222Ssam 
196*30286Ssam 	return (ikrw(dev, uio, B_READ));
19730222Ssam }
19830222Ssam 
19930222Ssam ikwrite(dev, uio)
200*30286Ssam 	dev_t dev;
201*30286Ssam 	struct uio *uio;
20230222Ssam {
20330222Ssam 
204*30286Ssam 	return (ikrw(dev, uio, B_WRITE));
20530222Ssam }
20630222Ssam 
20730222Ssam /*
20830222Ssam  * Take read/write request and perform physical i/o
20930222Ssam  * transaction with PS300.  This involves constructing
21030222Ssam  * a physical i/o request vector based on the uio
21130222Ssam  * vector, performing the dma, and, finally, moving
21230222Ssam  * the data to it's final destination (because of CCI
21330222Ssam  * VERSAbus bogosities).
21430222Ssam  */
21530222Ssam ikrw(dev, uio, rw)
216*30286Ssam 	dev_t dev;
217*30286Ssam 	register struct uio *uio;
218*30286Ssam 	int rw;
21930222Ssam {
220*30286Ssam 	int error, unit = IKUNIT(dev), s, wrcmd;
221*30286Ssam 	register struct buf *bp;
222*30286Ssam 	register struct iovec *iov;
223*30286Ssam 	register struct psalist *ap;
224*30286Ssam 	struct ik_softc *sc = &ik_softc[unit];
22530222Ssam 
226*30286Ssam 	if (unit >= NIK)
227*30286Ssam 		return (ENXIO);
228*30286Ssam 	bp = &rikbuf[unit];
229*30286Ssam 	error = 0, iov = uio->uio_iov, wrcmd = PS_WRPHY;
230*30286Ssam 	for (; !error && uio->uio_iovcnt; iov++, uio->uio_iovcnt--) {
231*30286Ssam 		/*
232*30286Ssam 		 * Hack way to set PS300 address w/o doing an lseek
233*30286Ssam 		 * and specify write physical w/ refresh synchronization.
234*30286Ssam 		 */
235*30286Ssam 		if (iov->iov_len == 0) {
236*30286Ssam 			if ((int)iov->iov_base&PSIO_SYNC)
237*30286Ssam 				wrcmd = PS_WRPHY_SYNC;
238*30286Ssam 			uio->uio_offset = (int)iov->iov_base & ~PSIO_SYNC;
239*30286Ssam 			continue;
240*30286Ssam 		}
241*30286Ssam 		if (iov->iov_len > PS_MAXDMA) {
242*30286Ssam 			sc->is_error = PSERROR_INVALBC, error = EINVAL;
243*30286Ssam 			continue;
244*30286Ssam 		}
245*30286Ssam 		if ((int)uio->uio_offset&01) {
246*30286Ssam 			sc->is_error = PSERROR_BADADDR, error = EINVAL;
247*30286Ssam 			continue;
248*30286Ssam 		}
249*30286Ssam 		s = splbio();
250*30286Ssam 		while (bp->b_flags&B_BUSY) {
251*30286Ssam 			bp->b_flags |= B_WANTED;
252*30286Ssam 			sleep((caddr_t)bp, PRIBIO+1);
253*30286Ssam 		}
254*30286Ssam 		splx(s);
255*30286Ssam 		bp->b_flags = B_BUSY | rw;
256*30286Ssam 		/*
257*30286Ssam 		 * Construct address descriptor in buffer.
258*30286Ssam 		 */
259*30286Ssam 		ap = (struct psalist *)sc->is_buf;
260*30286Ssam 		ap->nblocks = 1;
261*30286Ssam 		/* work-around dr300 word swapping */
262*30286Ssam 		ap->addr[0] = uio->uio_offset & 0xffff;
263*30286Ssam 		ap->addr[1] = uio->uio_offset >> 16;
264*30286Ssam 		ap->wc = (iov->iov_len + 1) >> 1;
265*30286Ssam 		if (rw == B_WRITE) {
266*30286Ssam 			error = copyin(iov->iov_base, (caddr_t)&ap[1],
267*30286Ssam 			    iov->iov_len);
268*30286Ssam 			if (!error)
269*30286Ssam 				error = ikcommand(dev, wrcmd,
270*30286Ssam 				    iov->iov_len + sizeof (*ap));
271*30286Ssam 		} else {
272*30286Ssam 			caddr_t cp;
273*30286Ssam 			int len;
27430222Ssam 
275*30286Ssam 			error = ikcommand(dev, PS_RDPHY, sizeof (*ap));
276*30286Ssam 			cp = (caddr_t)&ap[1], len = iov->iov_len;
277*30286Ssam 			for (; len > 0; len -= NBPG, cp += NBPG)
278*30286Ssam 				mtpr(P1DC, cp);
279*30286Ssam 			if (!error)
280*30286Ssam 				error = copyout((caddr_t)&ap[1], iov->iov_base,
281*30286Ssam 				    iov->iov_len);
282*30286Ssam 		}
283*30286Ssam 		(void) splbio();
284*30286Ssam 		if (bp->b_flags&B_WANTED)
285*30286Ssam 			wakeup((caddr_t)bp);
286*30286Ssam 		splx(s);
287*30286Ssam 		uio->uio_resid -= iov->iov_len;
288*30286Ssam 		uio->uio_offset += iov->iov_len;
289*30286Ssam 		bp->b_flags &= ~(B_BUSY|B_WANTED);
290*30286Ssam 	}
291*30286Ssam 	return (error);
29230222Ssam }
29330222Ssam 
29430222Ssam /*
29530222Ssam  * Perform a PS300 command.
29630222Ssam  */
29730222Ssam ikcommand(dev, com, count)
298*30286Ssam 	dev_t dev;
299*30286Ssam 	int com, count;
30030222Ssam {
301*30286Ssam 	register struct buf *bp;
302*30286Ssam 	register int s;
30330222Ssam 
304*30286Ssam 	bp = &cikbuf[IKUNIT(dev)];
305*30286Ssam 	s = splik();
306*30286Ssam 	while (bp->b_flags&B_BUSY) {
307*30286Ssam 		if (bp->b_flags&B_DONE)
308*30286Ssam 			break;
309*30286Ssam 		bp->b_flags |= B_WANTED;
310*30286Ssam 		sleep((caddr_t)bp, PRIBIO);
311*30286Ssam 	}
312*30286Ssam 	bp->b_flags = B_BUSY|B_READ;
313*30286Ssam 	splx(s);
314*30286Ssam 	bp->b_dev = dev;
315*30286Ssam 	bp->b_command = com;
316*30286Ssam 	bp->b_bcount = count;
317*30286Ssam 	ikstrategy(bp);
318*30286Ssam 	biowait(bp);
319*30286Ssam 	if (bp->b_flags&B_WANTED)
320*30286Ssam 		wakeup((caddr_t)bp);
321*30286Ssam 	bp->b_flags &= B_ERROR;
322*30286Ssam 	return (geterror(bp));
32330222Ssam }
32430222Ssam 
32530222Ssam /*
32630222Ssam  * Physio strategy routine
32730222Ssam  */
32830222Ssam ikstrategy(bp)
329*30286Ssam 	register struct buf *bp;
33030222Ssam {
331*30286Ssam 	register struct buf *dp;
33230222Ssam 
333*30286Ssam 	/*
334*30286Ssam 	 * Put request at end of controller queue.
335*30286Ssam 	 */
336*30286Ssam 	dp = &iktab[IKUNIT(bp->b_dev)];
337*30286Ssam 	bp->av_forw = NULL;
338*30286Ssam 	(void) splik();
339*30286Ssam 	if (dp->b_actf != NULL) {
340*30286Ssam 		dp->b_actl->av_forw = bp;
341*30286Ssam 		dp->b_actl = bp;
342*30286Ssam 	} else
343*30286Ssam 		dp->b_actf = dp->b_actl = bp;
344*30286Ssam 	if (!dp->b_active)
345*30286Ssam 		ikstart(dp);
346*30286Ssam 	(void) spl0();
34730222Ssam }
34830222Ssam 
34930222Ssam /*
35030222Ssam  * Start the next command on the controller's queue.
35130222Ssam  */
35230222Ssam ikstart(dp)
353*30286Ssam 	register struct buf *dp;
35430222Ssam {
355*30286Ssam 	register struct buf *bp;
356*30286Ssam 	register struct ikdevice *ik;
357*30286Ssam 	register struct ik_softc *sc;
358*30286Ssam 	register struct psalist *ap;
359*30286Ssam 	u_short bc, csr;
360*30286Ssam 	u_int addr;
361*30286Ssam 	int unit;
36230222Ssam 
36330222Ssam loop:
364*30286Ssam 	/*
365*30286Ssam 	 * Pull a request off the controller queue
366*30286Ssam 	 */
367*30286Ssam 	if ((bp = dp->b_actf) == NULL) {
368*30286Ssam 		dp->b_active = 0;
369*30286Ssam 		return;
370*30286Ssam 	}
371*30286Ssam 	/*
372*30286Ssam 	 * Mark controller busy and process this request.
373*30286Ssam 	 */
374*30286Ssam 	dp->b_active = 1;
375*30286Ssam 	unit = IKUNIT(bp->b_dev);
376*30286Ssam 	sc = &ik_softc[unit];
377*30286Ssam 	ik = (struct ikdevice *)ikinfo[unit]->ui_addr;
378*30286Ssam 	switch (bp->b_command) {
37930222Ssam 
380*30286Ssam 	case PS_ATTACH:		/* logical unit attach */
381*30286Ssam 	case PS_DETACH:		/* logical unit detach */
382*30286Ssam 	case PS_LOOKUP:		/* name lookup */
383*30286Ssam 	case PS_RDPHY:		/* physical i/o read */
384*30286Ssam 	case PS_WRPHY:		/* physical i/o write */
385*30286Ssam 	case PS_WRPHY_SYNC:	/* physical i/o write w/ sync */
386*30286Ssam 		/*
387*30286Ssam 		 * Handshake command and, optionally,
388*30286Ssam 		 * byte count and byte swap flag.
389*30286Ssam 		 */
390*30286Ssam 		if (sc->is_error = diowrite(ik, bp->b_command))
391*30286Ssam 			goto bad;
392*30286Ssam 		if (bp->b_command < PS_DETACH) {
393*30286Ssam 			if (sc->is_error = diowrite(ik, bp->b_bcount))
394*30286Ssam 				goto bad;
395*30286Ssam 			if (sc->is_error = diowrite(ik, 0 /* !swab */))
396*30286Ssam 				goto bad;
397*30286Ssam 		}
398*30286Ssam 		/*
399*30286Ssam 		 * Set timeout and wait for an attention interrupt.
400*30286Ssam 		 */
401*30286Ssam 		sc->is_timeout = iktimeout;
402*30286Ssam 		return;
40330222Ssam 
404*30286Ssam 	case PS_DMAOUT:		/* dma data host->PS300 */
405*30286Ssam 		bc = bp->b_bcount;
406*30286Ssam 		csr = IKCSR_CYCLE;
407*30286Ssam 		break;
40830222Ssam 
409*30286Ssam 	case PS_DMAIN:		/* dma data PS300->host */
410*30286Ssam 		bc = bp->b_bcount;
411*30286Ssam 		csr = IKCSR_CYCLE|IKCSR_FNC1;
412*30286Ssam 		break;
41330222Ssam 
414*30286Ssam 	default:
415*30286Ssam 		log(LOG_ERR, "ik%d: bad cmd %x\n", unit, bp->b_command);
416*30286Ssam 		sc->is_error = PSERROR_BADCMD;
417*30286Ssam 		goto bad;
418*30286Ssam 	}
419*30286Ssam 	/* initiate dma transfer */
420*30286Ssam 	addr = vtoph((struct proc *)0, sc->is_buf);
421*30286Ssam 	ik->ik_bahi = addr >> 17;
422*30286Ssam 	ik->ik_balo = (addr >> 1) & 0xffff;
423*30286Ssam 	ik->ik_wc = ((bc + 1) >> 1) - 1;	/* round & convert */
424*30286Ssam 	ik->ik_pulse = IKPULSE_RATTF|IKPULSE_RDMAF;
425*30286Ssam 	sc->is_timeout = iktimeout;
426*30286Ssam 	ik->ik_csr = IKCSR_IENA|IKCSR_GO|csr;
427*30286Ssam 	return;
42830222Ssam bad:
429*30286Ssam 	bp->b_flags |= B_ERROR;
430*30286Ssam 	dp->b_actf = bp->av_forw;		/* remove from queue */
431*30286Ssam 	biodone(bp);
432*30286Ssam 	goto loop;
43330222Ssam }
43430222Ssam 
43530222Ssam #define FETCHWORD(i) { \
436*30286Ssam 	int v; \
43730222Ssam \
438*30286Ssam 	v = dioread(ik); \
439*30286Ssam 	if (v == -1) { \
440*30286Ssam 		sc->is_error = PSERROR_NAMETIMO; \
441*30286Ssam 		goto bad; \
442*30286Ssam 	} \
443*30286Ssam 	sc->is_nameaddr.w[i] = v; \
44430222Ssam }
44530222Ssam 
44630222Ssam /*
44730222Ssam  * Process a device interrupt.
44830222Ssam  */
44930222Ssam ikintr(ikon)
450*30286Ssam 	int ikon;
45130222Ssam {
452*30286Ssam 	register struct ikdevice *ik;
453*30286Ssam 	register struct buf *bp, *dp;
454*30286Ssam 	struct ik_softc *sc;
455*30286Ssam 	register u_short data;
456*30286Ssam 	u_short i, v;
45730222Ssam 
458*30286Ssam 	/* should go by controller, but for now... */
459*30286Ssam 	if (ikinfo[ikon] == 0)
460*30286Ssam 		return;
461*30286Ssam 	ik = (struct ikdevice *)ikinfo[ikon]->ui_addr;
462*30286Ssam 	/*
463*30286Ssam 	 * Discard all non-attention interrupts.  The
464*30286Ssam 	 * interrupts we're throwing away should all be
465*30286Ssam 	 * associated with DMA completion.
466*30286Ssam 	 */
467*30286Ssam 	data = ik->ik_data;
468*30286Ssam 	if ((ik->ik_csr&(IKCSR_ATTF|IKCSR_STATC)) != IKCSR_ATTF) {
469*30286Ssam 		ik->ik_pulse = IKPULSE_RATTF|IKPULSE_RDMAF|IKPULSE_SIENA;
470*30286Ssam 		return;
471*30286Ssam 	}
472*30286Ssam 	/*
473*30286Ssam 	 * Fetch attention code immediately.
474*30286Ssam 	 */
475*30286Ssam 	ik->ik_csr = IKCSR_RATTF|IKCSR_RDMAF|IKCSR_FNC1;
476*30286Ssam 	ik->ik_pulse = IKPULSE_FNC2;
477*30286Ssam 	/*
478*30286Ssam 	 * Get device and block structures, and a pointer
479*30286Ssam 	 * to the vba_device for the device.  We receive an
480*30286Ssam 	 * unsolicited interrupt whenever the PS300 is power
481*30286Ssam 	 * cycled (so ignore it in that case).
482*30286Ssam 	 */
483*30286Ssam 	dp = &iktab[ikon];
484*30286Ssam 	if ((bp = dp->b_actf) == NULL) {
485*30286Ssam 		if (PS_CODE(data) != PS_RESET)		/* power failure */
486*30286Ssam 			log(LOG_WARNING, "ik%d: spurious interrupt, code %x\n",
487*30286Ssam 			    ikon, data);
488*30286Ssam 		goto enable;
489*30286Ssam 	}
490*30286Ssam 	sc = &ik_softc[IKUNIT(bp->b_dev)];
491*30286Ssam 	sc->is_timeout = 0;			/* disable timer */
492*30286Ssam 	switch (PS_CODE(data)) {
49330222Ssam 
494*30286Ssam 	case PS_LOOKUP:				/* name lookup */
495*30286Ssam 		if (data == PS_LOOKUP) {	/* dma name */
496*30286Ssam 			bp->b_command = PS_DMAOUT;
497*30286Ssam 			goto opcont;
498*30286Ssam 		}
499*30286Ssam 		if (data == PS_DMAOK(PS_LOOKUP)) {
500*30286Ssam 			/* reenable interrupt and wait for address */
501*30286Ssam 			sc->is_timeout = iktimeout;
502*30286Ssam 			goto enable;
503*30286Ssam 		}
504*30286Ssam 		/*
505*30286Ssam 		 * Address should be present, extract it one
506*30286Ssam 		 * word at a time from the PS300 (yech).
507*30286Ssam 		 */
508*30286Ssam 		if (data != PS_ADROK(PS_LOOKUP))
509*30286Ssam 			goto bad;
510*30286Ssam 		FETCHWORD(0);
511*30286Ssam 		FETCHWORD(1);
512*30286Ssam 		goto opdone;
51330222Ssam 
514*30286Ssam 	case PS_WRPHY_SYNC:			/* physical i/o write w/ sync */
515*30286Ssam 		if (data == PS_WRPHY_SYNC) {	/* start dma transfer */
516*30286Ssam 			bp->b_command = PS_DMAOUT;
517*30286Ssam 			goto opcont;
518*30286Ssam 		}
519*30286Ssam 		if (data != PS_DMAOK(PS_WRPHY_SYNC))
520*30286Ssam 			goto bad;
521*30286Ssam 		goto opdone;
52230222Ssam 
523*30286Ssam 	case PS_WRPHY:				/* physical i/o write */
524*30286Ssam 		if (data == PS_WRPHY) { /* start dma transfer */
525*30286Ssam 			bp->b_command = PS_DMAOUT;
526*30286Ssam 			goto opcont;
527*30286Ssam 		}
528*30286Ssam 		if (data != PS_DMAOK(PS_WRPHY))
529*30286Ssam 			goto bad;
530*30286Ssam 		goto opdone;
53130222Ssam 
532*30286Ssam 	case PS_ATTACH:				/* attach unit */
533*30286Ssam 	case PS_DETACH:				/* detach unit */
534*30286Ssam 	case PS_ABORT:				/* abort code from ps300 */
535*30286Ssam 		if (data != bp->b_command)
536*30286Ssam 			goto bad;
537*30286Ssam 		goto opdone;
53830222Ssam 
539*30286Ssam 	case PS_RDPHY:				/* physical i/o read */
540*30286Ssam 		if (data == PS_RDPHY) {		/* dma address list */
541*30286Ssam 			bp->b_command = PS_DMAOUT;
542*30286Ssam 			goto opcont;
543*30286Ssam 		}
544*30286Ssam 		if (data == PS_ADROK(PS_RDPHY)) {
545*30286Ssam 			/* collect read byte count and start dma */
546*30286Ssam 			bp->b_bcount = dioread(ik);
547*30286Ssam 			if (bp->b_bcount == -1)
548*30286Ssam 				goto bad;
549*30286Ssam 			bp->b_command = PS_DMAIN;
550*30286Ssam 			goto opcont;
551*30286Ssam 		}
552*30286Ssam 		if (data == PS_DMAOK(PS_RDPHY))
553*30286Ssam 			goto opdone;
554*30286Ssam 		goto bad;
555*30286Ssam 	}
55630222Ssam bad:
557*30286Ssam 	sc->is_error = data;
558*30286Ssam 	bp->b_flags |= B_ERROR;
55930222Ssam opdone:
560*30286Ssam 	dp->b_actf = bp->av_forw;		/* remove from queue */
561*30286Ssam 	biodone(bp);
56230222Ssam opcont:
563*30286Ssam 	ikstart(dp);
56430222Ssam enable:
565*30286Ssam 	ik->ik_pulse = IKPULSE_SIENA;		/* explicitly reenable */
56630222Ssam }
56730222Ssam 
56830222Ssam /*
56930222Ssam  * Watchdog timer.
57030222Ssam  */
57130222Ssam iktimer(unit)
572*30286Ssam 	int unit;
57330222Ssam {
574*30286Ssam 	register struct ik_softc *sc = &ik_softc[unit];
57530222Ssam 
576*30286Ssam 	if (sc->is_timeout && --sc->is_timeout == 0) {
577*30286Ssam 		register struct buf *dp, *bp;
578*30286Ssam 		int s;
57930222Ssam 
580*30286Ssam 		log(LOG_ERR, "ik%d: timeout\n", unit);
581*30286Ssam 		s = splik();
582*30286Ssam 		/* should abort current command */
583*30286Ssam 		dp = &iktab[unit];
584*30286Ssam 		if (bp = dp->b_actf) {
585*30286Ssam 			sc->is_error = PSERROR_CMDTIMO;
586*30286Ssam 			bp->b_flags |= B_ERROR;
587*30286Ssam 			dp->b_actf = bp->av_forw;	/* remove from queue */
588*30286Ssam 			biodone(bp);
589*30286Ssam 			ikstart(dp);
590*30286Ssam 		}
591*30286Ssam 		splx(s);
592*30286Ssam 	}
593*30286Ssam 	timeout(iktimer, unit, hz);
59430222Ssam }
59530222Ssam 
59630222Ssam /*
59730222Ssam  * Handshake read from DR300.
59830222Ssam  */
59930222Ssam dioread(ik)
600*30286Ssam 	register struct ikdevice *ik;
60130222Ssam {
602*30286Ssam 	register int timeout;
603*30286Ssam 	u_short data;
60430222Ssam 
605*30286Ssam 	for (timeout = ikdiotimo; timeout > 0; timeout--)
606*30286Ssam 		if ((ik->ik_csr&(IKCSR_ATTF|IKCSR_STATC)) == IKCSR_ATTF) {
607*30286Ssam 			data = ik->ik_data;
608*30286Ssam 			ik->ik_csr = IKCSR_RATTF|IKCSR_RDMAF|IKCSR_FNC1;
609*30286Ssam 			ik->ik_pulse = IKPULSE_FNC2;
610*30286Ssam 			return (data);
611*30286Ssam 		}
612*30286Ssam 	return (-1);
61330222Ssam }
61430222Ssam 
61530222Ssam /*
61630222Ssam  * Handshake write to DR300.
61730222Ssam  *
61830222Ssam  * Interrupts are enabled before completing the work
61930222Ssam  * so the caller should either be at splik or be
62030222Ssam  * prepared to take the interrupt immediately.
62130222Ssam  */
62230222Ssam diowrite(ik, v)
623*30286Ssam 	register struct ikdevice *ik;
624*30286Ssam 	u_short v;
62530222Ssam {
626*30286Ssam 	register int timeout;
627*30286Ssam 	register u_short csr;
62830222Ssam 
62930222Ssam top:
630*30286Ssam 	/*
631*30286Ssam 	 * Deposit data and generate dr300 attention
632*30286Ssam 	 */
633*30286Ssam 	ik->ik_data = v;
634*30286Ssam 	ik->ik_csr = IKCSR_RDMAF|IKCSR_RATTF;
635*30286Ssam 	ik->ik_pulse = IKPULSE_FNC2;
636*30286Ssam 	for (timeout = ikdiotimo; timeout > 0; timeout--) {
637*30286Ssam 		csr = ik->ik_csr;
638*30286Ssam #define IKCSR_DONE	(IKCSR_STATA|IKCSR_STATC)
639*30286Ssam 		if ((csr&IKCSR_DONE) == IKCSR_DONE) {
640*30286Ssam 			/*
641*30286Ssam 			 * Done, complete handshake by notifying dr300.
642*30286Ssam 			 */
643*30286Ssam 			ik->ik_csr = IKCSR_IENA;	/* ~IKCSR_FNC1 */
644*30286Ssam 			ik->ik_pulse = IKPULSE_FNC2;
645*30286Ssam 			return (0);
646*30286Ssam 		}
647*30286Ssam 		/* beware of potential deadlock with dioread */
648*30286Ssam 		if ((csr&(IKCSR_ATTF|IKCSR_STATC)) == IKCSR_ATTF)
649*30286Ssam 			goto top;
650*30286Ssam 	}
651*30286Ssam 	ik->ik_csr = IKCSR_IENA;
652*30286Ssam 	return (PSERROR_DIOTIMO);
65330222Ssam }
65430222Ssam 
65530222Ssam /*ARGSUSED*/
65630222Ssam ikioctl(dev, cmd, data, flag)
657*30286Ssam 	dev_t dev;
658*30286Ssam 	int cmd;
659*30286Ssam 	caddr_t data;
660*30286Ssam 	int flag;
66130222Ssam {
662*30286Ssam 	int error = 0, unit = IKUNIT(dev), s;
663*30286Ssam 	register struct ik_softc *sc = &ik_softc[unit];
66430222Ssam 
665*30286Ssam 	switch (cmd) {
66630222Ssam 
667*30286Ssam 	case PSIOGETERROR:		/* get error code for last operation */
668*30286Ssam 		*(int *)data = sc->is_error;
669*30286Ssam 		break;
67030222Ssam 
671*30286Ssam 	case PSIOLOOKUP: {		/* PS300 name lookup */
672*30286Ssam 		register struct pslookup *lp = (struct pslookup *)data;
673*30286Ssam 		register struct buf *bp;
67430222Ssam 
675*30286Ssam 		if (lp->pl_len > PS_MAXNAMELEN)
676*30286Ssam 			return (EINVAL);
677*30286Ssam 		bp = &rikbuf[unit];
678*30286Ssam 		s = splbio();
679*30286Ssam 		while (bp->b_flags&B_BUSY) {
680*30286Ssam 			bp->b_flags |= B_WANTED;
681*30286Ssam 			sleep((caddr_t)bp, PRIBIO+1);
682*30286Ssam 		}
683*30286Ssam 		splx(s);
684*30286Ssam 		bp->b_flags = B_BUSY | B_WRITE;
685*30286Ssam 		error = copyin(lp->pl_name, sc->is_buf, lp->pl_len);
686*30286Ssam 		if (error == 0) {
687*30286Ssam 			if (lp->pl_len&1)
688*30286Ssam 				sc->is_buf[lp->pl_len] = '\0';
689*30286Ssam 			error = ikcommand(dev, PS_LOOKUP, lp->pl_len);
690*30286Ssam 		}
691*30286Ssam 		s = splbio();
692*30286Ssam 		if (bp->b_flags&B_WANTED)
693*30286Ssam 			wakeup((caddr_t)bp);
694*30286Ssam 		splx(s);
695*30286Ssam 		bp->b_flags &= ~(B_BUSY|B_WANTED);
696*30286Ssam 		lp->pl_addr = sc->is_nameaddr.l;
697*30286Ssam 		break;
698*30286Ssam 	}
699*30286Ssam 	default:
700*30286Ssam 		return (ENOTTY);
701*30286Ssam 	}
702*30286Ssam 	return (error);
70330222Ssam }
70430222Ssam #endif
705