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