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