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