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