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