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