1*25877Ssam /* vxc.c 1.5 86/01/12 */
224002Ssam
324002Ssam #include "vx.h"
424002Ssam #if NVX > 0
524002Ssam /*
6*25877Ssam * VIOC driver
724002Ssam */
8*25877Ssam #ifdef VXPERF
9*25877Ssam #define DOSCOPE
10*25877Ssam #endif
11*25877Ssam
1225861Ssam #include "param.h"
1325861Ssam #include "file.h"
1425861Ssam #include "ioctl.h"
1525861Ssam #include "tty.h"
1625861Ssam #include "errno.h"
1725861Ssam #include "time.h"
1825861Ssam #include "kernel.h"
1925861Ssam #include "proc.h"
2025861Ssam
2125675Ssam #include "../tahoevba/vioc.h"
2225861Ssam #include "../tahoesna/snadebug.h"
2325675Ssam #include "../tahoevba/scope.h"
2424002Ssam
2524002Ssam #define CMDquals 0
2624002Ssam #define RSPquals 1
2724002Ssam #define UNSquals 2
2824002Ssam
2924002Ssam extern struct vcx vcx[] ;
3024002Ssam extern struct tty vx_tty[];
3124002Ssam struct vcmds v_cmds[NVIOCX] ;
3224002Ssam
3324002Ssam extern char vxtype[];
3424002Ssam extern char vxbbno;
3524002Ssam extern char vxbopno[];
3624002Ssam #ifdef SNA_DEBUG
3724002Ssam extern vbrall();
3824002Ssam #endif SNA_DEBUG
3924002Ssam extern struct vxcmd *vobtain();
4024002Ssam
4124002Ssam #ifdef VX_DEBUG
4224002Ssam #include "../vba/vxdebug.h"
4324002Ssam #endif
4424002Ssam
4524002Ssam /*
4624002Ssam * Write a command out to the VIOC
4724002Ssam */
vcmd(n,cmdad)4824002Ssam vcmd(n, cmdad)
4924002Ssam register int n ;
5024002Ssam register caddr_t cmdad ; /* command address */
5124002Ssam {
5224002Ssam
5324002Ssam register struct vcmds *cp ;
5424002Ssam register struct vcx *xp;
5524002Ssam int s ;
5624002Ssam
5724002Ssam s = spl8() ;
5824002Ssam cp = &v_cmds[n] ;
5924002Ssam xp = &vcx[n];
6024002Ssam if (xp->v_state&V_RESETTING && cmdad != NULL) {
6124002Ssam /*
6224002Ssam * When the vioc is resetting, don't process
6324002Ssam * anything other than LIDENT commands.
6424002Ssam */
6525675Ssam register struct vxcmd *cmdp = (struct vxcmd *)
6625675Ssam ((char *)cmdad - sizeof(cmdp->c_fwd));
6725675Ssam if (cmdp->cmd != LIDENT) {
6825675Ssam vrelease(xp, cmdp);
6924002Ssam return(0);
7024002Ssam }
7124002Ssam }
7224002Ssam if (cmdad != (caddr_t) 0) {
7324002Ssam cp->cmdbuf[cp->v_fill] = cmdad ;
7424002Ssam if( ++cp->v_fill >= VC_CMDBUFL ) cp->v_fill = 0 ;
7524002Ssam if(cp->v_fill == cp->v_empty) {
7624002Ssam vpanic("vc: CMD Q OVFLO") ;
7724002Ssam vxstreset(n);
7824002Ssam splx(s);
7924002Ssam return(0);
8024002Ssam }
8124002Ssam cp->v_cmdsem++;
8224002Ssam }
8324002Ssam if(cp->v_cmdsem && cp->v_curcnt < vcx[n].v_maxcmd) {
8424002Ssam cp->v_cmdsem--;
8524002Ssam cp->v_curcnt++;
8624002Ssam vinthandl(n, ((V_BSY | CMDquals) << 8) | V_INTR ) ;
8724002Ssam }
8824002Ssam splx(s) ;
8925675Ssam return(1);
9024002Ssam }
9124002Ssam
9224002Ssam /*
9324002Ssam * VIOC acknowledge interrupt. The VIOC has received the new
9424002Ssam * command. If no errors, the new command becomes one of 16 (max)
9524002Ssam * current commands being executed.
9624002Ssam */
vackint(n)9724002Ssam vackint(n)
9824002Ssam register n ; /* VIOC number */
9924002Ssam {
10024002Ssam
10124002Ssam register struct vblok *vp ;
10224002Ssam register struct vcmds *cp ;
10324002Ssam register s;
10424002Ssam
10524002Ssam scope_out(5);
10624002Ssam if (vxtype[n]) { /* Its a BOP */
10724002Ssam #ifdef SNA_DEBUG
10824002Ssam if (snadebug & SVIOC)
10924002Ssam printf("vack: interrupt from BOP at VIOC%d,1st vector.\n",n);
11024002Ssam vbrall(n); /* Int. from BOP, port 0 */
11124002Ssam #endif
11224002Ssam return;
11324002Ssam }
11424002Ssam s = spl8();
11524002Ssam vp = VBAS(n) ;
11624002Ssam cp = &v_cmds[n] ;
11724002Ssam if( vp->v_vcid & V_ERR ) {
11824002Ssam register char *resp;
11924002Ssam register i;
12024002Ssam printf ("INTR ERR type = %x VIOC = %x, v_dcd: %lx\n",
12124002Ssam vp->v_vcid & 07, n, vp->v_dcd & 0xff);
12224002Ssam /* resp = (char *)vp + (vp->v_rspoff & 0x7FFF); */
12324002Ssam resp = (char *)(&vcx[n])->v_mricmd;
12424002Ssam for(i=0; i<16; i++)
12524002Ssam printf("%x ", resp[i]&0xff);
12624002Ssam vpanic( "\nvcc: vackint") ;
12724002Ssam splx(s);
12824002Ssam vxstreset(n);
12924002Ssam return ;
13024002Ssam } else
13124002Ssam if((vp->v_hdwre&017) == CMDquals) {
13224002Ssam #ifdef VX_DEBUG
13324002Ssam if (vxintr4 & VXERR4) { /* causes VIOC INTR ERR 4 */
13424002Ssam register struct vxcmd *cp1;
13524002Ssam register struct vxcmd *cp0 = (struct vxcmd *)
13624002Ssam ((long)cp->cmdbuf[cp->v_empty] - 4);
13724002Ssam if ((cp0->cmd == XMITDTA) || (cp0->cmd == XMITIMM)) {
13824002Ssam cp1 = vobtain(&vcx[n]);
13924002Ssam *cp1 = *cp0;
14024002Ssam vxintr4 &= ~VXERR4;
14125675Ssam (void) vcmd(n,&cp1->cmd);
14224002Ssam }
14324002Ssam }
14424002Ssam #endif
14524002Ssam cp->v_curcmd[vp->v_vcid & VCMDLEN-1] = cp->cmdbuf[cp->v_empty] ;
14624002Ssam if( ++cp->v_empty >= VC_CMDBUFL ) cp->v_empty = 0 ;
14724002Ssam }
14824002Ssam if( ++cp->v_itrempt >= VC_IQLEN ) cp->v_itrempt = 0 ;
14924002Ssam vintempt(n) ;
15024002Ssam splx(s);
15125675Ssam (void) vcmd(n, (caddr_t)0); /* queue next cmd, if any */
15224002Ssam }
15324002Ssam
15424002Ssam /*
15524002Ssam * Command Response interrupt. The Vioc has completed
15624002Ssam * a command. The command may now be returned to
15724002Ssam * the appropriate device driver .
15824002Ssam */
vcmdrsp(n)15924002Ssam vcmdrsp(n)
16024002Ssam register n ;
16124002Ssam {
16224002Ssam
16324002Ssam register struct vblok *vp ;
16424002Ssam register struct vcmds *cp ;
16524002Ssam register caddr_t cmd ;
16624002Ssam register char *resp ;
16724002Ssam register k ;
16824002Ssam register int s ;
16924002Ssam
17024002Ssam scope_out(6);
17124002Ssam if (vxtype[n]) { /* Its a BOP */
17224002Ssam printf("vcmdrsp: stray interrupt from BOP at VIOC%d...\n",n);
17324002Ssam return;
17424002Ssam }
17524002Ssam s = spl8();
17624002Ssam vp = VBAS(n) ;
17724002Ssam cp = &v_cmds[n] ;
17824002Ssam resp = (char *)vp;
17924002Ssam resp += vp->v_rspoff & 0x7FFF;
18024002Ssam
18124002Ssam if( (k=resp[1]) & V_UNBSY ) {
18224002Ssam k &= VCMDLEN-1;
18324002Ssam cmd = cp->v_curcmd[k];
18424002Ssam cp->v_curcmd[k] = (caddr_t)0;
18524002Ssam cp->v_curcnt--;
18624002Ssam k = *((short *)&resp[4]); /* cmd operation code */
18724002Ssam if((k & 0xFF00) == LIDENT) { /* want hiport number */
18824002Ssam for(k=0; k<VRESPLEN; k++)
18924002Ssam cmd[k] = resp[k+4];
19024002Ssam }
19124002Ssam resp[1] = 0;
19225675Ssam vxxint(n, (struct vxcmd *)cmd) ;
19324002Ssam if ((&vcx[n])->v_state == V_RESETTING) return;
19424002Ssam }
19524002Ssam else {
19624002Ssam vpanic( "vc, cmdresp debug") ;
19724002Ssam splx(s);
19824002Ssam vxstreset(n);
19924002Ssam return;
20024002Ssam }
20124002Ssam
20224002Ssam vinthandl(n, ( (V_BSY | RSPquals) << 8 ) | V_INTR ) ;
20324002Ssam splx(s);
20424002Ssam
20524002Ssam }
20624002Ssam
20724002Ssam
20824002Ssam /*
20924002Ssam * Unsolicited interrupt.
21024002Ssam */
21124002Ssam vunsol(n)
21224002Ssam register(n) ;
21324002Ssam {
21424002Ssam
21524002Ssam register struct vblok *vp ;
21624002Ssam register s;
21724002Ssam
21824002Ssam scope_out(1);
21924002Ssam if (vxtype[n]) { /* Its a BOP */
22024002Ssam printf("vunsol: stray interrupt from BOP at VIOC%d...\n",n);
22124002Ssam return;
22224002Ssam }
22324002Ssam s = spl8();
22424002Ssam vp = VBAS(n) ;
22524002Ssam if(vp->v_uqual & V_UNBSY) {
22624002Ssam vxrint(n) ;
22724002Ssam vinthandl(n, ( (V_BSY | UNSquals) << 8 ) | V_INTR ) ;
22825857Ssam #ifdef notdef
22925857Ssam } else {
23024002Ssam vpanic("vc: UNSOL INT ERR") ;
23124002Ssam splx(s);
23224002Ssam vxstreset(n);
23325857Ssam #endif
23424002Ssam }
23525857Ssam splx(s);
23624002Ssam }
23724002Ssam
23824002Ssam /*
23924002Ssam * Enqueue an interrupt
24024002Ssam */
vinthandl(n,item)24124002Ssam vinthandl(n, item)
24224002Ssam register int n ;
24324002Ssam register item ;
24424002Ssam {
24524002Ssam
24624002Ssam register struct vcmds *cp ;
24724002Ssam register int empflag = 0 ;
24824002Ssam
24924002Ssam cp = &v_cmds[n] ;
25024002Ssam if( cp->v_itrfill == cp->v_itrempt ) empflag++ ;
25124002Ssam cp->v_itrqueu[cp->v_itrfill] = item ;
25224002Ssam if( ++cp->v_itrfill >= VC_IQLEN ) cp->v_itrfill = 0 ;
25324002Ssam if(cp->v_itrfill == cp->v_itrempt) {
25424002Ssam vpanic( "vc: INT Q OVFLO" ) ;
25524002Ssam vxstreset(n);
25624002Ssam }
25724002Ssam else if( empflag ) vintempt(n) ;
25824002Ssam }
25924002Ssam
vintempt(n)26024002Ssam vintempt(n)
26124002Ssam register int n ;
26224002Ssam {
26324002Ssam register struct vcmds *cp ;
26424002Ssam register struct vblok *vp ;
26524002Ssam register short item ;
26624002Ssam register short *intr ;
26724002Ssam
26824002Ssam vp = VBAS(n) ;
26924002Ssam if(vp->v_vioc & V_BSY) return ;
27024002Ssam cp = &v_cmds[n] ;
27124002Ssam if(cp->v_itrempt == cp->v_itrfill) return ;
27224002Ssam item = cp->v_itrqueu[cp->v_itrempt] ;
27324002Ssam intr = (short *)&vp->v_vioc ;
27424002Ssam switch( (item >> 8) & 03 ) {
27524002Ssam
27624002Ssam case CMDquals: /* command */
27724002Ssam {
27824002Ssam int phys;
27924002Ssam
28024002Ssam if(cp->v_empty == cp->v_fill || vp->v_vcbsy&V_BSY)
28124002Ssam break;
28224002Ssam (&vcx[n])->v_mricmd = (caddr_t)cp->cmdbuf[cp->v_empty];
28325675Ssam phys = vtoph((struct proc *)0, (unsigned)cp->cmdbuf[cp->v_empty]) ; /* should be a sys address */
28424002Ssam vp->v_vcp[0] = ((short *)&phys)[0];
28524002Ssam vp->v_vcp[1] = ((short *)&phys)[1];
28624002Ssam vp->v_vcbsy = V_BSY ;
28724002Ssam *intr = item ;
28824002Ssam }
289*25877Ssam scope_out(4);
29024002Ssam break ;
29124002Ssam
29224002Ssam case RSPquals: /* command response */
29324002Ssam *intr = item ;
294*25877Ssam scope_out(7);
29524002Ssam break ;
29624002Ssam
29724002Ssam case UNSquals: /* unsolicited interrupt */
29824002Ssam vp->v_uqual = 0 ;
29924002Ssam *intr = item ;
300*25877Ssam scope_out(2);
30124002Ssam break ;
30224002Ssam }
30324002Ssam }
30424002Ssam
30524002Ssam
30624002Ssam /* start a reset on a vioc after error (hopefully) */
vxstreset(n)30724002Ssam vxstreset(n)
30824002Ssam register n;
30924002Ssam {
31024002Ssam register struct vcx *xp;
31124002Ssam register struct vblok *vp ;
31224002Ssam register struct vxcmd *cp;
31324002Ssam register int j;
31424002Ssam extern int vxinreset();
31524002Ssam int s ;
31624002Ssam
31724002Ssam s = spl8() ;
31824002Ssam vp = VBAS(n);
31924002Ssam xp = &vcx[n];
32024002Ssam
32124002Ssam if (xp->v_state&V_RESETTING)
32224002Ssam /*
32324002Ssam * Avoid infinite recursion.
32424002Ssam */
32524002Ssam return;
32624002Ssam
32724002Ssam /*
32824002Ssam * Zero out the vioc structures, mark the vioc as being
32924002Ssam * reset, reinitialize the free command list, reset the vioc
33024002Ssam * and start a timer to check on the progress of the reset.
33124002Ssam */
33225675Ssam bzero((caddr_t)&v_cmds[n], (unsigned)sizeof (struct vcmds));
33325675Ssam bzero((caddr_t)xp, (unsigned)sizeof (struct vcx));
33424002Ssam
33524002Ssam /*
33624002Ssam * Setting V_RESETTING prevents others from issuing
33724002Ssam * commands while allowing currently queued commands to
33824002Ssam * be passed to the VIOC.
33924002Ssam */
34024002Ssam xp->v_state |= V_RESETTING;
34124002Ssam for(j=0; j<NVCXBUFS; j++) /* init all cmd buffers */
34224002Ssam {
34324002Ssam cp = &xp->vx_lst[j]; /* index a buffer */
34424002Ssam cp->c_fwd = &xp->vx_lst[j+1]; /* point to next buf */
34524002Ssam }
34624002Ssam xp->vx_avail = &xp->vx_lst[0]; /* set idx to 1st free buf */
34724002Ssam cp->c_fwd = (struct vxcmd *)0; /* mark last buf in free list */
34824002Ssam
34924002Ssam printf("resetting VIOC %x .. ", n);
35024002Ssam
35124002Ssam vp->v_fault = 0 ;
35224002Ssam vp->v_vioc = V_BSY ;
35324002Ssam vp->v_hdwre = V_RESET ; /* reset interrupt */
35424002Ssam
35524002Ssam timeout(vxinreset, (caddr_t)n, hz*5);
35624002Ssam splx(s);
35724002Ssam return;
35824002Ssam }
35924002Ssam
36024002Ssam /* continue processing a reset on a vioc after an error (hopefully) */
vxinreset(vioc)36124002Ssam vxinreset(vioc)
36224002Ssam caddr_t vioc;
36324002Ssam {
36425675Ssam register int n = (int)vioc;
36524002Ssam register struct vblok *vp ;
36624002Ssam int s = spl8();
36724002Ssam printf("vxinreset ");
36824002Ssam
36924002Ssam vp = VBAS(n);
37024002Ssam
37124002Ssam /*
37224002Ssam * See if the vioc has reset.
37324002Ssam */
37424002Ssam if (vp->v_fault != VREADY) {
37524002Ssam printf("failed\n");
37624002Ssam splx(s);
37724002Ssam return;
37824002Ssam }
37924002Ssam
38024002Ssam /*
38124002Ssam * Send a LIDENT to the vioc and mess with carrier flags
38224002Ssam * on parallel printer ports.
38324002Ssam */
38425675Ssam vxinit(n, (long)0);
38524002Ssam splx(s);
38624002Ssam }
38724002Ssam
38824002Ssam /*
38924002Ssam * Restore modem control, parameters and restart output.
39024002Ssam * Since the vioc can handle no more then 24 commands at a time
39124002Ssam * and we could generate as many as 48 commands, we must do this in
39224002Ssam * phases, issuing no more then 16 commands at a time.
39324002Ssam */
39424002Ssam /* finish the reset on the vioc after an error (hopefully) */
vxfnreset(n,cp)39524002Ssam vxfnreset(n, cp)
39624002Ssam register int n;
39724002Ssam register struct vxcmd *cp;
39824002Ssam {
39924002Ssam register struct vcx *xp;
40024002Ssam register struct vblok *vp ;
40124002Ssam register struct tty *tp;
40224002Ssam register int i;
40325675Ssam #ifdef notdef
40424002Ssam register int on;
40525675Ssam #endif
40624002Ssam extern int vxrestart();
40724002Ssam int s = spl8();
40824002Ssam printf("vxfnreset ");
40924002Ssam
41024002Ssam vp = VBAS(n);
41124002Ssam xp = &vcx[n];
41224002Ssam
41324002Ssam xp->v_loport = cp->par[5]; /* save low port number */
41424002Ssam xp->v_hiport = cp->par[7];/* VIOC knows high port numbr */
41524002Ssam vrelease(xp,cp); /* done with this control block */
41624002Ssam xp->v_nbr = n; /* assign VIOC-X board number */
41724002Ssam
41824002Ssam xp->v_state &= ~V_RESETTING;
41924002Ssam
42024002Ssam vp->v_vcid = 0;
42124002Ssam
42224002Ssam /*
42324002Ssam * Restore modem information and control.
42424002Ssam */
42524002Ssam for(i=xp->v_loport; i<=xp->v_hiport; i++) {
42624002Ssam tp = &vx_tty[i+n*16];
42724002Ssam if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) {
42824002Ssam tp->t_state &= ~TS_CARR_ON;
42924002Ssam vcmodem(tp->t_dev, VMOD_ON);
43024002Ssam if (tp->t_state&TS_CARR_ON) {
43124002Ssam wakeup((caddr_t)&tp->t_canq) ;
43224002Ssam }
43324002Ssam else {
43424002Ssam if(tp->t_state & TS_ISOPEN) {
43524002Ssam ttyflush(tp, FREAD|FWRITE);
43624002Ssam if(tp->t_state&TS_FLUSH)
43724002Ssam wakeup((caddr_t)&tp->t_state) ;
43824002Ssam if((tp->t_flags&NOHANG)==0) {
43924002Ssam gsignal(tp->t_pgrp, SIGHUP) ;
44024002Ssam gsignal(tp->t_pgrp, SIGCONT);
44124002Ssam }
44224002Ssam }
44324002Ssam }
44424002Ssam }
44524002Ssam /*
44624002Ssam * If carrier has changed while we were resetting,
44724002Ssam * take appropriate action.
44824002Ssam */
44925675Ssam #ifdef notdef
45024002Ssam on = vp->v_dcd & 1<<i;
45124002Ssam if (on && (tp->t_state&TS_CARR_ON) == 0) {
45224002Ssam tp->t_state |= TS_CARR_ON ;
45324002Ssam wakeup((caddr_t)&tp->t_canq) ;
45424002Ssam } else if (!on && tp->t_state&TS_CARR_ON) {
45524002Ssam tp->t_state &= ~TS_CARR_ON ;
45624002Ssam if(tp->t_state & TS_ISOPEN) {
45724002Ssam ttyflush(tp, FREAD|FWRITE);
45824002Ssam if(tp->t_state&TS_FLUSH)
45924002Ssam wakeup((caddr_t)&tp->t_state) ;
46024002Ssam if((tp->t_flags&NOHANG)==0) {
46124002Ssam gsignal(tp->t_pgrp, SIGHUP) ;
46224002Ssam gsignal(tp->t_pgrp, SIGCONT);
46324002Ssam }
46424002Ssam }
46524002Ssam }
46625675Ssam #endif
46724002Ssam }
46824002Ssam
46924002Ssam xp->v_state |= V_RESETTING;
47024002Ssam
47124002Ssam timeout(vxrestart, (caddr_t)n, hz);
47224002Ssam splx(s);
47324002Ssam }
47424002Ssam
47524002Ssam /*
47624002Ssam * Restore a particular aspect of the VIOC.
47724002Ssam */
vxrestart(vioc)47824002Ssam vxrestart(vioc)
47924002Ssam caddr_t vioc;
48024002Ssam {
48124002Ssam register struct tty *tp, *tp0;
48224002Ssam register struct vcx *xp;
48324002Ssam register int i, cnt;
48424002Ssam register int n = (int)vioc;
48524002Ssam int s = spl8();
48624002Ssam
48724002Ssam cnt = n>>8;
48824002Ssam printf("vxrestart %d ",cnt);
48924002Ssam n &= 0xff;
49024002Ssam
49124002Ssam tp0 = &vx_tty[n*16];
49224002Ssam xp = &vcx[n];
49324002Ssam
49424002Ssam xp->v_state &= ~V_RESETTING;
49524002Ssam
49624002Ssam for(i=xp->v_loport; i<=xp->v_hiport; i++) {
49724002Ssam tp = tp0 + i;
49824002Ssam if (cnt != 0) {
49924002Ssam tp->t_state &= ~(TS_BUSY|TS_TIMEOUT);
50024002Ssam if(tp->t_state&(TS_ISOPEN|TS_WOPEN)) /* restart pending output */
50124002Ssam vxstart(tp);
50224002Ssam } else {
50324002Ssam if (tp->t_state&(TS_WOPEN|TS_ISOPEN))
50424002Ssam vxcparam(tp->t_dev, 0);
50524002Ssam }
50624002Ssam }
50724002Ssam
50824002Ssam if (cnt == 0) {
50924002Ssam xp->v_state |= V_RESETTING;
51024002Ssam timeout(vxrestart, (caddr_t)(n + 1*256), hz);
51124002Ssam } else
51224002Ssam printf("done\n");
51324002Ssam splx(s);
51424002Ssam }
51524002Ssam
vxreset(dev)51624002Ssam vxreset(dev)
51724002Ssam dev_t dev;
51824002Ssam {
51924002Ssam vxstreset(minor(dev)>>4); /* completes asynchronously */
52024002Ssam }
52124002Ssam
vxfreset(n)52224002Ssam vxfreset(n)
52324002Ssam register int n;
52424002Ssam {
52524002Ssam
52624002Ssam if (n < 0 || n > NVX || VBAS(n) == NULL)
52724002Ssam return(ENODEV);
52824002Ssam vcx[n].v_state &= ~V_RESETTING;
52924002Ssam vxstreset(n);
53024002Ssam return(0); /* completes asynchronously */
53124002Ssam }
53224002Ssam #endif
53324002Ssam
534