1*25861Ssam /* vxc.c 1.4 86/01/12 */ 224002Ssam 324002Ssam #include "vx.h" 424002Ssam #if NVX > 0 524002Ssam /* 624002Ssam * VIOC driver 724002Ssam */ 8*25861Ssam #include "param.h" 9*25861Ssam #include "file.h" 10*25861Ssam #include "ioctl.h" 11*25861Ssam #include "tty.h" 12*25861Ssam #include "errno.h" 13*25861Ssam #include "time.h" 14*25861Ssam #include "kernel.h" 15*25861Ssam #include "proc.h" 16*25861Ssam 1725675Ssam #include "../tahoevba/vioc.h" 18*25861Ssam #include "../tahoesna/snadebug.h" 1924002Ssam #ifdef VXPERF 2025675Ssam #include "../tahoevba/scope.h" 2124002Ssam #endif VXPERF 2224002Ssam 2324002Ssam #define CMDquals 0 2424002Ssam #define RSPquals 1 2524002Ssam #define UNSquals 2 2624002Ssam 2724002Ssam extern struct vcx vcx[] ; 2824002Ssam extern struct tty vx_tty[]; 2924002Ssam struct vcmds v_cmds[NVIOCX] ; 3024002Ssam 3124002Ssam extern char vxtype[]; 3224002Ssam extern char vxbbno; 3324002Ssam extern char vxbopno[]; 3424002Ssam #ifdef SNA_DEBUG 3524002Ssam extern vbrall(); 3624002Ssam #endif SNA_DEBUG 3724002Ssam extern struct vxcmd *vobtain(); 3824002Ssam 3924002Ssam #ifdef VX_DEBUG 4024002Ssam #include "../vba/vxdebug.h" 4124002Ssam #endif 4224002Ssam 4324002Ssam /* 4424002Ssam * Write a command out to the VIOC 4524002Ssam */ 4624002Ssam vcmd(n, cmdad) 4724002Ssam register int n ; 4824002Ssam register caddr_t cmdad ; /* command address */ 4924002Ssam { 5024002Ssam 5124002Ssam register struct vcmds *cp ; 5224002Ssam register struct vcx *xp; 5324002Ssam int s ; 5424002Ssam 5524002Ssam s = spl8() ; 5624002Ssam cp = &v_cmds[n] ; 5724002Ssam xp = &vcx[n]; 5824002Ssam if (xp->v_state&V_RESETTING && cmdad != NULL) { 5924002Ssam /* 6024002Ssam * When the vioc is resetting, don't process 6124002Ssam * anything other than LIDENT commands. 6224002Ssam */ 6325675Ssam register struct vxcmd *cmdp = (struct vxcmd *) 6425675Ssam ((char *)cmdad - sizeof(cmdp->c_fwd)); 6525675Ssam if (cmdp->cmd != LIDENT) { 6625675Ssam vrelease(xp, cmdp); 6724002Ssam return(0); 6824002Ssam } 6924002Ssam } 7024002Ssam if (cmdad != (caddr_t) 0) { 7124002Ssam cp->cmdbuf[cp->v_fill] = cmdad ; 7224002Ssam if( ++cp->v_fill >= VC_CMDBUFL ) cp->v_fill = 0 ; 7324002Ssam if(cp->v_fill == cp->v_empty) { 7424002Ssam vpanic("vc: CMD Q OVFLO") ; 7524002Ssam vxstreset(n); 7624002Ssam splx(s); 7724002Ssam return(0); 7824002Ssam } 7924002Ssam cp->v_cmdsem++; 8024002Ssam } 8124002Ssam if(cp->v_cmdsem && cp->v_curcnt < vcx[n].v_maxcmd) { 8224002Ssam cp->v_cmdsem--; 8324002Ssam cp->v_curcnt++; 8424002Ssam vinthandl(n, ((V_BSY | CMDquals) << 8) | V_INTR ) ; 8524002Ssam } 8624002Ssam splx(s) ; 8725675Ssam return(1); 8824002Ssam } 8924002Ssam 9024002Ssam /* 9124002Ssam * VIOC acknowledge interrupt. The VIOC has received the new 9224002Ssam * command. If no errors, the new command becomes one of 16 (max) 9324002Ssam * current commands being executed. 9424002Ssam */ 9524002Ssam vackint(n) 9624002Ssam register n ; /* VIOC number */ 9724002Ssam { 9824002Ssam 9924002Ssam register struct vblok *vp ; 10024002Ssam register struct vcmds *cp ; 10124002Ssam register s; 10224002Ssam 10324002Ssam #ifdef VXPERF 10424002Ssam scope_out(5); 10524002Ssam #endif VXPERF 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 */ 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 #ifdef VXPERF 17124002Ssam scope_out(6); 17224002Ssam #endif VXPERF 17324002Ssam if (vxtype[n]) { /* Its a BOP */ 17424002Ssam printf("vcmdrsp: stray interrupt from BOP at VIOC%d...\n",n); 17524002Ssam return; 17624002Ssam } 17724002Ssam s = spl8(); 17824002Ssam vp = VBAS(n) ; 17924002Ssam cp = &v_cmds[n] ; 18024002Ssam resp = (char *)vp; 18124002Ssam resp += vp->v_rspoff & 0x7FFF; 18224002Ssam 18324002Ssam if( (k=resp[1]) & V_UNBSY ) { 18424002Ssam k &= VCMDLEN-1; 18524002Ssam cmd = cp->v_curcmd[k]; 18624002Ssam cp->v_curcmd[k] = (caddr_t)0; 18724002Ssam cp->v_curcnt--; 18824002Ssam k = *((short *)&resp[4]); /* cmd operation code */ 18924002Ssam if((k & 0xFF00) == LIDENT) { /* want hiport number */ 19024002Ssam for(k=0; k<VRESPLEN; k++) 19124002Ssam cmd[k] = resp[k+4]; 19224002Ssam } 19324002Ssam resp[1] = 0; 19425675Ssam vxxint(n, (struct vxcmd *)cmd) ; 19524002Ssam if ((&vcx[n])->v_state == V_RESETTING) return; 19624002Ssam } 19724002Ssam else { 19824002Ssam vpanic( "vc, cmdresp debug") ; 19924002Ssam splx(s); 20024002Ssam vxstreset(n); 20124002Ssam return; 20224002Ssam } 20324002Ssam 20424002Ssam vinthandl(n, ( (V_BSY | RSPquals) << 8 ) | V_INTR ) ; 20524002Ssam splx(s); 20624002Ssam 20724002Ssam } 20824002Ssam 20924002Ssam 21024002Ssam /* 21124002Ssam * Unsolicited interrupt. 21224002Ssam */ 21324002Ssam vunsol(n) 21424002Ssam register(n) ; 21524002Ssam { 21624002Ssam 21724002Ssam register struct vblok *vp ; 21824002Ssam register s; 21924002Ssam 22024002Ssam #ifdef VXPERF 22124002Ssam scope_out(1); 22224002Ssam #endif VXPERF 22324002Ssam if (vxtype[n]) { /* Its a BOP */ 22424002Ssam printf("vunsol: stray interrupt from BOP at VIOC%d...\n",n); 22524002Ssam return; 22624002Ssam } 22724002Ssam s = spl8(); 22824002Ssam vp = VBAS(n) ; 22924002Ssam if(vp->v_uqual & V_UNBSY) { 23024002Ssam vxrint(n) ; 23124002Ssam vinthandl(n, ( (V_BSY | UNSquals) << 8 ) | V_INTR ) ; 23225857Ssam #ifdef notdef 23325857Ssam } else { 23424002Ssam vpanic("vc: UNSOL INT ERR") ; 23524002Ssam splx(s); 23624002Ssam vxstreset(n); 23725857Ssam #endif 23824002Ssam } 23925857Ssam splx(s); 24024002Ssam } 24124002Ssam 24224002Ssam /* 24324002Ssam * Enqueue an interrupt 24424002Ssam */ 24524002Ssam vinthandl(n, item) 24624002Ssam register int n ; 24724002Ssam register item ; 24824002Ssam { 24924002Ssam 25024002Ssam register struct vcmds *cp ; 25124002Ssam register int empflag = 0 ; 25224002Ssam 25324002Ssam cp = &v_cmds[n] ; 25424002Ssam if( cp->v_itrfill == cp->v_itrempt ) empflag++ ; 25524002Ssam cp->v_itrqueu[cp->v_itrfill] = item ; 25624002Ssam if( ++cp->v_itrfill >= VC_IQLEN ) cp->v_itrfill = 0 ; 25724002Ssam if(cp->v_itrfill == cp->v_itrempt) { 25824002Ssam vpanic( "vc: INT Q OVFLO" ) ; 25924002Ssam vxstreset(n); 26024002Ssam } 26124002Ssam else if( empflag ) vintempt(n) ; 26224002Ssam } 26324002Ssam 26424002Ssam vintempt(n) 26524002Ssam register int n ; 26624002Ssam { 26724002Ssam register struct vcmds *cp ; 26824002Ssam register struct vblok *vp ; 26924002Ssam register short item ; 27024002Ssam register short *intr ; 27124002Ssam 27224002Ssam vp = VBAS(n) ; 27324002Ssam if(vp->v_vioc & V_BSY) return ; 27424002Ssam cp = &v_cmds[n] ; 27524002Ssam if(cp->v_itrempt == cp->v_itrfill) return ; 27624002Ssam item = cp->v_itrqueu[cp->v_itrempt] ; 27724002Ssam intr = (short *)&vp->v_vioc ; 27824002Ssam switch( (item >> 8) & 03 ) { 27924002Ssam 28024002Ssam case CMDquals: /* command */ 28124002Ssam { 28224002Ssam int phys; 28324002Ssam 28424002Ssam if(cp->v_empty == cp->v_fill || vp->v_vcbsy&V_BSY) 28524002Ssam break; 28624002Ssam (&vcx[n])->v_mricmd = (caddr_t)cp->cmdbuf[cp->v_empty]; 28725675Ssam phys = vtoph((struct proc *)0, (unsigned)cp->cmdbuf[cp->v_empty]) ; /* should be a sys address */ 28824002Ssam vp->v_vcp[0] = ((short *)&phys)[0]; 28924002Ssam vp->v_vcp[1] = ((short *)&phys)[1]; 29024002Ssam vp->v_vcbsy = V_BSY ; 29124002Ssam *intr = item ; 29224002Ssam } 29324002Ssam #ifdef VXPERF 29424002Ssam scope_out(4); 29524002Ssam #endif VXPERF 29624002Ssam break ; 29724002Ssam 29824002Ssam case RSPquals: /* command response */ 29924002Ssam *intr = item ; 30024002Ssam #ifdef VXPERF 30124002Ssam scope_out(7); 30224002Ssam #endif VXPERF 30324002Ssam break ; 30424002Ssam 30524002Ssam case UNSquals: /* unsolicited interrupt */ 30624002Ssam vp->v_uqual = 0 ; 30724002Ssam *intr = item ; 30824002Ssam #ifdef VXPERF 30924002Ssam scope_out(2); 31024002Ssam #endif VXPERF 31124002Ssam break ; 31224002Ssam } 31324002Ssam } 31424002Ssam 31524002Ssam 31624002Ssam /* start a reset on a vioc after error (hopefully) */ 31724002Ssam vxstreset(n) 31824002Ssam register n; 31924002Ssam { 32024002Ssam register struct vcx *xp; 32124002Ssam register struct vblok *vp ; 32224002Ssam register struct vxcmd *cp; 32324002Ssam register int j; 32424002Ssam extern int vxinreset(); 32524002Ssam int s ; 32624002Ssam 32724002Ssam s = spl8() ; 32824002Ssam vp = VBAS(n); 32924002Ssam xp = &vcx[n]; 33024002Ssam 33124002Ssam if (xp->v_state&V_RESETTING) 33224002Ssam /* 33324002Ssam * Avoid infinite recursion. 33424002Ssam */ 33524002Ssam return; 33624002Ssam 33724002Ssam /* 33824002Ssam * Zero out the vioc structures, mark the vioc as being 33924002Ssam * reset, reinitialize the free command list, reset the vioc 34024002Ssam * and start a timer to check on the progress of the reset. 34124002Ssam */ 34225675Ssam bzero((caddr_t)&v_cmds[n], (unsigned)sizeof (struct vcmds)); 34325675Ssam bzero((caddr_t)xp, (unsigned)sizeof (struct vcx)); 34424002Ssam 34524002Ssam /* 34624002Ssam * Setting V_RESETTING prevents others from issuing 34724002Ssam * commands while allowing currently queued commands to 34824002Ssam * be passed to the VIOC. 34924002Ssam */ 35024002Ssam xp->v_state |= V_RESETTING; 35124002Ssam for(j=0; j<NVCXBUFS; j++) /* init all cmd buffers */ 35224002Ssam { 35324002Ssam cp = &xp->vx_lst[j]; /* index a buffer */ 35424002Ssam cp->c_fwd = &xp->vx_lst[j+1]; /* point to next buf */ 35524002Ssam } 35624002Ssam xp->vx_avail = &xp->vx_lst[0]; /* set idx to 1st free buf */ 35724002Ssam cp->c_fwd = (struct vxcmd *)0; /* mark last buf in free list */ 35824002Ssam 35924002Ssam printf("resetting VIOC %x .. ", n); 36024002Ssam 36124002Ssam vp->v_fault = 0 ; 36224002Ssam vp->v_vioc = V_BSY ; 36324002Ssam vp->v_hdwre = V_RESET ; /* reset interrupt */ 36424002Ssam 36524002Ssam timeout(vxinreset, (caddr_t)n, hz*5); 36624002Ssam splx(s); 36724002Ssam return; 36824002Ssam } 36924002Ssam 37024002Ssam /* continue processing a reset on a vioc after an error (hopefully) */ 37124002Ssam vxinreset(vioc) 37224002Ssam caddr_t vioc; 37324002Ssam { 37425675Ssam register int n = (int)vioc; 37524002Ssam register struct vblok *vp ; 37624002Ssam int s = spl8(); 37724002Ssam printf("vxinreset "); 37824002Ssam 37924002Ssam vp = VBAS(n); 38024002Ssam 38124002Ssam /* 38224002Ssam * See if the vioc has reset. 38324002Ssam */ 38424002Ssam if (vp->v_fault != VREADY) { 38524002Ssam printf("failed\n"); 38624002Ssam splx(s); 38724002Ssam return; 38824002Ssam } 38924002Ssam 39024002Ssam /* 39124002Ssam * Send a LIDENT to the vioc and mess with carrier flags 39224002Ssam * on parallel printer ports. 39324002Ssam */ 39425675Ssam vxinit(n, (long)0); 39524002Ssam splx(s); 39624002Ssam } 39724002Ssam 39824002Ssam /* 39924002Ssam * Restore modem control, parameters and restart output. 40024002Ssam * Since the vioc can handle no more then 24 commands at a time 40124002Ssam * and we could generate as many as 48 commands, we must do this in 40224002Ssam * phases, issuing no more then 16 commands at a time. 40324002Ssam */ 40424002Ssam /* finish the reset on the vioc after an error (hopefully) */ 40524002Ssam vxfnreset(n, cp) 40624002Ssam register int n; 40724002Ssam register struct vxcmd *cp; 40824002Ssam { 40924002Ssam register struct vcx *xp; 41024002Ssam register struct vblok *vp ; 41124002Ssam register struct tty *tp; 41224002Ssam register int i; 41325675Ssam #ifdef notdef 41424002Ssam register int on; 41525675Ssam #endif 41624002Ssam extern int vxrestart(); 41724002Ssam int s = spl8(); 41824002Ssam printf("vxfnreset "); 41924002Ssam 42024002Ssam vp = VBAS(n); 42124002Ssam xp = &vcx[n]; 42224002Ssam 42324002Ssam xp->v_loport = cp->par[5]; /* save low port number */ 42424002Ssam xp->v_hiport = cp->par[7];/* VIOC knows high port numbr */ 42524002Ssam vrelease(xp,cp); /* done with this control block */ 42624002Ssam xp->v_nbr = n; /* assign VIOC-X board number */ 42724002Ssam 42824002Ssam xp->v_state &= ~V_RESETTING; 42924002Ssam 43024002Ssam vp->v_vcid = 0; 43124002Ssam 43224002Ssam /* 43324002Ssam * Restore modem information and control. 43424002Ssam */ 43524002Ssam for(i=xp->v_loport; i<=xp->v_hiport; i++) { 43624002Ssam tp = &vx_tty[i+n*16]; 43724002Ssam if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) { 43824002Ssam tp->t_state &= ~TS_CARR_ON; 43924002Ssam vcmodem(tp->t_dev, VMOD_ON); 44024002Ssam if (tp->t_state&TS_CARR_ON) { 44124002Ssam wakeup((caddr_t)&tp->t_canq) ; 44224002Ssam } 44324002Ssam else { 44424002Ssam if(tp->t_state & TS_ISOPEN) { 44524002Ssam ttyflush(tp, FREAD|FWRITE); 44624002Ssam if(tp->t_state&TS_FLUSH) 44724002Ssam wakeup((caddr_t)&tp->t_state) ; 44824002Ssam if((tp->t_flags&NOHANG)==0) { 44924002Ssam gsignal(tp->t_pgrp, SIGHUP) ; 45024002Ssam gsignal(tp->t_pgrp, SIGCONT); 45124002Ssam } 45224002Ssam } 45324002Ssam } 45424002Ssam } 45524002Ssam /* 45624002Ssam * If carrier has changed while we were resetting, 45724002Ssam * take appropriate action. 45824002Ssam */ 45925675Ssam #ifdef notdef 46024002Ssam on = vp->v_dcd & 1<<i; 46124002Ssam if (on && (tp->t_state&TS_CARR_ON) == 0) { 46224002Ssam tp->t_state |= TS_CARR_ON ; 46324002Ssam wakeup((caddr_t)&tp->t_canq) ; 46424002Ssam } else if (!on && tp->t_state&TS_CARR_ON) { 46524002Ssam tp->t_state &= ~TS_CARR_ON ; 46624002Ssam if(tp->t_state & TS_ISOPEN) { 46724002Ssam ttyflush(tp, FREAD|FWRITE); 46824002Ssam if(tp->t_state&TS_FLUSH) 46924002Ssam wakeup((caddr_t)&tp->t_state) ; 47024002Ssam if((tp->t_flags&NOHANG)==0) { 47124002Ssam gsignal(tp->t_pgrp, SIGHUP) ; 47224002Ssam gsignal(tp->t_pgrp, SIGCONT); 47324002Ssam } 47424002Ssam } 47524002Ssam } 47625675Ssam #endif 47724002Ssam } 47824002Ssam 47924002Ssam xp->v_state |= V_RESETTING; 48024002Ssam 48124002Ssam timeout(vxrestart, (caddr_t)n, hz); 48224002Ssam splx(s); 48324002Ssam } 48424002Ssam 48524002Ssam /* 48624002Ssam * Restore a particular aspect of the VIOC. 48724002Ssam */ 48824002Ssam vxrestart(vioc) 48924002Ssam caddr_t vioc; 49024002Ssam { 49124002Ssam register struct tty *tp, *tp0; 49224002Ssam register struct vcx *xp; 49324002Ssam register int i, cnt; 49424002Ssam register int n = (int)vioc; 49524002Ssam int s = spl8(); 49624002Ssam 49724002Ssam cnt = n>>8; 49824002Ssam printf("vxrestart %d ",cnt); 49924002Ssam n &= 0xff; 50024002Ssam 50124002Ssam tp0 = &vx_tty[n*16]; 50224002Ssam xp = &vcx[n]; 50324002Ssam 50424002Ssam xp->v_state &= ~V_RESETTING; 50524002Ssam 50624002Ssam for(i=xp->v_loport; i<=xp->v_hiport; i++) { 50724002Ssam tp = tp0 + i; 50824002Ssam if (cnt != 0) { 50924002Ssam tp->t_state &= ~(TS_BUSY|TS_TIMEOUT); 51024002Ssam if(tp->t_state&(TS_ISOPEN|TS_WOPEN)) /* restart pending output */ 51124002Ssam vxstart(tp); 51224002Ssam } else { 51324002Ssam if (tp->t_state&(TS_WOPEN|TS_ISOPEN)) 51424002Ssam vxcparam(tp->t_dev, 0); 51524002Ssam } 51624002Ssam } 51724002Ssam 51824002Ssam if (cnt == 0) { 51924002Ssam xp->v_state |= V_RESETTING; 52024002Ssam timeout(vxrestart, (caddr_t)(n + 1*256), hz); 52124002Ssam } else 52224002Ssam printf("done\n"); 52324002Ssam splx(s); 52424002Ssam } 52524002Ssam 52624002Ssam vxreset(dev) 52724002Ssam dev_t dev; 52824002Ssam { 52924002Ssam vxstreset(minor(dev)>>4); /* completes asynchronously */ 53024002Ssam } 53124002Ssam 53224002Ssam vxfreset(n) 53324002Ssam register int n; 53424002Ssam { 53524002Ssam 53624002Ssam if (n < 0 || n > NVX || VBAS(n) == NULL) 53724002Ssam return(ENODEV); 53824002Ssam vcx[n].v_state &= ~V_RESETTING; 53924002Ssam vxstreset(n); 54024002Ssam return(0); /* completes asynchronously */ 54124002Ssam } 54224002Ssam #endif 54324002Ssam 544