xref: /original-bsd/sys/tahoe/vba/vx.c (revision f25de740)
1 /*
2  * Copyright (c) 1988 Regents of the University of California.
3  * All rights reserved.  The Berkeley software License Agreement
4  * specifies the terms and conditions for redistribution.
5  *
6  *	@(#)vx.c	7.1 (Berkeley) 05/21/88
7  */
8 
9 #include "vx.h"
10 #if NVX > 0
11 /*
12  * VIOC-X driver
13  */
14 #ifdef VXPERF
15 #define	DOSCOPE
16 #endif
17 
18 #include "param.h"
19 #include "ioctl.h"
20 #include "tty.h"
21 #include "dir.h"
22 #include "user.h"
23 #include "map.h"
24 #include "buf.h"
25 #include "conf.h"
26 #include "file.h"
27 #include "uio.h"
28 #include "proc.h"
29 #include "vm.h"
30 #include "kernel.h"
31 #include "syslog.h"
32 
33 #include "../tahoe/pte.h"
34 
35 #include "../tahoevba/vbavar.h"
36 #include "../tahoevba/vxreg.h"
37 #include "../tahoevba/scope.h"
38 
39 #ifdef VX_DEBUG
40 long	vxintr4 = 0;
41 #define	VXERR4	1
42 #define	VXNOBUF	2
43 long	vxdebug = 0;
44 #define	VXVCM	1
45 #define	VXVCC	2
46 #define	VXVCX	4
47 #endif
48 
49 /*
50  * Interrupt type bits passed to vinthandl().
51  */
52 #define	CMDquals 0		/* command completed interrupt */
53 #define	RSPquals 1		/* command response interrupt */
54 #define	UNSquals 2		/* unsolicited interrupt */
55 
56 #define	VXUNIT(n)	((n) >> 4)
57 #define	VXPORT(n)	((n) & 0xf)
58 
59 struct	tty vx_tty[NVX*16];
60 #ifndef lint
61 int	nvx = NVX*16;
62 #endif
63 int	vxstart(), ttrstrt();
64 struct	vxcmd *vobtain(), *nextcmd();
65 
66 /*
67  * Driver information for auto-configuration stuff.
68  */
69 int	vxprobe(), vxattach(), vxrint();
70 struct	vba_device *vxinfo[NVX];
71 long	vxstd[] = { 0 };
72 struct	vba_driver vxdriver =
73     { vxprobe, 0, vxattach, 0, vxstd, "vx", vxinfo };
74 
75 struct	vx_softc {
76 	u_char	vs_type;	/* 0: viox-x/vioc-b, 1: vioc-bop */
77 	u_char	vs_bop;		/* bop board # for vioc-bop's */
78 	u_char	vs_loport;	/* low port nbr */
79 	u_char	vs_hiport;	/* high port nbr */
80 	u_short	vs_nbr;		/* viocx number */
81 	u_short	vs_maxcmd;	/* max number of concurrent cmds */
82 	u_short	vs_silosiz;	/* silo size */
83 	short	vs_vers;	/* vioc/pvioc version */
84 #define	VXV_OLD	0		/* PVIOCX | VIOCX */
85 #define	VXV_NEW	1		/* NPVIOCX | NVIOCX */
86 	short	vs_xmtcnt;	/* xmit commands pending */
87 	short	vs_brkreq;	/* send break requests pending */
88 	short 	vs_state;	/* controller state */
89 #define	VXS_READY	0	/* ready for commands */
90 #define	VXS_RESET	1	/* in process of reseting */
91 	u_short	vs_softCAR;	/* soft carrier */
92 	caddr_t vs_mricmd;	/* most recent issued cmd */
93 	u_int	vs_ivec;	/* interrupt vector base */
94 	struct	vxcmd *vs_avail;/* next available command buffer */
95 	struct	vxcmd *vs_build;
96 	struct	vxcmd vs_lst[NVCXBUFS];
97 	struct	vcmds vs_cmds;
98 } vx_softc[NVX];
99 
100 vxprobe(reg, vi)
101 	caddr_t reg;
102 	struct vba_device *vi;
103 {
104 	register int br, cvec;			/* must be r12, r11 */
105 	register struct vxdevice *vp = (struct vxdevice *)reg;
106 	register struct vx_softc *vs;
107 
108 #ifdef lint
109 	br = 0; cvec = br; br = cvec;
110 	vackint(0); vunsol(0); vcmdrsp(0); vxfreset(0);
111 #endif
112 	if (badaddr((caddr_t)vp, 1))
113 		return (0);
114 	vp->v_fault = 0;
115 	vp->v_vioc = V_BSY;
116 	vp->v_hdwre = V_RESET;		/* reset interrupt */
117 	DELAY(4000000);
118 	if (vp->v_fault != VXF_READY)
119 		return (0);
120 	vs = &vx_softc[vi->ui_unit];
121 #ifdef notdef
122 	/*
123 	 * Align vioc interrupt vector base to 4 vector
124 	 * boundary and fitting in 8 bits (is this necessary,
125 	 * wish we had documentation).
126 	 */
127 	if ((vi->ui_hd->vh_lastiv -= 3) > 0xff)
128 		vi->ui_hd->vh_lastiv = 0xff;
129 	vs->vs_ivec = vi->ui_hd->vh_lastiv = vi->ui_hd->vh_lastiv &~ 0x3;
130 #else
131 	vs->vs_ivec = 0x40+vi->ui_unit*4;
132 #endif
133 	br = 0x18, cvec = vs->vs_ivec;	/* XXX */
134 	return (sizeof (struct vxdevice));
135 }
136 
137 vxattach(vi)
138 	register struct vba_device *vi;
139 {
140 
141 	vx_softc[vi->ui_unit].vs_softCAR = vi->ui_flags;
142 	vxinit(vi->ui_unit, 1);
143 }
144 
145 /*
146  * Open a VX line.
147  */
148 /*ARGSUSED*/
149 vxopen(dev, flag)
150 	dev_t dev;
151 	int flag;
152 {
153 	register struct tty *tp;	/* pointer to tty struct for port */
154 	register struct vx_softc *vs;
155 	register struct vba_device *vi;
156 	int unit, vx, s, error;
157 
158 	unit = minor(dev);
159 	vx = VXUNIT(unit);
160 	if (vx >= NVX || (vi = vxinfo[vx])== 0 || vi->ui_alive == 0)
161 		return (ENXIO);
162 	vs = &vx_softc[vx];
163 	tp = &vx_tty[unit];
164 	unit = VXPORT(unit);
165 	if (tp->t_state&TS_XCLUDE && u.u_uid != 0)
166 		return (EBUSY);
167 	if (unit < vs->vs_loport || unit > vs->vs_hiport)
168 		return (ENXIO);
169 	tp->t_addr = (caddr_t)vs;
170 	tp->t_oproc = vxstart;
171 	tp->t_dev = dev;
172 	s = spl8();
173 	tp->t_state |= TS_WOPEN;
174 	if ((tp->t_state&TS_ISOPEN) == 0) {
175 		ttychars(tp);
176 		if (tp->t_ispeed == 0) {
177 			tp->t_ispeed = SSPEED;
178 			tp->t_ospeed = SSPEED;
179 			tp->t_flags |= ODDP|EVENP|ECHO;
180 		}
181 		vxparam(dev);
182 	}
183 	vcmodem(dev, VMOD_ON);
184 	while ((tp->t_state&TS_CARR_ON) == 0)
185 		sleep((caddr_t)&tp->t_rawq, TTIPRI);
186 	error = (*linesw[tp->t_line].l_open)(dev,tp);
187 	splx(s);
188 	return (error);
189 }
190 
191 /*
192  * Close a VX line.
193  */
194 /*ARGSUSED*/
195 vxclose(dev, flag)
196 	dev_t dev;
197 	int flag;
198 {
199 	register struct tty *tp;
200 	int unit, s;
201 
202 	unit = minor(dev);
203 	tp = &vx_tty[unit];
204 	s = spl8();
205 	(*linesw[tp->t_line].l_close)(tp);
206 	if (tp->t_state & TS_HUPCLS || (tp->t_state & TS_ISOPEN) == 0)
207 		vcmodem(dev, VMOD_OFF);
208 	/* wait for the last response */
209 	while (tp->t_state&TS_FLUSH)
210 		sleep((caddr_t)&tp->t_state, TTOPRI);
211 	ttyclose(tp);
212 	splx(s);
213 }
214 
215 /*
216  * Read from a VX line.
217  */
218 vxread(dev, uio)
219 	dev_t dev;
220 	struct uio *uio;
221 {
222 	struct tty *tp = &vx_tty[minor(dev)];
223 
224 	return ((*linesw[tp->t_line].l_read)(tp, uio));
225 }
226 
227 /*
228  * write on a VX line
229  */
230 vxwrite(dev, uio)
231 	dev_t dev;
232 	struct uio *uio;
233 {
234 	register struct tty *tp = &vx_tty[minor(dev)];
235 
236 	return ((*linesw[tp->t_line].l_write)(tp, uio));
237 }
238 
239 /*
240  * VIOCX unsolicited interrupt.
241  */
242 vxrint(vx)
243 	register vx;
244 {
245 	register struct tty *tp, *tp0;
246 	register struct vxdevice *addr;
247 	register struct vx_softc *vs;
248 	struct vba_device *vi;
249 	register int nc, c;
250 	register struct silo {
251 		char	data, port;
252 	} *sp;
253 	short *osp;
254 	int overrun = 0;
255 
256 	vi = vxinfo[vx];
257 	if (vi == 0 || vi->ui_alive == 0)
258 		return;
259 	addr = (struct vxdevice *)vi->ui_addr;
260 	switch (addr->v_uqual&037) {
261 	case 0:
262 		break;
263 	case 2:
264 		printf("vx%d: vc proc err, ustat %x\n", vx, addr->v_ustat);
265 		vxstreset(vx);
266 		return;
267 	case 3:
268 		vcmintr(vx);
269 		return;
270 	case 4:
271 		return;
272 	default:
273 		printf("vx%d: vc uqual err, uqual %x\n", vx, addr->v_uqual);
274 		vxstreset(vx);
275 		return;
276 	}
277 	vs = &vx_softc[vx];
278 	if (vs->vs_vers == VXV_NEW)
279 		sp = (struct silo *)((caddr_t)addr + *(short *)addr->v_usdata);
280 	else
281 		sp = (struct silo *)((caddr_t)addr+VX_SILO+(addr->v_usdata[0]<<6));
282 	nc = *(osp = (short *)sp);
283 	if (nc == 0)
284 		return;
285 	if (vs->vs_vers == VXV_NEW && nc > vs->vs_silosiz) {
286 		printf("vx%d: %d exceeds silo size\n", nc);
287 		nc = vs->vs_silosiz;
288 	}
289 	tp0 = &vx_tty[vx*16];
290 	sp = (struct silo *)(((short *)sp)+1);
291 	for (; nc > 0; nc--, sp = (struct silo *)(((short *)sp)+1)) {
292 		c = sp->port & 017;
293 		if (vs->vs_loport > c || c > vs->vs_hiport)
294 			continue;
295 		tp = tp0 + c;
296 		if( (tp->t_state&TS_ISOPEN) == 0) {
297 			wakeup((caddr_t)&tp->t_rawq);
298 			continue;
299 		}
300 		c = sp->data;
301 		if ((sp->port&VX_RO) == VX_RO && !overrun) {
302 			log(LOG_ERR, "vx%d: receiver overrun\n", vi->ui_unit);
303 			overrun = 1;
304 			continue;
305 		}
306 		if (sp->port&VX_PE)
307 			if ((tp->t_flags&(EVENP|ODDP)) == EVENP ||
308 			    (tp->t_flags&(EVENP|ODDP)) == ODDP)
309 				continue;
310 		if ((tp->t_flags & (RAW | PASS8)) == 0)
311 			c &= 0177;
312 		if (sp->port&VX_FE) {
313 			/*
314 			 * At framing error (break) generate
315 			 * a null (in raw mode, for getty), or a
316 			 * interrupt (in cooked/cbreak mode).
317 			 */
318 			if (tp->t_flags&RAW)
319 				c = 0;
320 			else
321 				c = tp->t_intrc;
322 		}
323 		(*linesw[tp->t_line].l_rint)(c, tp);
324 	}
325 	*osp = 0;
326 }
327 
328 /*
329  * Ioctl for VX.
330  */
331 vxioctl(dev, cmd, data, flag)
332 	dev_t dev;
333 	caddr_t	data;
334 {
335 	register struct tty *tp;
336 	int error;
337 
338 	tp = &vx_tty[minor(dev)];
339 	error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag);
340 	if (error == 0)
341 		return (error);
342 	error = ttioctl(tp, cmd, data, flag);
343 	if (error >= 0) {
344 		if (cmd == TIOCSETP || cmd == TIOCSETN || cmd == TIOCLBIS ||
345 		    cmd == TIOCLBIC || cmd == TIOCLSET)
346 			vxparam(dev);
347 		return (error);
348 	}
349 	return (ENOTTY);
350 }
351 
352 vxparam(dev)
353 	dev_t dev;
354 {
355 
356 	vxcparam(dev, 1);
357 }
358 
359 /*
360  * Set parameters from open or stty into the VX hardware
361  * registers.
362  */
363 vxcparam(dev, wait)
364 	dev_t dev;
365 	int wait;
366 {
367 	register struct tty *tp;
368 	register struct vx_softc *vs;
369 	register struct vxcmd *cp;
370 	int s, unit = minor(dev);
371 
372 	tp = &vx_tty[unit];
373 	if ((tp->t_ispeed)==0) {
374 		tp->t_state |= TS_HUPCLS;
375 		vcmodem(dev, VMOD_OFF);
376 		return;
377 	}
378 	vs = (struct vx_softc *)tp->t_addr;
379 	cp = vobtain(vs);
380 	s = spl8();
381 	/*
382 	 * Construct ``load parameters'' command block
383 	 * to setup baud rates, xon-xoff chars, parity,
384 	 * and stop bits for the specified port.
385 	 */
386 	cp->cmd = VXC_LPARAX;
387 	cp->par[1] = VXPORT(unit);
388 	cp->par[2] = (tp->t_flags&RAW) ? 0 : tp->t_startc;
389 	cp->par[3] = (tp->t_flags&RAW) ? 0 : tp->t_stopc;
390 #ifdef notnow
391 	if (tp->t_flags & (RAW|LITOUT|PASS8)) {
392 #endif
393 		cp->par[4] = BITS8;		/* 8 bits of data */
394 		cp->par[7] = VNOPARITY;		/* no parity */
395 #ifdef notnow
396 	} else {
397 		cp->par[4] = BITS7;		/* 7 bits of data */
398 		if ((tp->t_flags&(EVENP|ODDP)) == ODDP)
399 			cp->par[7] = VODDP;	/* odd parity */
400 		else
401 			cp->par[7] = VEVENP;	/* even parity */
402 	}
403 #endif
404 	if (tp->t_ospeed == B110)
405 		cp->par[5] = VSTOP2;		/* 2 stop bits */
406 	else
407 		cp->par[5] = VSTOP1;		/* 1 stop bit */
408 	if (tp->t_ospeed == EXTA || tp->t_ospeed == EXTB)
409 		cp->par[6] = V19200;
410 	else
411 		cp->par[6] = tp->t_ospeed;
412 	if (vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd) && wait)
413 		sleep((caddr_t)cp,TTIPRI);
414 	splx(s);
415 }
416 
417 /*
418  * VIOCX command response interrupt.
419  * For transmission, restart output to any active port.
420  * For all other commands, just clean up.
421  */
422 vxxint(vx, cp)
423 	register int vx;
424 	register struct vxcmd *cp;
425 {
426 	register struct vxmit *vp;
427 	register struct tty *tp, *tp0;
428 	register struct vx_softc *vs;
429 
430 	vs = &vx_softc[vx];
431 	cp = (struct vxcmd *)((long *)cp-1);
432 
433 	switch (cp->cmd&0xff00) {
434 
435 	case VXC_LIDENT:	/* initialization complete */
436 		if (vs->vs_state == VXS_RESET) {
437 			vxfnreset(vx, cp);
438 			vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
439 		}
440 		cp->cmd++;
441 		return;
442 
443 	case VXC_XMITDTA:
444 	case VXC_XMITIMM:
445 		break;
446 
447 	case VXC_LPARAX:
448 		wakeup((caddr_t)cp);
449 		/* fall thru... */
450 	default:	/* VXC_MDMCTL or VXC_FDTATOX */
451 		vrelease(vs, cp);
452 		if (vs->vs_state == VXS_RESET)
453 			vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
454 		return;
455 	}
456 	tp0 = &vx_tty[vx*16];
457 	vp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit));
458 	for (; vp >= (struct vxmit *)cp->par; vp--) {
459 		tp = tp0 + (vp->line & 017);
460 		tp->t_state &= ~TS_BUSY;
461 		if (tp->t_state & TS_FLUSH) {
462 			tp->t_state &= ~TS_FLUSH;
463 			wakeup((caddr_t)&tp->t_state);
464 		} else
465 		 	ndflush(&tp->t_outq, vp->bcount+1);
466 	}
467 	vrelease(vs, cp);
468 	if (vs->vs_vers == VXV_NEW)
469 		(*linesw[tp->t_line].l_start)(tp);
470 	else {
471 		tp0 = &vx_tty[vx*16 + vs->vs_hiport];
472 		for(tp = &vx_tty[vx*16 + vs->vs_loport]; tp <= tp0; tp++)
473 			(*linesw[tp->t_line].l_start)(tp);
474 		if ((cp = nextcmd(vs)) != NULL) {	/* command to send? */
475 			vs->vs_xmtcnt++;
476 			(void) vcmd(vx, (caddr_t)&cp->cmd);
477 		}
478 	}
479 	vs->vs_xmtcnt--;
480 }
481 
482 /*
483  * Force out partial XMIT command after timeout
484  */
485 vxforce(vs)
486 	register struct vx_softc *vs;
487 {
488 	register struct vxcmd *cp;
489 	int s;
490 
491 	s = spl8();
492 	if ((cp = nextcmd(vs)) != NULL) {
493 		vs->vs_xmtcnt++;
494 		(void) vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd);
495 	}
496 	splx(s);
497 }
498 
499 /*
500  * Start (restart) transmission on the given VX line.
501  */
502 vxstart(tp)
503 	register struct tty *tp;
504 {
505 	register short n;
506 	register struct vx_softc *vs;
507 	int s, port;
508 
509 	s = spl8();
510 	port = minor(tp->t_dev) & 017;
511 	vs = (struct vx_softc *)tp->t_addr;
512 	if ((tp->t_state&(TS_TIMEOUT|TS_BUSY|TS_TTSTOP)) == 0) {
513 		if (tp->t_outq.c_cc <= TTLOWAT(tp)) {
514 			if (tp->t_state&TS_ASLEEP) {
515 				tp->t_state &= ~TS_ASLEEP;
516 				wakeup((caddr_t)&tp->t_outq);
517 			}
518 			if (tp->t_wsel) {
519 				selwakeup(tp->t_wsel, tp->t_state & TS_WCOLL);
520 				tp->t_wsel = 0;
521 				tp->t_state &= ~TS_WCOLL;
522 			}
523 		}
524 		if (tp->t_outq.c_cc == 0) {
525 			splx(s);
526 			return;
527 		}
528 		scope_out(3);
529 		if (tp->t_flags & (RAW|LITOUT))
530 			n = ndqb(&tp->t_outq, 0);
531 		else {
532 			n = ndqb(&tp->t_outq, 0200);
533 			if (n == 0) {
534 				n = getc(&tp->t_outq);
535 				timeout(ttrstrt, (caddr_t)tp, (n&0177)+6);
536 				tp->t_state |= TS_TIMEOUT;
537 				n = 0;
538 			}
539 		}
540 		if (n) {
541 			tp->t_state |= TS_BUSY;
542 			vsetq(vs, port, (char *)tp->t_outq.c_cf, n);
543 		}
544 	}
545 	splx(s);
546 }
547 
548 /*
549  * Stop output on a line.
550  */
551 vxstop(tp)
552 	register struct tty *tp;
553 {
554 	int s;
555 
556 	s = spl8();
557 	if (tp->t_state&TS_BUSY)
558 		if ((tp->t_state&TS_TTSTOP) == 0)
559 			tp->t_state |= TS_FLUSH;
560 	splx(s);
561 }
562 
563 static	int vxbbno = -1;
564 /*
565  * VIOCX Initialization.  Makes free lists of command buffers.
566  * Resets all viocx's.  Issues a LIDENT command to each
567  * viocx to establish interrupt vectors and logical port numbers.
568  */
569 vxinit(vx, wait)
570 	register int vx;
571 	int wait;
572 {
573 	register struct vx_softc *vs;
574 	register struct vxdevice *addr;
575 	register struct vxcmd *cp;
576 	register char *resp;
577 	register int j;
578 	char type, *typestring;
579 
580 	vs = &vx_softc[vx];
581 	vs->vs_type = 0;		/* vioc-x by default */
582 	addr = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
583 	type = addr->v_ident;
584 	vs->vs_vers = (type&VXT_NEW) ? VXV_NEW : VXV_OLD;
585 	if (vs->vs_vers == VXV_NEW)
586 		vs->vs_silosiz = addr->v_maxsilo;
587 	switch (type) {
588 
589 	case VXT_VIOCX:
590 	case VXT_VIOCX|VXT_NEW:
591 		typestring = "VIOC-X";
592 		/* set soft carrier for printer ports */
593 		for (j = 0; j < 16; j++)
594 			if (addr->v_portyp[j] == VXT_PARALLEL) {
595 				vs->vs_softCAR |= 1 << j;
596 				addr->v_dcd |= 1 << j;
597 			}
598 		break;
599 
600 	case VXT_PVIOCX:
601 	case VXT_PVIOCX|VXT_NEW:
602 		typestring = "VIOC-X (old connector panel)";
603 		break;
604 	case VXT_VIOCBOP:		/* VIOC-BOP */
605 		vs->vs_type = 1;
606 		vs->vs_bop = ++vxbbno;
607 		printf("VIOC-BOP no. %d at %x\n", vs->vs_bop, addr);
608 
609 	default:
610 		printf("vx%d: unknown type %x\n", vx, type);
611 		vxinfo[vx]->ui_alive = 0;
612 		return;
613 	}
614 	vs->vs_nbr = -1;
615 	vs->vs_maxcmd = (vs->vs_vers == VXV_NEW) ? 24 : 4;
616 	/*
617 	 * Initialize all cmd buffers by linking them
618 	 * into a free list.
619 	 */
620 	for (j = 0; j < NVCXBUFS; j++) {
621 		cp = &vs->vs_lst[j];
622 		cp->c_fwd = &vs->vs_lst[j+1];
623 	}
624 	vs->vs_avail = &vs->vs_lst[0];	/* set idx to 1st free buf */
625 	cp->c_fwd = (struct vxcmd *)0;	/* mark last buf in free list */
626 
627 	/*
628 	 * Establish the interrupt vectors and define the port numbers.
629 	 */
630 	cp = vobtain(vs);
631 	cp->cmd = VXC_LIDENT;
632 	cp->par[0] = vs->vs_ivec; 	/* ack vector */
633 	cp->par[1] = cp->par[0]+1;	/* cmd resp vector */
634 	cp->par[3] = cp->par[0]+2;	/* unsol intr vector */
635 	cp->par[4] = 15;		/* max ports, no longer used */
636 	cp->par[5] = 0;			/* set 1st port number */
637 	(void) vcmd(vx, (caddr_t)&cp->cmd);
638 	if (!wait)
639 		return;
640 	for (j = 0; cp->cmd == VXC_LIDENT && j < 4000000; j++)
641 		;
642 	if (j >= 4000000)
643 		printf("vx%d: didn't respond to LIDENT\n", vx);
644 
645  	/* calculate address of response buffer */
646  	resp = (char *)addr + (addr->v_rspoff&0x3fff);
647 	if (resp[0] != 0 && (resp[0]&0177) != 3) {
648 		vrelease(vs, cp);	/* init failed */
649 		return;
650 	}
651 	vs->vs_loport = cp->par[5];
652 	vs->vs_hiport = cp->par[7];
653 	printf("vx%d: %s%s, ports %d-%d\n", vx,
654 	    (vs->vs_vers == VXV_NEW) ? "" : "old ", typestring,
655 	    vs->vs_loport, vs->vs_hiport);
656 	vrelease(vs, cp);
657 	vs->vs_nbr = vx;		/* assign board number */
658 }
659 
660 /*
661  * Obtain a command buffer
662  */
663 struct vxcmd *
664 vobtain(vs)
665 	register struct vx_softc *vs;
666 {
667 	register struct vxcmd *p;
668 	int s;
669 
670 	s = spl8();
671 	p = vs->vs_avail;
672 	if (p == (struct vxcmd *)0) {
673 #ifdef VX_DEBUG
674 		if (vxintr4&VXNOBUF)
675 			vxintr4 &= ~VXNOBUF;
676 #endif
677 		printf("vx%d: no buffers\n", vs - vx_softc);
678 		vxstreset(vs - vx_softc);
679 		splx(s);
680 		return (vobtain(vs));
681 	}
682 	vs->vs_avail = p->c_fwd;
683 	splx(s);
684 	return ((struct vxcmd *)p);
685 }
686 
687 /*
688  * Release a command buffer
689  */
690 vrelease(vs, cp)
691 	register struct vx_softc *vs;
692 	register struct vxcmd *cp;
693 {
694 	int s;
695 
696 #ifdef VX_DEBUG
697 	if (vxintr4&VXNOBUF)
698 		return;
699 #endif
700 	s = spl8();
701 	cp->c_fwd = vs->vs_avail;
702 	vs->vs_avail = cp;
703 	splx(s);
704 }
705 
706 struct vxcmd *
707 nextcmd(vs)
708 	register struct vx_softc *vs;
709 {
710 	register struct vxcmd *cp;
711 	int s;
712 
713 	s = spl8();
714 	cp = vs->vs_build;
715 	vs->vs_build = (struct vxcmd *)0;
716 	splx(s);
717 	return (cp);
718 }
719 
720 /*
721  * Assemble transmits into a multiple command;
722  * up to 8 transmits to 8 lines can be assembled together
723  * (on PVIOCX only).
724  */
725 vsetq(vs, line, addr, n)
726 	register struct vx_softc *vs;
727 	caddr_t	addr;
728 {
729 	register struct vxcmd *cp;
730 	register struct vxmit *mp;
731 
732 	/*
733 	 * Grab a new command buffer or append
734 	 * to the current one being built.
735 	 */
736 	cp = vs->vs_build;
737 	if (cp == (struct vxcmd *)0) {
738 		cp = vobtain(vs);
739 		vs->vs_build = cp;
740 		cp->cmd = VXC_XMITDTA;
741 	} else {
742 		if ((cp->cmd & 07) == 07 || vs->vs_vers == VXV_NEW) {
743 			printf("vx%d: setq overflow\n", vs-vx_softc);
744 			vxstreset((int)vs->vs_nbr);
745 			return;
746 		}
747 		cp->cmd++;
748 	}
749 	/*
750 	 * Select the next vxmit buffer and copy the
751 	 * characters into the buffer (if there's room
752 	 * and the device supports ``immediate mode'',
753 	 * or store an indirect pointer to the data.
754 	 */
755 	mp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit));
756 	mp->bcount = n-1;
757 	mp->line = line;
758 	if (vs->vs_vers == VXV_NEW && n <= sizeof (mp->ostream)) {
759 		cp->cmd = VXC_XMITIMM;
760 		bcopy(addr, mp->ostream, (unsigned)n);
761 	} else {
762 		/* get system address of clist block */
763 		addr = (caddr_t)vtoph((struct proc *)0, (unsigned)addr);
764 		bcopy((caddr_t)&addr, mp->ostream, sizeof (addr));
765 	}
766 	/*
767 	 * We send the data immediately if a VIOCX,
768 	 * the command buffer is full, or if we've nothing
769 	 * currently outstanding.  If we don't send it,
770 	 * set a timeout to force the data to be sent soon.
771 	 */
772 	if (vs->vs_vers == VXV_NEW || (cp->cmd & 07) == 7 ||
773 	    vs->vs_xmtcnt == 0) {
774 		vs->vs_xmtcnt++;
775 		(void) vcmd((int)vs->vs_nbr, (char *)&cp->cmd);
776 		vs->vs_build = 0;
777 	} else
778 		timeout(vxforce, (caddr_t)vs, 3);
779 }
780 
781 /*
782  * Write a command out to the VIOC
783  */
784 vcmd(vx, cmdad)
785 	register int vx;
786 	register caddr_t cmdad;
787 {
788 	register struct vcmds *cp;
789 	register struct vx_softc *vs;
790 	int s;
791 
792 	s = spl8();
793 	vs = &vx_softc[vx];
794 	/*
795 	 * When the vioc is resetting, don't process
796 	 * anything other than VXC_LIDENT commands.
797 	 */
798 	if (vs->vs_state == VXS_RESET && cmdad != NULL) {
799 		struct vxcmd *vcp = (struct vxcmd *)(cmdad-sizeof (vcp->c_fwd));
800 
801 		if (vcp->cmd != VXC_LIDENT) {
802 			vrelease(vs, vcp);
803 			return (0);
804 		}
805 	}
806 	cp = &vs->vs_cmds;
807 	if (cmdad != (caddr_t)0) {
808 		cp->cmdbuf[cp->v_fill] = cmdad;
809 		if (++cp->v_fill >= VC_CMDBUFL)
810 			cp->v_fill = 0;
811 		if (cp->v_fill == cp->v_empty) {
812 			printf("vx%d: cmd q overflow\n", vx);
813 			vxstreset(vx);
814 			splx(s);
815 			return (0);
816 		}
817 		cp->v_cmdsem++;
818 	}
819 	if (cp->v_cmdsem && cp->v_curcnt < vs->vs_maxcmd) {
820 		cp->v_cmdsem--;
821 		cp->v_curcnt++;
822 		vinthandl(vx, ((V_BSY|CMDquals) << 8)|V_INTR);
823 	}
824 	splx(s);
825 	return (1);
826 }
827 
828 /*
829  * VIOC acknowledge interrupt.  The VIOC has received the new
830  * command.  If no errors, the new command becomes one of 16 (max)
831  * current commands being executed.
832  */
833 vackint(vx)
834 	register vx;
835 {
836 	register struct vxdevice *vp;
837 	register struct vcmds *cp;
838 	struct vx_softc *vs;
839 	int s;
840 
841 	scope_out(5);
842 	vs = &vx_softc[vx];
843 	if (vs->vs_type)	/* Its a BOP */
844 		return;
845 	s = spl8();
846 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
847 	cp = &vs->vs_cmds;
848 	if (vp->v_vcid&V_ERR) {
849 		register char *resp;
850 		register i;
851 
852 		printf("vx%d: ackint error type %x v_dcd %x\n", vx,
853 		    vp->v_vcid & 07, vp->v_dcd & 0xff);
854 		resp = (char *)vs->vs_mricmd;
855 		for (i = 0; i < 16; i++)
856 			printf("%x ", resp[i]&0xff);
857 		printf("\n");
858 		splx(s);
859 		vxstreset(vx);
860 		return;
861 	}
862 	if ((vp->v_hdwre&017) == CMDquals) {
863 #ifdef VX_DEBUG
864 		if (vxintr4 & VXERR4) {	/* causes VIOC INTR ERR 4 */
865 			struct vxcmd *cp1, *cp0;
866 
867 			cp0 = (struct vxcmd *)
868 			    ((caddr_t)cp->cmdbuf[cp->v_empty]-sizeof (cp0->c_fwd));
869 			if (cp0->cmd == VXC_XMITDTA || cp0->cmd == VXC_XMITIMM) {
870 				cp1 = vobtain(vs);
871 				*cp1 = *cp0;
872 				vxintr4 &= ~VXERR4;
873 				(void) vcmd(vx, &cp1->cmd);
874 			}
875 		}
876 #endif
877 		cp->v_curcmd[vp->v_vcid & VCMDLEN-1] = cp->cmdbuf[cp->v_empty];
878 		if (++cp->v_empty >= VC_CMDBUFL)
879 			cp->v_empty = 0;
880 	}
881 	if (++cp->v_itrempt >= VC_IQLEN)
882 		cp->v_itrempt = 0;
883 	vintempt(vx);
884 	splx(s);
885 	(void) vcmd(vx, (caddr_t)0);	/* queue next cmd, if any */
886 }
887 
888 /*
889  * Command Response interrupt.  The Vioc has completed
890  * a command.  The command may now be returned to
891  * the appropriate device driver.
892  */
893 vcmdrsp(vx)
894 	register vx;
895 {
896 	register struct vxdevice *vp;
897 	register struct vcmds *cp;
898 	register caddr_t cmd;
899 	register struct vx_softc *vs;
900 	register char *resp;
901 	register k;
902 	register int s;
903 
904 	scope_out(6);
905 	vs = &vx_softc[vx];
906 	if (vs->vs_type) {	/* Its a BOP */
907 		printf("vx%d: vcmdrsp interrupt\n", vx);
908 		return;
909 	}
910 	s = spl8();
911 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
912 	cp = &vs->vs_cmds;
913 	resp = (char *)vp + (vp->v_rspoff&0x7fff);
914 	if (((k = resp[1])&V_UNBSY) == 0) {
915 		printf("vx%d: cmdresp debug\n", vx);
916 		splx(s);
917 		vxstreset(vx);
918 		return;
919 	}
920 	k &= VCMDLEN-1;
921 	cmd = cp->v_curcmd[k];
922 	cp->v_curcmd[k] = (caddr_t)0;
923 	cp->v_curcnt--;
924 	k = *((short *)&resp[4]);	/* cmd operation code */
925 	if ((k&0xff00) == VXC_LIDENT)	/* want hiport number */
926 		for (k = 0; k < VRESPLEN; k++)
927 			cmd[k] = resp[k+4];
928 	resp[1] = 0;
929 	vxxint(vx, (struct vxcmd *)cmd);
930 	if (vs->vs_state == VXS_READY)
931 		vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
932 	splx(s);
933 }
934 
935 /*
936  * Unsolicited interrupt.
937  */
938 vunsol(vx)
939 	register vx;
940 {
941 	register struct vxdevice *vp;
942 	struct vx_softc *vs;
943 	int s;
944 
945 	scope_out(1);
946 	vs = &vx_softc[vx];
947 	if (vs->vs_type) {	/* Its a BOP */
948 		printf("vx%d: vunsol from BOP\n", vx);
949 		return;
950 	}
951 	s = spl8();
952 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
953 	if (vp->v_uqual&V_UNBSY) {
954 		vxrint(vx);
955 		vinthandl(vx, ((V_BSY|UNSquals) << 8)|V_INTR);
956 #ifdef notdef
957 	} else {
958 		printf("vx%d: unsolicited interrupt error\n", vx);
959 		splx(s);
960 		vxstreset(vx);
961 #endif
962 	}
963 	splx(s);
964 }
965 
966 /*
967  * Enqueue an interrupt.
968  */
969 vinthandl(vx, item)
970 	register int vx;
971 	register item;
972 {
973 	register struct vcmds *cp;
974 	int empty;
975 
976 	cp = &vx_softc[vx].vs_cmds;
977 	empty = (cp->v_itrfill == cp->v_itrempt);
978 	cp->v_itrqueu[cp->v_itrfill] = item;
979 	if (++cp->v_itrfill >= VC_IQLEN)
980 		cp->v_itrfill = 0;
981 	if (cp->v_itrfill == cp->v_itrempt) {
982 		printf("vx%d: interrupt q overflow\n", vx);
983 		vxstreset(vx);
984 	} else if (empty)
985 		vintempt(vx);
986 }
987 
988 vintempt(vx)
989 	register int vx;
990 {
991 	register struct vcmds *cp;
992 	register struct vxdevice *vp;
993 	register short item;
994 	register short *intr;
995 
996 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
997 	if (vp->v_vioc&V_BSY)
998 		return;
999 	cp = &vx_softc[vx].vs_cmds;
1000 	if (cp->v_itrempt == cp->v_itrfill)
1001 		return;
1002 	item = cp->v_itrqueu[cp->v_itrempt];
1003 	intr = (short *)&vp->v_vioc;
1004 	switch ((item >> 8)&03) {
1005 
1006 	case CMDquals: {		/* command */
1007 		int phys;
1008 
1009 		if (cp->v_empty == cp->v_fill || vp->v_vcbsy&V_BSY)
1010 			break;
1011 		vx_softc[vx].vs_mricmd = (caddr_t)cp->cmdbuf[cp->v_empty];
1012 		phys = vtoph((struct proc *)0,
1013 		    (unsigned)cp->cmdbuf[cp->v_empty]);
1014 		vp->v_vcp[0] = ((short *)&phys)[0];
1015 		vp->v_vcp[1] = ((short *)&phys)[1];
1016 		vp->v_vcbsy = V_BSY;
1017 		*intr = item;
1018 		scope_out(4);
1019 		break;
1020 	}
1021 
1022 	case RSPquals:		/* command response */
1023 		*intr = item;
1024 		scope_out(7);
1025 		break;
1026 
1027 	case UNSquals:		/* unsolicited interrupt */
1028 		vp->v_uqual = 0;
1029 		*intr = item;
1030 		scope_out(2);
1031 		break;
1032 	}
1033 }
1034 
1035 /*
1036  * Start a reset on a vioc after error (hopefully)
1037  */
1038 vxstreset(vx)
1039 	register vx;
1040 {
1041 	register struct vx_softc *vs;
1042 	register struct vxdevice *vp;
1043 	register struct vxcmd *cp;
1044 	register int j;
1045 	extern int vxinreset();
1046 	int s;
1047 
1048 	s = spl8() ;
1049 	vs = &vx_softc[vx];
1050 	if (vs->vs_state == VXS_RESET) {	/* avoid recursion */
1051 		splx(s);
1052 		return;
1053 	}
1054 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
1055 	/*
1056 	 * Zero out the vioc structures, mark the vioc as being
1057 	 * reset, reinitialize the free command list, reset the vioc
1058 	 * and start a timer to check on the progress of the reset.
1059 	 */
1060 	bzero((caddr_t)vs, (unsigned)sizeof (*vs));
1061 
1062 	/*
1063 	 * Setting VXS_RESET prevents others from issuing
1064 	 * commands while allowing currently queued commands to
1065 	 * be passed to the VIOC.
1066 	 */
1067 	vs->vs_state = VXS_RESET;
1068 	/* init all cmd buffers */
1069 	for (j = 0; j < NVCXBUFS; j++) {
1070 		cp = &vs->vs_lst[j];
1071 		cp->c_fwd = &vs->vs_lst[j+1];
1072 	}
1073 	vs->vs_avail = &vs->vs_lst[0];
1074 	cp->c_fwd = (struct vxcmd *)0;
1075 	printf("vx%d: reset...", vx);
1076 	vp->v_fault = 0;
1077 	vp->v_vioc = V_BSY;
1078 	vp->v_hdwre = V_RESET;		/* generate reset interrupt */
1079 	timeout(vxinreset, (caddr_t)vx, hz*5);
1080 	splx(s);
1081 }
1082 
1083 /* continue processing a reset on a vioc after an error (hopefully) */
1084 vxinreset(vx)
1085 	int vx;
1086 {
1087 	register struct vxdevice *vp;
1088 	int s = spl8();
1089 
1090 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
1091 	/*
1092 	 * See if the vioc has reset.
1093 	 */
1094 	if (vp->v_fault != VXF_READY) {
1095 		printf("failed\n");
1096 		splx(s);
1097 		return;
1098 	}
1099 	/*
1100 	 * Send a LIDENT to the vioc and mess with carrier flags
1101 	 * on parallel printer ports.
1102 	 */
1103 	vxinit(vx, 0);
1104 	splx(s);
1105 }
1106 
1107 /*
1108  * Finish the reset on the vioc after an error (hopefully).
1109  *
1110  * Restore modem control, parameters and restart output.
1111  * Since the vioc can handle no more then 24 commands at a time
1112  * and we could generate as many as 48 commands, we must do this in
1113  * phases, issuing no more then 16 commands at a time.
1114  */
1115 vxfnreset(vx, cp)
1116 	register int vx;
1117 	register struct vxcmd *cp;
1118 {
1119 	register struct vx_softc *vs;
1120 	register struct vxdevice *vp ;
1121 	register struct tty *tp, *tp0;
1122 	register int i;
1123 #ifdef notdef
1124 	register int on;
1125 #endif
1126 	extern int vxrestart();
1127 	int s = spl8();
1128 
1129 	vs = &vx_softc[vx];
1130 	vs->vs_loport = cp->par[5];
1131 	vs->vs_hiport = cp->par[7];
1132 	vrelease(vs, cp);
1133 	vs->vs_nbr = vx;			/* assign VIOC-X board number */
1134 	vs->vs_state = VXS_READY;
1135 
1136 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
1137 	vp->v_vcid = 0;
1138 
1139 	/*
1140 	 * Restore modem information and control.
1141 	 */
1142 	tp0 = &vx_tty[vx*16];
1143 	for (i = vs->vs_loport; i <= vs->vs_hiport; i++) {
1144 		tp = tp0 + i;
1145 		if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) {
1146 			tp->t_state &= ~TS_CARR_ON;
1147 			vcmodem(tp->t_dev, VMOD_ON);
1148 			if (tp->t_state&TS_CARR_ON)
1149 				(void)(*linesw[tp->t_line].l_modem)(tp, 1);
1150 			else if (tp->t_state & TS_ISOPEN)
1151 				(void)(*linesw[tp->t_line].l_modem)(tp, 0);
1152 		}
1153 #ifdef notdef
1154 		/*
1155 		 * If carrier has changed while we were resetting,
1156 		 * take appropriate action.
1157 		 */
1158 		on = vp->v_dcd & 1<<i;
1159 		if (on && (tp->t_state&TS_CARR_ON) == 0)
1160 			(void)(*linesw[tp->t_line].l_modem)(tp, 1);
1161 		else if (!on && tp->t_state&TS_CARR_ON)
1162 			(void)(*linesw[tp->t_line].l_modem)(tp, 0);
1163 #endif
1164 	}
1165 	vs->vs_state = VXS_RESET;
1166 	timeout(vxrestart, (caddr_t)vx, hz);
1167 	splx(s);
1168 }
1169 
1170 /*
1171  * Restore a particular aspect of the VIOC.
1172  */
1173 vxrestart(vx)
1174 	int vx;
1175 {
1176 	register struct tty *tp, *tp0;
1177 	register struct vx_softc *vs;
1178 	register int i, count;
1179 	int s = spl8();
1180 
1181 	count = vx >> 8;
1182 	vx &= 0xff;
1183 	vs = &vx_softc[vx];
1184 	vs->vs_state = VXS_READY;
1185 	tp0 = &vx_tty[vx*16];
1186 	for (i = vs->vs_loport; i <= vs->vs_hiport; i++) {
1187 		tp = tp0 + i;
1188 		if (count != 0) {
1189 			tp->t_state &= ~(TS_BUSY|TS_TIMEOUT);
1190 			if (tp->t_state&(TS_ISOPEN|TS_WOPEN))
1191 				vxstart(tp);	/* restart pending output */
1192 		} else {
1193 			if (tp->t_state&(TS_WOPEN|TS_ISOPEN))
1194 				vxcparam(tp->t_dev, 0);
1195 		}
1196 	}
1197 	if (count == 0) {
1198 		vs->vs_state = VXS_RESET;
1199 		timeout(vxrestart, (caddr_t)(vx + 1*256), hz);
1200 	} else
1201 		printf("done\n");
1202 	splx(s);
1203 }
1204 
1205 vxreset(dev)
1206 	dev_t dev;
1207 {
1208 
1209 	vxstreset((int)VXUNIT(minor(dev)));	/* completes asynchronously */
1210 }
1211 
1212 #ifdef notdef
1213 vxfreset(vx)
1214 	register int vx;
1215 {
1216 	struct vba_device *vi;
1217 
1218 	if ((unsigned)vx > NVX || (vi = vxinfo[vx]) == 0 || vi->ui_addr == 0)
1219 		return (ENODEV);
1220 	vx_softc[vx].vs_state = VXS_READY;
1221 	vxstreset(vx);
1222 	return (0);		/* completes asynchronously */
1223 }
1224 #endif
1225 
1226 vcmodem(dev, flag)
1227 	dev_t dev;
1228 {
1229 	struct tty *tp;
1230 	register struct vxcmd *cp;
1231 	register struct vx_softc *vs;
1232 	register struct vxdevice *kp;
1233 	register port;
1234 	int unit;
1235 
1236 	unit = minor(dev);
1237 	tp = &vx_tty[unit];
1238 	vs = (struct vx_softc *)tp->t_addr;
1239 	if (vs->vs_state != VXS_READY)
1240 		return;
1241 	cp = vobtain(vs);
1242 	kp = (struct vxdevice *)((struct vba_device *)vxinfo[vs->vs_nbr])->ui_addr;
1243 
1244 	port = unit & 017;
1245 	/*
1246 	 * Issue MODEM command
1247 	 */
1248 	cp->cmd = VXC_MDMCTL;
1249 	if (flag == VMOD_ON) {
1250 		if (vs->vs_softCAR & (1 << port))
1251 			cp->par[0] = V_MANUAL | V_DTR_ON | V_RTS;
1252 		else
1253 			cp->par[0] = V_AUTO | V_DTR_ON | V_RTS;
1254 	} else
1255 		cp->par[0] = V_DTR_OFF;
1256 	cp->par[1] = port;
1257 	(void) vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd);
1258 	if (vs->vs_softCAR & (1 << port))
1259 		kp->v_dcd |= (1 << port);
1260 	if ((kp->v_dcd | vs->vs_softCAR) & (1 << port) && flag == VMOD_ON)
1261 		tp->t_state |= TS_CARR_ON;
1262 }
1263 
1264 /*
1265  * VCMINTR called when an unsolicited interrup occurs signaling
1266  * some change of modem control state.
1267  */
1268 vcmintr(vx)
1269 	register vx;
1270 {
1271 	register struct vxdevice *kp;
1272 	register struct tty *tp;
1273 	register port;
1274 	register struct vx_softc *vs;
1275 
1276 	kp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
1277 	port = kp->v_usdata[0] & 017;
1278 	tp = &vx_tty[vx*16+port];
1279 	vs = &vx_softc[vx];
1280 
1281 	if (kp->v_ustat & DCD_ON)
1282 		(void)(*linesw[tp->t_line].l_modem)(tp, 1);
1283 	else if ((kp->v_ustat & DCD_OFF) &&
1284 	    ((vs->vs_softCAR & (1 << port))) == 0 &&
1285 	    (*linesw[tp->t_line].l_modem)(tp, 0) == 0) {
1286 		register struct vcmds *cp;
1287 		register struct vxcmd *cmdp;
1288 
1289 		/* clear all pending transmits */
1290 		if (tp->t_state&(TS_BUSY|TS_FLUSH) &&
1291 		    vs->vs_vers == VXV_NEW) {
1292 			int i, cmdfound = 0;
1293 
1294 			cp = &vs->vs_cmds;
1295 			for (i = cp->v_empty; i != cp->v_fill; ) {
1296 				cmdp = (struct vxcmd *)((long *)cp->cmdbuf[i]-1);
1297 				if ((cmdp->cmd == VXC_XMITDTA ||
1298 				    cmdp->cmd == VXC_XMITIMM) &&
1299 				    ((struct vxmit *)cmdp->par)->line == port) {
1300 					cmdfound++;
1301 					cmdp->cmd = VXC_FDTATOX;
1302 					cmdp->par[1] = port;
1303 				}
1304 				if (++i >= VC_CMDBUFL)
1305 					i = 0;
1306 			}
1307 			if (cmdfound)
1308 				tp->t_state &= ~(TS_BUSY|TS_FLUSH);
1309 			/* cmd is already in vioc, have to flush it */
1310 			else {
1311 				cmdp = vobtain(vs);
1312 				cmdp->cmd = VXC_FDTATOX;
1313 				cmdp->par[1] = port;
1314 				(void) vcmd(vx, (caddr_t)&cmdp->cmd);
1315 			}
1316 		}
1317 	} else if ((kp->v_ustat&BRK_CHR) && (tp->t_state&TS_ISOPEN)) {
1318 		(*linesw[tp->t_line].l_rint)((tp->t_flags & RAW) ?
1319 		    0 : tp->t_intrc, tp);
1320 		return;
1321 	}
1322 }
1323 #endif
1324