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