xref: /csrg-svn/sys/tahoe/vba/vx.c (revision 38114)
134406Skarels /*
234406Skarels  * Copyright (c) 1988 Regents of the University of California.
335057Skarels  * All rights reserved.
434406Skarels  *
535057Skarels  * This code is derived from software contributed to Berkeley by
635057Skarels  * Computer Consoles Inc.
735057Skarels  *
835057Skarels  * Redistribution and use in source and binary forms are permitted
935057Skarels  * provided that the above copyright notice and this paragraph are
1035057Skarels  * duplicated in all such forms and that any documentation,
1135057Skarels  * advertising materials, and other materials related to such
1235057Skarels  * distribution and use acknowledge that the software was developed
1335057Skarels  * by the University of California, Berkeley.  The name of the
1435057Skarels  * University may not be used to endorse or promote products derived
1535057Skarels  * from this software without specific prior written permission.
1635057Skarels  * THIS SOFTWARE IS PROVIDED ``AS IS'' AND WITHOUT ANY EXPRESS OR
1735057Skarels  * IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED
1835057Skarels  * WARRANTIES OF MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE.
1935057Skarels  *
20*38114Sbostic  *	@(#)vx.c	7.5 (Berkeley) 05/23/89
2134406Skarels  */
2224003Ssam 
2324003Ssam #include "vx.h"
2424003Ssam #if NVX > 0
2524003Ssam /*
2625857Ssam  * VIOC-X driver
2724003Ssam  */
2825877Ssam #ifdef VXPERF
2925948Ssam #define	DOSCOPE
3025877Ssam #endif
3125877Ssam 
3225877Ssam #include "param.h"
3325877Ssam #include "ioctl.h"
3425877Ssam #include "tty.h"
3525877Ssam #include "user.h"
3625877Ssam #include "map.h"
3725877Ssam #include "buf.h"
3825877Ssam #include "conf.h"
3925877Ssam #include "file.h"
4025877Ssam #include "proc.h"
4125877Ssam #include "vm.h"
4225881Ssam #include "kernel.h"
4329954Skarels #include "syslog.h"
4425675Ssam 
4534406Skarels #include "../tahoe/pte.h"
4634406Skarels 
4725675Ssam #include "../tahoevba/vbavar.h"
48*38114Sbostic #include "../tahoevba/vbaparam.h"
4925881Ssam #include "../tahoevba/vxreg.h"
5025675Ssam #include "../tahoevba/scope.h"
5124003Ssam 
5225881Ssam #ifdef VX_DEBUG
5325881Ssam long	vxintr4 = 0;
5425948Ssam #define	VXERR4	1
5525948Ssam #define	VXNOBUF	2
5625881Ssam long	vxdebug = 0;
5725948Ssam #define	VXVCM	1
5825948Ssam #define	VXVCC	2
5925948Ssam #define	VXVCX	4
6025881Ssam #endif
6124003Ssam 
6225881Ssam /*
6325881Ssam  * Interrupt type bits passed to vinthandl().
6425881Ssam  */
6525948Ssam #define	CMDquals 0		/* command completed interrupt */
6625948Ssam #define	RSPquals 1		/* command response interrupt */
6725948Ssam #define	UNSquals 2		/* unsolicited interrupt */
6824003Ssam 
6930372Skarels #define	VXUNIT(n)	((n) >> 4)
7030372Skarels #define	VXPORT(n)	((n) & 0xf)
7130372Skarels 
7225881Ssam struct	tty vx_tty[NVX*16];
7329954Skarels #ifndef lint
7429954Skarels int	nvx = NVX*16;
7529954Skarels #endif
7625881Ssam int	vxstart(), ttrstrt();
7725881Ssam struct	vxcmd *vobtain(), *nextcmd();
7824003Ssam 
7924003Ssam /*
8024003Ssam  * Driver information for auto-configuration stuff.
8124003Ssam  */
8224003Ssam int	vxprobe(), vxattach(), vxrint();
8325881Ssam struct	vba_device *vxinfo[NVX];
8424003Ssam long	vxstd[] = { 0 };
8524003Ssam struct	vba_driver vxdriver =
8625857Ssam     { vxprobe, 0, vxattach, 0, vxstd, "vx", vxinfo };
8724003Ssam 
8825881Ssam struct	vx_softc {
8925881Ssam 	u_char	vs_type;	/* 0: viox-x/vioc-b, 1: vioc-bop */
9025881Ssam 	u_char	vs_bop;		/* bop board # for vioc-bop's */
9125881Ssam 	u_char	vs_loport;	/* low port nbr */
9225881Ssam 	u_char	vs_hiport;	/* high port nbr */
9325881Ssam 	u_short	vs_nbr;		/* viocx number */
9425881Ssam 	u_short	vs_maxcmd;	/* max number of concurrent cmds */
9525881Ssam 	u_short	vs_silosiz;	/* silo size */
9625881Ssam 	short	vs_vers;	/* vioc/pvioc version */
9725948Ssam #define	VXV_OLD	0		/* PVIOCX | VIOCX */
9825948Ssam #define	VXV_NEW	1		/* NPVIOCX | NVIOCX */
9925881Ssam 	short	vs_xmtcnt;	/* xmit commands pending */
10025881Ssam 	short	vs_brkreq;	/* send break requests pending */
10125881Ssam 	short 	vs_state;	/* controller state */
10225948Ssam #define	VXS_READY	0	/* ready for commands */
10325948Ssam #define	VXS_RESET	1	/* in process of reseting */
10430372Skarels 	u_short	vs_softCAR;	/* soft carrier */
10525881Ssam 	caddr_t vs_mricmd;	/* most recent issued cmd */
10625881Ssam 	u_int	vs_ivec;	/* interrupt vector base */
10725881Ssam 	struct	vxcmd *vs_avail;/* next available command buffer */
10825881Ssam 	struct	vxcmd *vs_build;
10925881Ssam 	struct	vxcmd vs_lst[NVCXBUFS];
11025881Ssam 	struct	vcmds vs_cmds;
11125881Ssam } vx_softc[NVX];
11224003Ssam 
11337608Smarc struct speedtab vxspeedtab[] = {
11437608Smarc 	EXTA,	V19200,
11537608Smarc 	EXTB,	V19200,
11637608Smarc 	19200,	V19200,
11737608Smarc 	9600,	13,
11837608Smarc 	4800,	12,
11937608Smarc 	2400,	11,
12037608Smarc 	1800,	10,
12137608Smarc 	1200,	9,
12237608Smarc 	600,	8,
12337608Smarc 	300,	7,
12437608Smarc 	200,	6,
12537608Smarc 	150,	5,
12637608Smarc 	134,	4,
12737608Smarc 	110,	3,
12837608Smarc 	75,	2,
12937608Smarc 	50,	1,
13037608Smarc 	0,	0,
13137608Smarc 	-1,	-1,
13237608Smarc };
13337608Smarc 
13425857Ssam vxprobe(reg, vi)
13524003Ssam 	caddr_t reg;
13625857Ssam 	struct vba_device *vi;
13724003Ssam {
13825857Ssam 	register int br, cvec;			/* must be r12, r11 */
139*38114Sbostic 	register struct vxdevice *vp;
14025881Ssam 	register struct vx_softc *vs;
141*38114Sbostic 	struct pte *dummypte;
14224003Ssam 
14324003Ssam #ifdef lint
14424003Ssam 	br = 0; cvec = br; br = cvec;
14525675Ssam 	vackint(0); vunsol(0); vcmdrsp(0); vxfreset(0);
14624003Ssam #endif
147*38114Sbostic 	if (!VBIOMAPPED(reg) && !vbmemalloc(16, reg, &dummypte, &reg)) {
148*38114Sbostic 		printf("vx%d: vbmemalloc failed.\n", vi->ui_unit);
149*38114Sbostic 		return(0);
150*38114Sbostic 	}
151*38114Sbostic 	vp = (struct vxdevice *)reg;
15225675Ssam 	if (badaddr((caddr_t)vp, 1))
15325675Ssam 		return (0);
15425675Ssam 	vp->v_fault = 0;
15525675Ssam 	vp->v_vioc = V_BSY;
15625675Ssam 	vp->v_hdwre = V_RESET;		/* reset interrupt */
15724003Ssam 	DELAY(4000000);
15825881Ssam 	if (vp->v_fault != VXF_READY)
15925675Ssam 		return (0);
16025881Ssam 	vs = &vx_softc[vi->ui_unit];
16125857Ssam #ifdef notdef
16225857Ssam 	/*
16325857Ssam 	 * Align vioc interrupt vector base to 4 vector
16425857Ssam 	 * boundary and fitting in 8 bits (is this necessary,
16525857Ssam 	 * wish we had documentation).
16625857Ssam 	 */
16725857Ssam 	if ((vi->ui_hd->vh_lastiv -= 3) > 0xff)
16825857Ssam 		vi->ui_hd->vh_lastiv = 0xff;
16925881Ssam 	vs->vs_ivec = vi->ui_hd->vh_lastiv = vi->ui_hd->vh_lastiv &~ 0x3;
17025857Ssam #else
17125881Ssam 	vs->vs_ivec = 0x40+vi->ui_unit*4;
17225857Ssam #endif
17325881Ssam 	br = 0x18, cvec = vs->vs_ivec;	/* XXX */
17425881Ssam 	return (sizeof (struct vxdevice));
17524003Ssam }
17624003Ssam 
17725857Ssam vxattach(vi)
17825857Ssam 	register struct vba_device *vi;
17924003Ssam {
18025675Ssam 
18130372Skarels 	vx_softc[vi->ui_unit].vs_softCAR = vi->ui_flags;
18229954Skarels 	vxinit(vi->ui_unit, 1);
18324003Ssam }
18424003Ssam 
18524003Ssam /*
18624003Ssam  * Open a VX line.
18724003Ssam  */
18825675Ssam /*ARGSUSED*/
18924003Ssam vxopen(dev, flag)
19025881Ssam 	dev_t dev;
19125881Ssam 	int flag;
19224003Ssam {
19324003Ssam 	register struct tty *tp;	/* pointer to tty struct for port */
19425881Ssam 	register struct vx_softc *vs;
19525881Ssam 	register struct vba_device *vi;
19625881Ssam 	int unit, vx, s, error;
19737608Smarc 	int vxparam();
19824003Ssam 
19925881Ssam 	unit = minor(dev);
20030372Skarels 	vx = VXUNIT(unit);
20130372Skarels 	if (vx >= NVX || (vi = vxinfo[vx])== 0 || vi->ui_alive == 0)
20225881Ssam 		return (ENXIO);
20330372Skarels 	vs = &vx_softc[vx];
20425881Ssam 	tp = &vx_tty[unit];
20530372Skarels 	unit = VXPORT(unit);
20625881Ssam 	if (tp->t_state&TS_XCLUDE && u.u_uid != 0)
20725881Ssam 		return (EBUSY);
20830372Skarels 	if (unit < vs->vs_loport || unit > vs->vs_hiport)
20925881Ssam 		return (ENXIO);
21025881Ssam 	tp->t_addr = (caddr_t)vs;
21125881Ssam 	tp->t_oproc = vxstart;
21237608Smarc 	tp->t_param = vxparam;
21325881Ssam 	tp->t_dev = dev;
21425881Ssam 	s = spl8();
21525881Ssam 	tp->t_state |= TS_WOPEN;
21625881Ssam 	if ((tp->t_state&TS_ISOPEN) == 0) {
21725881Ssam 		ttychars(tp);
21825881Ssam 		if (tp->t_ispeed == 0) {
21937608Smarc 			tp->t_iflag = TTYDEF_IFLAG;
22037608Smarc 			tp->t_oflag = TTYDEF_OFLAG;
22137608Smarc 			tp->t_lflag = TTYDEF_LFLAG;
22237608Smarc 			tp->t_cflag = TTYDEF_CFLAG;
22337608Smarc 			tp->t_ispeed = tp->t_ospeed = TTYDEF_SPEED;
22424003Ssam 		}
22537608Smarc 		vxparam(tp, &tp->t_termios);
22637608Smarc 		ttsetwater(tp);
22724003Ssam 	}
22830372Skarels 	vcmodem(dev, VMOD_ON);
22937608Smarc 	while (!(flag&O_NONBLOCK) && !(tp->t_cflag&CLOCAL) &&
23037608Smarc 	      (tp->t_state&TS_CARR_ON) == 0)
23130372Skarels 		sleep((caddr_t)&tp->t_rawq, TTIPRI);
23225881Ssam 	error = (*linesw[tp->t_line].l_open)(dev,tp);
23325881Ssam 	splx(s);
23425881Ssam 	return (error);
23524003Ssam }
23624003Ssam 
23724003Ssam /*
23824003Ssam  * Close a VX line.
23924003Ssam  */
24025675Ssam /*ARGSUSED*/
24124003Ssam vxclose(dev, flag)
24225881Ssam 	dev_t dev;
24325881Ssam 	int flag;
24424003Ssam {
24524003Ssam 	register struct tty *tp;
24625881Ssam 	int unit, s;
24724003Ssam 
24825881Ssam 	unit = minor(dev);
24925881Ssam 	tp = &vx_tty[unit];
25025881Ssam 	s = spl8();
25124003Ssam 	(*linesw[tp->t_line].l_close)(tp);
25237608Smarc 	if (tp->t_cflag & HUPCL || (tp->t_state & TS_ISOPEN) == 0)
25330372Skarels 		vcmodem(dev, VMOD_OFF);
25424003Ssam 	/* wait for the last response */
25525881Ssam 	while (tp->t_state&TS_FLUSH)
25625881Ssam 		sleep((caddr_t)&tp->t_state, TTOPRI);
25725881Ssam 	ttyclose(tp);
25825881Ssam 	splx(s);
25924003Ssam }
26024003Ssam 
26124003Ssam /*
26224003Ssam  * Read from a VX line.
26324003Ssam  */
26437608Smarc vxread(dev, uio, flag)
26524003Ssam 	dev_t dev;
26624003Ssam 	struct uio *uio;
26724003Ssam {
26825881Ssam 	struct tty *tp = &vx_tty[minor(dev)];
26925881Ssam 
27037608Smarc 	return ((*linesw[tp->t_line].l_read)(tp, uio, flag));
27124003Ssam }
27224003Ssam 
27324003Ssam /*
27424003Ssam  * write on a VX line
27524003Ssam  */
27637608Smarc vxwrite(dev, uio, flag)
27724003Ssam 	dev_t dev;
27824003Ssam 	struct uio *uio;
27924003Ssam {
28025881Ssam 	register struct tty *tp = &vx_tty[minor(dev)];
28125881Ssam 
28237608Smarc 	return ((*linesw[tp->t_line].l_write)(tp, uio, flag));
28324003Ssam }
28424003Ssam 
28524003Ssam /*
28624003Ssam  * VIOCX unsolicited interrupt.
28724003Ssam  */
28825881Ssam vxrint(vx)
28925881Ssam 	register vx;
29024003Ssam {
29125881Ssam 	register struct tty *tp, *tp0;
29225881Ssam 	register struct vxdevice *addr;
29325881Ssam 	register struct vx_softc *vs;
29425881Ssam 	struct vba_device *vi;
29525881Ssam 	register int nc, c;
29625881Ssam 	register struct silo {
29725881Ssam 		char	data, port;
29825881Ssam 	} *sp;
29925881Ssam 	short *osp;
30025881Ssam 	int overrun = 0;
30124003Ssam 
30225881Ssam 	vi = vxinfo[vx];
30325881Ssam 	if (vi == 0 || vi->ui_alive == 0)
30425881Ssam 		return;
30525881Ssam 	addr = (struct vxdevice *)vi->ui_addr;
30625881Ssam 	switch (addr->v_uqual&037) {
30724003Ssam 	case 0:
30824003Ssam 		break;
30924003Ssam 	case 2:
31030372Skarels 		printf("vx%d: vc proc err, ustat %x\n", vx, addr->v_ustat);
31125881Ssam 		vxstreset(vx);
31230372Skarels 		return;
31324003Ssam 	case 3:
31425881Ssam 		vcmintr(vx);
31530372Skarels 		return;
31624003Ssam 	case 4:
31730372Skarels 		return;
31824003Ssam 	default:
31930372Skarels 		printf("vx%d: vc uqual err, uqual %x\n", vx, addr->v_uqual);
32025881Ssam 		vxstreset(vx);
32130372Skarels 		return;
32224003Ssam 	}
32325881Ssam 	vs = &vx_softc[vx];
32425881Ssam 	if (vs->vs_vers == VXV_NEW)
32525881Ssam 		sp = (struct silo *)((caddr_t)addr + *(short *)addr->v_usdata);
32625881Ssam 	else
32725881Ssam 		sp = (struct silo *)((caddr_t)addr+VX_SILO+(addr->v_usdata[0]<<6));
32825881Ssam 	nc = *(osp = (short *)sp);
32925881Ssam 	if (nc == 0)
33030372Skarels 		return;
33125881Ssam 	if (vs->vs_vers == VXV_NEW && nc > vs->vs_silosiz) {
33225881Ssam 		printf("vx%d: %d exceeds silo size\n", nc);
33325881Ssam 		nc = vs->vs_silosiz;
33424003Ssam 	}
33525881Ssam 	tp0 = &vx_tty[vx*16];
33625881Ssam 	sp = (struct silo *)(((short *)sp)+1);
33725881Ssam 	for (; nc > 0; nc--, sp = (struct silo *)(((short *)sp)+1)) {
33825881Ssam 		c = sp->port & 017;
33925881Ssam 		if (vs->vs_loport > c || c > vs->vs_hiport)
34025881Ssam 			continue;
34125881Ssam 		tp = tp0 + c;
34225881Ssam 		if( (tp->t_state&TS_ISOPEN) == 0) {
34324003Ssam 			wakeup((caddr_t)&tp->t_rawq);
34424003Ssam 			continue;
34524003Ssam 		}
34637608Smarc 		c = sp->data&((tp->t_cflag&CSIZE)==CS8 ? 0xff : 0x7f);
34725881Ssam 		if ((sp->port&VX_RO) == VX_RO && !overrun) {
34829954Skarels 			log(LOG_ERR, "vx%d: receiver overrun\n", vi->ui_unit);
34925881Ssam 			overrun = 1;
35025881Ssam 			continue;
35125881Ssam 		}
35225881Ssam 		if (sp->port&VX_PE)
35337608Smarc 			c |= TTY_PE;
35437608Smarc 		if (sp->port&VX_FE)
35537608Smarc 			c |= TTY_FE;
35624003Ssam 		(*linesw[tp->t_line].l_rint)(c, tp);
35724003Ssam 	}
35825881Ssam 	*osp = 0;
35924003Ssam }
36024003Ssam 
36124003Ssam /*
36225881Ssam  * Ioctl for VX.
36324003Ssam  */
36424003Ssam vxioctl(dev, cmd, data, flag)
36525881Ssam 	dev_t dev;
36625881Ssam 	caddr_t	data;
36724003Ssam {
36825881Ssam 	register struct tty *tp;
36925881Ssam 	int error;
37024003Ssam 
37125881Ssam 	tp = &vx_tty[minor(dev)];
37224003Ssam 	error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag);
37337608Smarc 	if (error >= 0)
37425881Ssam 		return (error);
37525881Ssam 	error = ttioctl(tp, cmd, data, flag);
37637608Smarc 	if (error >= 0)
37725881Ssam 		return (error);
37825881Ssam 	return (ENOTTY);
37924003Ssam }
38024003Ssam 
38137608Smarc vxparam(tp, t)
38237608Smarc 	struct tty *tp;
38337608Smarc 	struct termios *t;
38424003Ssam {
38525881Ssam 
38637608Smarc 	return (vxcparam(tp, t, 1));
38724003Ssam }
38824003Ssam 
38924003Ssam /*
39024003Ssam  * Set parameters from open or stty into the VX hardware
39124003Ssam  * registers.
39224003Ssam  */
39337608Smarc vxcparam(tp, t, wait)
39437608Smarc 	struct tty *tp;
39537608Smarc 	struct termios *t;
39625881Ssam 	int wait;
39724003Ssam {
39825881Ssam 	register struct vx_softc *vs;
39925881Ssam 	register struct vxcmd *cp;
40037608Smarc 	dev_t dev = tp->t_dev;
40125933Ssam 	int s, unit = minor(dev);
40237608Smarc 	int speedcode = ttspeedtab(t->c_ospeed, vxspeedtab);
40324003Ssam 
40437608Smarc 	if (speedcode < 0 || (t->c_ispeed != t->c_ospeed && t->c_ispeed))
40537608Smarc 		return(EINVAL);
40625881Ssam 	vs = (struct vx_softc *)tp->t_addr;
40725881Ssam 	cp = vobtain(vs);
40824003Ssam 	s = spl8();
40925933Ssam 	/*
41025933Ssam 	 * Construct ``load parameters'' command block
41125933Ssam 	 * to setup baud rates, xon-xoff chars, parity,
41225933Ssam 	 * and stop bits for the specified port.
41325933Ssam 	 */
41425933Ssam 	cp->cmd = VXC_LPARAX;
41530372Skarels 	cp->par[1] = VXPORT(unit);
41637608Smarc 	/*
41737608Smarc 	 * note: if the hardware does flow control, ^V doesn't work
41837608Smarc 	 * to escape ^S
41937608Smarc 	 */
42037608Smarc 	if (t->c_iflag&IXON) {
42137608Smarc 		if (t->c_cc[VSTART] == _POSIX_VDISABLE)
42237608Smarc 			cp->par[2] = 0;
42337608Smarc 		else
42437608Smarc 			cp->par[2] = t->c_cc[VSTART];
42537608Smarc 		if (t->c_cc[VSTOP] == _POSIX_VDISABLE)
42637608Smarc 			cp->par[3] = 0;
42737608Smarc 		else
42837608Smarc 			cp->par[3] = t->c_cc[VSTOP];
42937608Smarc 	} else
43037608Smarc 		cp->par[2] = cp->par[3] = 0;
43130372Skarels #ifdef notnow
43237608Smarc 	if (tp->t_flags & (RAW|LITOUT|PASS8)) {	/* XXX */
43330372Skarels #endif
43430372Skarels 		cp->par[4] = BITS8;		/* 8 bits of data */
43530372Skarels 		cp->par[7] = VNOPARITY;		/* no parity */
43630372Skarels #ifdef notnow
43724003Ssam 	} else {
43830372Skarels 		cp->par[4] = BITS7;		/* 7 bits of data */
43925881Ssam 		if ((tp->t_flags&(EVENP|ODDP)) == ODDP)
44030372Skarels 			cp->par[7] = VODDP;	/* odd parity */
44129954Skarels 		else
44230372Skarels 			cp->par[7] = VEVENP;	/* even parity */
44324003Ssam 	}
44430372Skarels #endif
44537608Smarc 	cp->par[5] = (t->c_cflag&CSTOPB) ? VSTOP2 : VSTOP1;
44637608Smarc 	cp->par[6] = speedcode;
44730372Skarels 	if (vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd) && wait)
44825675Ssam 		sleep((caddr_t)cp,TTIPRI);
44937608Smarc 	if ((t->c_ospeed)==0) {
45037608Smarc 		tp->t_cflag |= HUPCL;
45137608Smarc 		vcmodem(dev, VMOD_OFF);
45237608Smarc 	}
45324003Ssam 	splx(s);
45437608Smarc 	return 0;
45524003Ssam }
45624003Ssam 
45724003Ssam /*
45824003Ssam  * VIOCX command response interrupt.
45924003Ssam  * For transmission, restart output to any active port.
46024003Ssam  * For all other commands, just clean up.
46124003Ssam  */
46225881Ssam vxxint(vx, cp)
46325881Ssam 	register int vx;
46425881Ssam 	register struct vxcmd *cp;
46524003Ssam {
46630372Skarels 	register struct vxmit *vp;
46725933Ssam 	register struct tty *tp, *tp0;
46825933Ssam 	register struct vx_softc *vs;
46924003Ssam 
47025881Ssam 	vs = &vx_softc[vx];
47125881Ssam 	cp = (struct vxcmd *)((long *)cp-1);
47229954Skarels 
47325881Ssam 	switch (cp->cmd&0xff00) {
47425881Ssam 
47525881Ssam 	case VXC_LIDENT:	/* initialization complete */
47625881Ssam 		if (vs->vs_state == VXS_RESET) {
47725881Ssam 			vxfnreset(vx, cp);
47825881Ssam 			vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
47924003Ssam 		}
48024003Ssam 		cp->cmd++;
48124003Ssam 		return;
48225881Ssam 
48325881Ssam 	case VXC_XMITDTA:
48425881Ssam 	case VXC_XMITIMM:
48524003Ssam 		break;
48625881Ssam 
48725881Ssam 	case VXC_LPARAX:
48825675Ssam 		wakeup((caddr_t)cp);
48925881Ssam 		/* fall thru... */
49025881Ssam 	default:	/* VXC_MDMCTL or VXC_FDTATOX */
49125881Ssam 		vrelease(vs, cp);
49225881Ssam 		if (vs->vs_state == VXS_RESET)
49325881Ssam 			vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
49424003Ssam 		return;
49524003Ssam 	}
49625881Ssam 	tp0 = &vx_tty[vx*16];
49725881Ssam 	vp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit));
49825881Ssam 	for (; vp >= (struct vxmit *)cp->par; vp--) {
49925881Ssam 		tp = tp0 + (vp->line & 017);
50024003Ssam 		tp->t_state &= ~TS_BUSY;
50125881Ssam 		if (tp->t_state & TS_FLUSH) {
50224003Ssam 			tp->t_state &= ~TS_FLUSH;
50325881Ssam 			wakeup((caddr_t)&tp->t_state);
50425881Ssam 		} else
50524003Ssam 		 	ndflush(&tp->t_outq, vp->bcount+1);
50624003Ssam 	}
50725881Ssam 	vrelease(vs, cp);
50830372Skarels 	if (vs->vs_vers == VXV_NEW)
50932112Skarels 		(*linesw[tp->t_line].l_start)(tp);
51030372Skarels 	else {
51125881Ssam 		tp0 = &vx_tty[vx*16 + vs->vs_hiport];
51225881Ssam 		for(tp = &vx_tty[vx*16 + vs->vs_loport]; tp <= tp0; tp++)
51332112Skarels 			(*linesw[tp->t_line].l_start)(tp);
51425881Ssam 		if ((cp = nextcmd(vs)) != NULL) {	/* command to send? */
51525881Ssam 			vs->vs_xmtcnt++;
51630372Skarels 			(void) vcmd(vx, (caddr_t)&cp->cmd);
51724003Ssam 		}
51824003Ssam 	}
51930372Skarels 	vs->vs_xmtcnt--;
52024003Ssam }
52124003Ssam 
52224003Ssam /*
52324003Ssam  * Force out partial XMIT command after timeout
52424003Ssam  */
52525881Ssam vxforce(vs)
52625881Ssam 	register struct vx_softc *vs;
52724003Ssam {
52825881Ssam 	register struct vxcmd *cp;
52925881Ssam 	int s;
53024003Ssam 
53124003Ssam 	s = spl8();
53225881Ssam 	if ((cp = nextcmd(vs)) != NULL) {
53325881Ssam 		vs->vs_xmtcnt++;
53430372Skarels 		(void) vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd);
53524003Ssam 	}
53624003Ssam 	splx(s);
53724003Ssam }
53824003Ssam 
53924003Ssam /*
54024003Ssam  * Start (restart) transmission on the given VX line.
54124003Ssam  */
54224003Ssam vxstart(tp)
54325881Ssam 	register struct tty *tp;
54424003Ssam {
54525675Ssam 	register short n;
54625933Ssam 	register struct vx_softc *vs;
54725933Ssam 	int s, port;
54824003Ssam 
54924003Ssam 	s = spl8();
55024003Ssam 	port = minor(tp->t_dev) & 017;
55125881Ssam 	vs = (struct vx_softc *)tp->t_addr;
55225881Ssam 	if ((tp->t_state&(TS_TIMEOUT|TS_BUSY|TS_TTSTOP)) == 0) {
55337608Smarc 		if (tp->t_outq.c_cc <= tp->t_lowat) {
55424003Ssam 			if (tp->t_state&TS_ASLEEP) {
55524003Ssam 				tp->t_state &= ~TS_ASLEEP;
55624003Ssam 				wakeup((caddr_t)&tp->t_outq);
55724003Ssam 			}
55824003Ssam 			if (tp->t_wsel) {
55924003Ssam 				selwakeup(tp->t_wsel, tp->t_state & TS_WCOLL);
56024003Ssam 				tp->t_wsel = 0;
56124003Ssam 				tp->t_state &= ~TS_WCOLL;
56224003Ssam 			}
56324003Ssam 		}
56425881Ssam 		if (tp->t_outq.c_cc == 0) {
56524003Ssam 			splx(s);
56630372Skarels 			return;
56724003Ssam 		}
56825877Ssam 		scope_out(3);
56937608Smarc 		if (1 || !(tp->t_oflag&OPOST))	/* XXX */
57030372Skarels 			n = ndqb(&tp->t_outq, 0);
57130372Skarels 		else {
57230372Skarels 			n = ndqb(&tp->t_outq, 0200);
57330372Skarels 			if (n == 0) {
57425675Ssam 				n = getc(&tp->t_outq);
57525881Ssam 				timeout(ttrstrt, (caddr_t)tp, (n&0177)+6);
57624003Ssam 				tp->t_state |= TS_TIMEOUT;
57730372Skarels 				n = 0;
57824003Ssam 			}
57930372Skarels 		}
58030372Skarels 		if (n) {
58124003Ssam 			tp->t_state |= TS_BUSY;
58230372Skarels 			vsetq(vs, port, (char *)tp->t_outq.c_cf, n);
58324003Ssam 		}
58424003Ssam 	}
58524003Ssam 	splx(s);
58624003Ssam }
58724003Ssam 
58824003Ssam /*
58924003Ssam  * Stop output on a line.
59024003Ssam  */
59124003Ssam vxstop(tp)
59225881Ssam 	register struct tty *tp;
59324003Ssam {
59425881Ssam 	int s;
59524003Ssam 
59624003Ssam 	s = spl8();
59725881Ssam 	if (tp->t_state&TS_BUSY)
59825881Ssam 		if ((tp->t_state&TS_TTSTOP) == 0)
59924003Ssam 			tp->t_state |= TS_FLUSH;
60024003Ssam 	splx(s);
60124003Ssam }
60224003Ssam 
60325881Ssam static	int vxbbno = -1;
60424003Ssam /*
60524003Ssam  * VIOCX Initialization.  Makes free lists of command buffers.
60624003Ssam  * Resets all viocx's.  Issues a LIDENT command to each
60725933Ssam  * viocx to establish interrupt vectors and logical port numbers.
60824003Ssam  */
60925881Ssam vxinit(vx, wait)
61025881Ssam 	register int vx;
61125881Ssam 	int wait;
61224003Ssam {
61325933Ssam 	register struct vx_softc *vs;
61425933Ssam 	register struct vxdevice *addr;
61525933Ssam 	register struct vxcmd *cp;
61625881Ssam 	register char *resp;
61725881Ssam 	register int j;
61830372Skarels 	char type, *typestring;
61924003Ssam 
62025881Ssam 	vs = &vx_softc[vx];
62125933Ssam 	vs->vs_type = 0;		/* vioc-x by default */
62225933Ssam 	addr = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
62325881Ssam 	type = addr->v_ident;
62425881Ssam 	vs->vs_vers = (type&VXT_NEW) ? VXV_NEW : VXV_OLD;
62525881Ssam 	if (vs->vs_vers == VXV_NEW)
62625881Ssam 		vs->vs_silosiz = addr->v_maxsilo;
62725881Ssam 	switch (type) {
62824003Ssam 
62925881Ssam 	case VXT_VIOCX:
63025881Ssam 	case VXT_VIOCX|VXT_NEW:
63130372Skarels 		typestring = "VIOC-X";
63230372Skarels 		/* set soft carrier for printer ports */
63330372Skarels 		for (j = 0; j < 16; j++)
63430372Skarels 			if (addr->v_portyp[j] == VXT_PARALLEL) {
63530372Skarels 				vs->vs_softCAR |= 1 << j;
63625881Ssam 				addr->v_dcd |= 1 << j;
63730372Skarels 			}
63825881Ssam 		break;
63924003Ssam 
64025881Ssam 	case VXT_PVIOCX:
64125881Ssam 	case VXT_PVIOCX|VXT_NEW:
64230372Skarels 		typestring = "VIOC-X (old connector panel)";
64325881Ssam 		break;
64425881Ssam 	case VXT_VIOCBOP:		/* VIOC-BOP */
64525881Ssam 		vs->vs_type = 1;
64625881Ssam 		vs->vs_bop = ++vxbbno;
64725881Ssam 		printf("VIOC-BOP no. %d at %x\n", vs->vs_bop, addr);
64824003Ssam 
64925933Ssam 	default:
65025881Ssam 		printf("vx%d: unknown type %x\n", vx, type);
65130372Skarels 		vxinfo[vx]->ui_alive = 0;
65225881Ssam 		return;
65324003Ssam 	}
65425881Ssam 	vs->vs_nbr = -1;
65525933Ssam 	vs->vs_maxcmd = (vs->vs_vers == VXV_NEW) ? 24 : 4;
65625933Ssam 	/*
65725933Ssam 	 * Initialize all cmd buffers by linking them
65825933Ssam 	 * into a free list.
65925933Ssam 	 */
66025881Ssam 	for (j = 0; j < NVCXBUFS; j++) {
66125933Ssam 		cp = &vs->vs_lst[j];
66225933Ssam 		cp->c_fwd = &vs->vs_lst[j+1];
66325881Ssam 	}
66425881Ssam 	vs->vs_avail = &vs->vs_lst[0];	/* set idx to 1st free buf */
66524003Ssam 	cp->c_fwd = (struct vxcmd *)0;	/* mark last buf in free list */
66624003Ssam 
66725933Ssam 	/*
66825933Ssam 	 * Establish the interrupt vectors and define the port numbers.
66925933Ssam 	 */
67025933Ssam 	cp = vobtain(vs);
67125933Ssam 	cp->cmd = VXC_LIDENT;
67225881Ssam 	cp->par[0] = vs->vs_ivec; 	/* ack vector */
67325857Ssam 	cp->par[1] = cp->par[0]+1;	/* cmd resp vector */
67425857Ssam 	cp->par[3] = cp->par[0]+2;	/* unsol intr vector */
67525881Ssam 	cp->par[4] = 15;		/* max ports, no longer used */
67625881Ssam 	cp->par[5] = 0;			/* set 1st port number */
67730372Skarels 	(void) vcmd(vx, (caddr_t)&cp->cmd);
67825881Ssam 	if (!wait)
67925881Ssam 		return;
68025881Ssam 	for (j = 0; cp->cmd == VXC_LIDENT && j < 4000000; j++)
68125857Ssam 		;
68225857Ssam 	if (j >= 4000000)
68325881Ssam 		printf("vx%d: didn't respond to LIDENT\n", vx);
68424003Ssam 
68524003Ssam  	/* calculate address of response buffer */
68625881Ssam  	resp = (char *)addr + (addr->v_rspoff&0x3fff);
68725933Ssam 	if (resp[0] != 0 && (resp[0]&0177) != 3) {
68825933Ssam 		vrelease(vs, cp);	/* init failed */
68925881Ssam 		return;
69024003Ssam 	}
69125881Ssam 	vs->vs_loport = cp->par[5];
69225881Ssam 	vs->vs_hiport = cp->par[7];
69330372Skarels 	printf("vx%d: %s%s, ports %d-%d\n", vx,
69430372Skarels 	    (vs->vs_vers == VXV_NEW) ? "" : "old ", typestring,
69530372Skarels 	    vs->vs_loport, vs->vs_hiport);
69625881Ssam 	vrelease(vs, cp);
69725933Ssam 	vs->vs_nbr = vx;		/* assign board number */
69824003Ssam }
69924003Ssam 
70024003Ssam /*
70124003Ssam  * Obtain a command buffer
70224003Ssam  */
70325881Ssam struct vxcmd *
70425881Ssam vobtain(vs)
70525933Ssam 	register struct vx_softc *vs;
70624003Ssam {
70725933Ssam 	register struct vxcmd *p;
70825881Ssam 	int s;
70924003Ssam 
71024003Ssam 	s = spl8();
71125881Ssam 	p = vs->vs_avail;
71225881Ssam 	if (p == (struct vxcmd *)0) {
71324003Ssam #ifdef VX_DEBUG
71425881Ssam 		if (vxintr4&VXNOBUF)
71525881Ssam 			vxintr4 &= ~VXNOBUF;
71624003Ssam #endif
71725881Ssam 		printf("vx%d: no buffers\n", vs - vx_softc);
71825881Ssam 		vxstreset(vs - vx_softc);
71924003Ssam 		splx(s);
72025881Ssam 		return (vobtain(vs));
72124003Ssam 	}
72230372Skarels 	vs->vs_avail = p->c_fwd;
72324003Ssam 	splx(s);
72425881Ssam 	return ((struct vxcmd *)p);
72524003Ssam }
72624003Ssam 
72724003Ssam /*
72824003Ssam  * Release a command buffer
72924003Ssam  */
73025881Ssam vrelease(vs, cp)
73125933Ssam 	register struct vx_softc *vs;
73225933Ssam 	register struct vxcmd *cp;
73324003Ssam {
73425881Ssam 	int s;
73524003Ssam 
73624003Ssam #ifdef VX_DEBUG
73725881Ssam 	if (vxintr4&VXNOBUF)
73825881Ssam 		return;
73924003Ssam #endif
74024003Ssam 	s = spl8();
74125881Ssam 	cp->c_fwd = vs->vs_avail;
74225881Ssam 	vs->vs_avail = cp;
74324003Ssam 	splx(s);
74424003Ssam }
74524003Ssam 
74625881Ssam struct vxcmd *
74725881Ssam nextcmd(vs)
74825933Ssam 	register struct vx_softc *vs;
74924003Ssam {
75025933Ssam 	register struct vxcmd *cp;
75125881Ssam 	int s;
75224003Ssam 
75324003Ssam 	s = spl8();
75425881Ssam 	cp = vs->vs_build;
75525881Ssam 	vs->vs_build = (struct vxcmd *)0;
75624003Ssam 	splx(s);
75725881Ssam 	return (cp);
75824003Ssam }
75924003Ssam 
76024003Ssam /*
76125933Ssam  * Assemble transmits into a multiple command;
76230372Skarels  * up to 8 transmits to 8 lines can be assembled together
76330372Skarels  * (on PVIOCX only).
76424003Ssam  */
76525933Ssam vsetq(vs, line, addr, n)
76625933Ssam 	register struct vx_softc *vs;
76725881Ssam 	caddr_t	addr;
76824003Ssam {
76925933Ssam 	register struct vxcmd *cp;
77025933Ssam 	register struct vxmit *mp;
77124003Ssam 
77225933Ssam 	/*
77325933Ssam 	 * Grab a new command buffer or append
77425933Ssam 	 * to the current one being built.
77525933Ssam 	 */
77625881Ssam 	cp = vs->vs_build;
77725881Ssam 	if (cp == (struct vxcmd *)0) {
77825881Ssam 		cp = vobtain(vs);
77925881Ssam 		vs->vs_build = cp;
78025881Ssam 		cp->cmd = VXC_XMITDTA;
78124003Ssam 	} else {
78230372Skarels 		if ((cp->cmd & 07) == 07 || vs->vs_vers == VXV_NEW) {
78325881Ssam 			printf("vx%d: setq overflow\n", vs-vx_softc);
78430372Skarels 			vxstreset((int)vs->vs_nbr);
78530372Skarels 			return;
78624003Ssam 		}
78724003Ssam 		cp->cmd++;
78824003Ssam 	}
78925933Ssam 	/*
79025933Ssam 	 * Select the next vxmit buffer and copy the
79125933Ssam 	 * characters into the buffer (if there's room
79225933Ssam 	 * and the device supports ``immediate mode'',
79325933Ssam 	 * or store an indirect pointer to the data.
79425933Ssam 	 */
79525881Ssam 	mp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit));
79625675Ssam 	mp->bcount = n-1;
79725933Ssam 	mp->line = line;
79825933Ssam 	if (vs->vs_vers == VXV_NEW && n <= sizeof (mp->ostream)) {
79925881Ssam 		cp->cmd = VXC_XMITIMM;
80030372Skarels 		bcopy(addr, mp->ostream, (unsigned)n);
80124003Ssam 	} else {
80225933Ssam 		/* get system address of clist block */
80325675Ssam 		addr = (caddr_t)vtoph((struct proc *)0, (unsigned)addr);
80430372Skarels 		bcopy((caddr_t)&addr, mp->ostream, sizeof (addr));
80524003Ssam 	}
80630372Skarels 	/*
80730372Skarels 	 * We send the data immediately if a VIOCX,
80830372Skarels 	 * the command buffer is full, or if we've nothing
80930372Skarels 	 * currently outstanding.  If we don't send it,
81030372Skarels 	 * set a timeout to force the data to be sent soon.
81130372Skarels 	 */
81230372Skarels 	if (vs->vs_vers == VXV_NEW || (cp->cmd & 07) == 7 ||
81330372Skarels 	    vs->vs_xmtcnt == 0) {
81430372Skarels 		vs->vs_xmtcnt++;
81530372Skarels 		(void) vcmd((int)vs->vs_nbr, (char *)&cp->cmd);
81630372Skarels 		vs->vs_build = 0;
81730372Skarels 	} else
81830372Skarels 		timeout(vxforce, (caddr_t)vs, 3);
81924003Ssam }
82025881Ssam 
82125881Ssam /*
82225881Ssam  * Write a command out to the VIOC
82325881Ssam  */
82425881Ssam vcmd(vx, cmdad)
82525881Ssam 	register int vx;
82625881Ssam 	register caddr_t cmdad;
82725881Ssam {
82825933Ssam 	register struct vcmds *cp;
82925881Ssam 	register struct vx_softc *vs;
83025881Ssam 	int s;
83125881Ssam 
83225881Ssam 	s = spl8();
83325881Ssam 	vs = &vx_softc[vx];
83425933Ssam 	/*
83525933Ssam 	 * When the vioc is resetting, don't process
83625933Ssam 	 * anything other than VXC_LIDENT commands.
83725933Ssam 	 */
83825881Ssam 	if (vs->vs_state == VXS_RESET && cmdad != NULL) {
83925933Ssam 		struct vxcmd *vcp = (struct vxcmd *)(cmdad-sizeof (vcp->c_fwd));
84025881Ssam 
84125933Ssam 		if (vcp->cmd != VXC_LIDENT) {
84225933Ssam 			vrelease(vs, vcp);
84325881Ssam 			return (0);
84425881Ssam 		}
84525881Ssam 	}
84625881Ssam 	cp = &vs->vs_cmds;
84725881Ssam 	if (cmdad != (caddr_t)0) {
84825881Ssam 		cp->cmdbuf[cp->v_fill] = cmdad;
84925881Ssam 		if (++cp->v_fill >= VC_CMDBUFL)
85025881Ssam 			cp->v_fill = 0;
85125881Ssam 		if (cp->v_fill == cp->v_empty) {
85225881Ssam 			printf("vx%d: cmd q overflow\n", vx);
85325881Ssam 			vxstreset(vx);
85425881Ssam 			splx(s);
85525881Ssam 			return (0);
85625881Ssam 		}
85725881Ssam 		cp->v_cmdsem++;
85825881Ssam 	}
85925881Ssam 	if (cp->v_cmdsem && cp->v_curcnt < vs->vs_maxcmd) {
86025881Ssam 		cp->v_cmdsem--;
86125881Ssam 		cp->v_curcnt++;
86225881Ssam 		vinthandl(vx, ((V_BSY|CMDquals) << 8)|V_INTR);
86325881Ssam 	}
86425881Ssam 	splx(s);
86525881Ssam 	return (1);
86625881Ssam }
86725881Ssam 
86825881Ssam /*
86925881Ssam  * VIOC acknowledge interrupt.  The VIOC has received the new
87025881Ssam  * command.  If no errors, the new command becomes one of 16 (max)
87125881Ssam  * current commands being executed.
87225881Ssam  */
87325881Ssam vackint(vx)
87425881Ssam 	register vx;
87525881Ssam {
87625933Ssam 	register struct vxdevice *vp;
87725933Ssam 	register struct vcmds *cp;
87825881Ssam 	struct vx_softc *vs;
87925881Ssam 	int s;
88025881Ssam 
88125881Ssam 	scope_out(5);
88225881Ssam 	vs = &vx_softc[vx];
88329954Skarels 	if (vs->vs_type)	/* Its a BOP */
88425881Ssam 		return;
88525881Ssam 	s = spl8();
88625881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
88725881Ssam 	cp = &vs->vs_cmds;
88825933Ssam 	if (vp->v_vcid&V_ERR) {
88925881Ssam 		register char *resp;
89025881Ssam 		register i;
89125933Ssam 
89230372Skarels 		printf("vx%d: ackint error type %x v_dcd %x\n", vx,
89325881Ssam 		    vp->v_vcid & 07, vp->v_dcd & 0xff);
89425881Ssam 		resp = (char *)vs->vs_mricmd;
89525881Ssam 		for (i = 0; i < 16; i++)
89625881Ssam 			printf("%x ", resp[i]&0xff);
89725881Ssam 		printf("\n");
89825881Ssam 		splx(s);
89925881Ssam 		vxstreset(vx);
90025881Ssam 		return;
90125881Ssam 	}
90225881Ssam 	if ((vp->v_hdwre&017) == CMDquals) {
90325881Ssam #ifdef VX_DEBUG
90425881Ssam 		if (vxintr4 & VXERR4) {	/* causes VIOC INTR ERR 4 */
90525933Ssam 			struct vxcmd *cp1, *cp0;
90625881Ssam 
90725933Ssam 			cp0 = (struct vxcmd *)
90825933Ssam 			    ((caddr_t)cp->cmdbuf[cp->v_empty]-sizeof (cp0->c_fwd));
90925881Ssam 			if (cp0->cmd == VXC_XMITDTA || cp0->cmd == VXC_XMITIMM) {
91025881Ssam 				cp1 = vobtain(vs);
91125881Ssam 				*cp1 = *cp0;
91225881Ssam 				vxintr4 &= ~VXERR4;
91325881Ssam 				(void) vcmd(vx, &cp1->cmd);
91425881Ssam 			}
91525881Ssam 		}
91625881Ssam #endif
91725881Ssam 		cp->v_curcmd[vp->v_vcid & VCMDLEN-1] = cp->cmdbuf[cp->v_empty];
91825881Ssam 		if (++cp->v_empty >= VC_CMDBUFL)
91925881Ssam 			cp->v_empty = 0;
92025881Ssam 	}
92125881Ssam 	if (++cp->v_itrempt >= VC_IQLEN)
92225881Ssam 		cp->v_itrempt = 0;
92325881Ssam 	vintempt(vx);
92425881Ssam 	splx(s);
92525881Ssam 	(void) vcmd(vx, (caddr_t)0);	/* queue next cmd, if any */
92625881Ssam }
92725881Ssam 
92825881Ssam /*
92925881Ssam  * Command Response interrupt.  The Vioc has completed
93025881Ssam  * a command.  The command may now be returned to
93125881Ssam  * the appropriate device driver.
93225881Ssam  */
93325881Ssam vcmdrsp(vx)
93425881Ssam 	register vx;
93525881Ssam {
93625933Ssam 	register struct vxdevice *vp;
93725933Ssam 	register struct vcmds *cp;
93825881Ssam 	register caddr_t cmd;
93925881Ssam 	register struct vx_softc *vs;
94025881Ssam 	register char *resp;
94125881Ssam 	register k;
94225881Ssam 	register int s;
94325881Ssam 
94425881Ssam 	scope_out(6);
94525881Ssam 	vs = &vx_softc[vx];
94625881Ssam 	if (vs->vs_type) {	/* Its a BOP */
94725881Ssam 		printf("vx%d: vcmdrsp interrupt\n", vx);
94825881Ssam 		return;
94925881Ssam 	}
95025881Ssam 	s = spl8();
95125881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
95225881Ssam 	cp = &vs->vs_cmds;
95325881Ssam 	resp = (char *)vp + (vp->v_rspoff&0x7fff);
95425881Ssam 	if (((k = resp[1])&V_UNBSY) == 0) {
95525881Ssam 		printf("vx%d: cmdresp debug\n", vx);
95625881Ssam 		splx(s);
95725881Ssam 		vxstreset(vx);
95825881Ssam 		return;
95925881Ssam 	}
96025881Ssam 	k &= VCMDLEN-1;
96125881Ssam 	cmd = cp->v_curcmd[k];
96225881Ssam 	cp->v_curcmd[k] = (caddr_t)0;
96325881Ssam 	cp->v_curcnt--;
96425881Ssam 	k = *((short *)&resp[4]);	/* cmd operation code */
96525881Ssam 	if ((k&0xff00) == VXC_LIDENT)	/* want hiport number */
96625881Ssam 		for (k = 0; k < VRESPLEN; k++)
96725881Ssam 			cmd[k] = resp[k+4];
96825881Ssam 	resp[1] = 0;
96925881Ssam 	vxxint(vx, (struct vxcmd *)cmd);
97025881Ssam 	if (vs->vs_state == VXS_READY)
97125881Ssam 		vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
97225881Ssam 	splx(s);
97325881Ssam }
97425881Ssam 
97525881Ssam /*
97625881Ssam  * Unsolicited interrupt.
97725881Ssam  */
97825881Ssam vunsol(vx)
97925881Ssam 	register vx;
98025881Ssam {
98125933Ssam 	register struct vxdevice *vp;
98225881Ssam 	struct vx_softc *vs;
98325881Ssam 	int s;
98425881Ssam 
98525881Ssam 	scope_out(1);
98625881Ssam 	vs = &vx_softc[vx];
98725881Ssam 	if (vs->vs_type) {	/* Its a BOP */
98825881Ssam 		printf("vx%d: vunsol from BOP\n", vx);
98925881Ssam 		return;
99025881Ssam 	}
99125881Ssam 	s = spl8();
99225881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
99325881Ssam 	if (vp->v_uqual&V_UNBSY) {
99425881Ssam 		vxrint(vx);
99525881Ssam 		vinthandl(vx, ((V_BSY|UNSquals) << 8)|V_INTR);
99625881Ssam #ifdef notdef
99725881Ssam 	} else {
99825881Ssam 		printf("vx%d: unsolicited interrupt error\n", vx);
99925881Ssam 		splx(s);
100025881Ssam 		vxstreset(vx);
100125881Ssam #endif
100225881Ssam 	}
100325881Ssam 	splx(s);
100425881Ssam }
100525881Ssam 
100625881Ssam /*
100725933Ssam  * Enqueue an interrupt.
100825881Ssam  */
100925881Ssam vinthandl(vx, item)
101025881Ssam 	register int vx;
101125881Ssam 	register item;
101225881Ssam {
101325881Ssam 	register struct vcmds *cp;
101425881Ssam 	int empty;
101525881Ssam 
101625881Ssam 	cp = &vx_softc[vx].vs_cmds;
101725933Ssam 	empty = (cp->v_itrfill == cp->v_itrempt);
101825881Ssam 	cp->v_itrqueu[cp->v_itrfill] = item;
101925881Ssam 	if (++cp->v_itrfill >= VC_IQLEN)
102025881Ssam 		cp->v_itrfill = 0;
102125881Ssam 	if (cp->v_itrfill == cp->v_itrempt) {
102225881Ssam 		printf("vx%d: interrupt q overflow\n", vx);
102325881Ssam 		vxstreset(vx);
102425881Ssam 	} else if (empty)
102525881Ssam 		vintempt(vx);
102625881Ssam }
102725881Ssam 
102825881Ssam vintempt(vx)
102925881Ssam 	register int vx;
103025881Ssam {
103125881Ssam 	register struct vcmds *cp;
103225881Ssam 	register struct vxdevice *vp;
103325881Ssam 	register short item;
103425881Ssam 	register short *intr;
103525881Ssam 
103625881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
103725881Ssam 	if (vp->v_vioc&V_BSY)
103825881Ssam 		return;
103925881Ssam 	cp = &vx_softc[vx].vs_cmds;
104025881Ssam 	if (cp->v_itrempt == cp->v_itrfill)
104125881Ssam 		return;
104225881Ssam 	item = cp->v_itrqueu[cp->v_itrempt];
104325881Ssam 	intr = (short *)&vp->v_vioc;
104425881Ssam 	switch ((item >> 8)&03) {
104525881Ssam 
104625881Ssam 	case CMDquals: {		/* command */
104725881Ssam 		int phys;
104825881Ssam 
104925881Ssam 		if (cp->v_empty == cp->v_fill || vp->v_vcbsy&V_BSY)
105025881Ssam 			break;
105125881Ssam 		vx_softc[vx].vs_mricmd = (caddr_t)cp->cmdbuf[cp->v_empty];
105225881Ssam 		phys = vtoph((struct proc *)0,
105325881Ssam 		    (unsigned)cp->cmdbuf[cp->v_empty]);
105425881Ssam 		vp->v_vcp[0] = ((short *)&phys)[0];
105525881Ssam 		vp->v_vcp[1] = ((short *)&phys)[1];
105625881Ssam 		vp->v_vcbsy = V_BSY;
105725881Ssam 		*intr = item;
105825881Ssam 		scope_out(4);
105925881Ssam 		break;
106025881Ssam 	}
106125881Ssam 
106225881Ssam 	case RSPquals:		/* command response */
106325881Ssam 		*intr = item;
106425881Ssam 		scope_out(7);
106525881Ssam 		break;
106625881Ssam 
106725881Ssam 	case UNSquals:		/* unsolicited interrupt */
106825881Ssam 		vp->v_uqual = 0;
106925881Ssam 		*intr = item;
107025881Ssam 		scope_out(2);
107125881Ssam 		break;
107225881Ssam 	}
107325881Ssam }
107425881Ssam 
107525881Ssam /*
107625881Ssam  * Start a reset on a vioc after error (hopefully)
107725881Ssam  */
107825881Ssam vxstreset(vx)
107925881Ssam 	register vx;
108025881Ssam {
108125881Ssam 	register struct vx_softc *vs;
108225933Ssam 	register struct vxdevice *vp;
108325881Ssam 	register struct vxcmd *cp;
108425881Ssam 	register int j;
108525881Ssam 	extern int vxinreset();
108625881Ssam 	int s;
108725881Ssam 
108825881Ssam 	s = spl8() ;
108925881Ssam 	vs = &vx_softc[vx];
109025881Ssam 	if (vs->vs_state == VXS_RESET) {	/* avoid recursion */
109125881Ssam 		splx(s);
109225881Ssam 		return;
109325881Ssam 	}
109425881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
109525881Ssam 	/*
109625881Ssam 	 * Zero out the vioc structures, mark the vioc as being
109725881Ssam 	 * reset, reinitialize the free command list, reset the vioc
109825881Ssam 	 * and start a timer to check on the progress of the reset.
109925881Ssam 	 */
110025881Ssam 	bzero((caddr_t)vs, (unsigned)sizeof (*vs));
110125881Ssam 
110225881Ssam 	/*
110325881Ssam 	 * Setting VXS_RESET prevents others from issuing
110425881Ssam 	 * commands while allowing currently queued commands to
110525881Ssam 	 * be passed to the VIOC.
110625881Ssam 	 */
110725881Ssam 	vs->vs_state = VXS_RESET;
110825881Ssam 	/* init all cmd buffers */
110925881Ssam 	for (j = 0; j < NVCXBUFS; j++) {
111025933Ssam 		cp = &vs->vs_lst[j];
111125933Ssam 		cp->c_fwd = &vs->vs_lst[j+1];
111225881Ssam 	}
111325933Ssam 	vs->vs_avail = &vs->vs_lst[0];
111425933Ssam 	cp->c_fwd = (struct vxcmd *)0;
111525881Ssam 	printf("vx%d: reset...", vx);
111625881Ssam 	vp->v_fault = 0;
111725881Ssam 	vp->v_vioc = V_BSY;
111825933Ssam 	vp->v_hdwre = V_RESET;		/* generate reset interrupt */
111925881Ssam 	timeout(vxinreset, (caddr_t)vx, hz*5);
112025881Ssam 	splx(s);
112125881Ssam }
112225881Ssam 
112325881Ssam /* continue processing a reset on a vioc after an error (hopefully) */
112425881Ssam vxinreset(vx)
112525881Ssam 	int vx;
112625881Ssam {
112725933Ssam 	register struct vxdevice *vp;
112825881Ssam 	int s = spl8();
112925881Ssam 
113025881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
113125881Ssam 	/*
113225881Ssam 	 * See if the vioc has reset.
113325881Ssam 	 */
113425881Ssam 	if (vp->v_fault != VXF_READY) {
113525881Ssam 		printf("failed\n");
113625881Ssam 		splx(s);
113725881Ssam 		return;
113825881Ssam 	}
113925881Ssam 	/*
114025881Ssam 	 * Send a LIDENT to the vioc and mess with carrier flags
114125881Ssam 	 * on parallel printer ports.
114225881Ssam 	 */
114329954Skarels 	vxinit(vx, 0);
114425881Ssam 	splx(s);
114525881Ssam }
114625881Ssam 
114725881Ssam /*
114825933Ssam  * Finish the reset on the vioc after an error (hopefully).
114925933Ssam  *
115025881Ssam  * Restore modem control, parameters and restart output.
115125881Ssam  * Since the vioc can handle no more then 24 commands at a time
115225881Ssam  * and we could generate as many as 48 commands, we must do this in
115325881Ssam  * phases, issuing no more then 16 commands at a time.
115425881Ssam  */
115525881Ssam vxfnreset(vx, cp)
115625881Ssam 	register int vx;
115725881Ssam 	register struct vxcmd *cp;
115825881Ssam {
115925881Ssam 	register struct vx_softc *vs;
116025933Ssam 	register struct vxdevice *vp ;
116125881Ssam 	register struct tty *tp, *tp0;
116225881Ssam 	register int i;
116325881Ssam #ifdef notdef
116425881Ssam 	register int on;
116525881Ssam #endif
116625881Ssam 	extern int vxrestart();
116725881Ssam 	int s = spl8();
116825881Ssam 
116925881Ssam 	vs = &vx_softc[vx];
117025881Ssam 	vs->vs_loport = cp->par[5];
117125881Ssam 	vs->vs_hiport = cp->par[7];
117225881Ssam 	vrelease(vs, cp);
117325881Ssam 	vs->vs_nbr = vx;			/* assign VIOC-X board number */
117425881Ssam 	vs->vs_state = VXS_READY;
117525881Ssam 
117625881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
117725881Ssam 	vp->v_vcid = 0;
117825881Ssam 
117925881Ssam 	/*
118025881Ssam 	 * Restore modem information and control.
118125881Ssam 	 */
118225881Ssam 	tp0 = &vx_tty[vx*16];
118325881Ssam 	for (i = vs->vs_loport; i <= vs->vs_hiport; i++) {
118425881Ssam 		tp = tp0 + i;
118525881Ssam 		if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) {
118625881Ssam 			tp->t_state &= ~TS_CARR_ON;
118725881Ssam 			vcmodem(tp->t_dev, VMOD_ON);
118825881Ssam 			if (tp->t_state&TS_CARR_ON)
118929954Skarels 				(void)(*linesw[tp->t_line].l_modem)(tp, 1);
119029954Skarels 			else if (tp->t_state & TS_ISOPEN)
119129954Skarels 				(void)(*linesw[tp->t_line].l_modem)(tp, 0);
119225881Ssam 		}
119329954Skarels #ifdef notdef
119425881Ssam 		/*
119525881Ssam 		 * If carrier has changed while we were resetting,
119625881Ssam 		 * take appropriate action.
119725881Ssam 		 */
119825881Ssam 		on = vp->v_dcd & 1<<i;
119929954Skarels 		if (on && (tp->t_state&TS_CARR_ON) == 0)
120029954Skarels 			(void)(*linesw[tp->t_line].l_modem)(tp, 1);
120129954Skarels 		else if (!on && tp->t_state&TS_CARR_ON)
120229954Skarels 			(void)(*linesw[tp->t_line].l_modem)(tp, 0);
120325881Ssam #endif
120425881Ssam 	}
120525881Ssam 	vs->vs_state = VXS_RESET;
120625881Ssam 	timeout(vxrestart, (caddr_t)vx, hz);
120725881Ssam 	splx(s);
120825881Ssam }
120925881Ssam 
121025881Ssam /*
121125881Ssam  * Restore a particular aspect of the VIOC.
121225881Ssam  */
121325881Ssam vxrestart(vx)
121425881Ssam 	int vx;
121525881Ssam {
121625881Ssam 	register struct tty *tp, *tp0;
121725881Ssam 	register struct vx_softc *vs;
121830372Skarels 	register int i, count;
121925881Ssam 	int s = spl8();
122025881Ssam 
122130372Skarels 	count = vx >> 8;
122225881Ssam 	vx &= 0xff;
122325881Ssam 	vs = &vx_softc[vx];
122425881Ssam 	vs->vs_state = VXS_READY;
122525881Ssam 	tp0 = &vx_tty[vx*16];
122625881Ssam 	for (i = vs->vs_loport; i <= vs->vs_hiport; i++) {
122725881Ssam 		tp = tp0 + i;
122830372Skarels 		if (count != 0) {
122925881Ssam 			tp->t_state &= ~(TS_BUSY|TS_TIMEOUT);
123025881Ssam 			if (tp->t_state&(TS_ISOPEN|TS_WOPEN))
123125881Ssam 				vxstart(tp);	/* restart pending output */
123225881Ssam 		} else {
123325881Ssam 			if (tp->t_state&(TS_WOPEN|TS_ISOPEN))
123437608Smarc 				vxcparam(tp, &tp->t_termios, 0);
123525881Ssam 		}
123625881Ssam 	}
123730372Skarels 	if (count == 0) {
123825881Ssam 		vs->vs_state = VXS_RESET;
123925881Ssam 		timeout(vxrestart, (caddr_t)(vx + 1*256), hz);
124025881Ssam 	} else
124125881Ssam 		printf("done\n");
124225881Ssam 	splx(s);
124325881Ssam }
124425881Ssam 
124525881Ssam vxreset(dev)
124625881Ssam 	dev_t dev;
124725881Ssam {
124825881Ssam 
124930372Skarels 	vxstreset((int)VXUNIT(minor(dev)));	/* completes asynchronously */
125025881Ssam }
125125881Ssam 
125230372Skarels #ifdef notdef
125325881Ssam vxfreset(vx)
125425881Ssam 	register int vx;
125525881Ssam {
125625881Ssam 	struct vba_device *vi;
125725881Ssam 
125825881Ssam 	if ((unsigned)vx > NVX || (vi = vxinfo[vx]) == 0 || vi->ui_addr == 0)
125925881Ssam 		return (ENODEV);
126025881Ssam 	vx_softc[vx].vs_state = VXS_READY;
126125881Ssam 	vxstreset(vx);
126225881Ssam 	return (0);		/* completes asynchronously */
126325881Ssam }
126430372Skarels #endif
126525881Ssam 
126625881Ssam vcmodem(dev, flag)
126725881Ssam 	dev_t dev;
126825881Ssam {
126925881Ssam 	struct tty *tp;
127025881Ssam 	register struct vxcmd *cp;
127125881Ssam 	register struct vx_softc *vs;
127225881Ssam 	register struct vxdevice *kp;
127325881Ssam 	register port;
127425881Ssam 	int unit;
127525881Ssam 
127625881Ssam 	unit = minor(dev);
127725881Ssam 	tp = &vx_tty[unit];
127825881Ssam 	vs = (struct vx_softc *)tp->t_addr;
127930372Skarels 	if (vs->vs_state != VXS_READY)
128030372Skarels 		return;
128125881Ssam 	cp = vobtain(vs);
128225881Ssam 	kp = (struct vxdevice *)((struct vba_device *)vxinfo[vs->vs_nbr])->ui_addr;
128325881Ssam 
128425881Ssam 	port = unit & 017;
128525881Ssam 	/*
128625881Ssam 	 * Issue MODEM command
128725881Ssam 	 */
128825881Ssam 	cp->cmd = VXC_MDMCTL;
128930372Skarels 	if (flag == VMOD_ON) {
129030372Skarels 		if (vs->vs_softCAR & (1 << port))
129130372Skarels 			cp->par[0] = V_MANUAL | V_DTR_ON | V_RTS;
129230372Skarels 		else
129330372Skarels 			cp->par[0] = V_AUTO | V_DTR_ON | V_RTS;
129430372Skarels 	} else
129530372Skarels 		cp->par[0] = V_DTR_OFF;
129625881Ssam 	cp->par[1] = port;
129730372Skarels 	(void) vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd);
129830372Skarels 	if (vs->vs_softCAR & (1 << port))
129930372Skarels 		kp->v_dcd |= (1 << port);
130030372Skarels 	if ((kp->v_dcd | vs->vs_softCAR) & (1 << port) && flag == VMOD_ON)
130130372Skarels 		tp->t_state |= TS_CARR_ON;
130225881Ssam }
130325881Ssam 
130425881Ssam /*
130525881Ssam  * VCMINTR called when an unsolicited interrup occurs signaling
130625881Ssam  * some change of modem control state.
130725881Ssam  */
130825881Ssam vcmintr(vx)
130925881Ssam 	register vx;
131025881Ssam {
131125881Ssam 	register struct vxdevice *kp;
131225881Ssam 	register struct tty *tp;
131325881Ssam 	register port;
131430372Skarels 	register struct vx_softc *vs;
131525881Ssam 
131625881Ssam 	kp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
131725881Ssam 	port = kp->v_usdata[0] & 017;
131825881Ssam 	tp = &vx_tty[vx*16+port];
131930372Skarels 	vs = &vx_softc[vx];
132025881Ssam 
132129954Skarels 	if (kp->v_ustat & DCD_ON)
132229954Skarels 		(void)(*linesw[tp->t_line].l_modem)(tp, 1);
132329954Skarels 	else if ((kp->v_ustat & DCD_OFF) &&
132430372Skarels 	    ((vs->vs_softCAR & (1 << port))) == 0 &&
132529954Skarels 	    (*linesw[tp->t_line].l_modem)(tp, 0) == 0) {
132629954Skarels 		register struct vcmds *cp;
132729954Skarels 		register struct vxcmd *cmdp;
132825881Ssam 
132930372Skarels 		/* clear all pending transmits */
133029954Skarels 		if (tp->t_state&(TS_BUSY|TS_FLUSH) &&
133129954Skarels 		    vs->vs_vers == VXV_NEW) {
133229954Skarels 			int i, cmdfound = 0;
133325881Ssam 
133429954Skarels 			cp = &vs->vs_cmds;
133529954Skarels 			for (i = cp->v_empty; i != cp->v_fill; ) {
133629954Skarels 				cmdp = (struct vxcmd *)((long *)cp->cmdbuf[i]-1);
133729954Skarels 				if ((cmdp->cmd == VXC_XMITDTA ||
133829954Skarels 				    cmdp->cmd == VXC_XMITIMM) &&
133929954Skarels 				    ((struct vxmit *)cmdp->par)->line == port) {
134029954Skarels 					cmdfound++;
134125881Ssam 					cmdp->cmd = VXC_FDTATOX;
134225881Ssam 					cmdp->par[1] = port;
134325881Ssam 				}
134429954Skarels 				if (++i >= VC_CMDBUFL)
134529954Skarels 					i = 0;
134625881Ssam 			}
134729954Skarels 			if (cmdfound)
134829954Skarels 				tp->t_state &= ~(TS_BUSY|TS_FLUSH);
134929954Skarels 			/* cmd is already in vioc, have to flush it */
135029954Skarels 			else {
135129954Skarels 				cmdp = vobtain(vs);
135229954Skarels 				cmdp->cmd = VXC_FDTATOX;
135329954Skarels 				cmdp->par[1] = port;
135430372Skarels 				(void) vcmd(vx, (caddr_t)&cmdp->cmd);
135525881Ssam 			}
135625881Ssam 		}
135729954Skarels 	} else if ((kp->v_ustat&BRK_CHR) && (tp->t_state&TS_ISOPEN)) {
135837608Smarc 		(*linesw[tp->t_line].l_rint)(TTY_FE, tp);
135925881Ssam 		return;
136025881Ssam 	}
136125881Ssam }
136225881Ssam #endif
1363