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