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