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