xref: /csrg-svn/sys/tahoe/vba/vx.c (revision 25857)
1*25857Ssam /*	vx.c	1.3	86/01/12	*/
224003Ssam 
324003Ssam #include "vx.h"
424003Ssam #if NVX > 0
524003Ssam /*
6*25857Ssam  * VIOC-X driver
724003Ssam  */
825675Ssam #include "../tahoe/pte.h"
924003Ssam 
1024003Ssam #include "../h/param.h"
1124003Ssam #include "../h/ioctl.h"
1224003Ssam #include "../h/tty.h"
1324003Ssam #include "../h/dir.h"
1424003Ssam #include "../h/user.h"
1524003Ssam #include "../h/map.h"
1624003Ssam #include "../h/buf.h"
1724003Ssam #include "../h/conf.h"
1824003Ssam #include "../h/file.h"
1924003Ssam #include "../h/uio.h"
2025675Ssam #include "../h/proc.h"
2125675Ssam #include "../h/vm.h"
2225675Ssam 
2325675Ssam #include "../tahoevba/vbavar.h"
2425675Ssam #include "../tahoevba/vioc.h"
2524003Ssam #ifdef VXPERF
2625675Ssam #include "../tahoevba/scope.h"
2724003Ssam #endif VXPERF
2824003Ssam #include "vbsc.h"
2924003Ssam #if NVBSC > 0
3024003Ssam #include "../bsc/bscio.h"
3124003Ssam #include "../bsc/bsc.h"
3224003Ssam char bscport[NVXPORTS];
3324003Ssam #endif
3424003Ssam 
3524003Ssam #ifdef BSC_DEBUG
3624003Ssam #include "../bsc/bscdebug.h"
3724003Ssam #endif
3824003Ssam 
3924003Ssam #ifdef	VX_DEBUG
4024003Ssam long vxintr4 = 0;
4124003Ssam long vxdebug = 0;
4224003Ssam #include "../vba/vxdebug.h"
4324003Ssam #endif
4424003Ssam 
4524003Ssam #define RSPquals	1
4624003Ssam 
47*25857Ssam struct	vcx vcx[NVIOCX] ;
48*25857Ssam struct	tty vx_tty[NVXPORTS];
49*25857Ssam extern	struct vcmds v_cmds[];
50*25857Ssam extern	long reinit;
5124003Ssam 
5224003Ssam int	vxstart() ;
5324003Ssam int	ttrstrt() ;
54*25857Ssam struct	vxcmd *vobtain() ;
55*25857Ssam struct	vxcmd *nextcmd() ;
5624003Ssam 
5724003Ssam /*
5824003Ssam  * Driver information for auto-configuration stuff.
5924003Ssam  * (not tested and probably should be changed)
6024003Ssam  */
6124003Ssam int	vxprobe(), vxattach(), vxrint();
6224003Ssam struct	vba_device *vxinfo[NVIOCX];
6324003Ssam long	vxstd[] = { 0 };
6424003Ssam struct	vba_driver vxdriver =
65*25857Ssam     { vxprobe, 0, vxattach, 0, vxstd, "vx", vxinfo };
6624003Ssam 
67*25857Ssam char	vxtype[NVIOCX];	/* 0: viox-x/vioc-b; 1: vioc-bop */
68*25857Ssam char	vxbbno = -1;
69*25857Ssam char	vxbopno[NVIOCX];	/* BOP board no. if indicated by vxtype[] */
70*25857Ssam int	vxivec[NVIOCX];		/* interrupt vector base */
71*25857Ssam extern	vbrall();
7224003Ssam 
73*25857Ssam vxprobe(reg, vi)
7424003Ssam 	caddr_t reg;
75*25857Ssam 	struct vba_device *vi;
7624003Ssam {
77*25857Ssam 	register int br, cvec;			/* must be r12, r11 */
7824003Ssam 	register struct vblok *vp = (struct vblok *)reg;
7924003Ssam 
8024003Ssam #ifdef lint
8124003Ssam 	br = 0; cvec = br; br = cvec;
8225675Ssam 	vackint(0); vunsol(0); vcmdrsp(0); vxfreset(0);
8324003Ssam #endif
8425675Ssam 	if (badaddr((caddr_t)vp, 1))
8525675Ssam 		return (0);
8625675Ssam 	vp->v_fault = 0;
8725675Ssam 	vp->v_vioc = V_BSY;
8825675Ssam 	vp->v_hdwre = V_RESET;		/* reset interrupt */
8924003Ssam 	DELAY(4000000);
9025675Ssam 	if (vp->v_fault != VREADY)
9125675Ssam 		return (0);
92*25857Ssam #ifdef notdef
93*25857Ssam 	/*
94*25857Ssam 	 * Align vioc interrupt vector base to 4 vector
95*25857Ssam 	 * boundary and fitting in 8 bits (is this necessary,
96*25857Ssam 	 * wish we had documentation).
97*25857Ssam 	 */
98*25857Ssam 	if ((vi->ui_hd->vh_lastiv -= 3) > 0xff)
99*25857Ssam 		vi->ui_hd->vh_lastiv = 0xff;
100*25857Ssam 	vxivec[vi->ui_unit] = vi->ui_hd->vh_lastiv =
101*25857Ssam 	    vi->ui_hd->vh_lastiv &~ 0x3;
102*25857Ssam #else
103*25857Ssam 	vxivec[vi->ui_unit] = 0x40+vi->ui_unit*4;
104*25857Ssam #endif
105*25857Ssam 	br = 0x18, cvec = vxivec[vi->ui_unit];	/* XXX */
10625675Ssam 	return (sizeof (*vp));
10724003Ssam }
10824003Ssam 
109*25857Ssam vxattach(vi)
110*25857Ssam 	register struct vba_device *vi;
11124003Ssam {
11225675Ssam 
113*25857Ssam 	VIOCBAS[vi->ui_unit] = vi->ui_addr;
114*25857Ssam 	vxinit(vi->ui_unit, (long)1);
11524003Ssam }
11624003Ssam 
11724003Ssam /*
11824003Ssam  * Open a VX line.
11924003Ssam  */
12025675Ssam /*ARGSUSED*/
12124003Ssam vxopen(dev, flag)
12224003Ssam {
12324003Ssam 	register struct tty *tp;	/* pointer to tty struct for port */
12424003Ssam 	register struct vcx *xp;	/* pointer to VIOC-X info/cmd buffer */
12524003Ssam 	register d;			/* minor device number */
12624003Ssam 	register long jj;
12724003Ssam 
12824003Ssam 
12924003Ssam 	d = minor(dev);			/* get minor device number */
13024003Ssam 	if (d >= NVXPORTS)		/* validate minor device number */
13124003Ssam 		return ENXIO;		/* set errno to indicate bad port # */
13224003Ssam 	tp = &vx_tty[d];		/* index the tty structure for port */
13324003Ssam 
13424003Ssam 	xp = &vcx[d>>4];			/* index VIOC-X info/cmd area */
13524003Ssam 	d &= 017;
13624003Ssam 
13724003Ssam 	/* If we did not find a board with the correct port number on
13824003Ssam 	   it, or the entry for the VIOC-X had no ports on it, inform the
13924003Ssam 	   caller that the port does not exist. */
14024003Ssam 	if(!( xp->v_loport <= d && d <= xp->v_hiport )	/* home? */
14124003Ssam 	 || (xp->v_hiport - xp->v_loport)==0)
14224003Ssam 		return ENXIO;	/* bad minor device number */
14324003Ssam 	tp->t_addr = (caddr_t)xp;	/* store address of VIOC-X info */
14424003Ssam 	tp->t_oproc = vxstart;		/* store address of startup routine */
14524003Ssam 	tp->t_dev = dev;		/* store major/minor device numbers */
14624003Ssam 	d = spl8();
14724003Ssam 	tp->t_state |= TS_WOPEN;	/* mark device as waiting for open */
14824003Ssam 	if ((tp->t_state&TS_ISOPEN) == 0)	/* is device already open? */
14924003Ssam 	{				/*  no, open it */
15024003Ssam 		ttychars(tp);		/* set default control chars */
15124003Ssam 		if (tp->t_ispeed == 0)	/* if no default speeds set them */
15224003Ssam 		{
15324003Ssam 			tp->t_ispeed = SSPEED;	/* default input baud */
15424003Ssam 			tp->t_ospeed = SSPEED;	/* default output baud */
15524003Ssam 			tp->t_flags |= (ODDP|EVENP|ECHO); /* default modes */
15624003Ssam 		}
15724003Ssam 		vxparam(dev);		/* set parameters for this port */
15824003Ssam 	}
15924003Ssam 	splx(d);
16024003Ssam 	/* ? if already open for exclusive use open fails unless caller is
16124003Ssam 	     root. */
16224003Ssam 	if (tp->t_state&TS_XCLUDE && u.u_uid!=0)
16324003Ssam 		return EBUSY;	/* device is busy, sorry */
16424003Ssam 
16524003Ssam 	/* wait for data carrier detect to go high */
16624003Ssam 	d = spl8();
16724003Ssam 	if( !vcmodem(dev,VMOD_ON) )
16824003Ssam 		while( (tp->t_state&TS_CARR_ON) == 0 )
16925675Ssam 			sleep((caddr_t)&tp->t_canq,TTIPRI);
17024003Ssam 	jj= (*linesw[tp->t_line].l_open)(dev,tp); /*let tty.c finish the open */
17124003Ssam 	splx(d);	/* 1/2/85 : assures open complete */
17224003Ssam 	return (jj);
17324003Ssam }
17424003Ssam 
17524003Ssam /*
17624003Ssam  * Close a VX line.
17724003Ssam  */
17825675Ssam /*ARGSUSED*/
17924003Ssam vxclose(dev, flag)
18024003Ssam dev_t dev;
18124003Ssam int  flag;
18224003Ssam {
18324003Ssam 	register struct tty *tp;
18424003Ssam 	register d;
18524003Ssam 
18624003Ssam 	d = minor(dev) & 0377;
18724003Ssam 	tp = &vx_tty[d];
18824003Ssam 	d = spl8();
18924003Ssam 	(*linesw[tp->t_line].l_close)(tp);
19024003Ssam 	if ((tp->t_state&TS_ISOPEN) && (tp->t_state&TS_HUPCLS))
19124003Ssam 		if( !vcmodem(dev,VMOD_OFF) )
19224003Ssam 			tp->t_state &= ~TS_CARR_ON;
19324003Ssam 	/* wait for the last response */
19424003Ssam 	while(tp->t_state & TS_FLUSH)
19524003Ssam 		sleep( (caddr_t)&tp->t_state, TTOPRI ) ;
19624003Ssam 	ttyclose(tp);	/* let tty.c finish the close */
19724003Ssam 	splx(d);
19824003Ssam }
19924003Ssam 
20024003Ssam /*
20124003Ssam  * Read from a VX line.
20224003Ssam  */
20324003Ssam vxread(dev, uio)
20424003Ssam 	dev_t dev;
20524003Ssam 	struct uio *uio;
20624003Ssam {
20724003Ssam 	register struct tty *tp = &vx_tty[minor(dev) & 0377];
20824003Ssam 	return (*linesw[tp->t_line].l_read)(tp, uio);
20924003Ssam }
21024003Ssam 
21124003Ssam /*
21224003Ssam  * write on a VX line
21324003Ssam  */
21424003Ssam vxwrite(dev, uio)
21524003Ssam 	dev_t dev;
21624003Ssam 	struct uio *uio;
21724003Ssam {
21824003Ssam 	register struct tty *tp = &vx_tty[minor(dev) & 0377];
21924003Ssam 	return (*linesw[tp->t_line].l_write)(tp, uio);
22024003Ssam }
22124003Ssam 
22224003Ssam /*
22324003Ssam  * VIOCX unsolicited interrupt.
22424003Ssam  */
22524003Ssam vxrint(n)
22624003Ssam register n;				/* mux number */
22724003Ssam {
22824003Ssam 	register struct tty *tp;
22924003Ssam 	register struct vcx *xp;
23024003Ssam 	register short *sp;
23124003Ssam 	register struct vblok *kp;
23224003Ssam 	register int i, c;
23324003Ssam 	short *savsilo;
23424003Ssam 	struct silo {
23524003Ssam 		char	data;
23624003Ssam 		char	port;
23724003Ssam 	};
23824003Ssam 
23924003Ssam 	kp = VBAS(n);
24024003Ssam 	xp = &vcx[n];
24124003Ssam 	switch(kp->v_uqual&037) {
24224003Ssam 	case 0:
24324003Ssam 		break;
24424003Ssam 	case 2:
24524003Ssam 		printf(" ERR NBR %x\n",kp->v_ustat);
24624003Ssam 		vpanic("vc: VC PROC ERR");
24724003Ssam 		vxstreset(n);
24824003Ssam 		return(0);
24924003Ssam 	case 3:
25024003Ssam 		vcmintr(n);
25124003Ssam 		return(1);
25224003Ssam 	case 4:
25324003Ssam 		return(1);
25424003Ssam 	default:
25524003Ssam 		printf(" ERR NBR %x\n",kp->v_uqual);
25624003Ssam 		vpanic("vc: VC UQUAL ERR");
25724003Ssam 		vxstreset(n);
25824003Ssam 		return(0);
25924003Ssam 	}
26024003Ssam 	if(xp->v_vers == V_NEW) {
26124003Ssam 		register short *aa ;
26224003Ssam 		aa = (short *)kp->v_usdata;
26324003Ssam 		sp = (short *)(*aa  + (char *)kp) ;
26424003Ssam 	} else {
26524003Ssam 		c = kp->v_usdata[0] << 6;
26624003Ssam 		sp = (short *)((char *)kp + SILOBAS + c);
26724003Ssam 	}
26824003Ssam 	i = *(savsilo = sp);
26924003Ssam 	if (i == 0) return(1);
27024003Ssam 	if(xp->v_vers == V_NEW)
27124003Ssam 		if( i > xp->v_silosiz ) {
27224003Ssam 			printf("vx: %d exceeds silo size\n",i) ;
27324003Ssam 			i = xp->v_silosiz;
27424003Ssam 		}
27524003Ssam 	for(sp++;i > 0;i--,sp++) {
27624003Ssam 		c = ((struct silo *)sp)->port & 017;
27724003Ssam 		tp = &vx_tty[c+n*16];
27824003Ssam 		if(xp->v_loport > c || c > xp->v_hiport)
27924003Ssam 			continue;	/* port out of bounds */
28024003Ssam 		if( (tp->t_state & TS_ISOPEN) == 0) {
28124003Ssam 			wakeup((caddr_t)&tp->t_rawq);
28224003Ssam 			continue;
28324003Ssam 		}
28424003Ssam 		c = ((struct silo *)sp)->data;
28524003Ssam 		switch(((struct silo *)sp)->port&(PERROR|FERROR)) {
28624003Ssam 		case PERROR:
28724003Ssam 		case PERROR|FERROR:
28824003Ssam 			if( (tp->t_flags&(EVENP|ODDP)) == EVENP
28924003Ssam 			|| (tp->t_flags & (EVENP|ODDP)) == ODDP )
29024003Ssam 				continue;
29124003Ssam 			if(!(((struct silo *)sp)->port&FERROR))
29224003Ssam 				break;
29324003Ssam 		case FERROR:
29424003Ssam 			if(tp->t_flags & RAW) c = 0;
29524003Ssam 			else c = tp->t_intrc;
29624003Ssam 		}
29724003Ssam 		(*linesw[tp->t_line].l_rint)(c, tp);
29824003Ssam 	}
29924003Ssam 	*savsilo = 0;
30024003Ssam 	return(1);
30124003Ssam }
30224003Ssam 
30324003Ssam /*
30424003Ssam  * stty/gtty for VX
30524003Ssam  */
30624003Ssam vxioctl(dev, cmd, data, flag)
30724003Ssam int	dev;			/* major, minor device numbers */
30824003Ssam int	cmd;			/* command */
30924003Ssam caddr_t	data;
31024003Ssam int	flag;
31124003Ssam {
31224003Ssam 	register struct tty	*tp;
31324003Ssam 	register error;
31424003Ssam 
31524003Ssam 	tp = &vx_tty[minor(dev) & 0377];
31624003Ssam 	error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag);
31724003Ssam 	if (error == 0)
31824003Ssam 		return error;
31924003Ssam 	if((error = ttioctl(tp, cmd, data, flag)) >= 0)
32024003Ssam 	{
32124003Ssam 		if (cmd==TIOCSETP||cmd==TIOCSETN)
32224003Ssam 			vxparam(dev);
32324003Ssam 		return error;
32424003Ssam 	} else
32524003Ssam 		return ENOTTY;
32624003Ssam }
32724003Ssam 
32824003Ssam 
32924003Ssam vxparam(dev)
33024003Ssam dev_t	dev;
33124003Ssam {
33224003Ssam 	vxcparam(dev, 1);
33324003Ssam }
33424003Ssam 
33524003Ssam /*
33624003Ssam  * Set parameters from open or stty into the VX hardware
33724003Ssam  * registers.
33824003Ssam  */
33924003Ssam vxcparam(dev, wait)
34024003Ssam dev_t	dev;			/* major, minor device numbers */
34124003Ssam int wait;			/* nonzero if we should wait for finish */
34224003Ssam {
34324003Ssam 	register struct tty	*tp;
34424003Ssam 	register struct vcx	*xp;
34524003Ssam 	register struct vxcmd	*cp;
34624003Ssam 	register s;
34724003Ssam 
34824003Ssam 	tp = &vx_tty[minor(dev)];	/* pointer to tty structure for port */
34924003Ssam 	xp = (struct vcx *)tp->t_addr;	/* pointer to VIOCX info/cmd buffer */
35024003Ssam 	cp = vobtain(xp);
35124003Ssam 	s = spl8();
35224003Ssam 	cp->cmd = LPARAX;		/* set command to "load parameters" */
35324003Ssam 	cp->par[1] = minor(dev)&017;	/* port number */
35424003Ssam 
35524003Ssam 	cp->par[2] = (tp->t_flags&RAW)? 0 : tp->t_startc;	/* XON char */
35624003Ssam 	cp->par[3] = (tp->t_flags&RAW)? 0 : tp->t_stopc;	/* XOFF char */
35724003Ssam 
35824003Ssam 	if(tp->t_flags&(RAW|LITOUT) ||
35924003Ssam 	  (tp->t_flags&(EVENP|ODDP)) == (EVENP|ODDP)) {
36024003Ssam 		cp->par[4] = 0xc0;	/* 8 bits of data */
36124003Ssam 		cp->par[7] = 0;		/* no parity */
36224003Ssam 	} else {
36324003Ssam 		cp->par[4] = 0x40;	/* 7 bits of data */
36424003Ssam 		if((tp->t_flags&(EVENP|ODDP)) == ODDP)
36524003Ssam 			cp->par[7] = 1;		/* odd parity */
36624003Ssam 		else if((tp->t_flags&(EVENP|ODDP)) == EVENP)
36724003Ssam 			cp->par[7] = 3;		/* even parity */
36824003Ssam 		else
36924003Ssam 			cp->par[7] = 0;		/* no parity */
37024003Ssam 	}
37124003Ssam 	cp->par[5] = 0x4;			/* 1 stop bit */
37224003Ssam 	cp->par[6] = tp->t_ospeed;
37324003Ssam 
37425675Ssam 	if (vcmd(xp->v_nbr, (caddr_t)&cp->cmd) && wait)
37525675Ssam 		sleep((caddr_t)cp,TTIPRI);
37624003Ssam 	splx(s);
37724003Ssam }
37824003Ssam 
37924003Ssam /*
38024003Ssam  * VIOCX command response interrupt.
38124003Ssam  * For transmission, restart output to any active port.
38224003Ssam  * For all other commands, just clean up.
38324003Ssam  */
38424003Ssam vxxint(n,cp)
38524003Ssam register int n;			/* VIOC number */
38624003Ssam register struct vxcmd	*cp;	/* command structure */
38724003Ssam {
38824003Ssam 	register struct	vxmit	*vp, *pvp;
38924003Ssam 	register struct	tty	*tp;
39024003Ssam 	register struct	vcx	*xp;
39124003Ssam 	register struct tty	*hp;
39224003Ssam 
39324003Ssam 	xp = &vcx[n];
39424003Ssam 	cp = (struct vxcmd *)( (long *)cp - 1);
39524003Ssam #if NVBSC > 0
39624003Ssam 	switch(cp->cmd) {
39724003Ssam 	case MDMCTL1: case HUNTMD1: case LPARAX1:
39824003Ssam 		vrelease(xp, cp);
39924003Ssam 		wakeup(cp);
40024003Ssam 		return;
40124003Ssam 	}
40224003Ssam #endif
40324003Ssam 	switch(cp->cmd&0xff00) {
40424003Ssam 	case LIDENT:	/* initialization complete */
40524003Ssam 		if (xp->v_state & V_RESETTING) {
40624003Ssam 			vxfnreset(n,cp);
40724003Ssam 			vinthandl(n,((V_BSY | RSPquals) << 8) | V_INTR);
40824003Ssam 		}
40924003Ssam 		cp->cmd++;
41024003Ssam 		return;
41124003Ssam 	case XMITDTA: case XMITIMM:
41224003Ssam 		break;
41324003Ssam 	case LPARAX:
41425675Ssam 		wakeup((caddr_t)cp);
41524003Ssam 	default:	/* MDMCTL or FDTATOX */
41624003Ssam 		vrelease(xp, cp);
41724003Ssam 		if (xp->v_state & V_RESETTING) {
41824003Ssam 			vinthandl(n,((V_BSY | RSPquals) << 8) | V_INTR);
41924003Ssam 		}
42024003Ssam 		return;
42124003Ssam 	}
42224003Ssam 	for(vp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizvxmit);
42324003Ssam 	    vp >= (struct vxmit *)cp->par;
42424003Ssam 	    vp = (struct vxmit *) ((char *)vp - sizvxmit) )
42524003Ssam 	{
42624003Ssam 		tp = &vx_tty[(vp->line & 017)+n*16];
42724003Ssam /* cjk buffer bug */
42824003Ssam #if NVBSC > 0
42924003Ssam 					/* bsc change */
43024003Ssam 		if (tp->t_line == LDISP) {
43124003Ssam 			vrelease(xp, cp);
43224003Ssam 			bsctxd((vp->line & 017));
43324003Ssam 			return ;
43424003Ssam 		}
43524003Ssam 					/* End of bsc change */
43624003Ssam #endif
43724003Ssam /* cjk */
43824003Ssam 		pvp = vp;
43924003Ssam 		tp->t_state &= ~TS_BUSY;
44024003Ssam 		if(tp->t_state & TS_FLUSH) {
44124003Ssam 			tp->t_state &= ~TS_FLUSH;
44224003Ssam 			wakeup( (caddr_t)&tp->t_state ) ;
44324003Ssam 		}
44424003Ssam 		else
44524003Ssam 		 	ndflush(&tp->t_outq, vp->bcount+1);
44624003Ssam 	}
44724003Ssam 	xp->v_xmtcnt--;
44824003Ssam 	vrelease(xp,cp);
44924003Ssam 	if(xp->v_vers == V_NEW) {
45024003Ssam 		vp = pvp;
45124003Ssam 		xp->v_actport[(vp->line & 017) - xp->v_loport] |= 1 ;
45224003Ssam 		if(vxstart(tp) && (cp = nextcmd(xp)) != NULL)
45324003Ssam 		{
45424003Ssam 			xp->v_xmtcnt++;
45525675Ssam 			vcmd(n, (caddr_t)&cp->cmd);
45624003Ssam 			return ;
45724003Ssam 		}
45824003Ssam 		xp->v_actport[(vp->line & 017) - xp->v_loport] = 0 ;
45924003Ssam 		return ;
46024003Ssam 	}
46124003Ssam 	xp->v_actflg = 1;
46224003Ssam 	hp = &vx_tty[xp->v_hiport+n*16];
46324003Ssam 	for(tp = &vx_tty[xp->v_loport+n*16];tp <= hp;tp++)
46424003Ssam 		if(vxstart(tp) && (cp = nextcmd(xp)) != NULL)
46524003Ssam 		{
46624003Ssam 			xp->v_xmtcnt++;
46725675Ssam 			vcmd(n, (caddr_t)&cp->cmd);
46824003Ssam 		}
46924003Ssam 	if( (cp = nextcmd(xp)) != NULL )		/* command to send ? */
47024003Ssam 	{
47124003Ssam 		xp->v_xmtcnt++;
47225675Ssam 		vcmd(n, (caddr_t)&cp->cmd);
47324003Ssam 	}
47424003Ssam 	xp->v_actflg = 0;
47524003Ssam }
47624003Ssam 
47724003Ssam /*
47824003Ssam  * Force out partial XMIT command after timeout
47924003Ssam  */
48024003Ssam vxforce(xp)
48124003Ssam register struct vcx	*xp;
48224003Ssam {
48324003Ssam 	register struct vxcmd	*cp;
48424003Ssam 	register int s;
48524003Ssam 
48624003Ssam 	s = spl8();
48724003Ssam 	if((cp = nextcmd(xp)) != NULL) {
48824003Ssam 		xp->v_xmtcnt++;
48925675Ssam 		vcmd(xp->v_nbr, (caddr_t)&cp->cmd);
49024003Ssam 	}
49124003Ssam 	splx(s);
49224003Ssam }
49324003Ssam 
49424003Ssam /*
49524003Ssam  * Start (restart) transmission on the given VX line.
49624003Ssam  */
49724003Ssam vxstart(tp)
49824003Ssam register struct tty *tp;
49924003Ssam {
50025675Ssam 	register short n;
50124003Ssam 	register struct	vcx	*xp;
50224003Ssam 	register char *outb;
50324003Ssam 	register full = 0;
50424003Ssam 	int k, s, port;
50524003Ssam 
50624003Ssam 	s = spl8();
50724003Ssam 	port = minor(tp->t_dev) & 017;
50824003Ssam 	xp = (struct vcx *)tp->t_addr;
50924003Ssam 	if (!(tp->t_state&(TS_TIMEOUT|TS_BUSY|TS_TTSTOP))) {
51024003Ssam 		if (tp->t_outq.c_cc<=TTLOWAT(tp)) {
51124003Ssam 			if (tp->t_state&TS_ASLEEP) {
51224003Ssam 				tp->t_state &= ~TS_ASLEEP;
51324003Ssam 				wakeup((caddr_t)&tp->t_outq);
51424003Ssam 			}
51524003Ssam 			if (tp->t_wsel) {
51624003Ssam 				selwakeup(tp->t_wsel, tp->t_state & TS_WCOLL);
51724003Ssam 				tp->t_wsel = 0;
51824003Ssam 				tp->t_state &= ~TS_WCOLL;
51924003Ssam 			}
52024003Ssam 		}
52124003Ssam 		if(tp->t_outq.c_cc == 0) {
52224003Ssam 			splx(s);
52324003Ssam 			return(0);
52424003Ssam 		}
52524003Ssam #ifdef VXPERF
52624003Ssam 	scope_out(3);
52724003Ssam #endif VXPERF
52824003Ssam 		if(!(tp->t_flags&(RAW|LITOUT)))
52924003Ssam 			full = 0200;
53025675Ssam 		if((n = ndqb(&tp->t_outq, full)) == 0)   {
53124003Ssam 			if(full) {
53225675Ssam 				n = getc(&tp->t_outq);
53325675Ssam 				timeout(ttrstrt, (caddr_t)tp, (n&0177) +6);
53424003Ssam 				tp->t_state |= TS_TIMEOUT;
53524003Ssam 				full = 0;
53624003Ssam 			}
53724003Ssam 		} else {
53824003Ssam 			outb = (char *)tp->t_outq.c_cf;
53924003Ssam 			tp->t_state |= TS_BUSY;
54024003Ssam 			if(xp->v_vers == V_NEW)
54124003Ssam 				k = xp->v_actport[port - xp->v_loport] ;
54224003Ssam 			else
54324003Ssam 				k = xp->v_actflg ;
54424003Ssam 
54525675Ssam 			full = vsetq(xp, port, outb, n);
54624003Ssam 
54724003Ssam 			if( (k&1) == 0 ) {	/* not called from vxxint */
54824003Ssam 				if(full || xp->v_xmtcnt == 0) {
54924003Ssam 					outb = (char *)(&nextcmd(xp)->cmd);
55024003Ssam 					xp->v_xmtcnt++;
55124003Ssam 					vcmd(xp->v_nbr, outb );
55224003Ssam 				} else
55325675Ssam 					timeout(vxforce,(caddr_t)xp,3);
55424003Ssam 			}
55524003Ssam 		}
55624003Ssam 	}
55724003Ssam 	splx(s);
55824003Ssam 	return(full);	/* indicate if max commands or not */
55924003Ssam }
56024003Ssam 
56124003Ssam /*
56224003Ssam  * Stop output on a line.
56324003Ssam  */
56424003Ssam vxstop(tp)
56524003Ssam register struct tty *tp;
56624003Ssam {
56724003Ssam 	register  s;
56824003Ssam 
56924003Ssam 	s = spl8();
57024003Ssam 	if (tp->t_state & TS_BUSY) {
57124003Ssam 		if ((tp->t_state&TS_TTSTOP)==0) {
57224003Ssam 			tp->t_state |= TS_FLUSH;
57324003Ssam 		}
57424003Ssam 	}
57524003Ssam 	splx(s);
57624003Ssam }
57724003Ssam 
57824003Ssam /*
57924003Ssam  * VIOCX Initialization.  Makes free lists of command buffers.
58024003Ssam  * Resets all viocx's.  Issues a LIDENT command to each
58124003Ssam  * viocx which establishes interrupt vectors and logical
58224003Ssam  * port numbers
58324003Ssam  */
58424003Ssam vxinit(i,wait)
58524003Ssam register int	i;
58624003Ssam long wait;
58724003Ssam {
58824003Ssam 	register struct	vcx	*xp;	/* ptr to VIOC-X info/cmd buffer */
58924003Ssam 	register struct	vblok	*kp;	/* pointer to VIOC-X control block */
59024003Ssam 	register struct	vxcmd	*cp;	/* pointer to a command buffer */
59124003Ssam 	register char	*resp;		/* pointer to response buffer */
59224003Ssam 	register int	j;
59324003Ssam 	char type;
59425675Ssam #if NVBSC > 0
59524003Ssam 	register struct	bsc	*bp;	/* bsc change */
59624003Ssam 	extern	 struct	bsc	bsc[];
59725675Ssam #endif
59824003Ssam 
59924003Ssam 
60024003Ssam 	kp = VBAS(i);		/* get base adr of cntl blok for VIOC */
60124003Ssam 
60224003Ssam 	xp = &vcx[i];		/* index info/command buffers */
60324003Ssam 	type = kp->v_ident;
60424003Ssam 	vxtype[i] =  0;		/* Type is Viox-x */
60524003Ssam 	switch(type) {
60624003Ssam 	case VIOCX:
60724003Ssam 		{
60824003Ssam 		xp->v_vers = V_OLD ;
60924003Ssam 		/* set DCD for printer ports */
61024003Ssam 		for(j = 0;j < 16;j++)
61124003Ssam 			if (kp->v_portyp[j] == 4 )
61224003Ssam 				kp->v_dcd |= 1 << j ;
61324003Ssam 		}
61424003Ssam 		break ;
61524003Ssam 	case NWVIOCX:
61624003Ssam 		{
61724003Ssam 		xp->v_vers = V_NEW ;
61824003Ssam 		xp->v_silosiz = kp->v_maxsilo ;
61924003Ssam 		/* set DCD for printer ports */
62024003Ssam 		for(j = 0;j < 16;j++)
62124003Ssam 			if (kp->v_portyp[j] == 4 )
62224003Ssam 				kp->v_dcd |= 1 << j ;
62324003Ssam 		}
62424003Ssam 		break ;
62524003Ssam 	case PVIOCX:
62624003Ssam 		xp->v_vers = V_OLD ;
62724003Ssam 		break ;
62824003Ssam 	case NPVIOCX:
62924003Ssam 		xp->v_vers = V_NEW ;
63024003Ssam 		xp->v_silosiz = kp->v_maxsilo ;
63124003Ssam 		break ;
63224003Ssam #if NVBSC > 0
63324003Ssam 	case VIOCB:	/* old f/w, Bisync board */
63424003Ssam 		printf("%X: %x%x OLD VIOC-B, ",
63524003Ssam 					(long)kp, (int)kp->v_ident,
63624003Ssam 					(int)kp->v_fault);
63724003Ssam 		xp->v_vers = V_OLD ;
63824003Ssam 		/* save device specific info */
63924003Ssam 		for(bp = &bsc[0]; bp <= &bsc[NBSC]; bp++)
64024003Ssam 			bp->b_devregs = (caddr_t)xp ;
64124003Ssam 		printf("%d BSC Ports initialized.\n",NBSC);
64224003Ssam 		break ;
64324003Ssam 
64424003Ssam 	case NWVIOCB:	/* new f/w, Bisync board */
64524003Ssam 		printf("%X: %x%x 16K VIOC-B, ",
64624003Ssam 					(long)kp, (int)kp->v_ident,
64724003Ssam 					(int)kp->v_fault);
64824003Ssam 		xp->v_vers = V_NEW ;
64924003Ssam 		xp->v_silosiz = kp->v_maxsilo ;
65024003Ssam 		/* save device specific info */
65124003Ssam 		for(bp = &bsc[0]; bp <= &bsc[NBSC]; bp++)
65224003Ssam 			bp->b_devregs = (caddr_t)xp ;
65324003Ssam 		printf("%d BSC Ports initialized.\n",NBSC);
65424003Ssam 		if(CBSIZE > kp->v_maxxmt)
65524003Ssam 			printf("vxinit: Warning CBSIZE > maxxmt\n") ;
65624003Ssam 		break ;
65724003Ssam #endif
65824003Ssam 	case VBOPID:		/* VIOC-BOP */
65924003Ssam 		vxbbno++;
66024003Ssam 		vxtype[i] = 1;
66124003Ssam 		vxbopno[i] = vxbbno;
66224003Ssam 		printf("VIOC-BOP no. %d at %lx\n",vxbopno[i],VIOCBAS[i]);
66324003Ssam 	default:
66424003Ssam 		return ;	/* Not a viocx type */
66524003Ssam 	}
66624003Ssam 	xp->v_nbr = -1;		/* no number for it yet */
66724003Ssam 	xp->v_maxcmd = xp->v_vers == V_NEW ? 24 : 4;
66824003Ssam 
66924003Ssam 	for(j=0; j<NVCXBUFS; j++)	/* init all cmd buffers */
67024003Ssam 	{
67124003Ssam 		cp = &xp->vx_lst[j];	/* index a buffer */
67224003Ssam 		cp->c_fwd = &xp->vx_lst[j+1];	/* point to next buf */
67324003Ssam 	}
67424003Ssam 	xp->vx_avail = &xp->vx_lst[0];	/* set idx to 1st free buf */
67524003Ssam 	cp->c_fwd = (struct vxcmd *)0;	/* mark last buf in free list */
67624003Ssam 
67724003Ssam 	cp = vobtain(xp);	/* grap the control block */
67824003Ssam 	cp->cmd = LIDENT;	/* set command type */
679*25857Ssam 	cp->par[0] = vxivec[i]; 	/* ack vector */
680*25857Ssam 	cp->par[1] = cp->par[0]+1;	/* cmd resp vector */
681*25857Ssam 	cp->par[3] = cp->par[0]+2;	/* unsol intr vector */
68224003Ssam 	cp->par[4] = 15;	/* max ports, no longer used */
68324003Ssam 	cp->par[5] = 0;		/* set 1st port number */
68425675Ssam 	vcmd(i, (caddr_t)&cp->cmd);	/* initialize the VIOC-X */
68524003Ssam 
68624003Ssam 	if (!wait) return;
687*25857Ssam 	for (j = 0; cp->cmd == LIDENT && j < 4000000; j++)
688*25857Ssam 		;
689*25857Ssam 	if (j >= 4000000)
690*25857Ssam 		printf("vx%d: didn't respond to LIDENT\n", i);
69124003Ssam 
69224003Ssam  	/* calculate address of response buffer */
69324003Ssam  	resp = (char *)kp;
69424003Ssam  	resp += kp->v_rspoff & 0x3FFF;
69524003Ssam 
69624003Ssam 	if(resp[0] != 0 && (resp[0]&0177) != 3)	/* did init work? */
69724003Ssam 	{
69824003Ssam 		vrelease(xp,cp);	/* init failed */
69924003Ssam 		return;			/* try next VIOC-X */
70024003Ssam 	}
70124003Ssam 
70224003Ssam 	xp->v_loport = cp->par[5];	/* save low port number */
70324003Ssam 	xp->v_hiport = cp->par[7];/* VIOC knows high port numbr */
70424003Ssam 	vrelease(xp,cp);	/* done with this control block */
70524003Ssam 	xp->v_nbr = i;		/* assign VIOC-X board number */
70624003Ssam }
70724003Ssam 
70824003Ssam /*
70924003Ssam  * Obtain a command buffer
71024003Ssam  */
71124003Ssam struct	vxcmd *
71224003Ssam vobtain(xp)
71324003Ssam register struct	vcx	*xp;
71424003Ssam {
71524003Ssam 
71624003Ssam 	register struct	vxcmd	*p;
71724003Ssam 	register s;
71824003Ssam 
71924003Ssam 	s = spl8();
72024003Ssam 	p = xp->vx_avail;
72124003Ssam 	if(p == (struct vxcmd *)0) {
72224003Ssam #ifdef VX_DEBUG
72324003Ssam 		if (vxintr4 & VXNOBUF) vxintr4 &= ~VXNOBUF;
72424003Ssam #endif
72524003Ssam 		vpanic("vx: no buffs");
72624003Ssam 		vxstreset(xp - vcx);
72724003Ssam 		splx(s);
72824003Ssam 		return(vobtain(xp));
72924003Ssam 	}
73024003Ssam 	xp->vx_avail = (xp->vx_avail)->c_fwd;
73124003Ssam 	splx(s);
73224003Ssam 	return( (struct vxcmd *)p);
73324003Ssam }
73424003Ssam 
73524003Ssam /*
73624003Ssam  * Release a command buffer
73724003Ssam  */
73824003Ssam vrelease(xp,cp)
73924003Ssam register struct	vcx	*xp;
74024003Ssam register struct	vxcmd	*cp;
74124003Ssam {
74224003Ssam 
74324003Ssam 	register s;
74424003Ssam 
74524003Ssam #ifdef VX_DEBUG
74624003Ssam 	if (vxintr4 & VXNOBUF) return;
74724003Ssam #endif
74824003Ssam 	s = spl8();
74924003Ssam 	cp->c_fwd = xp->vx_avail;
75024003Ssam 	xp->vx_avail = cp;
75124003Ssam 	splx(s);
75224003Ssam }
75324003Ssam 
75424003Ssam /*
75524003Ssam  * vxcmd -
75624003Ssam  *
75724003Ssam  */
75824003Ssam struct vxcmd 	*
75924003Ssam nextcmd(xp)
76024003Ssam register struct	vcx	*xp;
76124003Ssam {
76224003Ssam 	register struct	vxcmd	*cp;
76324003Ssam 	register int	s;
76424003Ssam 
76524003Ssam 	s = spl8();
76624003Ssam 	cp = xp->vx_build;
76724003Ssam 	xp->vx_build = (struct vxcmd *)0;
76824003Ssam 	splx(s);
76924003Ssam 	return(cp);
77024003Ssam }
77124003Ssam 
77224003Ssam /*
77324003Ssam  * assemble transmits into a multiple command.
77424003Ssam  * up to 8 transmits to 8 lines can be assembled together
77524003Ssam  */
77625675Ssam vsetq(xp ,d ,addr, n)
77724003Ssam register struct	vcx	*xp;
77824003Ssam caddr_t	addr;
77924003Ssam {
78024003Ssam 
78124003Ssam 	register struct	vxcmd	*cp;
78224003Ssam 	register struct	vxmit	*mp;
78324003Ssam 	register char	*p;
78424003Ssam 	register i;
78524003Ssam 
78624003Ssam 	cp = xp->vx_build;
78724003Ssam 	if(cp == (struct vxcmd *)0) {
78824003Ssam 		cp = vobtain(xp);
78924003Ssam 		xp->vx_build = cp;
79024003Ssam 		cp->cmd = XMITDTA;
79124003Ssam 	} else {
79224003Ssam 		if((cp->cmd & 07) == 07) {
79324003Ssam 			vpanic("vx: vsetq overflow");
79424003Ssam 			vxstreset(xp->v_nbr);
79524003Ssam 			return(0);
79624003Ssam 		}
79724003Ssam 		cp->cmd++;
79824003Ssam 	}
79924003Ssam 
80024003Ssam 	mp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizvxmit);
80125675Ssam 	mp->bcount = n-1;
80224003Ssam 
80324003Ssam 	mp->line = d;
80425675Ssam 	if((xp->v_vers == V_NEW) && (n <= 6)) {
80524003Ssam 		cp->cmd = XMITIMM ;
80624003Ssam 		p = addr;
80725675Ssam 		/* bcopy(addr, &(char *)mp->ostream, n) ; */
80824003Ssam 	} else {
80925675Ssam 		addr = (caddr_t)vtoph((struct proc *)0, (unsigned)addr);
81025675Ssam 				/* should be a sys address */
81124003Ssam 		p = (char *)&addr;
81225675Ssam 		n = sizeof addr;
81324003Ssam 		/* mp->ostream = addr ; */
81424003Ssam 	}
81525675Ssam 	for(i=0; i<n; i++)
81624003Ssam 		mp->ostream[i] = *p++;
81724003Ssam 	if(xp->v_vers == V_NEW)
81824003Ssam 		return(1) ;
81924003Ssam 	else
82024003Ssam 		return((cp->cmd&07) == 7) ;	/* Indicate if full */
82124003Ssam }
82224003Ssam #endif
823