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