xref: /csrg-svn/sys/tahoe/vba/ik.c (revision 30294)
1 /*	ik.c	1.4	86/12/15	*/
2 
3 #include "ik.h"
4 #if NIK > 0
5 /*
6  * PS300/IKON DR-11W Device Driver.
7  */
8 #include "param.h"
9 #include "buf.h"
10 #include "cmap.h"
11 #include "conf.h"
12 #include "dir.h"
13 #include "dkstat.h"
14 #include "map.h"
15 #include "systm.h"
16 #include "user.h"
17 #include "vmmac.h"
18 #include "proc.h"
19 #include "uio.h"
20 #include "kernel.h"
21 #include "syslog.h"
22 
23 #include "../tahoe/mtpr.h"
24 #include "../tahoe/pte.h"
25 
26 #include "../tahoevba/vbavar.h"
27 #include "../tahoevba/ikreg.h"
28 #include "../tahoevba/psreg.h"
29 #include "../tahoevba/psproto.h"
30 
31 int	ikprobe(), ikattach(), iktimer();
32 struct	vba_device *ikinfo[NIK];
33 long	ikstd[] = { 0 };
34 struct	vba_driver ikdriver = { ikprobe, 0, ikattach, 0, ikstd, "ik", ikinfo };
35 
36 #define splik()		spl4()
37 /*
38  * Devices are organized in pairs with the odd valued
39  * device being used for ``diagnostic'' purposes.  That
40  * is diagnostic devices don't get auto-attach'd and
41  * detach'd on open-close.
42  */
43 #define IKUNIT(dev)	(minor(dev) >> 1)
44 #define IKDIAG(dev)	(minor(dev) & 01)	/* is a diagnostic unit */
45 
46 struct	ik_softc {
47 	uid_t	is_uid;		/* uid of open processes */
48 	u_short is_timeout;	/* current timeout (seconds) */
49 	u_short is_error;	/* internal error codes */
50 	u_short is_flags;
51 #define IKF_ATTACHED	0x1	/* unit is attached (not used yet) */
52 	union {
53 		u_short w[2];
54 		u_long	l;
55 	} is_nameaddr;		/* address of last symbol lookup */
56 	caddr_t is_buf;		/* i/o buffer XXX */
57 } ik_softc[NIK];
58 
59 struct	buf iktab[NIK];		/* unit command queue headers */
60 struct	buf rikbuf[NIK];	/* buffers for read/write operations */
61 struct	buf cikbuf[NIK];	/* buffers for control operations */
62 
63 /* buf overlay definitions */
64 #define b_command	b_resid
65 
66 int	ikdiotimo = PS_DIOTIMO; /* dio polling timeout */
67 int	iktimeout = PS_TIMEOUT; /* attention/dma timeout (in hz) */
68 
69 ikprobe(reg, vi)
70 	caddr_t reg;
71 	struct vba_device *vi;
72 {
73 	register int br, cvec;		/* r12, r11 */
74 	register struct ikdevice *ik;
75 
76 #ifdef lint
77 	br = 0; cvec = br; br = cvec;
78 	ikintr(0);
79 #endif
80 	if (badaddr(reg, 2))
81 		return (0);
82 	ik = (struct ikdevice *)reg;
83 	ik->ik_vec = --vi->ui_hd->vh_lastiv;
84 	/*
85 	 * Use extended non-privileged address modifier to
86 	 * insure DMA to/from intermediate buffer works when
87 	 * buffer is not in lower 16Mb of memory (also avoids
88 	 * other 24-bit devices mapped into overlapping regions).
89 	 */
90 	ik->ik_mod = 0xf1;			/* address modifier */
91 	/*
92 	 * Try and reset the PS300.  Since this
93 	 * won't work if it's powered off, we
94 	 * can't use sucess/failure to decide
95 	 * if the device is present.
96 	 */
97 	br = 0;
98 	(void) psreset(ik, IKCSR_IENA);
99 	if (br == 0)				/* XXX */
100 		br = 0x18, cvec = ik->ik_vec;	/* XXX */
101 	return (sizeof (struct ikdevice));
102 }
103 
104 /*
105  * Perform a ``hard'' reset.
106  */
107 psreset(ik, iena)
108 	register struct ikdevice *ik;
109 {
110 
111 	ik->ik_csr = IKCSR_MCLR|iena;
112 	DELAY(10000);
113 	ik->ik_csr = IKCSR_FNC3|iena;
114 	if (!iena)
115 		return (dioread(ik) == PS_RESET);
116 	return (1);
117 }
118 
119 ikattach(vi)
120 	struct vba_device *vi;
121 {
122 
123 	ik_softc[vi->ui_unit].is_uid = -1;
124 }
125 
126 /*
127  * Open a PS300 and attach.  We allow multiple
128  * processes with the same uid to share a unit.
129  */
130 /*ARGSUSED*/
131 ikopen(dev, flag)
132 	dev_t dev;
133 	int flag;
134 {
135 	register int unit = IKUNIT(dev);
136 	register struct ik_softc *sc;
137 	struct vba_device *vi;
138 	struct ikdevice *ik;
139 	int reset;
140 
141 	if (unit >= NIK || (vi = ikinfo[unit]) == 0 || vi->ui_alive == 0)
142 		return (ENXIO);
143 	sc = &ik_softc[unit];
144 	if (sc->is_uid != (uid_t)-1 && sc->is_uid != u.u_uid)
145 		return (EBUSY);
146 	if (sc->is_uid == (uid_t)-1) {
147 		sc->is_buf = (caddr_t)wmemall(vmemall, PS_MAXDMA);
148 		if (sc->is_buf == 0)
149 			return (ENOMEM);
150 		sc->is_timeout = 0;
151 		timeout(iktimer, (caddr_t)unit, hz);
152 		/*
153 		 * Perform PS300 attach for first process.
154 		 */
155 		if (!IKDIAG(dev)) {
156 			reset = 0;
157 		again:
158 			if (ikcommand(dev, PS_ATTACH, 1)) {
159 				/*
160 				 * If attach fails, perform a hard
161 				 * reset once, then retry the command.
162 				 */
163 				ik = (struct ikdevice *)ikinfo[unit]->ui_addr;
164 				if (!reset++ && psreset(ik, 0))
165 					goto again;
166 				untimeout(iktimer, (caddr_t)unit);
167 				wmemfree(sc->is_buf, PS_MAXDMA);
168 				sc->is_buf = 0;
169 				return (EIO);
170 			}
171 		}
172 		sc->is_uid = u.u_uid;
173 	}
174 	return (0);
175 }
176 
177 /*ARGSUSED*/
178 ikclose(dev, flag)
179 	dev_t dev;
180 	int flag;
181 {
182 	int unit = IKUNIT(dev);
183 	register struct ik_softc *sc = &ik_softc[unit];
184 
185 	if (!IKDIAG(dev))
186 		(void) ikcommand(dev, PS_DETACH, 1);	/* auto detach */
187 	sc->is_uid = -1;
188 	if (sc->is_buf) {
189 		wmemfree(sc->is_buf, PS_MAXDMA);
190 		sc->is_buf = 0;
191 	}
192 	untimeout(iktimer, (caddr_t)unit);
193 }
194 
195 ikread(dev, uio)
196 	dev_t dev;
197 	struct uio *uio;
198 {
199 
200 	return (ikrw(dev, uio, B_READ));
201 }
202 
203 ikwrite(dev, uio)
204 	dev_t dev;
205 	struct uio *uio;
206 {
207 
208 	return (ikrw(dev, uio, B_WRITE));
209 }
210 
211 /*
212  * Take read/write request and perform physical i/o
213  * transaction with PS300.  This involves constructing
214  * a physical i/o request vector based on the uio
215  * vector, performing the dma, and, finally, moving
216  * the data to it's final destination (because of CCI
217  * VERSAbus bogosities).
218  */
219 ikrw(dev, uio, rw)
220 	dev_t dev;
221 	register struct uio *uio;
222 	int rw;
223 {
224 	int error, unit = IKUNIT(dev), s, wrcmd;
225 	register struct buf *bp;
226 	register struct iovec *iov;
227 	register struct psalist *ap;
228 	struct ik_softc *sc = &ik_softc[unit];
229 
230 	if (unit >= NIK)
231 		return (ENXIO);
232 	bp = &rikbuf[unit];
233 	error = 0, iov = uio->uio_iov, wrcmd = PS_WRPHY;
234 	for (; !error && uio->uio_iovcnt; iov++, uio->uio_iovcnt--) {
235 		/*
236 		 * Hack way to set PS300 address w/o doing an lseek
237 		 * and specify write physical w/ refresh synchronization.
238 		 */
239 		if (iov->iov_len == 0) {
240 			if ((int)iov->iov_base&PSIO_SYNC)
241 				wrcmd = PS_WRPHY_SYNC;
242 			uio->uio_offset = (int)iov->iov_base & ~PSIO_SYNC;
243 			continue;
244 		}
245 		if (iov->iov_len > PS_MAXDMA) {
246 			sc->is_error = PSERROR_INVALBC, error = EINVAL;
247 			continue;
248 		}
249 		if ((int)uio->uio_offset&01) {
250 			sc->is_error = PSERROR_BADADDR, error = EINVAL;
251 			continue;
252 		}
253 		s = splbio();
254 		while (bp->b_flags&B_BUSY) {
255 			bp->b_flags |= B_WANTED;
256 			sleep((caddr_t)bp, PRIBIO+1);
257 		}
258 		splx(s);
259 		bp->b_flags = B_BUSY | rw;
260 		/*
261 		 * Construct address descriptor in buffer.
262 		 */
263 		ap = (struct psalist *)sc->is_buf;
264 		ap->nblocks = 1;
265 		/* work-around dr300 word swapping */
266 		ap->addr[0] = uio->uio_offset & 0xffff;
267 		ap->addr[1] = uio->uio_offset >> 16;
268 		ap->wc = (iov->iov_len + 1) >> 1;
269 		if (rw == B_WRITE) {
270 			error = copyin(iov->iov_base, (caddr_t)&ap[1],
271 			    (unsigned)iov->iov_len);
272 			if (!error)
273 				error = ikcommand(dev, wrcmd,
274 				    iov->iov_len + sizeof (*ap));
275 		} else {
276 			caddr_t cp;
277 			int len;
278 
279 			error = ikcommand(dev, PS_RDPHY, sizeof (*ap));
280 			cp = (caddr_t)&ap[1], len = iov->iov_len;
281 			for (; len > 0; len -= NBPG, cp += NBPG)
282 				mtpr(P1DC, cp);
283 			if (!error)
284 				error = copyout((caddr_t)&ap[1], iov->iov_base,
285 				    (unsigned)iov->iov_len);
286 		}
287 		(void) splbio();
288 		if (bp->b_flags&B_WANTED)
289 			wakeup((caddr_t)bp);
290 		splx(s);
291 		uio->uio_resid -= iov->iov_len;
292 		uio->uio_offset += iov->iov_len;
293 		bp->b_flags &= ~(B_BUSY|B_WANTED);
294 	}
295 	return (error);
296 }
297 
298 /*
299  * Perform a PS300 command.
300  */
301 ikcommand(dev, com, count)
302 	dev_t dev;
303 	int com, count;
304 {
305 	register struct buf *bp;
306 	register int s;
307 
308 	bp = &cikbuf[IKUNIT(dev)];
309 	s = splik();
310 	while (bp->b_flags&B_BUSY) {
311 		if (bp->b_flags&B_DONE)
312 			break;
313 		bp->b_flags |= B_WANTED;
314 		sleep((caddr_t)bp, PRIBIO);
315 	}
316 	bp->b_flags = B_BUSY|B_READ;
317 	splx(s);
318 	bp->b_dev = dev;
319 	bp->b_command = com;
320 	bp->b_bcount = count;
321 	ikstrategy(bp);
322 	biowait(bp);
323 	if (bp->b_flags&B_WANTED)
324 		wakeup((caddr_t)bp);
325 	bp->b_flags &= B_ERROR;
326 	return (geterror(bp));
327 }
328 
329 /*
330  * Physio strategy routine
331  */
332 ikstrategy(bp)
333 	register struct buf *bp;
334 {
335 	register struct buf *dp;
336 
337 	/*
338 	 * Put request at end of controller queue.
339 	 */
340 	dp = &iktab[IKUNIT(bp->b_dev)];
341 	bp->av_forw = NULL;
342 	(void) splik();
343 	if (dp->b_actf != NULL) {
344 		dp->b_actl->av_forw = bp;
345 		dp->b_actl = bp;
346 	} else
347 		dp->b_actf = dp->b_actl = bp;
348 	if (!dp->b_active)
349 		ikstart(dp);
350 	(void) spl0();
351 }
352 
353 /*
354  * Start the next command on the controller's queue.
355  */
356 ikstart(dp)
357 	register struct buf *dp;
358 {
359 	register struct buf *bp;
360 	register struct ikdevice *ik;
361 	register struct ik_softc *sc;
362 	u_short bc, csr;
363 	u_int addr;
364 	int unit;
365 
366 loop:
367 	/*
368 	 * Pull a request off the controller queue
369 	 */
370 	if ((bp = dp->b_actf) == NULL) {
371 		dp->b_active = 0;
372 		return;
373 	}
374 	/*
375 	 * Mark controller busy and process this request.
376 	 */
377 	dp->b_active = 1;
378 	unit = IKUNIT(bp->b_dev);
379 	sc = &ik_softc[unit];
380 	ik = (struct ikdevice *)ikinfo[unit]->ui_addr;
381 	switch ((int)bp->b_command) {
382 
383 	case PS_ATTACH:		/* logical unit attach */
384 	case PS_DETACH:		/* logical unit detach */
385 	case PS_LOOKUP:		/* name lookup */
386 	case PS_RDPHY:		/* physical i/o read */
387 	case PS_WRPHY:		/* physical i/o write */
388 	case PS_WRPHY_SYNC:	/* physical i/o write w/ sync */
389 		/*
390 		 * Handshake command and, optionally,
391 		 * byte count and byte swap flag.
392 		 */
393 		if (sc->is_error = diowrite(ik, (u_short)bp->b_command))
394 			goto bad;
395 		if (bp->b_command < PS_DETACH) {
396 			if (sc->is_error = diowrite(ik, (u_short)bp->b_bcount))
397 				goto bad;
398 			if (sc->is_error = diowrite(ik, (u_short)0 /* !swab */))
399 				goto bad;
400 		}
401 		/*
402 		 * Set timeout and wait for an attention interrupt.
403 		 */
404 		sc->is_timeout = iktimeout;
405 		return;
406 
407 	case PS_DMAOUT:		/* dma data host->PS300 */
408 		bc = bp->b_bcount;
409 		csr = IKCSR_CYCLE;
410 		break;
411 
412 	case PS_DMAIN:		/* dma data PS300->host */
413 		bc = bp->b_bcount;
414 		csr = IKCSR_CYCLE|IKCSR_FNC1;
415 		break;
416 
417 	default:
418 		log(LOG_ERR, "ik%d: bad cmd %x\n", unit, bp->b_command);
419 		sc->is_error = PSERROR_BADCMD;
420 		goto bad;
421 	}
422 	/* initiate dma transfer */
423 	addr = vtoph((struct proc *)0, (unsigned)sc->is_buf);
424 	ik->ik_bahi = addr >> 17;
425 	ik->ik_balo = (addr >> 1) & 0xffff;
426 	ik->ik_wc = ((bc + 1) >> 1) - 1;	/* round & convert */
427 	ik->ik_pulse = IKPULSE_RATTF|IKPULSE_RDMAF;
428 	sc->is_timeout = iktimeout;
429 	ik->ik_csr = IKCSR_IENA|IKCSR_GO|csr;
430 	return;
431 bad:
432 	bp->b_flags |= B_ERROR;
433 	dp->b_actf = bp->av_forw;		/* remove from queue */
434 	biodone(bp);
435 	goto loop;
436 }
437 
438 #define FETCHWORD(i) { \
439 	v = dioread(ik); \
440 	if (v == -1) { \
441 		sc->is_error = PSERROR_NAMETIMO; \
442 		goto bad; \
443 	} \
444 	sc->is_nameaddr.w[i] = v; \
445 }
446 
447 /*
448  * Process a device interrupt.
449  */
450 ikintr(ikon)
451 	int ikon;
452 {
453 	register struct ikdevice *ik;
454 	register struct buf *bp, *dp;
455 	struct ik_softc *sc;
456 	register u_short data;
457 	int v;
458 
459 	/* should go by controller, but for now... */
460 	if (ikinfo[ikon] == 0)
461 		return;
462 	ik = (struct ikdevice *)ikinfo[ikon]->ui_addr;
463 	/*
464 	 * Discard all non-attention interrupts.  The
465 	 * interrupts we're throwing away should all be
466 	 * associated with DMA completion.
467 	 */
468 	data = ik->ik_data;
469 	if ((ik->ik_csr&(IKCSR_ATTF|IKCSR_STATC)) != IKCSR_ATTF) {
470 		ik->ik_pulse = IKPULSE_RATTF|IKPULSE_RDMAF|IKPULSE_SIENA;
471 		return;
472 	}
473 	/*
474 	 * Fetch attention code immediately.
475 	 */
476 	ik->ik_csr = IKCSR_RATTF|IKCSR_RDMAF|IKCSR_FNC1;
477 	ik->ik_pulse = IKPULSE_FNC2;
478 	/*
479 	 * Get device and block structures, and a pointer
480 	 * to the vba_device for the device.  We receive an
481 	 * unsolicited interrupt whenever the PS300 is power
482 	 * cycled (so ignore it in that case).
483 	 */
484 	dp = &iktab[ikon];
485 	if ((bp = dp->b_actf) == NULL) {
486 		if (PS_CODE(data) != PS_RESET)		/* power failure */
487 			log(LOG_WARNING, "ik%d: spurious interrupt, code %x\n",
488 			    ikon, data);
489 		goto enable;
490 	}
491 	sc = &ik_softc[IKUNIT(bp->b_dev)];
492 	sc->is_timeout = 0;			/* disable timer */
493 	switch (PS_CODE(data)) {
494 
495 	case PS_LOOKUP:				/* name lookup */
496 		if (data == PS_LOOKUP) {	/* dma name */
497 			bp->b_command = PS_DMAOUT;
498 			goto opcont;
499 		}
500 		if (data == PS_DMAOK(PS_LOOKUP)) {
501 			/* reenable interrupt and wait for address */
502 			sc->is_timeout = iktimeout;
503 			goto enable;
504 		}
505 		/*
506 		 * Address should be present, extract it one
507 		 * word at a time from the PS300 (yech).
508 		 */
509 		if (data != PS_ADROK(PS_LOOKUP))
510 			goto bad;
511 		FETCHWORD(0);
512 		FETCHWORD(1);
513 		goto opdone;
514 
515 	case PS_WRPHY_SYNC:			/* physical i/o write w/ sync */
516 		if (data == PS_WRPHY_SYNC) {	/* start dma transfer */
517 			bp->b_command = PS_DMAOUT;
518 			goto opcont;
519 		}
520 		if (data != PS_DMAOK(PS_WRPHY_SYNC))
521 			goto bad;
522 		goto opdone;
523 
524 	case PS_WRPHY:				/* physical i/o write */
525 		if (data == PS_WRPHY) { /* start dma transfer */
526 			bp->b_command = PS_DMAOUT;
527 			goto opcont;
528 		}
529 		if (data != PS_DMAOK(PS_WRPHY))
530 			goto bad;
531 		goto opdone;
532 
533 	case PS_ATTACH:				/* attach unit */
534 	case PS_DETACH:				/* detach unit */
535 	case PS_ABORT:				/* abort code from ps300 */
536 		if (data != bp->b_command)
537 			goto bad;
538 		goto opdone;
539 
540 	case PS_RDPHY:				/* physical i/o read */
541 		if (data == PS_RDPHY) {		/* dma address list */
542 			bp->b_command = PS_DMAOUT;
543 			goto opcont;
544 		}
545 		if (data == PS_ADROK(PS_RDPHY)) {
546 			/* collect read byte count and start dma */
547 			bp->b_bcount = dioread(ik);
548 			if (bp->b_bcount == -1)
549 				goto bad;
550 			bp->b_command = PS_DMAIN;
551 			goto opcont;
552 		}
553 		if (data == PS_DMAOK(PS_RDPHY))
554 			goto opdone;
555 		goto bad;
556 	}
557 bad:
558 	sc->is_error = data;
559 	bp->b_flags |= B_ERROR;
560 opdone:
561 	dp->b_actf = bp->av_forw;		/* remove from queue */
562 	biodone(bp);
563 opcont:
564 	ikstart(dp);
565 enable:
566 	ik->ik_pulse = IKPULSE_SIENA;		/* explicitly reenable */
567 }
568 
569 /*
570  * Watchdog timer.
571  */
572 iktimer(unit)
573 	int unit;
574 {
575 	register struct ik_softc *sc = &ik_softc[unit];
576 
577 	if (sc->is_timeout && --sc->is_timeout == 0) {
578 		register struct buf *dp, *bp;
579 		int s;
580 
581 		log(LOG_ERR, "ik%d: timeout\n", unit);
582 		s = splik();
583 		/* should abort current command */
584 		dp = &iktab[unit];
585 		if (bp = dp->b_actf) {
586 			sc->is_error = PSERROR_CMDTIMO;
587 			bp->b_flags |= B_ERROR;
588 			dp->b_actf = bp->av_forw;	/* remove from queue */
589 			biodone(bp);
590 			ikstart(dp);
591 		}
592 		splx(s);
593 	}
594 	timeout(iktimer, (caddr_t)unit, hz);
595 }
596 
597 /*
598  * Handshake read from DR300.
599  */
600 dioread(ik)
601 	register struct ikdevice *ik;
602 {
603 	register int t;
604 	u_short data;
605 
606 	for (t = ikdiotimo; t > 0; t--)
607 		if ((ik->ik_csr&(IKCSR_ATTF|IKCSR_STATC)) == IKCSR_ATTF) {
608 			data = ik->ik_data;
609 			ik->ik_csr = IKCSR_RATTF|IKCSR_RDMAF|IKCSR_FNC1;
610 			ik->ik_pulse = IKPULSE_FNC2;
611 			return (data);
612 		}
613 	return (-1);
614 }
615 
616 /*
617  * Handshake write to DR300.
618  *
619  * Interrupts are enabled before completing the work
620  * so the caller should either be at splik or be
621  * prepared to take the interrupt immediately.
622  */
623 diowrite(ik, v)
624 	register struct ikdevice *ik;
625 	u_short v;
626 {
627 	register int t;
628 	register u_short csr;
629 
630 top:
631 	/*
632 	 * Deposit data and generate dr300 attention
633 	 */
634 	ik->ik_data = v;
635 	ik->ik_csr = IKCSR_RDMAF|IKCSR_RATTF;
636 	ik->ik_pulse = IKPULSE_FNC2;
637 	for (t = ikdiotimo; t > 0; t--) {
638 		csr = ik->ik_csr;
639 #define IKCSR_DONE	(IKCSR_STATA|IKCSR_STATC)
640 		if ((csr&IKCSR_DONE) == IKCSR_DONE) {
641 			/*
642 			 * Done, complete handshake by notifying dr300.
643 			 */
644 			ik->ik_csr = IKCSR_IENA;	/* ~IKCSR_FNC1 */
645 			ik->ik_pulse = IKPULSE_FNC2;
646 			return (0);
647 		}
648 		/* beware of potential deadlock with dioread */
649 		if ((csr&(IKCSR_ATTF|IKCSR_STATC)) == IKCSR_ATTF)
650 			goto top;
651 	}
652 	ik->ik_csr = IKCSR_IENA;
653 	return (PSERROR_DIOTIMO);
654 }
655 
656 /*ARGSUSED*/
657 ikioctl(dev, cmd, data, flag)
658 	dev_t dev;
659 	int cmd;
660 	caddr_t data;
661 	int flag;
662 {
663 	int error = 0, unit = IKUNIT(dev), s;
664 	register struct ik_softc *sc = &ik_softc[unit];
665 
666 	switch (cmd) {
667 
668 	case PSIOGETERROR:		/* get error code for last operation */
669 		*(int *)data = sc->is_error;
670 		break;
671 
672 	case PSIOLOOKUP: {		/* PS300 name lookup */
673 		register struct pslookup *lp = (struct pslookup *)data;
674 		register struct buf *bp;
675 
676 		if (lp->pl_len > PS_MAXNAMELEN)
677 			return (EINVAL);
678 		bp = &rikbuf[unit];
679 		s = splbio();
680 		while (bp->b_flags&B_BUSY) {
681 			bp->b_flags |= B_WANTED;
682 			sleep((caddr_t)bp, PRIBIO+1);
683 		}
684 		splx(s);
685 		bp->b_flags = B_BUSY | B_WRITE;
686 		error = copyin(lp->pl_name, sc->is_buf, (unsigned)lp->pl_len);
687 		if (error == 0) {
688 			if (lp->pl_len&1)
689 				sc->is_buf[lp->pl_len] = '\0';
690 			error = ikcommand(dev, PS_LOOKUP, lp->pl_len);
691 		}
692 		s = splbio();
693 		if (bp->b_flags&B_WANTED)
694 			wakeup((caddr_t)bp);
695 		splx(s);
696 		bp->b_flags &= ~(B_BUSY|B_WANTED);
697 		lp->pl_addr = sc->is_nameaddr.l;
698 		break;
699 	}
700 	default:
701 		return (ENOTTY);
702 	}
703 	return (error);
704 }
705 #endif
706