xref: /csrg-svn/sys/tahoe/vba/vx.c (revision 37608)
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*37608Smarc  *	@(#)vx.c	7.3 (Berkeley) 05/01/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 "dir.h"
3625877Ssam #include "user.h"
3725877Ssam #include "map.h"
3825877Ssam #include "buf.h"
3925877Ssam #include "conf.h"
4025877Ssam #include "file.h"
4125877Ssam #include "uio.h"
4225877Ssam #include "proc.h"
4325877Ssam #include "vm.h"
4425881Ssam #include "kernel.h"
4529954Skarels #include "syslog.h"
4625675Ssam 
4734406Skarels #include "../tahoe/pte.h"
4834406Skarels 
4925675Ssam #include "../tahoevba/vbavar.h"
5025881Ssam #include "../tahoevba/vxreg.h"
5125675Ssam #include "../tahoevba/scope.h"
5224003Ssam 
5325881Ssam #ifdef VX_DEBUG
5425881Ssam long	vxintr4 = 0;
5525948Ssam #define	VXERR4	1
5625948Ssam #define	VXNOBUF	2
5725881Ssam long	vxdebug = 0;
5825948Ssam #define	VXVCM	1
5925948Ssam #define	VXVCC	2
6025948Ssam #define	VXVCX	4
6125881Ssam #endif
6224003Ssam 
6325881Ssam /*
6425881Ssam  * Interrupt type bits passed to vinthandl().
6525881Ssam  */
6625948Ssam #define	CMDquals 0		/* command completed interrupt */
6725948Ssam #define	RSPquals 1		/* command response interrupt */
6825948Ssam #define	UNSquals 2		/* unsolicited interrupt */
6924003Ssam 
7030372Skarels #define	VXUNIT(n)	((n) >> 4)
7130372Skarels #define	VXPORT(n)	((n) & 0xf)
7230372Skarels 
7325881Ssam struct	tty vx_tty[NVX*16];
7429954Skarels #ifndef lint
7529954Skarels int	nvx = NVX*16;
7629954Skarels #endif
7725881Ssam int	vxstart(), ttrstrt();
7825881Ssam struct	vxcmd *vobtain(), *nextcmd();
7924003Ssam 
8024003Ssam /*
8124003Ssam  * Driver information for auto-configuration stuff.
8224003Ssam  */
8324003Ssam int	vxprobe(), vxattach(), vxrint();
8425881Ssam struct	vba_device *vxinfo[NVX];
8524003Ssam long	vxstd[] = { 0 };
8624003Ssam struct	vba_driver vxdriver =
8725857Ssam     { vxprobe, 0, vxattach, 0, vxstd, "vx", vxinfo };
8824003Ssam 
8925881Ssam struct	vx_softc {
9025881Ssam 	u_char	vs_type;	/* 0: viox-x/vioc-b, 1: vioc-bop */
9125881Ssam 	u_char	vs_bop;		/* bop board # for vioc-bop's */
9225881Ssam 	u_char	vs_loport;	/* low port nbr */
9325881Ssam 	u_char	vs_hiport;	/* high port nbr */
9425881Ssam 	u_short	vs_nbr;		/* viocx number */
9525881Ssam 	u_short	vs_maxcmd;	/* max number of concurrent cmds */
9625881Ssam 	u_short	vs_silosiz;	/* silo size */
9725881Ssam 	short	vs_vers;	/* vioc/pvioc version */
9825948Ssam #define	VXV_OLD	0		/* PVIOCX | VIOCX */
9925948Ssam #define	VXV_NEW	1		/* NPVIOCX | NVIOCX */
10025881Ssam 	short	vs_xmtcnt;	/* xmit commands pending */
10125881Ssam 	short	vs_brkreq;	/* send break requests pending */
10225881Ssam 	short 	vs_state;	/* controller state */
10325948Ssam #define	VXS_READY	0	/* ready for commands */
10425948Ssam #define	VXS_RESET	1	/* in process of reseting */
10530372Skarels 	u_short	vs_softCAR;	/* soft carrier */
10625881Ssam 	caddr_t vs_mricmd;	/* most recent issued cmd */
10725881Ssam 	u_int	vs_ivec;	/* interrupt vector base */
10825881Ssam 	struct	vxcmd *vs_avail;/* next available command buffer */
10925881Ssam 	struct	vxcmd *vs_build;
11025881Ssam 	struct	vxcmd vs_lst[NVCXBUFS];
11125881Ssam 	struct	vcmds vs_cmds;
11225881Ssam } vx_softc[NVX];
11324003Ssam 
114*37608Smarc struct speedtab vxspeedtab[] = {
115*37608Smarc 	EXTA,	V19200,
116*37608Smarc 	EXTB,	V19200,
117*37608Smarc 	19200,	V19200,
118*37608Smarc 	9600,	13,
119*37608Smarc 	4800,	12,
120*37608Smarc 	2400,	11,
121*37608Smarc 	1800,	10,
122*37608Smarc 	1200,	9,
123*37608Smarc 	600,	8,
124*37608Smarc 	300,	7,
125*37608Smarc 	200,	6,
126*37608Smarc 	150,	5,
127*37608Smarc 	134,	4,
128*37608Smarc 	110,	3,
129*37608Smarc 	75,	2,
130*37608Smarc 	50,	1,
131*37608Smarc 	0,	0,
132*37608Smarc 	-1,	-1,
133*37608Smarc };
134*37608Smarc 
13525857Ssam vxprobe(reg, vi)
13624003Ssam 	caddr_t reg;
13725857Ssam 	struct vba_device *vi;
13824003Ssam {
13925857Ssam 	register int br, cvec;			/* must be r12, r11 */
14025881Ssam 	register struct vxdevice *vp = (struct vxdevice *)reg;
14125881Ssam 	register struct vx_softc *vs;
14224003Ssam 
14324003Ssam #ifdef lint
14424003Ssam 	br = 0; cvec = br; br = cvec;
14525675Ssam 	vackint(0); vunsol(0); vcmdrsp(0); vxfreset(0);
14624003Ssam #endif
14725675Ssam 	if (badaddr((caddr_t)vp, 1))
14825675Ssam 		return (0);
14925675Ssam 	vp->v_fault = 0;
15025675Ssam 	vp->v_vioc = V_BSY;
15125675Ssam 	vp->v_hdwre = V_RESET;		/* reset interrupt */
15224003Ssam 	DELAY(4000000);
15325881Ssam 	if (vp->v_fault != VXF_READY)
15425675Ssam 		return (0);
15525881Ssam 	vs = &vx_softc[vi->ui_unit];
15625857Ssam #ifdef notdef
15725857Ssam 	/*
15825857Ssam 	 * Align vioc interrupt vector base to 4 vector
15925857Ssam 	 * boundary and fitting in 8 bits (is this necessary,
16025857Ssam 	 * wish we had documentation).
16125857Ssam 	 */
16225857Ssam 	if ((vi->ui_hd->vh_lastiv -= 3) > 0xff)
16325857Ssam 		vi->ui_hd->vh_lastiv = 0xff;
16425881Ssam 	vs->vs_ivec = vi->ui_hd->vh_lastiv = vi->ui_hd->vh_lastiv &~ 0x3;
16525857Ssam #else
16625881Ssam 	vs->vs_ivec = 0x40+vi->ui_unit*4;
16725857Ssam #endif
16825881Ssam 	br = 0x18, cvec = vs->vs_ivec;	/* XXX */
16925881Ssam 	return (sizeof (struct vxdevice));
17024003Ssam }
17124003Ssam 
17225857Ssam vxattach(vi)
17325857Ssam 	register struct vba_device *vi;
17424003Ssam {
17525675Ssam 
17630372Skarels 	vx_softc[vi->ui_unit].vs_softCAR = vi->ui_flags;
17729954Skarels 	vxinit(vi->ui_unit, 1);
17824003Ssam }
17924003Ssam 
18024003Ssam /*
18124003Ssam  * Open a VX line.
18224003Ssam  */
18325675Ssam /*ARGSUSED*/
18424003Ssam vxopen(dev, flag)
18525881Ssam 	dev_t dev;
18625881Ssam 	int flag;
18724003Ssam {
18824003Ssam 	register struct tty *tp;	/* pointer to tty struct for port */
18925881Ssam 	register struct vx_softc *vs;
19025881Ssam 	register struct vba_device *vi;
19125881Ssam 	int unit, vx, s, error;
192*37608Smarc 	int vxparam();
19324003Ssam 
19425881Ssam 	unit = minor(dev);
19530372Skarels 	vx = VXUNIT(unit);
19630372Skarels 	if (vx >= NVX || (vi = vxinfo[vx])== 0 || vi->ui_alive == 0)
19725881Ssam 		return (ENXIO);
19830372Skarels 	vs = &vx_softc[vx];
19925881Ssam 	tp = &vx_tty[unit];
20030372Skarels 	unit = VXPORT(unit);
20125881Ssam 	if (tp->t_state&TS_XCLUDE && u.u_uid != 0)
20225881Ssam 		return (EBUSY);
20330372Skarels 	if (unit < vs->vs_loport || unit > vs->vs_hiport)
20425881Ssam 		return (ENXIO);
20525881Ssam 	tp->t_addr = (caddr_t)vs;
20625881Ssam 	tp->t_oproc = vxstart;
207*37608Smarc 	tp->t_param = vxparam;
20825881Ssam 	tp->t_dev = dev;
20925881Ssam 	s = spl8();
21025881Ssam 	tp->t_state |= TS_WOPEN;
21125881Ssam 	if ((tp->t_state&TS_ISOPEN) == 0) {
21225881Ssam 		ttychars(tp);
21325881Ssam 		if (tp->t_ispeed == 0) {
214*37608Smarc 			tp->t_iflag = TTYDEF_IFLAG;
215*37608Smarc 			tp->t_oflag = TTYDEF_OFLAG;
216*37608Smarc 			tp->t_lflag = TTYDEF_LFLAG;
217*37608Smarc 			tp->t_cflag = TTYDEF_CFLAG;
218*37608Smarc 			tp->t_ispeed = tp->t_ospeed = TTYDEF_SPEED;
21924003Ssam 		}
220*37608Smarc 		vxparam(tp, &tp->t_termios);
221*37608Smarc 		ttsetwater(tp);
22224003Ssam 	}
22330372Skarels 	vcmodem(dev, VMOD_ON);
224*37608Smarc 	while (!(flag&O_NONBLOCK) && !(tp->t_cflag&CLOCAL) &&
225*37608Smarc 	      (tp->t_state&TS_CARR_ON) == 0)
22630372Skarels 		sleep((caddr_t)&tp->t_rawq, TTIPRI);
22725881Ssam 	error = (*linesw[tp->t_line].l_open)(dev,tp);
22825881Ssam 	splx(s);
22925881Ssam 	return (error);
23024003Ssam }
23124003Ssam 
23224003Ssam /*
23324003Ssam  * Close a VX line.
23424003Ssam  */
23525675Ssam /*ARGSUSED*/
23624003Ssam vxclose(dev, flag)
23725881Ssam 	dev_t dev;
23825881Ssam 	int flag;
23924003Ssam {
24024003Ssam 	register struct tty *tp;
24125881Ssam 	int unit, s;
24224003Ssam 
24325881Ssam 	unit = minor(dev);
24425881Ssam 	tp = &vx_tty[unit];
24525881Ssam 	s = spl8();
24624003Ssam 	(*linesw[tp->t_line].l_close)(tp);
247*37608Smarc 	if (tp->t_cflag & HUPCL || (tp->t_state & TS_ISOPEN) == 0)
24830372Skarels 		vcmodem(dev, VMOD_OFF);
24924003Ssam 	/* wait for the last response */
25025881Ssam 	while (tp->t_state&TS_FLUSH)
25125881Ssam 		sleep((caddr_t)&tp->t_state, TTOPRI);
25225881Ssam 	ttyclose(tp);
25325881Ssam 	splx(s);
25424003Ssam }
25524003Ssam 
25624003Ssam /*
25724003Ssam  * Read from a VX line.
25824003Ssam  */
259*37608Smarc vxread(dev, uio, flag)
26024003Ssam 	dev_t dev;
26124003Ssam 	struct uio *uio;
26224003Ssam {
26325881Ssam 	struct tty *tp = &vx_tty[minor(dev)];
26425881Ssam 
265*37608Smarc 	return ((*linesw[tp->t_line].l_read)(tp, uio, flag));
26624003Ssam }
26724003Ssam 
26824003Ssam /*
26924003Ssam  * write on a VX line
27024003Ssam  */
271*37608Smarc vxwrite(dev, uio, flag)
27224003Ssam 	dev_t dev;
27324003Ssam 	struct uio *uio;
27424003Ssam {
27525881Ssam 	register struct tty *tp = &vx_tty[minor(dev)];
27625881Ssam 
277*37608Smarc 	return ((*linesw[tp->t_line].l_write)(tp, uio, flag));
27824003Ssam }
27924003Ssam 
28024003Ssam /*
28124003Ssam  * VIOCX unsolicited interrupt.
28224003Ssam  */
28325881Ssam vxrint(vx)
28425881Ssam 	register vx;
28524003Ssam {
28625881Ssam 	register struct tty *tp, *tp0;
28725881Ssam 	register struct vxdevice *addr;
28825881Ssam 	register struct vx_softc *vs;
28925881Ssam 	struct vba_device *vi;
29025881Ssam 	register int nc, c;
29125881Ssam 	register struct silo {
29225881Ssam 		char	data, port;
29325881Ssam 	} *sp;
29425881Ssam 	short *osp;
29525881Ssam 	int overrun = 0;
29624003Ssam 
29725881Ssam 	vi = vxinfo[vx];
29825881Ssam 	if (vi == 0 || vi->ui_alive == 0)
29925881Ssam 		return;
30025881Ssam 	addr = (struct vxdevice *)vi->ui_addr;
30125881Ssam 	switch (addr->v_uqual&037) {
30224003Ssam 	case 0:
30324003Ssam 		break;
30424003Ssam 	case 2:
30530372Skarels 		printf("vx%d: vc proc err, ustat %x\n", vx, addr->v_ustat);
30625881Ssam 		vxstreset(vx);
30730372Skarels 		return;
30824003Ssam 	case 3:
30925881Ssam 		vcmintr(vx);
31030372Skarels 		return;
31124003Ssam 	case 4:
31230372Skarels 		return;
31324003Ssam 	default:
31430372Skarels 		printf("vx%d: vc uqual err, uqual %x\n", vx, addr->v_uqual);
31525881Ssam 		vxstreset(vx);
31630372Skarels 		return;
31724003Ssam 	}
31825881Ssam 	vs = &vx_softc[vx];
31925881Ssam 	if (vs->vs_vers == VXV_NEW)
32025881Ssam 		sp = (struct silo *)((caddr_t)addr + *(short *)addr->v_usdata);
32125881Ssam 	else
32225881Ssam 		sp = (struct silo *)((caddr_t)addr+VX_SILO+(addr->v_usdata[0]<<6));
32325881Ssam 	nc = *(osp = (short *)sp);
32425881Ssam 	if (nc == 0)
32530372Skarels 		return;
32625881Ssam 	if (vs->vs_vers == VXV_NEW && nc > vs->vs_silosiz) {
32725881Ssam 		printf("vx%d: %d exceeds silo size\n", nc);
32825881Ssam 		nc = vs->vs_silosiz;
32924003Ssam 	}
33025881Ssam 	tp0 = &vx_tty[vx*16];
33125881Ssam 	sp = (struct silo *)(((short *)sp)+1);
33225881Ssam 	for (; nc > 0; nc--, sp = (struct silo *)(((short *)sp)+1)) {
33325881Ssam 		c = sp->port & 017;
33425881Ssam 		if (vs->vs_loport > c || c > vs->vs_hiport)
33525881Ssam 			continue;
33625881Ssam 		tp = tp0 + c;
33725881Ssam 		if( (tp->t_state&TS_ISOPEN) == 0) {
33824003Ssam 			wakeup((caddr_t)&tp->t_rawq);
33924003Ssam 			continue;
34024003Ssam 		}
341*37608Smarc 		c = sp->data&((tp->t_cflag&CSIZE)==CS8 ? 0xff : 0x7f);
34225881Ssam 		if ((sp->port&VX_RO) == VX_RO && !overrun) {
34329954Skarels 			log(LOG_ERR, "vx%d: receiver overrun\n", vi->ui_unit);
34425881Ssam 			overrun = 1;
34525881Ssam 			continue;
34625881Ssam 		}
34725881Ssam 		if (sp->port&VX_PE)
348*37608Smarc 			c |= TTY_PE;
349*37608Smarc 		if (sp->port&VX_FE)
350*37608Smarc 			c |= TTY_FE;
35124003Ssam 		(*linesw[tp->t_line].l_rint)(c, tp);
35224003Ssam 	}
35325881Ssam 	*osp = 0;
35424003Ssam }
35524003Ssam 
35624003Ssam /*
35725881Ssam  * Ioctl for VX.
35824003Ssam  */
35924003Ssam vxioctl(dev, cmd, data, flag)
36025881Ssam 	dev_t dev;
36125881Ssam 	caddr_t	data;
36224003Ssam {
36325881Ssam 	register struct tty *tp;
36425881Ssam 	int error;
36524003Ssam 
36625881Ssam 	tp = &vx_tty[minor(dev)];
36724003Ssam 	error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag);
368*37608Smarc 	if (error >= 0)
36925881Ssam 		return (error);
37025881Ssam 	error = ttioctl(tp, cmd, data, flag);
371*37608Smarc 	if (error >= 0)
37225881Ssam 		return (error);
37325881Ssam 	return (ENOTTY);
37424003Ssam }
37524003Ssam 
376*37608Smarc vxparam(tp, t)
377*37608Smarc 	struct tty *tp;
378*37608Smarc 	struct termios *t;
37924003Ssam {
38025881Ssam 
381*37608Smarc 	return (vxcparam(tp, t, 1));
38224003Ssam }
38324003Ssam 
38424003Ssam /*
38524003Ssam  * Set parameters from open or stty into the VX hardware
38624003Ssam  * registers.
38724003Ssam  */
388*37608Smarc vxcparam(tp, t, wait)
389*37608Smarc 	struct tty *tp;
390*37608Smarc 	struct termios *t;
39125881Ssam 	int wait;
39224003Ssam {
39325881Ssam 	register struct vx_softc *vs;
39425881Ssam 	register struct vxcmd *cp;
395*37608Smarc 	dev_t dev = tp->t_dev;
39625933Ssam 	int s, unit = minor(dev);
397*37608Smarc 	int speedcode = ttspeedtab(t->c_ospeed, vxspeedtab);
39824003Ssam 
399*37608Smarc 	if (speedcode < 0 || (t->c_ispeed != t->c_ospeed && t->c_ispeed))
400*37608Smarc 		return(EINVAL);
40125881Ssam 	vs = (struct vx_softc *)tp->t_addr;
40225881Ssam 	cp = vobtain(vs);
40324003Ssam 	s = spl8();
40425933Ssam 	/*
40525933Ssam 	 * Construct ``load parameters'' command block
40625933Ssam 	 * to setup baud rates, xon-xoff chars, parity,
40725933Ssam 	 * and stop bits for the specified port.
40825933Ssam 	 */
40925933Ssam 	cp->cmd = VXC_LPARAX;
41030372Skarels 	cp->par[1] = VXPORT(unit);
411*37608Smarc 	/*
412*37608Smarc 	 * note: if the hardware does flow control, ^V doesn't work
413*37608Smarc 	 * to escape ^S
414*37608Smarc 	 */
415*37608Smarc 	if (t->c_iflag&IXON) {
416*37608Smarc 		if (t->c_cc[VSTART] == _POSIX_VDISABLE)
417*37608Smarc 			cp->par[2] = 0;
418*37608Smarc 		else
419*37608Smarc 			cp->par[2] = t->c_cc[VSTART];
420*37608Smarc 		if (t->c_cc[VSTOP] == _POSIX_VDISABLE)
421*37608Smarc 			cp->par[3] = 0;
422*37608Smarc 		else
423*37608Smarc 			cp->par[3] = t->c_cc[VSTOP];
424*37608Smarc 	} else
425*37608Smarc 		cp->par[2] = cp->par[3] = 0;
42630372Skarels #ifdef notnow
427*37608Smarc 	if (tp->t_flags & (RAW|LITOUT|PASS8)) {	/* XXX */
42830372Skarels #endif
42930372Skarels 		cp->par[4] = BITS8;		/* 8 bits of data */
43030372Skarels 		cp->par[7] = VNOPARITY;		/* no parity */
43130372Skarels #ifdef notnow
43224003Ssam 	} else {
43330372Skarels 		cp->par[4] = BITS7;		/* 7 bits of data */
43425881Ssam 		if ((tp->t_flags&(EVENP|ODDP)) == ODDP)
43530372Skarels 			cp->par[7] = VODDP;	/* odd parity */
43629954Skarels 		else
43730372Skarels 			cp->par[7] = VEVENP;	/* even parity */
43824003Ssam 	}
43930372Skarels #endif
440*37608Smarc 	cp->par[5] = (t->c_cflag&CSTOPB) ? VSTOP2 : VSTOP1;
441*37608Smarc 	cp->par[6] = speedcode;
44230372Skarels 	if (vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd) && wait)
44325675Ssam 		sleep((caddr_t)cp,TTIPRI);
444*37608Smarc 	if ((t->c_ospeed)==0) {
445*37608Smarc 		tp->t_cflag |= HUPCL;
446*37608Smarc 		vcmodem(dev, VMOD_OFF);
447*37608Smarc 	}
44824003Ssam 	splx(s);
449*37608Smarc 	return 0;
45024003Ssam }
45124003Ssam 
45224003Ssam /*
45324003Ssam  * VIOCX command response interrupt.
45424003Ssam  * For transmission, restart output to any active port.
45524003Ssam  * For all other commands, just clean up.
45624003Ssam  */
45725881Ssam vxxint(vx, cp)
45825881Ssam 	register int vx;
45925881Ssam 	register struct vxcmd *cp;
46024003Ssam {
46130372Skarels 	register struct vxmit *vp;
46225933Ssam 	register struct tty *tp, *tp0;
46325933Ssam 	register struct vx_softc *vs;
46424003Ssam 
46525881Ssam 	vs = &vx_softc[vx];
46625881Ssam 	cp = (struct vxcmd *)((long *)cp-1);
46729954Skarels 
46825881Ssam 	switch (cp->cmd&0xff00) {
46925881Ssam 
47025881Ssam 	case VXC_LIDENT:	/* initialization complete */
47125881Ssam 		if (vs->vs_state == VXS_RESET) {
47225881Ssam 			vxfnreset(vx, cp);
47325881Ssam 			vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
47424003Ssam 		}
47524003Ssam 		cp->cmd++;
47624003Ssam 		return;
47725881Ssam 
47825881Ssam 	case VXC_XMITDTA:
47925881Ssam 	case VXC_XMITIMM:
48024003Ssam 		break;
48125881Ssam 
48225881Ssam 	case VXC_LPARAX:
48325675Ssam 		wakeup((caddr_t)cp);
48425881Ssam 		/* fall thru... */
48525881Ssam 	default:	/* VXC_MDMCTL or VXC_FDTATOX */
48625881Ssam 		vrelease(vs, cp);
48725881Ssam 		if (vs->vs_state == VXS_RESET)
48825881Ssam 			vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
48924003Ssam 		return;
49024003Ssam 	}
49125881Ssam 	tp0 = &vx_tty[vx*16];
49225881Ssam 	vp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit));
49325881Ssam 	for (; vp >= (struct vxmit *)cp->par; vp--) {
49425881Ssam 		tp = tp0 + (vp->line & 017);
49524003Ssam 		tp->t_state &= ~TS_BUSY;
49625881Ssam 		if (tp->t_state & TS_FLUSH) {
49724003Ssam 			tp->t_state &= ~TS_FLUSH;
49825881Ssam 			wakeup((caddr_t)&tp->t_state);
49925881Ssam 		} else
50024003Ssam 		 	ndflush(&tp->t_outq, vp->bcount+1);
50124003Ssam 	}
50225881Ssam 	vrelease(vs, cp);
50330372Skarels 	if (vs->vs_vers == VXV_NEW)
50432112Skarels 		(*linesw[tp->t_line].l_start)(tp);
50530372Skarels 	else {
50625881Ssam 		tp0 = &vx_tty[vx*16 + vs->vs_hiport];
50725881Ssam 		for(tp = &vx_tty[vx*16 + vs->vs_loport]; tp <= tp0; tp++)
50832112Skarels 			(*linesw[tp->t_line].l_start)(tp);
50925881Ssam 		if ((cp = nextcmd(vs)) != NULL) {	/* command to send? */
51025881Ssam 			vs->vs_xmtcnt++;
51130372Skarels 			(void) vcmd(vx, (caddr_t)&cp->cmd);
51224003Ssam 		}
51324003Ssam 	}
51430372Skarels 	vs->vs_xmtcnt--;
51524003Ssam }
51624003Ssam 
51724003Ssam /*
51824003Ssam  * Force out partial XMIT command after timeout
51924003Ssam  */
52025881Ssam vxforce(vs)
52125881Ssam 	register struct vx_softc *vs;
52224003Ssam {
52325881Ssam 	register struct vxcmd *cp;
52425881Ssam 	int s;
52524003Ssam 
52624003Ssam 	s = spl8();
52725881Ssam 	if ((cp = nextcmd(vs)) != NULL) {
52825881Ssam 		vs->vs_xmtcnt++;
52930372Skarels 		(void) vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd);
53024003Ssam 	}
53124003Ssam 	splx(s);
53224003Ssam }
53324003Ssam 
53424003Ssam /*
53524003Ssam  * Start (restart) transmission on the given VX line.
53624003Ssam  */
53724003Ssam vxstart(tp)
53825881Ssam 	register struct tty *tp;
53924003Ssam {
54025675Ssam 	register short n;
54125933Ssam 	register struct vx_softc *vs;
54225933Ssam 	int s, port;
54324003Ssam 
54424003Ssam 	s = spl8();
54524003Ssam 	port = minor(tp->t_dev) & 017;
54625881Ssam 	vs = (struct vx_softc *)tp->t_addr;
54725881Ssam 	if ((tp->t_state&(TS_TIMEOUT|TS_BUSY|TS_TTSTOP)) == 0) {
548*37608Smarc 		if (tp->t_outq.c_cc <= tp->t_lowat) {
54924003Ssam 			if (tp->t_state&TS_ASLEEP) {
55024003Ssam 				tp->t_state &= ~TS_ASLEEP;
55124003Ssam 				wakeup((caddr_t)&tp->t_outq);
55224003Ssam 			}
55324003Ssam 			if (tp->t_wsel) {
55424003Ssam 				selwakeup(tp->t_wsel, tp->t_state & TS_WCOLL);
55524003Ssam 				tp->t_wsel = 0;
55624003Ssam 				tp->t_state &= ~TS_WCOLL;
55724003Ssam 			}
55824003Ssam 		}
55925881Ssam 		if (tp->t_outq.c_cc == 0) {
56024003Ssam 			splx(s);
56130372Skarels 			return;
56224003Ssam 		}
56325877Ssam 		scope_out(3);
564*37608Smarc 		if (1 || !(tp->t_oflag&OPOST))	/* XXX */
56530372Skarels 			n = ndqb(&tp->t_outq, 0);
56630372Skarels 		else {
56730372Skarels 			n = ndqb(&tp->t_outq, 0200);
56830372Skarels 			if (n == 0) {
56925675Ssam 				n = getc(&tp->t_outq);
57025881Ssam 				timeout(ttrstrt, (caddr_t)tp, (n&0177)+6);
57124003Ssam 				tp->t_state |= TS_TIMEOUT;
57230372Skarels 				n = 0;
57324003Ssam 			}
57430372Skarels 		}
57530372Skarels 		if (n) {
57624003Ssam 			tp->t_state |= TS_BUSY;
57730372Skarels 			vsetq(vs, port, (char *)tp->t_outq.c_cf, n);
57824003Ssam 		}
57924003Ssam 	}
58024003Ssam 	splx(s);
58124003Ssam }
58224003Ssam 
58324003Ssam /*
58424003Ssam  * Stop output on a line.
58524003Ssam  */
58624003Ssam vxstop(tp)
58725881Ssam 	register struct tty *tp;
58824003Ssam {
58925881Ssam 	int s;
59024003Ssam 
59124003Ssam 	s = spl8();
59225881Ssam 	if (tp->t_state&TS_BUSY)
59325881Ssam 		if ((tp->t_state&TS_TTSTOP) == 0)
59424003Ssam 			tp->t_state |= TS_FLUSH;
59524003Ssam 	splx(s);
59624003Ssam }
59724003Ssam 
59825881Ssam static	int vxbbno = -1;
59924003Ssam /*
60024003Ssam  * VIOCX Initialization.  Makes free lists of command buffers.
60124003Ssam  * Resets all viocx's.  Issues a LIDENT command to each
60225933Ssam  * viocx to establish interrupt vectors and logical port numbers.
60324003Ssam  */
60425881Ssam vxinit(vx, wait)
60525881Ssam 	register int vx;
60625881Ssam 	int wait;
60724003Ssam {
60825933Ssam 	register struct vx_softc *vs;
60925933Ssam 	register struct vxdevice *addr;
61025933Ssam 	register struct vxcmd *cp;
61125881Ssam 	register char *resp;
61225881Ssam 	register int j;
61330372Skarels 	char type, *typestring;
61424003Ssam 
61525881Ssam 	vs = &vx_softc[vx];
61625933Ssam 	vs->vs_type = 0;		/* vioc-x by default */
61725933Ssam 	addr = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
61825881Ssam 	type = addr->v_ident;
61925881Ssam 	vs->vs_vers = (type&VXT_NEW) ? VXV_NEW : VXV_OLD;
62025881Ssam 	if (vs->vs_vers == VXV_NEW)
62125881Ssam 		vs->vs_silosiz = addr->v_maxsilo;
62225881Ssam 	switch (type) {
62324003Ssam 
62425881Ssam 	case VXT_VIOCX:
62525881Ssam 	case VXT_VIOCX|VXT_NEW:
62630372Skarels 		typestring = "VIOC-X";
62730372Skarels 		/* set soft carrier for printer ports */
62830372Skarels 		for (j = 0; j < 16; j++)
62930372Skarels 			if (addr->v_portyp[j] == VXT_PARALLEL) {
63030372Skarels 				vs->vs_softCAR |= 1 << j;
63125881Ssam 				addr->v_dcd |= 1 << j;
63230372Skarels 			}
63325881Ssam 		break;
63424003Ssam 
63525881Ssam 	case VXT_PVIOCX:
63625881Ssam 	case VXT_PVIOCX|VXT_NEW:
63730372Skarels 		typestring = "VIOC-X (old connector panel)";
63825881Ssam 		break;
63925881Ssam 	case VXT_VIOCBOP:		/* VIOC-BOP */
64025881Ssam 		vs->vs_type = 1;
64125881Ssam 		vs->vs_bop = ++vxbbno;
64225881Ssam 		printf("VIOC-BOP no. %d at %x\n", vs->vs_bop, addr);
64324003Ssam 
64425933Ssam 	default:
64525881Ssam 		printf("vx%d: unknown type %x\n", vx, type);
64630372Skarels 		vxinfo[vx]->ui_alive = 0;
64725881Ssam 		return;
64824003Ssam 	}
64925881Ssam 	vs->vs_nbr = -1;
65025933Ssam 	vs->vs_maxcmd = (vs->vs_vers == VXV_NEW) ? 24 : 4;
65125933Ssam 	/*
65225933Ssam 	 * Initialize all cmd buffers by linking them
65325933Ssam 	 * into a free list.
65425933Ssam 	 */
65525881Ssam 	for (j = 0; j < NVCXBUFS; j++) {
65625933Ssam 		cp = &vs->vs_lst[j];
65725933Ssam 		cp->c_fwd = &vs->vs_lst[j+1];
65825881Ssam 	}
65925881Ssam 	vs->vs_avail = &vs->vs_lst[0];	/* set idx to 1st free buf */
66024003Ssam 	cp->c_fwd = (struct vxcmd *)0;	/* mark last buf in free list */
66124003Ssam 
66225933Ssam 	/*
66325933Ssam 	 * Establish the interrupt vectors and define the port numbers.
66425933Ssam 	 */
66525933Ssam 	cp = vobtain(vs);
66625933Ssam 	cp->cmd = VXC_LIDENT;
66725881Ssam 	cp->par[0] = vs->vs_ivec; 	/* ack vector */
66825857Ssam 	cp->par[1] = cp->par[0]+1;	/* cmd resp vector */
66925857Ssam 	cp->par[3] = cp->par[0]+2;	/* unsol intr vector */
67025881Ssam 	cp->par[4] = 15;		/* max ports, no longer used */
67125881Ssam 	cp->par[5] = 0;			/* set 1st port number */
67230372Skarels 	(void) vcmd(vx, (caddr_t)&cp->cmd);
67325881Ssam 	if (!wait)
67425881Ssam 		return;
67525881Ssam 	for (j = 0; cp->cmd == VXC_LIDENT && j < 4000000; j++)
67625857Ssam 		;
67725857Ssam 	if (j >= 4000000)
67825881Ssam 		printf("vx%d: didn't respond to LIDENT\n", vx);
67924003Ssam 
68024003Ssam  	/* calculate address of response buffer */
68125881Ssam  	resp = (char *)addr + (addr->v_rspoff&0x3fff);
68225933Ssam 	if (resp[0] != 0 && (resp[0]&0177) != 3) {
68325933Ssam 		vrelease(vs, cp);	/* init failed */
68425881Ssam 		return;
68524003Ssam 	}
68625881Ssam 	vs->vs_loport = cp->par[5];
68725881Ssam 	vs->vs_hiport = cp->par[7];
68830372Skarels 	printf("vx%d: %s%s, ports %d-%d\n", vx,
68930372Skarels 	    (vs->vs_vers == VXV_NEW) ? "" : "old ", typestring,
69030372Skarels 	    vs->vs_loport, vs->vs_hiport);
69125881Ssam 	vrelease(vs, cp);
69225933Ssam 	vs->vs_nbr = vx;		/* assign board number */
69324003Ssam }
69424003Ssam 
69524003Ssam /*
69624003Ssam  * Obtain a command buffer
69724003Ssam  */
69825881Ssam struct vxcmd *
69925881Ssam vobtain(vs)
70025933Ssam 	register struct vx_softc *vs;
70124003Ssam {
70225933Ssam 	register struct vxcmd *p;
70325881Ssam 	int s;
70424003Ssam 
70524003Ssam 	s = spl8();
70625881Ssam 	p = vs->vs_avail;
70725881Ssam 	if (p == (struct vxcmd *)0) {
70824003Ssam #ifdef VX_DEBUG
70925881Ssam 		if (vxintr4&VXNOBUF)
71025881Ssam 			vxintr4 &= ~VXNOBUF;
71124003Ssam #endif
71225881Ssam 		printf("vx%d: no buffers\n", vs - vx_softc);
71325881Ssam 		vxstreset(vs - vx_softc);
71424003Ssam 		splx(s);
71525881Ssam 		return (vobtain(vs));
71624003Ssam 	}
71730372Skarels 	vs->vs_avail = p->c_fwd;
71824003Ssam 	splx(s);
71925881Ssam 	return ((struct vxcmd *)p);
72024003Ssam }
72124003Ssam 
72224003Ssam /*
72324003Ssam  * Release a command buffer
72424003Ssam  */
72525881Ssam vrelease(vs, cp)
72625933Ssam 	register struct vx_softc *vs;
72725933Ssam 	register struct vxcmd *cp;
72824003Ssam {
72925881Ssam 	int s;
73024003Ssam 
73124003Ssam #ifdef VX_DEBUG
73225881Ssam 	if (vxintr4&VXNOBUF)
73325881Ssam 		return;
73424003Ssam #endif
73524003Ssam 	s = spl8();
73625881Ssam 	cp->c_fwd = vs->vs_avail;
73725881Ssam 	vs->vs_avail = cp;
73824003Ssam 	splx(s);
73924003Ssam }
74024003Ssam 
74125881Ssam struct vxcmd *
74225881Ssam nextcmd(vs)
74325933Ssam 	register struct vx_softc *vs;
74424003Ssam {
74525933Ssam 	register struct vxcmd *cp;
74625881Ssam 	int s;
74724003Ssam 
74824003Ssam 	s = spl8();
74925881Ssam 	cp = vs->vs_build;
75025881Ssam 	vs->vs_build = (struct vxcmd *)0;
75124003Ssam 	splx(s);
75225881Ssam 	return (cp);
75324003Ssam }
75424003Ssam 
75524003Ssam /*
75625933Ssam  * Assemble transmits into a multiple command;
75730372Skarels  * up to 8 transmits to 8 lines can be assembled together
75830372Skarels  * (on PVIOCX only).
75924003Ssam  */
76025933Ssam vsetq(vs, line, addr, n)
76125933Ssam 	register struct vx_softc *vs;
76225881Ssam 	caddr_t	addr;
76324003Ssam {
76425933Ssam 	register struct vxcmd *cp;
76525933Ssam 	register struct vxmit *mp;
76624003Ssam 
76725933Ssam 	/*
76825933Ssam 	 * Grab a new command buffer or append
76925933Ssam 	 * to the current one being built.
77025933Ssam 	 */
77125881Ssam 	cp = vs->vs_build;
77225881Ssam 	if (cp == (struct vxcmd *)0) {
77325881Ssam 		cp = vobtain(vs);
77425881Ssam 		vs->vs_build = cp;
77525881Ssam 		cp->cmd = VXC_XMITDTA;
77624003Ssam 	} else {
77730372Skarels 		if ((cp->cmd & 07) == 07 || vs->vs_vers == VXV_NEW) {
77825881Ssam 			printf("vx%d: setq overflow\n", vs-vx_softc);
77930372Skarels 			vxstreset((int)vs->vs_nbr);
78030372Skarels 			return;
78124003Ssam 		}
78224003Ssam 		cp->cmd++;
78324003Ssam 	}
78425933Ssam 	/*
78525933Ssam 	 * Select the next vxmit buffer and copy the
78625933Ssam 	 * characters into the buffer (if there's room
78725933Ssam 	 * and the device supports ``immediate mode'',
78825933Ssam 	 * or store an indirect pointer to the data.
78925933Ssam 	 */
79025881Ssam 	mp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit));
79125675Ssam 	mp->bcount = n-1;
79225933Ssam 	mp->line = line;
79325933Ssam 	if (vs->vs_vers == VXV_NEW && n <= sizeof (mp->ostream)) {
79425881Ssam 		cp->cmd = VXC_XMITIMM;
79530372Skarels 		bcopy(addr, mp->ostream, (unsigned)n);
79624003Ssam 	} else {
79725933Ssam 		/* get system address of clist block */
79825675Ssam 		addr = (caddr_t)vtoph((struct proc *)0, (unsigned)addr);
79930372Skarels 		bcopy((caddr_t)&addr, mp->ostream, sizeof (addr));
80024003Ssam 	}
80130372Skarels 	/*
80230372Skarels 	 * We send the data immediately if a VIOCX,
80330372Skarels 	 * the command buffer is full, or if we've nothing
80430372Skarels 	 * currently outstanding.  If we don't send it,
80530372Skarels 	 * set a timeout to force the data to be sent soon.
80630372Skarels 	 */
80730372Skarels 	if (vs->vs_vers == VXV_NEW || (cp->cmd & 07) == 7 ||
80830372Skarels 	    vs->vs_xmtcnt == 0) {
80930372Skarels 		vs->vs_xmtcnt++;
81030372Skarels 		(void) vcmd((int)vs->vs_nbr, (char *)&cp->cmd);
81130372Skarels 		vs->vs_build = 0;
81230372Skarels 	} else
81330372Skarels 		timeout(vxforce, (caddr_t)vs, 3);
81424003Ssam }
81525881Ssam 
81625881Ssam /*
81725881Ssam  * Write a command out to the VIOC
81825881Ssam  */
81925881Ssam vcmd(vx, cmdad)
82025881Ssam 	register int vx;
82125881Ssam 	register caddr_t cmdad;
82225881Ssam {
82325933Ssam 	register struct vcmds *cp;
82425881Ssam 	register struct vx_softc *vs;
82525881Ssam 	int s;
82625881Ssam 
82725881Ssam 	s = spl8();
82825881Ssam 	vs = &vx_softc[vx];
82925933Ssam 	/*
83025933Ssam 	 * When the vioc is resetting, don't process
83125933Ssam 	 * anything other than VXC_LIDENT commands.
83225933Ssam 	 */
83325881Ssam 	if (vs->vs_state == VXS_RESET && cmdad != NULL) {
83425933Ssam 		struct vxcmd *vcp = (struct vxcmd *)(cmdad-sizeof (vcp->c_fwd));
83525881Ssam 
83625933Ssam 		if (vcp->cmd != VXC_LIDENT) {
83725933Ssam 			vrelease(vs, vcp);
83825881Ssam 			return (0);
83925881Ssam 		}
84025881Ssam 	}
84125881Ssam 	cp = &vs->vs_cmds;
84225881Ssam 	if (cmdad != (caddr_t)0) {
84325881Ssam 		cp->cmdbuf[cp->v_fill] = cmdad;
84425881Ssam 		if (++cp->v_fill >= VC_CMDBUFL)
84525881Ssam 			cp->v_fill = 0;
84625881Ssam 		if (cp->v_fill == cp->v_empty) {
84725881Ssam 			printf("vx%d: cmd q overflow\n", vx);
84825881Ssam 			vxstreset(vx);
84925881Ssam 			splx(s);
85025881Ssam 			return (0);
85125881Ssam 		}
85225881Ssam 		cp->v_cmdsem++;
85325881Ssam 	}
85425881Ssam 	if (cp->v_cmdsem && cp->v_curcnt < vs->vs_maxcmd) {
85525881Ssam 		cp->v_cmdsem--;
85625881Ssam 		cp->v_curcnt++;
85725881Ssam 		vinthandl(vx, ((V_BSY|CMDquals) << 8)|V_INTR);
85825881Ssam 	}
85925881Ssam 	splx(s);
86025881Ssam 	return (1);
86125881Ssam }
86225881Ssam 
86325881Ssam /*
86425881Ssam  * VIOC acknowledge interrupt.  The VIOC has received the new
86525881Ssam  * command.  If no errors, the new command becomes one of 16 (max)
86625881Ssam  * current commands being executed.
86725881Ssam  */
86825881Ssam vackint(vx)
86925881Ssam 	register vx;
87025881Ssam {
87125933Ssam 	register struct vxdevice *vp;
87225933Ssam 	register struct vcmds *cp;
87325881Ssam 	struct vx_softc *vs;
87425881Ssam 	int s;
87525881Ssam 
87625881Ssam 	scope_out(5);
87725881Ssam 	vs = &vx_softc[vx];
87829954Skarels 	if (vs->vs_type)	/* Its a BOP */
87925881Ssam 		return;
88025881Ssam 	s = spl8();
88125881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
88225881Ssam 	cp = &vs->vs_cmds;
88325933Ssam 	if (vp->v_vcid&V_ERR) {
88425881Ssam 		register char *resp;
88525881Ssam 		register i;
88625933Ssam 
88730372Skarels 		printf("vx%d: ackint error type %x v_dcd %x\n", vx,
88825881Ssam 		    vp->v_vcid & 07, vp->v_dcd & 0xff);
88925881Ssam 		resp = (char *)vs->vs_mricmd;
89025881Ssam 		for (i = 0; i < 16; i++)
89125881Ssam 			printf("%x ", resp[i]&0xff);
89225881Ssam 		printf("\n");
89325881Ssam 		splx(s);
89425881Ssam 		vxstreset(vx);
89525881Ssam 		return;
89625881Ssam 	}
89725881Ssam 	if ((vp->v_hdwre&017) == CMDquals) {
89825881Ssam #ifdef VX_DEBUG
89925881Ssam 		if (vxintr4 & VXERR4) {	/* causes VIOC INTR ERR 4 */
90025933Ssam 			struct vxcmd *cp1, *cp0;
90125881Ssam 
90225933Ssam 			cp0 = (struct vxcmd *)
90325933Ssam 			    ((caddr_t)cp->cmdbuf[cp->v_empty]-sizeof (cp0->c_fwd));
90425881Ssam 			if (cp0->cmd == VXC_XMITDTA || cp0->cmd == VXC_XMITIMM) {
90525881Ssam 				cp1 = vobtain(vs);
90625881Ssam 				*cp1 = *cp0;
90725881Ssam 				vxintr4 &= ~VXERR4;
90825881Ssam 				(void) vcmd(vx, &cp1->cmd);
90925881Ssam 			}
91025881Ssam 		}
91125881Ssam #endif
91225881Ssam 		cp->v_curcmd[vp->v_vcid & VCMDLEN-1] = cp->cmdbuf[cp->v_empty];
91325881Ssam 		if (++cp->v_empty >= VC_CMDBUFL)
91425881Ssam 			cp->v_empty = 0;
91525881Ssam 	}
91625881Ssam 	if (++cp->v_itrempt >= VC_IQLEN)
91725881Ssam 		cp->v_itrempt = 0;
91825881Ssam 	vintempt(vx);
91925881Ssam 	splx(s);
92025881Ssam 	(void) vcmd(vx, (caddr_t)0);	/* queue next cmd, if any */
92125881Ssam }
92225881Ssam 
92325881Ssam /*
92425881Ssam  * Command Response interrupt.  The Vioc has completed
92525881Ssam  * a command.  The command may now be returned to
92625881Ssam  * the appropriate device driver.
92725881Ssam  */
92825881Ssam vcmdrsp(vx)
92925881Ssam 	register vx;
93025881Ssam {
93125933Ssam 	register struct vxdevice *vp;
93225933Ssam 	register struct vcmds *cp;
93325881Ssam 	register caddr_t cmd;
93425881Ssam 	register struct vx_softc *vs;
93525881Ssam 	register char *resp;
93625881Ssam 	register k;
93725881Ssam 	register int s;
93825881Ssam 
93925881Ssam 	scope_out(6);
94025881Ssam 	vs = &vx_softc[vx];
94125881Ssam 	if (vs->vs_type) {	/* Its a BOP */
94225881Ssam 		printf("vx%d: vcmdrsp interrupt\n", vx);
94325881Ssam 		return;
94425881Ssam 	}
94525881Ssam 	s = spl8();
94625881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
94725881Ssam 	cp = &vs->vs_cmds;
94825881Ssam 	resp = (char *)vp + (vp->v_rspoff&0x7fff);
94925881Ssam 	if (((k = resp[1])&V_UNBSY) == 0) {
95025881Ssam 		printf("vx%d: cmdresp debug\n", vx);
95125881Ssam 		splx(s);
95225881Ssam 		vxstreset(vx);
95325881Ssam 		return;
95425881Ssam 	}
95525881Ssam 	k &= VCMDLEN-1;
95625881Ssam 	cmd = cp->v_curcmd[k];
95725881Ssam 	cp->v_curcmd[k] = (caddr_t)0;
95825881Ssam 	cp->v_curcnt--;
95925881Ssam 	k = *((short *)&resp[4]);	/* cmd operation code */
96025881Ssam 	if ((k&0xff00) == VXC_LIDENT)	/* want hiport number */
96125881Ssam 		for (k = 0; k < VRESPLEN; k++)
96225881Ssam 			cmd[k] = resp[k+4];
96325881Ssam 	resp[1] = 0;
96425881Ssam 	vxxint(vx, (struct vxcmd *)cmd);
96525881Ssam 	if (vs->vs_state == VXS_READY)
96625881Ssam 		vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
96725881Ssam 	splx(s);
96825881Ssam }
96925881Ssam 
97025881Ssam /*
97125881Ssam  * Unsolicited interrupt.
97225881Ssam  */
97325881Ssam vunsol(vx)
97425881Ssam 	register vx;
97525881Ssam {
97625933Ssam 	register struct vxdevice *vp;
97725881Ssam 	struct vx_softc *vs;
97825881Ssam 	int s;
97925881Ssam 
98025881Ssam 	scope_out(1);
98125881Ssam 	vs = &vx_softc[vx];
98225881Ssam 	if (vs->vs_type) {	/* Its a BOP */
98325881Ssam 		printf("vx%d: vunsol from BOP\n", vx);
98425881Ssam 		return;
98525881Ssam 	}
98625881Ssam 	s = spl8();
98725881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
98825881Ssam 	if (vp->v_uqual&V_UNBSY) {
98925881Ssam 		vxrint(vx);
99025881Ssam 		vinthandl(vx, ((V_BSY|UNSquals) << 8)|V_INTR);
99125881Ssam #ifdef notdef
99225881Ssam 	} else {
99325881Ssam 		printf("vx%d: unsolicited interrupt error\n", vx);
99425881Ssam 		splx(s);
99525881Ssam 		vxstreset(vx);
99625881Ssam #endif
99725881Ssam 	}
99825881Ssam 	splx(s);
99925881Ssam }
100025881Ssam 
100125881Ssam /*
100225933Ssam  * Enqueue an interrupt.
100325881Ssam  */
100425881Ssam vinthandl(vx, item)
100525881Ssam 	register int vx;
100625881Ssam 	register item;
100725881Ssam {
100825881Ssam 	register struct vcmds *cp;
100925881Ssam 	int empty;
101025881Ssam 
101125881Ssam 	cp = &vx_softc[vx].vs_cmds;
101225933Ssam 	empty = (cp->v_itrfill == cp->v_itrempt);
101325881Ssam 	cp->v_itrqueu[cp->v_itrfill] = item;
101425881Ssam 	if (++cp->v_itrfill >= VC_IQLEN)
101525881Ssam 		cp->v_itrfill = 0;
101625881Ssam 	if (cp->v_itrfill == cp->v_itrempt) {
101725881Ssam 		printf("vx%d: interrupt q overflow\n", vx);
101825881Ssam 		vxstreset(vx);
101925881Ssam 	} else if (empty)
102025881Ssam 		vintempt(vx);
102125881Ssam }
102225881Ssam 
102325881Ssam vintempt(vx)
102425881Ssam 	register int vx;
102525881Ssam {
102625881Ssam 	register struct vcmds *cp;
102725881Ssam 	register struct vxdevice *vp;
102825881Ssam 	register short item;
102925881Ssam 	register short *intr;
103025881Ssam 
103125881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
103225881Ssam 	if (vp->v_vioc&V_BSY)
103325881Ssam 		return;
103425881Ssam 	cp = &vx_softc[vx].vs_cmds;
103525881Ssam 	if (cp->v_itrempt == cp->v_itrfill)
103625881Ssam 		return;
103725881Ssam 	item = cp->v_itrqueu[cp->v_itrempt];
103825881Ssam 	intr = (short *)&vp->v_vioc;
103925881Ssam 	switch ((item >> 8)&03) {
104025881Ssam 
104125881Ssam 	case CMDquals: {		/* command */
104225881Ssam 		int phys;
104325881Ssam 
104425881Ssam 		if (cp->v_empty == cp->v_fill || vp->v_vcbsy&V_BSY)
104525881Ssam 			break;
104625881Ssam 		vx_softc[vx].vs_mricmd = (caddr_t)cp->cmdbuf[cp->v_empty];
104725881Ssam 		phys = vtoph((struct proc *)0,
104825881Ssam 		    (unsigned)cp->cmdbuf[cp->v_empty]);
104925881Ssam 		vp->v_vcp[0] = ((short *)&phys)[0];
105025881Ssam 		vp->v_vcp[1] = ((short *)&phys)[1];
105125881Ssam 		vp->v_vcbsy = V_BSY;
105225881Ssam 		*intr = item;
105325881Ssam 		scope_out(4);
105425881Ssam 		break;
105525881Ssam 	}
105625881Ssam 
105725881Ssam 	case RSPquals:		/* command response */
105825881Ssam 		*intr = item;
105925881Ssam 		scope_out(7);
106025881Ssam 		break;
106125881Ssam 
106225881Ssam 	case UNSquals:		/* unsolicited interrupt */
106325881Ssam 		vp->v_uqual = 0;
106425881Ssam 		*intr = item;
106525881Ssam 		scope_out(2);
106625881Ssam 		break;
106725881Ssam 	}
106825881Ssam }
106925881Ssam 
107025881Ssam /*
107125881Ssam  * Start a reset on a vioc after error (hopefully)
107225881Ssam  */
107325881Ssam vxstreset(vx)
107425881Ssam 	register vx;
107525881Ssam {
107625881Ssam 	register struct vx_softc *vs;
107725933Ssam 	register struct vxdevice *vp;
107825881Ssam 	register struct vxcmd *cp;
107925881Ssam 	register int j;
108025881Ssam 	extern int vxinreset();
108125881Ssam 	int s;
108225881Ssam 
108325881Ssam 	s = spl8() ;
108425881Ssam 	vs = &vx_softc[vx];
108525881Ssam 	if (vs->vs_state == VXS_RESET) {	/* avoid recursion */
108625881Ssam 		splx(s);
108725881Ssam 		return;
108825881Ssam 	}
108925881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
109025881Ssam 	/*
109125881Ssam 	 * Zero out the vioc structures, mark the vioc as being
109225881Ssam 	 * reset, reinitialize the free command list, reset the vioc
109325881Ssam 	 * and start a timer to check on the progress of the reset.
109425881Ssam 	 */
109525881Ssam 	bzero((caddr_t)vs, (unsigned)sizeof (*vs));
109625881Ssam 
109725881Ssam 	/*
109825881Ssam 	 * Setting VXS_RESET prevents others from issuing
109925881Ssam 	 * commands while allowing currently queued commands to
110025881Ssam 	 * be passed to the VIOC.
110125881Ssam 	 */
110225881Ssam 	vs->vs_state = VXS_RESET;
110325881Ssam 	/* init all cmd buffers */
110425881Ssam 	for (j = 0; j < NVCXBUFS; j++) {
110525933Ssam 		cp = &vs->vs_lst[j];
110625933Ssam 		cp->c_fwd = &vs->vs_lst[j+1];
110725881Ssam 	}
110825933Ssam 	vs->vs_avail = &vs->vs_lst[0];
110925933Ssam 	cp->c_fwd = (struct vxcmd *)0;
111025881Ssam 	printf("vx%d: reset...", vx);
111125881Ssam 	vp->v_fault = 0;
111225881Ssam 	vp->v_vioc = V_BSY;
111325933Ssam 	vp->v_hdwre = V_RESET;		/* generate reset interrupt */
111425881Ssam 	timeout(vxinreset, (caddr_t)vx, hz*5);
111525881Ssam 	splx(s);
111625881Ssam }
111725881Ssam 
111825881Ssam /* continue processing a reset on a vioc after an error (hopefully) */
111925881Ssam vxinreset(vx)
112025881Ssam 	int vx;
112125881Ssam {
112225933Ssam 	register struct vxdevice *vp;
112325881Ssam 	int s = spl8();
112425881Ssam 
112525881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
112625881Ssam 	/*
112725881Ssam 	 * See if the vioc has reset.
112825881Ssam 	 */
112925881Ssam 	if (vp->v_fault != VXF_READY) {
113025881Ssam 		printf("failed\n");
113125881Ssam 		splx(s);
113225881Ssam 		return;
113325881Ssam 	}
113425881Ssam 	/*
113525881Ssam 	 * Send a LIDENT to the vioc and mess with carrier flags
113625881Ssam 	 * on parallel printer ports.
113725881Ssam 	 */
113829954Skarels 	vxinit(vx, 0);
113925881Ssam 	splx(s);
114025881Ssam }
114125881Ssam 
114225881Ssam /*
114325933Ssam  * Finish the reset on the vioc after an error (hopefully).
114425933Ssam  *
114525881Ssam  * Restore modem control, parameters and restart output.
114625881Ssam  * Since the vioc can handle no more then 24 commands at a time
114725881Ssam  * and we could generate as many as 48 commands, we must do this in
114825881Ssam  * phases, issuing no more then 16 commands at a time.
114925881Ssam  */
115025881Ssam vxfnreset(vx, cp)
115125881Ssam 	register int vx;
115225881Ssam 	register struct vxcmd *cp;
115325881Ssam {
115425881Ssam 	register struct vx_softc *vs;
115525933Ssam 	register struct vxdevice *vp ;
115625881Ssam 	register struct tty *tp, *tp0;
115725881Ssam 	register int i;
115825881Ssam #ifdef notdef
115925881Ssam 	register int on;
116025881Ssam #endif
116125881Ssam 	extern int vxrestart();
116225881Ssam 	int s = spl8();
116325881Ssam 
116425881Ssam 	vs = &vx_softc[vx];
116525881Ssam 	vs->vs_loport = cp->par[5];
116625881Ssam 	vs->vs_hiport = cp->par[7];
116725881Ssam 	vrelease(vs, cp);
116825881Ssam 	vs->vs_nbr = vx;			/* assign VIOC-X board number */
116925881Ssam 	vs->vs_state = VXS_READY;
117025881Ssam 
117125881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
117225881Ssam 	vp->v_vcid = 0;
117325881Ssam 
117425881Ssam 	/*
117525881Ssam 	 * Restore modem information and control.
117625881Ssam 	 */
117725881Ssam 	tp0 = &vx_tty[vx*16];
117825881Ssam 	for (i = vs->vs_loport; i <= vs->vs_hiport; i++) {
117925881Ssam 		tp = tp0 + i;
118025881Ssam 		if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) {
118125881Ssam 			tp->t_state &= ~TS_CARR_ON;
118225881Ssam 			vcmodem(tp->t_dev, VMOD_ON);
118325881Ssam 			if (tp->t_state&TS_CARR_ON)
118429954Skarels 				(void)(*linesw[tp->t_line].l_modem)(tp, 1);
118529954Skarels 			else if (tp->t_state & TS_ISOPEN)
118629954Skarels 				(void)(*linesw[tp->t_line].l_modem)(tp, 0);
118725881Ssam 		}
118829954Skarels #ifdef notdef
118925881Ssam 		/*
119025881Ssam 		 * If carrier has changed while we were resetting,
119125881Ssam 		 * take appropriate action.
119225881Ssam 		 */
119325881Ssam 		on = vp->v_dcd & 1<<i;
119429954Skarels 		if (on && (tp->t_state&TS_CARR_ON) == 0)
119529954Skarels 			(void)(*linesw[tp->t_line].l_modem)(tp, 1);
119629954Skarels 		else if (!on && tp->t_state&TS_CARR_ON)
119729954Skarels 			(void)(*linesw[tp->t_line].l_modem)(tp, 0);
119825881Ssam #endif
119925881Ssam 	}
120025881Ssam 	vs->vs_state = VXS_RESET;
120125881Ssam 	timeout(vxrestart, (caddr_t)vx, hz);
120225881Ssam 	splx(s);
120325881Ssam }
120425881Ssam 
120525881Ssam /*
120625881Ssam  * Restore a particular aspect of the VIOC.
120725881Ssam  */
120825881Ssam vxrestart(vx)
120925881Ssam 	int vx;
121025881Ssam {
121125881Ssam 	register struct tty *tp, *tp0;
121225881Ssam 	register struct vx_softc *vs;
121330372Skarels 	register int i, count;
121425881Ssam 	int s = spl8();
121525881Ssam 
121630372Skarels 	count = vx >> 8;
121725881Ssam 	vx &= 0xff;
121825881Ssam 	vs = &vx_softc[vx];
121925881Ssam 	vs->vs_state = VXS_READY;
122025881Ssam 	tp0 = &vx_tty[vx*16];
122125881Ssam 	for (i = vs->vs_loport; i <= vs->vs_hiport; i++) {
122225881Ssam 		tp = tp0 + i;
122330372Skarels 		if (count != 0) {
122425881Ssam 			tp->t_state &= ~(TS_BUSY|TS_TIMEOUT);
122525881Ssam 			if (tp->t_state&(TS_ISOPEN|TS_WOPEN))
122625881Ssam 				vxstart(tp);	/* restart pending output */
122725881Ssam 		} else {
122825881Ssam 			if (tp->t_state&(TS_WOPEN|TS_ISOPEN))
1229*37608Smarc 				vxcparam(tp, &tp->t_termios, 0);
123025881Ssam 		}
123125881Ssam 	}
123230372Skarels 	if (count == 0) {
123325881Ssam 		vs->vs_state = VXS_RESET;
123425881Ssam 		timeout(vxrestart, (caddr_t)(vx + 1*256), hz);
123525881Ssam 	} else
123625881Ssam 		printf("done\n");
123725881Ssam 	splx(s);
123825881Ssam }
123925881Ssam 
124025881Ssam vxreset(dev)
124125881Ssam 	dev_t dev;
124225881Ssam {
124325881Ssam 
124430372Skarels 	vxstreset((int)VXUNIT(minor(dev)));	/* completes asynchronously */
124525881Ssam }
124625881Ssam 
124730372Skarels #ifdef notdef
124825881Ssam vxfreset(vx)
124925881Ssam 	register int vx;
125025881Ssam {
125125881Ssam 	struct vba_device *vi;
125225881Ssam 
125325881Ssam 	if ((unsigned)vx > NVX || (vi = vxinfo[vx]) == 0 || vi->ui_addr == 0)
125425881Ssam 		return (ENODEV);
125525881Ssam 	vx_softc[vx].vs_state = VXS_READY;
125625881Ssam 	vxstreset(vx);
125725881Ssam 	return (0);		/* completes asynchronously */
125825881Ssam }
125930372Skarels #endif
126025881Ssam 
126125881Ssam vcmodem(dev, flag)
126225881Ssam 	dev_t dev;
126325881Ssam {
126425881Ssam 	struct tty *tp;
126525881Ssam 	register struct vxcmd *cp;
126625881Ssam 	register struct vx_softc *vs;
126725881Ssam 	register struct vxdevice *kp;
126825881Ssam 	register port;
126925881Ssam 	int unit;
127025881Ssam 
127125881Ssam 	unit = minor(dev);
127225881Ssam 	tp = &vx_tty[unit];
127325881Ssam 	vs = (struct vx_softc *)tp->t_addr;
127430372Skarels 	if (vs->vs_state != VXS_READY)
127530372Skarels 		return;
127625881Ssam 	cp = vobtain(vs);
127725881Ssam 	kp = (struct vxdevice *)((struct vba_device *)vxinfo[vs->vs_nbr])->ui_addr;
127825881Ssam 
127925881Ssam 	port = unit & 017;
128025881Ssam 	/*
128125881Ssam 	 * Issue MODEM command
128225881Ssam 	 */
128325881Ssam 	cp->cmd = VXC_MDMCTL;
128430372Skarels 	if (flag == VMOD_ON) {
128530372Skarels 		if (vs->vs_softCAR & (1 << port))
128630372Skarels 			cp->par[0] = V_MANUAL | V_DTR_ON | V_RTS;
128730372Skarels 		else
128830372Skarels 			cp->par[0] = V_AUTO | V_DTR_ON | V_RTS;
128930372Skarels 	} else
129030372Skarels 		cp->par[0] = V_DTR_OFF;
129125881Ssam 	cp->par[1] = port;
129230372Skarels 	(void) vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd);
129330372Skarels 	if (vs->vs_softCAR & (1 << port))
129430372Skarels 		kp->v_dcd |= (1 << port);
129530372Skarels 	if ((kp->v_dcd | vs->vs_softCAR) & (1 << port) && flag == VMOD_ON)
129630372Skarels 		tp->t_state |= TS_CARR_ON;
129725881Ssam }
129825881Ssam 
129925881Ssam /*
130025881Ssam  * VCMINTR called when an unsolicited interrup occurs signaling
130125881Ssam  * some change of modem control state.
130225881Ssam  */
130325881Ssam vcmintr(vx)
130425881Ssam 	register vx;
130525881Ssam {
130625881Ssam 	register struct vxdevice *kp;
130725881Ssam 	register struct tty *tp;
130825881Ssam 	register port;
130930372Skarels 	register struct vx_softc *vs;
131025881Ssam 
131125881Ssam 	kp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
131225881Ssam 	port = kp->v_usdata[0] & 017;
131325881Ssam 	tp = &vx_tty[vx*16+port];
131430372Skarels 	vs = &vx_softc[vx];
131525881Ssam 
131629954Skarels 	if (kp->v_ustat & DCD_ON)
131729954Skarels 		(void)(*linesw[tp->t_line].l_modem)(tp, 1);
131829954Skarels 	else if ((kp->v_ustat & DCD_OFF) &&
131930372Skarels 	    ((vs->vs_softCAR & (1 << port))) == 0 &&
132029954Skarels 	    (*linesw[tp->t_line].l_modem)(tp, 0) == 0) {
132129954Skarels 		register struct vcmds *cp;
132229954Skarels 		register struct vxcmd *cmdp;
132325881Ssam 
132430372Skarels 		/* clear all pending transmits */
132529954Skarels 		if (tp->t_state&(TS_BUSY|TS_FLUSH) &&
132629954Skarels 		    vs->vs_vers == VXV_NEW) {
132729954Skarels 			int i, cmdfound = 0;
132825881Ssam 
132929954Skarels 			cp = &vs->vs_cmds;
133029954Skarels 			for (i = cp->v_empty; i != cp->v_fill; ) {
133129954Skarels 				cmdp = (struct vxcmd *)((long *)cp->cmdbuf[i]-1);
133229954Skarels 				if ((cmdp->cmd == VXC_XMITDTA ||
133329954Skarels 				    cmdp->cmd == VXC_XMITIMM) &&
133429954Skarels 				    ((struct vxmit *)cmdp->par)->line == port) {
133529954Skarels 					cmdfound++;
133625881Ssam 					cmdp->cmd = VXC_FDTATOX;
133725881Ssam 					cmdp->par[1] = port;
133825881Ssam 				}
133929954Skarels 				if (++i >= VC_CMDBUFL)
134029954Skarels 					i = 0;
134125881Ssam 			}
134229954Skarels 			if (cmdfound)
134329954Skarels 				tp->t_state &= ~(TS_BUSY|TS_FLUSH);
134429954Skarels 			/* cmd is already in vioc, have to flush it */
134529954Skarels 			else {
134629954Skarels 				cmdp = vobtain(vs);
134729954Skarels 				cmdp->cmd = VXC_FDTATOX;
134829954Skarels 				cmdp->par[1] = port;
134930372Skarels 				(void) vcmd(vx, (caddr_t)&cmdp->cmd);
135025881Ssam 			}
135125881Ssam 		}
135229954Skarels 	} else if ((kp->v_ustat&BRK_CHR) && (tp->t_state&TS_ISOPEN)) {
1353*37608Smarc 		(*linesw[tp->t_line].l_rint)(TTY_FE, tp);
135425881Ssam 		return;
135525881Ssam 	}
135625881Ssam }
135725881Ssam #endif
1358