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