1*25948Ssam /* vx.c 1.8 86/01/23 */ 224003Ssam 324003Ssam #include "vx.h" 424003Ssam #if NVX > 0 524003Ssam /* 625857Ssam * VIOC-X driver 724003Ssam */ 825877Ssam #ifdef VXPERF 9*25948Ssam #define DOSCOPE 1025877Ssam #endif 1125877Ssam 1225675Ssam #include "../tahoe/pte.h" 1324003Ssam 1425877Ssam #include "param.h" 1525877Ssam #include "ioctl.h" 1625877Ssam #include "tty.h" 1725877Ssam #include "dir.h" 1825877Ssam #include "user.h" 1925877Ssam #include "map.h" 2025877Ssam #include "buf.h" 2125877Ssam #include "conf.h" 2225877Ssam #include "file.h" 2325877Ssam #include "uio.h" 2425877Ssam #include "proc.h" 2525877Ssam #include "vm.h" 2625881Ssam #include "kernel.h" 2725675Ssam 2825675Ssam #include "../tahoevba/vbavar.h" 2925881Ssam #include "../tahoevba/vxreg.h" 3025675Ssam #include "../tahoevba/scope.h" 3124003Ssam #include "vbsc.h" 3224003Ssam #if NVBSC > 0 3325861Ssam #include "../tahoebsc/bscio.h" 3425861Ssam #include "../tahoebsc/bsc.h" 3524003Ssam #ifdef BSC_DEBUG 3625861Ssam #include "../tahoebsc/bscdebug.h" 3724003Ssam #endif 3824003Ssam 3925881Ssam char bscport[NVX*16]; 4024003Ssam #endif 4124003Ssam 4225881Ssam #ifdef VX_DEBUG 4325881Ssam long vxintr4 = 0; 44*25948Ssam #define VXERR4 1 45*25948Ssam #define VXNOBUF 2 4625881Ssam long vxdebug = 0; 47*25948Ssam #define VXVCM 1 48*25948Ssam #define VXVCC 2 49*25948Ssam #define VXVCX 4 5025881Ssam #include "../tahoesna/snadebug.h" 5125881Ssam #endif 5224003Ssam 5325881Ssam /* 5425881Ssam * Interrupt type bits passed to vinthandl(). 5525881Ssam */ 56*25948Ssam #define CMDquals 0 /* command completed interrupt */ 57*25948Ssam #define RSPquals 1 /* command response interrupt */ 58*25948Ssam #define UNSquals 2 /* unsolicited interrupt */ 5924003Ssam 6025881Ssam struct tty vx_tty[NVX*16]; 6125881Ssam int vxstart(), ttrstrt(); 6225881Ssam struct vxcmd *vobtain(), *nextcmd(); 6324003Ssam 6424003Ssam /* 6524003Ssam * Driver information for auto-configuration stuff. 6624003Ssam */ 6724003Ssam int vxprobe(), vxattach(), vxrint(); 6825881Ssam struct vba_device *vxinfo[NVX]; 6924003Ssam long vxstd[] = { 0 }; 7024003Ssam struct vba_driver vxdriver = 7125857Ssam { vxprobe, 0, vxattach, 0, vxstd, "vx", vxinfo }; 7224003Ssam 7325881Ssam struct vx_softc { 7425881Ssam u_char vs_type; /* 0: viox-x/vioc-b, 1: vioc-bop */ 7525881Ssam u_char vs_bop; /* bop board # for vioc-bop's */ 7625881Ssam u_char vs_loport; /* low port nbr */ 7725881Ssam u_char vs_hiport; /* high port nbr */ 7825881Ssam u_short vs_nbr; /* viocx number */ 7925881Ssam u_short vs_maxcmd; /* max number of concurrent cmds */ 8025881Ssam u_short vs_silosiz; /* silo size */ 8125881Ssam short vs_vers; /* vioc/pvioc version */ 82*25948Ssam #define VXV_OLD 0 /* PVIOCX | VIOCX */ 83*25948Ssam #define VXV_NEW 1 /* NPVIOCX | NVIOCX */ 8425881Ssam short vs_xmtcnt; /* xmit commands pending */ 8525881Ssam short vs_brkreq; /* send break requests pending */ 8625881Ssam short vs_active; /* active port bit array or flag */ 8725881Ssam short vs_state; /* controller state */ 88*25948Ssam #define VXS_READY 0 /* ready for commands */ 89*25948Ssam #define VXS_RESET 1 /* in process of reseting */ 9025881Ssam caddr_t vs_mricmd; /* most recent issued cmd */ 9125881Ssam u_int vs_ivec; /* interrupt vector base */ 9225881Ssam struct vxcmd *vs_avail;/* next available command buffer */ 9325881Ssam struct vxcmd *vs_build; 9425881Ssam struct vxcmd vs_lst[NVCXBUFS]; 9525881Ssam struct vcmds vs_cmds; 9625881Ssam } vx_softc[NVX]; 9724003Ssam 9825857Ssam vxprobe(reg, vi) 9924003Ssam caddr_t reg; 10025857Ssam struct vba_device *vi; 10124003Ssam { 10225857Ssam register int br, cvec; /* must be r12, r11 */ 10325881Ssam register struct vxdevice *vp = (struct vxdevice *)reg; 10425881Ssam register struct vx_softc *vs; 10524003Ssam 10624003Ssam #ifdef lint 10724003Ssam br = 0; cvec = br; br = cvec; 10825675Ssam vackint(0); vunsol(0); vcmdrsp(0); vxfreset(0); 10924003Ssam #endif 11025675Ssam if (badaddr((caddr_t)vp, 1)) 11125675Ssam return (0); 11225675Ssam vp->v_fault = 0; 11325675Ssam vp->v_vioc = V_BSY; 11425675Ssam vp->v_hdwre = V_RESET; /* reset interrupt */ 11524003Ssam DELAY(4000000); 11625881Ssam if (vp->v_fault != VXF_READY) 11725675Ssam return (0); 11825881Ssam vs = &vx_softc[vi->ui_unit]; 11925857Ssam #ifdef notdef 12025857Ssam /* 12125857Ssam * Align vioc interrupt vector base to 4 vector 12225857Ssam * boundary and fitting in 8 bits (is this necessary, 12325857Ssam * wish we had documentation). 12425857Ssam */ 12525857Ssam if ((vi->ui_hd->vh_lastiv -= 3) > 0xff) 12625857Ssam vi->ui_hd->vh_lastiv = 0xff; 12725881Ssam vs->vs_ivec = vi->ui_hd->vh_lastiv = vi->ui_hd->vh_lastiv &~ 0x3; 12825857Ssam #else 12925881Ssam vs->vs_ivec = 0x40+vi->ui_unit*4; 13025857Ssam #endif 13125881Ssam br = 0x18, cvec = vs->vs_ivec; /* XXX */ 13225881Ssam return (sizeof (struct vxdevice)); 13324003Ssam } 13424003Ssam 13525857Ssam vxattach(vi) 13625857Ssam register struct vba_device *vi; 13724003Ssam { 13825675Ssam 13925857Ssam vxinit(vi->ui_unit, (long)1); 14024003Ssam } 14124003Ssam 14224003Ssam /* 14324003Ssam * Open a VX line. 14424003Ssam */ 14525675Ssam /*ARGSUSED*/ 14624003Ssam vxopen(dev, flag) 14725881Ssam dev_t dev; 14825881Ssam int flag; 14924003Ssam { 15024003Ssam register struct tty *tp; /* pointer to tty struct for port */ 15125881Ssam register struct vx_softc *vs; 15225881Ssam register struct vba_device *vi; 15325881Ssam int unit, vx, s, error; 15424003Ssam 15525881Ssam unit = minor(dev); 15625881Ssam vx = unit >> 4; 15725881Ssam if (unit >= NVX*16 || (vi = vxinfo[vx])== 0 || vi->ui_alive == 0) 15825881Ssam return (ENXIO); 15925881Ssam tp = &vx_tty[unit]; 16025881Ssam if (tp->t_state&TS_XCLUDE && u.u_uid != 0) 16125881Ssam return (EBUSY); 16225881Ssam vs = &vx_softc[vx]; 16325881Ssam #ifdef notdef 16425881Ssam if (unit < vs->vs_loport || vs->vs_hiport < unit) /* ??? */ 16525881Ssam return (ENXIO); 16625881Ssam #endif 16725881Ssam tp->t_addr = (caddr_t)vs; 16825881Ssam tp->t_oproc = vxstart; 16925881Ssam tp->t_dev = dev; 17025881Ssam s = spl8(); 17125881Ssam tp->t_state |= TS_WOPEN; 17225881Ssam if ((tp->t_state&TS_ISOPEN) == 0) { 17325881Ssam ttychars(tp); 17425881Ssam if (tp->t_ispeed == 0) { 17525881Ssam tp->t_ispeed = SSPEED; 17625881Ssam tp->t_ospeed = SSPEED; 17725881Ssam tp->t_flags |= ODDP|EVENP|ECHO; 17824003Ssam } 17925881Ssam vxparam(dev); 18024003Ssam } 18125881Ssam if (!vcmodem(dev, VMOD_ON)) 18225881Ssam while ((tp->t_state&TS_CARR_ON) == 0) 18325881Ssam sleep((caddr_t)&tp->t_canq, TTIPRI); 18425881Ssam error = (*linesw[tp->t_line].l_open)(dev,tp); 18525881Ssam splx(s); 18625881Ssam return (error); 18724003Ssam } 18824003Ssam 18924003Ssam /* 19024003Ssam * Close a VX line. 19124003Ssam */ 19225675Ssam /*ARGSUSED*/ 19324003Ssam vxclose(dev, flag) 19425881Ssam dev_t dev; 19525881Ssam int flag; 19624003Ssam { 19724003Ssam register struct tty *tp; 19825881Ssam int unit, s; 19924003Ssam 20025881Ssam unit = minor(dev); 20125881Ssam tp = &vx_tty[unit]; 20225881Ssam s = spl8(); 20324003Ssam (*linesw[tp->t_line].l_close)(tp); 20425881Ssam if ((tp->t_state & (TS_ISOPEN|TS_HUPCLS)) == (TS_ISOPEN|TS_HUPCLS)) 20525881Ssam if (!vcmodem(dev, VMOD_OFF)) 20624003Ssam tp->t_state &= ~TS_CARR_ON; 20724003Ssam /* wait for the last response */ 20825881Ssam while (tp->t_state&TS_FLUSH) 20925881Ssam sleep((caddr_t)&tp->t_state, TTOPRI); 21025881Ssam ttyclose(tp); 21125881Ssam splx(s); 21224003Ssam } 21324003Ssam 21424003Ssam /* 21524003Ssam * Read from a VX line. 21624003Ssam */ 21724003Ssam vxread(dev, uio) 21824003Ssam dev_t dev; 21924003Ssam struct uio *uio; 22024003Ssam { 22125881Ssam struct tty *tp = &vx_tty[minor(dev)]; 22225881Ssam 22325881Ssam return ((*linesw[tp->t_line].l_read)(tp, uio)); 22424003Ssam } 22524003Ssam 22624003Ssam /* 22724003Ssam * write on a VX line 22824003Ssam */ 22924003Ssam vxwrite(dev, uio) 23024003Ssam dev_t dev; 23124003Ssam struct uio *uio; 23224003Ssam { 23325881Ssam register struct tty *tp = &vx_tty[minor(dev)]; 23425881Ssam 23525881Ssam return ((*linesw[tp->t_line].l_write)(tp, uio)); 23624003Ssam } 23724003Ssam 23824003Ssam /* 23924003Ssam * VIOCX unsolicited interrupt. 24024003Ssam */ 24125881Ssam vxrint(vx) 24225881Ssam register vx; 24324003Ssam { 24425881Ssam register struct tty *tp, *tp0; 24525881Ssam register struct vxdevice *addr; 24625881Ssam register struct vx_softc *vs; 24725881Ssam struct vba_device *vi; 24825881Ssam register int nc, c; 24925881Ssam register struct silo { 25025881Ssam char data, port; 25125881Ssam } *sp; 25225881Ssam short *osp; 25325881Ssam int overrun = 0; 25424003Ssam 25525881Ssam vi = vxinfo[vx]; 25625881Ssam if (vi == 0 || vi->ui_alive == 0) 25725881Ssam return; 25825881Ssam addr = (struct vxdevice *)vi->ui_addr; 25925881Ssam switch (addr->v_uqual&037) { 26024003Ssam case 0: 26124003Ssam break; 26224003Ssam case 2: 26325881Ssam printf("vx%d: vc proc err, ustat %x\n", addr->v_ustat); 26425881Ssam vxstreset(vx); 26525881Ssam return (0); 26624003Ssam case 3: 26725881Ssam vcmintr(vx); 26825881Ssam return (1); 26924003Ssam case 4: 27025881Ssam return (1); 27124003Ssam default: 27225881Ssam printf("vx%d: vc uqual err, uqual %x\n", addr->v_uqual); 27325881Ssam vxstreset(vx); 27425881Ssam return (0); 27524003Ssam } 27625881Ssam vs = &vx_softc[vx]; 27725881Ssam if (vs->vs_vers == VXV_NEW) 27825881Ssam sp = (struct silo *)((caddr_t)addr + *(short *)addr->v_usdata); 27925881Ssam else 28025881Ssam sp = (struct silo *)((caddr_t)addr+VX_SILO+(addr->v_usdata[0]<<6)); 28125881Ssam nc = *(osp = (short *)sp); 28225881Ssam if (nc == 0) 28325881Ssam return (1); 28425881Ssam if (vs->vs_vers == VXV_NEW && nc > vs->vs_silosiz) { 28525881Ssam printf("vx%d: %d exceeds silo size\n", nc); 28625881Ssam nc = vs->vs_silosiz; 28724003Ssam } 28825881Ssam tp0 = &vx_tty[vx*16]; 28925881Ssam sp = (struct silo *)(((short *)sp)+1); 29025881Ssam for (; nc > 0; nc--, sp = (struct silo *)(((short *)sp)+1)) { 29125881Ssam c = sp->port & 017; 29225881Ssam if (vs->vs_loport > c || c > vs->vs_hiport) 29325881Ssam continue; 29425881Ssam tp = tp0 + c; 29525881Ssam if( (tp->t_state&TS_ISOPEN) == 0) { 29624003Ssam wakeup((caddr_t)&tp->t_rawq); 29724003Ssam continue; 29824003Ssam } 29925881Ssam c = sp->data; 30025881Ssam if ((sp->port&VX_RO) == VX_RO && !overrun) { 30125881Ssam printf("vx%d: receiver overrun\n", vi->ui_unit); 30225881Ssam overrun = 1; 30325881Ssam continue; 30425881Ssam } 30525881Ssam if (sp->port&VX_PE) 30625881Ssam if ((tp->t_flags&(EVENP|ODDP)) == EVENP || 30725881Ssam (tp->t_flags&(EVENP|ODDP)) == ODDP) 30824003Ssam continue; 30925881Ssam if (sp->port&VX_FE) { 31025881Ssam /* 31125881Ssam * At framing error (break) generate 31225881Ssam * a null (in raw mode, for getty), or a 31325881Ssam * interrupt (in cooked/cbreak mode). 31425881Ssam */ 31525881Ssam if (tp->t_flags&RAW) 31625881Ssam c = 0; 31725881Ssam else 31825881Ssam c = tp->t_intrc; 31924003Ssam } 32024003Ssam (*linesw[tp->t_line].l_rint)(c, tp); 32124003Ssam } 32225881Ssam *osp = 0; 32325881Ssam return (1); 32424003Ssam } 32524003Ssam 32624003Ssam /* 32725881Ssam * Ioctl for VX. 32824003Ssam */ 32924003Ssam vxioctl(dev, cmd, data, flag) 33025881Ssam dev_t dev; 33125881Ssam caddr_t data; 33224003Ssam { 33325881Ssam register struct tty *tp; 33425881Ssam int error; 33524003Ssam 33625881Ssam tp = &vx_tty[minor(dev)]; 33724003Ssam error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag); 33824003Ssam if (error == 0) 33925881Ssam return (error); 34025881Ssam error = ttioctl(tp, cmd, data, flag); 34125881Ssam if (error >= 0) { 34225881Ssam if (cmd == TIOCSETP || cmd == TIOCSETN) 34324003Ssam vxparam(dev); 34425881Ssam return (error); 34525881Ssam } 34625881Ssam return (ENOTTY); 34724003Ssam } 34824003Ssam 34924003Ssam vxparam(dev) 35025881Ssam dev_t dev; 35124003Ssam { 35225881Ssam 35324003Ssam vxcparam(dev, 1); 35424003Ssam } 35524003Ssam 35624003Ssam /* 35724003Ssam * Set parameters from open or stty into the VX hardware 35824003Ssam * registers. 35924003Ssam */ 36024003Ssam vxcparam(dev, wait) 36125881Ssam dev_t dev; 36225881Ssam int wait; 36324003Ssam { 36425881Ssam register struct tty *tp; 36525881Ssam register struct vx_softc *vs; 36625881Ssam register struct vxcmd *cp; 36725933Ssam int s, unit = minor(dev); 36824003Ssam 36925933Ssam tp = &vx_tty[unit]; 37025881Ssam vs = (struct vx_softc *)tp->t_addr; 37125881Ssam cp = vobtain(vs); 37224003Ssam s = spl8(); 37325933Ssam /* 37425933Ssam * Construct ``load parameters'' command block 37525933Ssam * to setup baud rates, xon-xoff chars, parity, 37625933Ssam * and stop bits for the specified port. 37725933Ssam */ 37825933Ssam cp->cmd = VXC_LPARAX; 37925933Ssam cp->par[1] = unit & 017; /* port number */ 38025933Ssam cp->par[2] = (tp->t_flags&RAW) ? 0 : tp->t_startc; 38125933Ssam cp->par[3] = (tp->t_flags&RAW) ? 0 : tp->t_stopc; 38225881Ssam if (tp->t_flags&(RAW|LITOUT) || 38325881Ssam (tp->t_flags&(EVENP|ODDP)) == (EVENP|ODDP)) { 38424003Ssam cp->par[4] = 0xc0; /* 8 bits of data */ 38524003Ssam cp->par[7] = 0; /* no parity */ 38624003Ssam } else { 38724003Ssam cp->par[4] = 0x40; /* 7 bits of data */ 38825881Ssam if ((tp->t_flags&(EVENP|ODDP)) == ODDP) 38924003Ssam cp->par[7] = 1; /* odd parity */ 39025933Ssam else if ((tp->t_flags&(EVENP|ODDP)) == EVENP) 39124003Ssam cp->par[7] = 3; /* even parity */ 39224003Ssam else 39324003Ssam cp->par[7] = 0; /* no parity */ 39424003Ssam } 39525933Ssam cp->par[5] = 0x4; /* 1 stop bit - XXX */ 39624003Ssam cp->par[6] = tp->t_ospeed; 39725881Ssam if (vcmd(vs->vs_nbr, (caddr_t)&cp->cmd) && wait) 39825675Ssam sleep((caddr_t)cp,TTIPRI); 39924003Ssam splx(s); 40024003Ssam } 40124003Ssam 40224003Ssam /* 40324003Ssam * VIOCX command response interrupt. 40424003Ssam * For transmission, restart output to any active port. 40524003Ssam * For all other commands, just clean up. 40624003Ssam */ 40725881Ssam vxxint(vx, cp) 40825881Ssam register int vx; 40925881Ssam register struct vxcmd *cp; 41024003Ssam { 41125933Ssam register struct vxmit *vp, *pvp; 41225933Ssam register struct tty *tp, *tp0; 41325933Ssam register struct vx_softc *vs; 41425881Ssam register struct tty *hp; 41524003Ssam 41625881Ssam vs = &vx_softc[vx]; 41725881Ssam cp = (struct vxcmd *)((long *)cp-1); 41824003Ssam #if NVBSC > 0 41925881Ssam if (cp->cmd == VXC_MDMCTL1 || cp->cmd == VXC_HUNTMD1 || 42025881Ssam cp->cmd == VXC_LPARAX1) { 42125881Ssam vrelease(vs, cp); 42225881Ssam wakeup((caddr_t)cp); 42324003Ssam return; 42424003Ssam } 42524003Ssam #endif 42625881Ssam switch (cp->cmd&0xff00) { 42725881Ssam 42825881Ssam case VXC_LIDENT: /* initialization complete */ 42925881Ssam if (vs->vs_state == VXS_RESET) { 43025881Ssam vxfnreset(vx, cp); 43125881Ssam vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR); 43224003Ssam } 43324003Ssam cp->cmd++; 43424003Ssam return; 43525881Ssam 43625881Ssam case VXC_XMITDTA: 43725881Ssam case VXC_XMITIMM: 43824003Ssam break; 43925881Ssam 44025881Ssam case VXC_LPARAX: 44125675Ssam wakeup((caddr_t)cp); 44225881Ssam /* fall thru... */ 44325881Ssam default: /* VXC_MDMCTL or VXC_FDTATOX */ 44425881Ssam vrelease(vs, cp); 44525881Ssam if (vs->vs_state == VXS_RESET) 44625881Ssam vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR); 44724003Ssam return; 44824003Ssam } 44925881Ssam tp0 = &vx_tty[vx*16]; 45025881Ssam vp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit)); 45125881Ssam for (; vp >= (struct vxmit *)cp->par; vp--) { 45225881Ssam tp = tp0 + (vp->line & 017); 45324003Ssam #if NVBSC > 0 45424003Ssam if (tp->t_line == LDISP) { 45524003Ssam vrelease(xp, cp); 45625881Ssam bsctxd(vp->line & 017); 45725881Ssam return; 45824003Ssam } 45924003Ssam #endif 46024003Ssam pvp = vp; 46124003Ssam tp->t_state &= ~TS_BUSY; 46225881Ssam if (tp->t_state & TS_FLUSH) { 46324003Ssam tp->t_state &= ~TS_FLUSH; 46425881Ssam wakeup((caddr_t)&tp->t_state); 46525881Ssam } else 46624003Ssam ndflush(&tp->t_outq, vp->bcount+1); 46724003Ssam } 46825881Ssam vs->vs_xmtcnt--; 46925881Ssam vrelease(vs, cp); 47025881Ssam if (vs->vs_vers == VXV_NEW) { 47124003Ssam vp = pvp; 47225881Ssam vs->vs_active |= 1 << ((vp->line & 017) - vs->vs_loport); 47325881Ssam if (vxstart(tp) && (cp = nextcmd(vs)) != NULL) { 47425881Ssam vs->vs_xmtcnt++; 47525881Ssam vcmd(vx, (caddr_t)&cp->cmd); 47625881Ssam return; 47724003Ssam } 47825881Ssam vs->vs_active &= ~(1 << ((vp->line & 017) - vs->vs_loport)); 47925881Ssam } else { 48025933Ssam vs->vs_active = -1; 48125881Ssam tp0 = &vx_tty[vx*16 + vs->vs_hiport]; 48225881Ssam for(tp = &vx_tty[vx*16 + vs->vs_loport]; tp <= tp0; tp++) 48325881Ssam if (vxstart(tp) && (cp = nextcmd(vs)) != NULL) { 48425881Ssam vs->vs_xmtcnt++; 48525881Ssam vcmd(vx, (caddr_t)&cp->cmd); 48625881Ssam } 48725881Ssam if ((cp = nextcmd(vs)) != NULL) { /* command to send? */ 48825881Ssam vs->vs_xmtcnt++; 48925881Ssam vcmd(vx, (caddr_t)&cp->cmd); 49024003Ssam } 49125881Ssam vs->vs_active = 0; 49224003Ssam } 49324003Ssam } 49424003Ssam 49524003Ssam /* 49624003Ssam * Force out partial XMIT command after timeout 49724003Ssam */ 49825881Ssam vxforce(vs) 49925881Ssam register struct vx_softc *vs; 50024003Ssam { 50125881Ssam register struct vxcmd *cp; 50225881Ssam int s; 50324003Ssam 50424003Ssam s = spl8(); 50525881Ssam if ((cp = nextcmd(vs)) != NULL) { 50625881Ssam vs->vs_xmtcnt++; 50725881Ssam vcmd(vs->vs_nbr, (caddr_t)&cp->cmd); 50824003Ssam } 50924003Ssam splx(s); 51024003Ssam } 51124003Ssam 51224003Ssam /* 51324003Ssam * Start (restart) transmission on the given VX line. 51424003Ssam */ 51524003Ssam vxstart(tp) 51625881Ssam register struct tty *tp; 51724003Ssam { 51825675Ssam register short n; 51925933Ssam register struct vx_softc *vs; 52024003Ssam register full = 0; 52125933Ssam int s, port; 52224003Ssam 52324003Ssam s = spl8(); 52424003Ssam port = minor(tp->t_dev) & 017; 52525881Ssam vs = (struct vx_softc *)tp->t_addr; 52625881Ssam if ((tp->t_state&(TS_TIMEOUT|TS_BUSY|TS_TTSTOP)) == 0) { 52725881Ssam if (tp->t_outq.c_cc <= TTLOWAT(tp)) { 52824003Ssam if (tp->t_state&TS_ASLEEP) { 52924003Ssam tp->t_state &= ~TS_ASLEEP; 53024003Ssam wakeup((caddr_t)&tp->t_outq); 53124003Ssam } 53224003Ssam if (tp->t_wsel) { 53324003Ssam selwakeup(tp->t_wsel, tp->t_state & TS_WCOLL); 53424003Ssam tp->t_wsel = 0; 53524003Ssam tp->t_state &= ~TS_WCOLL; 53624003Ssam } 53724003Ssam } 53825881Ssam if (tp->t_outq.c_cc == 0) { 53924003Ssam splx(s); 54025881Ssam return (0); 54124003Ssam } 54225877Ssam scope_out(3); 54325881Ssam if ((tp->t_flags&(RAW|LITOUT)) == 0) 54424003Ssam full = 0200; 54525881Ssam if ((n = ndqb(&tp->t_outq, full)) == 0) { 54625881Ssam if (full) { 54725675Ssam n = getc(&tp->t_outq); 54825881Ssam timeout(ttrstrt, (caddr_t)tp, (n&0177)+6); 54924003Ssam tp->t_state |= TS_TIMEOUT; 55024003Ssam full = 0; 55124003Ssam } 55224003Ssam } else { 55325933Ssam char *cp = (char *)tp->t_outq.c_cf; 55425933Ssam 55524003Ssam tp->t_state |= TS_BUSY; 55625933Ssam full = vsetq(vs, port, cp, n); 55725933Ssam /* 55825933Ssam * If the port is not currently active, try to 55925933Ssam * send the data. We send it immediately if the 56025933Ssam * command buffer is full, or if we've nothing 56125933Ssam * currently outstanding. If we don't send it, 56225933Ssam * set a timeout to force the data to be sent soon. 56325933Ssam */ 56425933Ssam if ((vs->vs_active & (1 << (port-vs->vs_loport))) == 0) 56525881Ssam if (full || vs->vs_xmtcnt == 0) { 56625933Ssam cp = (char *)&nextcmd(vs)->cmd; 56725881Ssam vs->vs_xmtcnt++; 56825933Ssam vcmd(vs->vs_nbr, cp); 56924003Ssam } else 57025881Ssam timeout(vxforce, (caddr_t)vs, 3); 57124003Ssam } 57224003Ssam } 57324003Ssam splx(s); 57425881Ssam return (full); /* indicate if max commands or not */ 57524003Ssam } 57624003Ssam 57724003Ssam /* 57824003Ssam * Stop output on a line. 57924003Ssam */ 58024003Ssam vxstop(tp) 58125881Ssam register struct tty *tp; 58224003Ssam { 58325881Ssam int s; 58424003Ssam 58524003Ssam s = spl8(); 58625881Ssam if (tp->t_state&TS_BUSY) 58725881Ssam if ((tp->t_state&TS_TTSTOP) == 0) 58824003Ssam tp->t_state |= TS_FLUSH; 58924003Ssam splx(s); 59024003Ssam } 59124003Ssam 59225881Ssam static int vxbbno = -1; 59324003Ssam /* 59424003Ssam * VIOCX Initialization. Makes free lists of command buffers. 59524003Ssam * Resets all viocx's. Issues a LIDENT command to each 59625933Ssam * viocx to establish interrupt vectors and logical port numbers. 59724003Ssam */ 59825881Ssam vxinit(vx, wait) 59925881Ssam register int vx; 60025881Ssam int wait; 60124003Ssam { 60225933Ssam register struct vx_softc *vs; 60325933Ssam register struct vxdevice *addr; 60425933Ssam register struct vxcmd *cp; 60525881Ssam register char *resp; 60625881Ssam register int j; 60724003Ssam char type; 60824003Ssam 60925881Ssam vs = &vx_softc[vx]; 61025933Ssam vs->vs_type = 0; /* vioc-x by default */ 61125933Ssam addr = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 61225881Ssam type = addr->v_ident; 61325881Ssam vs->vs_vers = (type&VXT_NEW) ? VXV_NEW : VXV_OLD; 61425881Ssam if (vs->vs_vers == VXV_NEW) 61525881Ssam vs->vs_silosiz = addr->v_maxsilo; 61625881Ssam switch (type) { 61724003Ssam 61825881Ssam case VXT_VIOCX: 61925881Ssam case VXT_VIOCX|VXT_NEW: 62025881Ssam /* set dcd for printer ports */ 62125933Ssam for (j = 0; j < 16;j++) 62225881Ssam if (addr->v_portyp[j] == 4) 62325881Ssam addr->v_dcd |= 1 << j; 62425881Ssam break; 62524003Ssam 62625881Ssam case VXT_PVIOCX: 62725881Ssam case VXT_PVIOCX|VXT_NEW: 62825881Ssam break; 62924003Ssam #if NVBSC > 0 63025881Ssam case VX_VIOCB: /* old f/w bisync */ 63125881Ssam case VX_VIOCB|VXT_NEW: { /* new f/w bisync */ 63225933Ssam register struct bsc *bp; 63325881Ssam extern struct bsc bsc[]; 63424003Ssam 63525881Ssam printf("%X: %x%x %s VIOC-B, ", (long)addr, (int)addr->v_ident, 63625881Ssam (int)addr->v_fault, vs->vs_vers == VXV_OLD ? "old" : "16k"); 63725881Ssam for (bp = &bsc[0]; bp <= &bsc[NBSC]; bp++) 63825881Ssam bp->b_devregs = (caddr_t)vs; 63925881Ssam printf("%d BSC Ports initialized.\n", NBSC); 64025881Ssam break; 64125881Ssam if (vs->vs_vers == VXV_NEW && CBSIZE > addr->v_maxxmt) 64225881Ssam printf("vxinit: Warning CBSIZE > maxxmt\n"); 64325881Ssam break; 64424003Ssam #endif 64525881Ssam case VXT_VIOCBOP: /* VIOC-BOP */ 64625881Ssam vs->vs_type = 1; 64725881Ssam vs->vs_bop = ++vxbbno; 64825881Ssam printf("VIOC-BOP no. %d at %x\n", vs->vs_bop, addr); 64924003Ssam 65025933Ssam default: 65125881Ssam printf("vx%d: unknown type %x\n", vx, type); 65225881Ssam return; 65324003Ssam } 65425881Ssam vs->vs_nbr = -1; 65525933Ssam vs->vs_maxcmd = (vs->vs_vers == VXV_NEW) ? 24 : 4; 65625933Ssam /* 65725933Ssam * Initialize all cmd buffers by linking them 65825933Ssam * into a free list. 65925933Ssam */ 66025881Ssam for (j = 0; j < NVCXBUFS; j++) { 66125933Ssam cp = &vs->vs_lst[j]; 66225933Ssam cp->c_fwd = &vs->vs_lst[j+1]; 66325881Ssam } 66425881Ssam vs->vs_avail = &vs->vs_lst[0]; /* set idx to 1st free buf */ 66524003Ssam cp->c_fwd = (struct vxcmd *)0; /* mark last buf in free list */ 66624003Ssam 66725933Ssam /* 66825933Ssam * Establish the interrupt vectors and define the port numbers. 66925933Ssam */ 67025933Ssam cp = vobtain(vs); 67125933Ssam cp->cmd = VXC_LIDENT; 67225881Ssam cp->par[0] = vs->vs_ivec; /* ack vector */ 67325857Ssam cp->par[1] = cp->par[0]+1; /* cmd resp vector */ 67425857Ssam cp->par[3] = cp->par[0]+2; /* unsol intr vector */ 67525881Ssam cp->par[4] = 15; /* max ports, no longer used */ 67625881Ssam cp->par[5] = 0; /* set 1st port number */ 67725933Ssam vcmd(vx, (caddr_t)&cp->cmd); 67825881Ssam if (!wait) 67925881Ssam return; 68025881Ssam for (j = 0; cp->cmd == VXC_LIDENT && j < 4000000; j++) 68125857Ssam ; 68225857Ssam if (j >= 4000000) 68325881Ssam printf("vx%d: didn't respond to LIDENT\n", vx); 68424003Ssam 68524003Ssam /* calculate address of response buffer */ 68625881Ssam resp = (char *)addr + (addr->v_rspoff&0x3fff); 68725933Ssam if (resp[0] != 0 && (resp[0]&0177) != 3) { 68825933Ssam vrelease(vs, cp); /* init failed */ 68925881Ssam return; 69024003Ssam } 69125881Ssam vs->vs_loport = cp->par[5]; 69225881Ssam vs->vs_hiport = cp->par[7]; 69325881Ssam vrelease(vs, cp); 69425933Ssam vs->vs_nbr = vx; /* assign board number */ 69524003Ssam } 69624003Ssam 69724003Ssam /* 69824003Ssam * Obtain a command buffer 69924003Ssam */ 70025881Ssam struct vxcmd * 70125881Ssam vobtain(vs) 70225933Ssam register struct vx_softc *vs; 70324003Ssam { 70425933Ssam register struct vxcmd *p; 70525881Ssam int s; 70624003Ssam 70724003Ssam s = spl8(); 70825881Ssam p = vs->vs_avail; 70925881Ssam if (p == (struct vxcmd *)0) { 71024003Ssam #ifdef VX_DEBUG 71125881Ssam if (vxintr4&VXNOBUF) 71225881Ssam vxintr4 &= ~VXNOBUF; 71324003Ssam #endif 71425881Ssam printf("vx%d: no buffers\n", vs - vx_softc); 71525881Ssam vxstreset(vs - vx_softc); 71624003Ssam splx(s); 71725881Ssam return (vobtain(vs)); 71824003Ssam } 71925881Ssam vs->vs_avail = vs->vs_avail->c_fwd; 72024003Ssam splx(s); 72125881Ssam return ((struct vxcmd *)p); 72224003Ssam } 72324003Ssam 72424003Ssam /* 72524003Ssam * Release a command buffer 72624003Ssam */ 72725881Ssam vrelease(vs, cp) 72825933Ssam register struct vx_softc *vs; 72925933Ssam register struct vxcmd *cp; 73024003Ssam { 73125881Ssam int s; 73224003Ssam 73324003Ssam #ifdef VX_DEBUG 73425881Ssam if (vxintr4&VXNOBUF) 73525881Ssam return; 73624003Ssam #endif 73724003Ssam s = spl8(); 73825881Ssam cp->c_fwd = vs->vs_avail; 73925881Ssam vs->vs_avail = cp; 74024003Ssam splx(s); 74124003Ssam } 74224003Ssam 74325881Ssam struct vxcmd * 74425881Ssam nextcmd(vs) 74525933Ssam register struct vx_softc *vs; 74624003Ssam { 74725933Ssam register struct vxcmd *cp; 74825881Ssam int s; 74924003Ssam 75024003Ssam s = spl8(); 75125881Ssam cp = vs->vs_build; 75225881Ssam vs->vs_build = (struct vxcmd *)0; 75324003Ssam splx(s); 75425881Ssam return (cp); 75524003Ssam } 75624003Ssam 75724003Ssam /* 75825933Ssam * Assemble transmits into a multiple command; 75925933Ssam * up to 8 transmits to 8 lines can be assembled together. 76024003Ssam */ 76125933Ssam vsetq(vs, line, addr, n) 76225933Ssam register struct vx_softc *vs; 76325881Ssam caddr_t addr; 76424003Ssam { 76525933Ssam register struct vxcmd *cp; 76625933Ssam register struct vxmit *mp; 76724003Ssam 76825933Ssam /* 76925933Ssam * Grab a new command buffer or append 77025933Ssam * to the current one being built. 77125933Ssam */ 77225881Ssam cp = vs->vs_build; 77325881Ssam if (cp == (struct vxcmd *)0) { 77425881Ssam cp = vobtain(vs); 77525881Ssam vs->vs_build = cp; 77625881Ssam cp->cmd = VXC_XMITDTA; 77724003Ssam } else { 77825881Ssam if ((cp->cmd & 07) == 07) { 77925881Ssam printf("vx%d: setq overflow\n", vs-vx_softc); 78025881Ssam vxstreset(vs->vs_nbr); 78125881Ssam return (0); 78224003Ssam } 78324003Ssam cp->cmd++; 78424003Ssam } 78525933Ssam /* 78625933Ssam * Select the next vxmit buffer and copy the 78725933Ssam * characters into the buffer (if there's room 78825933Ssam * and the device supports ``immediate mode'', 78925933Ssam * or store an indirect pointer to the data. 79025933Ssam */ 79125881Ssam mp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit)); 79225675Ssam mp->bcount = n-1; 79325933Ssam mp->line = line; 79425933Ssam if (vs->vs_vers == VXV_NEW && n <= sizeof (mp->ostream)) { 79525881Ssam cp->cmd = VXC_XMITIMM; 79625933Ssam bcopy(addr, mp->ostream, n); 79724003Ssam } else { 79825933Ssam /* get system address of clist block */ 79925675Ssam addr = (caddr_t)vtoph((struct proc *)0, (unsigned)addr); 80025933Ssam bcopy(&addr, mp->ostream, sizeof (addr)); 80124003Ssam } 80225881Ssam return (vs->vs_vers == VXV_NEW ? 1 : (cp->cmd&07) == 7); 80324003Ssam } 80425881Ssam 80525881Ssam /* 80625881Ssam * Write a command out to the VIOC 80725881Ssam */ 80825881Ssam vcmd(vx, cmdad) 80925881Ssam register int vx; 81025881Ssam register caddr_t cmdad; 81125881Ssam { 81225933Ssam register struct vcmds *cp; 81325881Ssam register struct vx_softc *vs; 81425881Ssam int s; 81525881Ssam 81625881Ssam s = spl8(); 81725881Ssam vs = &vx_softc[vx]; 81825933Ssam /* 81925933Ssam * When the vioc is resetting, don't process 82025933Ssam * anything other than VXC_LIDENT commands. 82125933Ssam */ 82225881Ssam if (vs->vs_state == VXS_RESET && cmdad != NULL) { 82325933Ssam struct vxcmd *vcp = (struct vxcmd *)(cmdad-sizeof (vcp->c_fwd)); 82425881Ssam 82525933Ssam if (vcp->cmd != VXC_LIDENT) { 82625933Ssam vrelease(vs, vcp); 82725881Ssam return (0); 82825881Ssam } 82925881Ssam } 83025881Ssam cp = &vs->vs_cmds; 83125881Ssam if (cmdad != (caddr_t)0) { 83225881Ssam cp->cmdbuf[cp->v_fill] = cmdad; 83325881Ssam if (++cp->v_fill >= VC_CMDBUFL) 83425881Ssam cp->v_fill = 0; 83525881Ssam if (cp->v_fill == cp->v_empty) { 83625881Ssam printf("vx%d: cmd q overflow\n", vx); 83725881Ssam vxstreset(vx); 83825881Ssam splx(s); 83925881Ssam return (0); 84025881Ssam } 84125881Ssam cp->v_cmdsem++; 84225881Ssam } 84325881Ssam if (cp->v_cmdsem && cp->v_curcnt < vs->vs_maxcmd) { 84425881Ssam cp->v_cmdsem--; 84525881Ssam cp->v_curcnt++; 84625881Ssam vinthandl(vx, ((V_BSY|CMDquals) << 8)|V_INTR); 84725881Ssam } 84825881Ssam splx(s); 84925881Ssam return (1); 85025881Ssam } 85125881Ssam 85225881Ssam /* 85325881Ssam * VIOC acknowledge interrupt. The VIOC has received the new 85425881Ssam * command. If no errors, the new command becomes one of 16 (max) 85525881Ssam * current commands being executed. 85625881Ssam */ 85725881Ssam vackint(vx) 85825881Ssam register vx; 85925881Ssam { 86025933Ssam register struct vxdevice *vp; 86125933Ssam register struct vcmds *cp; 86225881Ssam struct vx_softc *vs; 86325881Ssam int s; 86425881Ssam 86525881Ssam scope_out(5); 86625881Ssam vs = &vx_softc[vx]; 86725881Ssam if (vs->vs_type) { /* Its a BOP */ 86825881Ssam #ifdef SNA_DEBUG 86925881Ssam extern vbrall(); 87025881Ssam 87125881Ssam if (snadebug & SVIOC) 87225881Ssam printf("vx%d: vack interrupt from BOP\n", vx); 87325881Ssam vbrall(vx); /* Int. from BOP, port 0 */ 87424003Ssam #endif 87525881Ssam return; 87625881Ssam } 87725881Ssam s = spl8(); 87825881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 87925881Ssam cp = &vs->vs_cmds; 88025933Ssam if (vp->v_vcid&V_ERR) { 88125881Ssam register char *resp; 88225881Ssam register i; 88325933Ssam 88425881Ssam printf("vx%d INTR ERR type %x v_dcd %x\n", vx, 88525881Ssam vp->v_vcid & 07, vp->v_dcd & 0xff); 88625881Ssam resp = (char *)vs->vs_mricmd; 88725881Ssam for (i = 0; i < 16; i++) 88825881Ssam printf("%x ", resp[i]&0xff); 88925881Ssam printf("\n"); 89025881Ssam splx(s); 89125881Ssam vxstreset(vx); 89225881Ssam return; 89325881Ssam } 89425881Ssam if ((vp->v_hdwre&017) == CMDquals) { 89525881Ssam #ifdef VX_DEBUG 89625881Ssam if (vxintr4 & VXERR4) { /* causes VIOC INTR ERR 4 */ 89725933Ssam struct vxcmd *cp1, *cp0; 89825881Ssam 89925933Ssam cp0 = (struct vxcmd *) 90025933Ssam ((caddr_t)cp->cmdbuf[cp->v_empty]-sizeof (cp0->c_fwd)); 90125881Ssam if (cp0->cmd == VXC_XMITDTA || cp0->cmd == VXC_XMITIMM) { 90225881Ssam cp1 = vobtain(vs); 90325881Ssam *cp1 = *cp0; 90425881Ssam vxintr4 &= ~VXERR4; 90525881Ssam (void) vcmd(vx, &cp1->cmd); 90625881Ssam } 90725881Ssam } 90825881Ssam #endif 90925881Ssam cp->v_curcmd[vp->v_vcid & VCMDLEN-1] = cp->cmdbuf[cp->v_empty]; 91025881Ssam if (++cp->v_empty >= VC_CMDBUFL) 91125881Ssam cp->v_empty = 0; 91225881Ssam } 91325881Ssam if (++cp->v_itrempt >= VC_IQLEN) 91425881Ssam cp->v_itrempt = 0; 91525881Ssam vintempt(vx); 91625881Ssam splx(s); 91725881Ssam (void) vcmd(vx, (caddr_t)0); /* queue next cmd, if any */ 91825881Ssam } 91925881Ssam 92025881Ssam /* 92125881Ssam * Command Response interrupt. The Vioc has completed 92225881Ssam * a command. The command may now be returned to 92325881Ssam * the appropriate device driver. 92425881Ssam */ 92525881Ssam vcmdrsp(vx) 92625881Ssam register vx; 92725881Ssam { 92825933Ssam register struct vxdevice *vp; 92925933Ssam register struct vcmds *cp; 93025881Ssam register caddr_t cmd; 93125881Ssam register struct vx_softc *vs; 93225881Ssam register char *resp; 93325881Ssam register k; 93425881Ssam register int s; 93525881Ssam 93625881Ssam scope_out(6); 93725881Ssam vs = &vx_softc[vx]; 93825881Ssam if (vs->vs_type) { /* Its a BOP */ 93925881Ssam printf("vx%d: vcmdrsp interrupt\n", vx); 94025881Ssam return; 94125881Ssam } 94225881Ssam s = spl8(); 94325881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 94425881Ssam cp = &vs->vs_cmds; 94525881Ssam resp = (char *)vp + (vp->v_rspoff&0x7fff); 94625881Ssam if (((k = resp[1])&V_UNBSY) == 0) { 94725881Ssam printf("vx%d: cmdresp debug\n", vx); 94825881Ssam splx(s); 94925881Ssam vxstreset(vx); 95025881Ssam return; 95125881Ssam } 95225881Ssam k &= VCMDLEN-1; 95325881Ssam cmd = cp->v_curcmd[k]; 95425881Ssam cp->v_curcmd[k] = (caddr_t)0; 95525881Ssam cp->v_curcnt--; 95625881Ssam k = *((short *)&resp[4]); /* cmd operation code */ 95725881Ssam if ((k&0xff00) == VXC_LIDENT) /* want hiport number */ 95825881Ssam for (k = 0; k < VRESPLEN; k++) 95925881Ssam cmd[k] = resp[k+4]; 96025881Ssam resp[1] = 0; 96125881Ssam vxxint(vx, (struct vxcmd *)cmd); 96225881Ssam if (vs->vs_state == VXS_READY) 96325881Ssam vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR); 96425881Ssam splx(s); 96525881Ssam } 96625881Ssam 96725881Ssam /* 96825881Ssam * Unsolicited interrupt. 96925881Ssam */ 97025881Ssam vunsol(vx) 97125881Ssam register vx; 97225881Ssam { 97325933Ssam register struct vxdevice *vp; 97425881Ssam struct vx_softc *vs; 97525881Ssam int s; 97625881Ssam 97725881Ssam scope_out(1); 97825881Ssam vs = &vx_softc[vx]; 97925881Ssam if (vs->vs_type) { /* Its a BOP */ 98025881Ssam printf("vx%d: vunsol from BOP\n", vx); 98125881Ssam return; 98225881Ssam } 98325881Ssam s = spl8(); 98425881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 98525881Ssam if (vp->v_uqual&V_UNBSY) { 98625881Ssam vxrint(vx); 98725881Ssam vinthandl(vx, ((V_BSY|UNSquals) << 8)|V_INTR); 98825881Ssam #ifdef notdef 98925881Ssam } else { 99025881Ssam printf("vx%d: unsolicited interrupt error\n", vx); 99125881Ssam splx(s); 99225881Ssam vxstreset(vx); 99325881Ssam #endif 99425881Ssam } 99525881Ssam splx(s); 99625881Ssam } 99725881Ssam 99825881Ssam /* 99925933Ssam * Enqueue an interrupt. 100025881Ssam */ 100125881Ssam vinthandl(vx, item) 100225881Ssam register int vx; 100325881Ssam register item; 100425881Ssam { 100525881Ssam register struct vcmds *cp; 100625881Ssam int empty; 100725881Ssam 100825881Ssam cp = &vx_softc[vx].vs_cmds; 100925933Ssam empty = (cp->v_itrfill == cp->v_itrempt); 101025881Ssam cp->v_itrqueu[cp->v_itrfill] = item; 101125881Ssam if (++cp->v_itrfill >= VC_IQLEN) 101225881Ssam cp->v_itrfill = 0; 101325881Ssam if (cp->v_itrfill == cp->v_itrempt) { 101425881Ssam printf("vx%d: interrupt q overflow\n", vx); 101525881Ssam vxstreset(vx); 101625881Ssam } else if (empty) 101725881Ssam vintempt(vx); 101825881Ssam } 101925881Ssam 102025881Ssam vintempt(vx) 102125881Ssam register int vx; 102225881Ssam { 102325881Ssam register struct vcmds *cp; 102425881Ssam register struct vxdevice *vp; 102525881Ssam register short item; 102625881Ssam register short *intr; 102725881Ssam 102825881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 102925881Ssam if (vp->v_vioc&V_BSY) 103025881Ssam return; 103125881Ssam cp = &vx_softc[vx].vs_cmds; 103225881Ssam if (cp->v_itrempt == cp->v_itrfill) 103325881Ssam return; 103425881Ssam item = cp->v_itrqueu[cp->v_itrempt]; 103525881Ssam intr = (short *)&vp->v_vioc; 103625881Ssam switch ((item >> 8)&03) { 103725881Ssam 103825881Ssam case CMDquals: { /* command */ 103925881Ssam int phys; 104025881Ssam 104125881Ssam if (cp->v_empty == cp->v_fill || vp->v_vcbsy&V_BSY) 104225881Ssam break; 104325881Ssam vx_softc[vx].vs_mricmd = (caddr_t)cp->cmdbuf[cp->v_empty]; 104425881Ssam phys = vtoph((struct proc *)0, 104525881Ssam (unsigned)cp->cmdbuf[cp->v_empty]); 104625881Ssam vp->v_vcp[0] = ((short *)&phys)[0]; 104725881Ssam vp->v_vcp[1] = ((short *)&phys)[1]; 104825881Ssam vp->v_vcbsy = V_BSY; 104925881Ssam *intr = item; 105025881Ssam scope_out(4); 105125881Ssam break; 105225881Ssam } 105325881Ssam 105425881Ssam case RSPquals: /* command response */ 105525881Ssam *intr = item; 105625881Ssam scope_out(7); 105725881Ssam break; 105825881Ssam 105925881Ssam case UNSquals: /* unsolicited interrupt */ 106025881Ssam vp->v_uqual = 0; 106125881Ssam *intr = item; 106225881Ssam scope_out(2); 106325881Ssam break; 106425881Ssam } 106525881Ssam } 106625881Ssam 106725881Ssam /* 106825881Ssam * Start a reset on a vioc after error (hopefully) 106925881Ssam */ 107025881Ssam vxstreset(vx) 107125881Ssam register vx; 107225881Ssam { 107325881Ssam register struct vx_softc *vs; 107425933Ssam register struct vxdevice *vp; 107525881Ssam register struct vxcmd *cp; 107625881Ssam register int j; 107725881Ssam extern int vxinreset(); 107825881Ssam int s; 107925881Ssam 108025881Ssam s = spl8() ; 108125881Ssam vs = &vx_softc[vx]; 108225881Ssam if (vs->vs_state == VXS_RESET) { /* avoid recursion */ 108325881Ssam splx(s); 108425881Ssam return; 108525881Ssam } 108625881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 108725881Ssam /* 108825881Ssam * Zero out the vioc structures, mark the vioc as being 108925881Ssam * reset, reinitialize the free command list, reset the vioc 109025881Ssam * and start a timer to check on the progress of the reset. 109125881Ssam */ 109225881Ssam bzero((caddr_t)vs, (unsigned)sizeof (*vs)); 109325881Ssam 109425881Ssam /* 109525881Ssam * Setting VXS_RESET prevents others from issuing 109625881Ssam * commands while allowing currently queued commands to 109725881Ssam * be passed to the VIOC. 109825881Ssam */ 109925881Ssam vs->vs_state = VXS_RESET; 110025881Ssam /* init all cmd buffers */ 110125881Ssam for (j = 0; j < NVCXBUFS; j++) { 110225933Ssam cp = &vs->vs_lst[j]; 110325933Ssam cp->c_fwd = &vs->vs_lst[j+1]; 110425881Ssam } 110525933Ssam vs->vs_avail = &vs->vs_lst[0]; 110625933Ssam cp->c_fwd = (struct vxcmd *)0; 110725881Ssam printf("vx%d: reset...", vx); 110825881Ssam vp->v_fault = 0; 110925881Ssam vp->v_vioc = V_BSY; 111025933Ssam vp->v_hdwre = V_RESET; /* generate reset interrupt */ 111125881Ssam timeout(vxinreset, (caddr_t)vx, hz*5); 111225881Ssam splx(s); 111325881Ssam } 111425881Ssam 111525881Ssam /* continue processing a reset on a vioc after an error (hopefully) */ 111625881Ssam vxinreset(vx) 111725881Ssam int vx; 111825881Ssam { 111925933Ssam register struct vxdevice *vp; 112025881Ssam int s = spl8(); 112125881Ssam 112225881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 112325881Ssam /* 112425881Ssam * See if the vioc has reset. 112525881Ssam */ 112625881Ssam if (vp->v_fault != VXF_READY) { 112725881Ssam printf("failed\n"); 112825881Ssam splx(s); 112925881Ssam return; 113025881Ssam } 113125881Ssam /* 113225881Ssam * Send a LIDENT to the vioc and mess with carrier flags 113325881Ssam * on parallel printer ports. 113425881Ssam */ 113525881Ssam vxinit(vx, (long)0); 113625881Ssam splx(s); 113725881Ssam } 113825881Ssam 113925881Ssam /* 114025933Ssam * Finish the reset on the vioc after an error (hopefully). 114125933Ssam * 114225881Ssam * Restore modem control, parameters and restart output. 114325881Ssam * Since the vioc can handle no more then 24 commands at a time 114425881Ssam * and we could generate as many as 48 commands, we must do this in 114525881Ssam * phases, issuing no more then 16 commands at a time. 114625881Ssam */ 114725881Ssam vxfnreset(vx, cp) 114825881Ssam register int vx; 114925881Ssam register struct vxcmd *cp; 115025881Ssam { 115125881Ssam register struct vx_softc *vs; 115225933Ssam register struct vxdevice *vp ; 115325881Ssam register struct tty *tp, *tp0; 115425881Ssam register int i; 115525881Ssam #ifdef notdef 115625881Ssam register int on; 115725881Ssam #endif 115825881Ssam extern int vxrestart(); 115925881Ssam int s = spl8(); 116025881Ssam 116125881Ssam vs = &vx_softc[vx]; 116225881Ssam vs->vs_loport = cp->par[5]; 116325881Ssam vs->vs_hiport = cp->par[7]; 116425881Ssam vrelease(vs, cp); 116525881Ssam vs->vs_nbr = vx; /* assign VIOC-X board number */ 116625881Ssam vs->vs_state = VXS_READY; 116725881Ssam 116825881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 116925881Ssam vp->v_vcid = 0; 117025881Ssam 117125881Ssam /* 117225881Ssam * Restore modem information and control. 117325881Ssam */ 117425881Ssam tp0 = &vx_tty[vx*16]; 117525881Ssam for (i = vs->vs_loport; i <= vs->vs_hiport; i++) { 117625881Ssam tp = tp0 + i; 117725881Ssam if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) { 117825881Ssam tp->t_state &= ~TS_CARR_ON; 117925881Ssam vcmodem(tp->t_dev, VMOD_ON); 118025881Ssam if (tp->t_state&TS_CARR_ON) 118125881Ssam wakeup((caddr_t)&tp->t_canq); 118225881Ssam else if (tp->t_state & TS_ISOPEN) { 118325881Ssam ttyflush(tp, FREAD|FWRITE); 118425881Ssam if (tp->t_state&TS_FLUSH) 118525881Ssam wakeup((caddr_t)&tp->t_state); 118625881Ssam if ((tp->t_flags&NOHANG) == 0) { 118725881Ssam gsignal(tp->t_pgrp, SIGHUP); 118825881Ssam gsignal(tp->t_pgrp, SIGCONT); 118925881Ssam } 119025881Ssam } 119125881Ssam } 119225881Ssam /* 119325881Ssam * If carrier has changed while we were resetting, 119425881Ssam * take appropriate action. 119525881Ssam */ 119625881Ssam #ifdef notdef 119725881Ssam on = vp->v_dcd & 1<<i; 119825881Ssam if (on && (tp->t_state&TS_CARR_ON) == 0) { 119925881Ssam tp->t_state |= TS_CARR_ON; 120025881Ssam wakeup((caddr_t)&tp->t_canq); 120125881Ssam } else if (!on && tp->t_state&TS_CARR_ON) { 120225881Ssam tp->t_state &= ~TS_CARR_ON; 120325881Ssam if (tp->t_state & TS_ISOPEN) { 120425881Ssam ttyflush(tp, FREAD|FWRITE); 120525881Ssam if (tp->t_state&TS_FLUSH) 120625881Ssam wakeup((caddr_t)&tp->t_state); 120725881Ssam if ((tp->t_flags&NOHANG) == 0) { 120825881Ssam gsignal(tp->t_pgrp, SIGHUP); 120925881Ssam gsignal(tp->t_pgrp, SIGCONT); 121025881Ssam } 121125881Ssam } 121225881Ssam } 121325881Ssam #endif 121425881Ssam } 121525881Ssam vs->vs_state = VXS_RESET; 121625881Ssam timeout(vxrestart, (caddr_t)vx, hz); 121725881Ssam splx(s); 121825881Ssam } 121925881Ssam 122025881Ssam /* 122125881Ssam * Restore a particular aspect of the VIOC. 122225881Ssam */ 122325881Ssam vxrestart(vx) 122425881Ssam int vx; 122525881Ssam { 122625881Ssam register struct tty *tp, *tp0; 122725881Ssam register struct vx_softc *vs; 122825881Ssam register int i, cnt; 122925881Ssam int s = spl8(); 123025881Ssam 123125881Ssam cnt = vx >> 8; 123225881Ssam vx &= 0xff; 123325881Ssam vs = &vx_softc[vx]; 123425881Ssam vs->vs_state = VXS_READY; 123525881Ssam tp0 = &vx_tty[vx*16]; 123625881Ssam for (i = vs->vs_loport; i <= vs->vs_hiport; i++) { 123725881Ssam tp = tp0 + i; 123825881Ssam if (cnt != 0) { 123925881Ssam tp->t_state &= ~(TS_BUSY|TS_TIMEOUT); 124025881Ssam if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) 124125881Ssam vxstart(tp); /* restart pending output */ 124225881Ssam } else { 124325881Ssam if (tp->t_state&(TS_WOPEN|TS_ISOPEN)) 124425881Ssam vxcparam(tp->t_dev, 0); 124525881Ssam } 124625881Ssam } 124725881Ssam if (cnt == 0) { 124825881Ssam vs->vs_state = VXS_RESET; 124925881Ssam timeout(vxrestart, (caddr_t)(vx + 1*256), hz); 125025881Ssam } else 125125881Ssam printf("done\n"); 125225881Ssam splx(s); 125325881Ssam } 125425881Ssam 125525881Ssam vxreset(dev) 125625881Ssam dev_t dev; 125725881Ssam { 125825881Ssam 125925881Ssam vxstreset(minor(dev) >> 4); /* completes asynchronously */ 126025881Ssam } 126125881Ssam 126225881Ssam vxfreset(vx) 126325881Ssam register int vx; 126425881Ssam { 126525881Ssam struct vba_device *vi; 126625881Ssam 126725881Ssam if ((unsigned)vx > NVX || (vi = vxinfo[vx]) == 0 || vi->ui_addr == 0) 126825881Ssam return (ENODEV); 126925881Ssam vx_softc[vx].vs_state = VXS_READY; 127025881Ssam vxstreset(vx); 127125881Ssam return (0); /* completes asynchronously */ 127225881Ssam } 127325881Ssam 127425881Ssam vcmodem(dev, flag) 127525881Ssam dev_t dev; 127625881Ssam { 127725881Ssam struct tty *tp; 127825881Ssam register struct vxcmd *cp; 127925881Ssam register struct vx_softc *vs; 128025881Ssam register struct vxdevice *kp; 128125881Ssam register port; 128225881Ssam int unit; 128325881Ssam 128425881Ssam unit = minor(dev); 128525881Ssam tp = &vx_tty[unit]; 128625881Ssam vs = (struct vx_softc *)tp->t_addr; 128725881Ssam cp = vobtain(vs); 128825881Ssam kp = (struct vxdevice *)((struct vba_device *)vxinfo[vs->vs_nbr])->ui_addr; 128925881Ssam 129025881Ssam port = unit & 017; 129125881Ssam /* 129225881Ssam * Issue MODEM command 129325881Ssam */ 129425881Ssam cp->cmd = VXC_MDMCTL; 129525881Ssam cp->par[0] = (flag == VMOD_ON) ? V_ENAB : V_DISAB; 129625881Ssam cp->par[1] = port; 129725881Ssam vcmd(vs->vs_nbr, (caddr_t)&cp->cmd); 129825881Ssam port -= vs->vs_loport; 129925881Ssam if ((kp->v_dcd >> port) & 1) { 130025881Ssam if (flag == VMOD_ON) 130125881Ssam tp->t_state |= TS_CARR_ON; 130225881Ssam return (1); 130325881Ssam } 130425881Ssam return (0); 130525881Ssam } 130625881Ssam 130725881Ssam /* 130825881Ssam * VCMINTR called when an unsolicited interrup occurs signaling 130925881Ssam * some change of modem control state. 131025881Ssam */ 131125881Ssam vcmintr(vx) 131225881Ssam register vx; 131325881Ssam { 131425881Ssam register struct vxdevice *kp; 131525881Ssam register struct tty *tp; 131625881Ssam register port; 131725881Ssam 131825881Ssam kp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 131925881Ssam port = kp->v_usdata[0] & 017; 132025881Ssam tp = &vx_tty[vx*16+port]; 132125881Ssam #if NVBSC > 0 132225881Ssam /* 132325881Ssam * Check for change in DSR for BISYNC port. 132425881Ssam */ 132525881Ssam if (bscport[vx*16+port]&BISYNC) { 132625881Ssam if (kp->v_ustat&DSR_CHG) { 132725933Ssam register struct vx_softc *xp; 132825881Ssam register struct bsc *bp; 132925881Ssam extern struct bsc bsc[]; 133025881Ssam 133125881Ssam vs = (struct vx_softc *)tp->t_addr; 133225881Ssam bp = &bsc[minor(tp->t_dev)] ; 133325881Ssam bp->b_hlflgs &= ~BSC_DSR ; 133425881Ssam if (kp->v_ustat & DSR_ON) 133525881Ssam bp->b_hlflgs |= BSC_DSR ; 133625881Ssam printf("BSC DSR Chg: %x\n", kp->v_ustat&DSR_CHG);/*XXX*/ 133725881Ssam } 133825881Ssam return; 133925881Ssam } 134025881Ssam #endif 134125881Ssam if ((kp->v_ustat&DCD_ON) && ((tp->t_state&TS_CARR_ON) == 0)) { 134225881Ssam tp->t_state |= TS_CARR_ON; 134325881Ssam wakeup((caddr_t)&tp->t_canq); 134425881Ssam return; 134525881Ssam } 134625881Ssam if ((kp->v_ustat&DCD_OFF) && (tp->t_state&TS_CARR_ON)) { 134725881Ssam tp->t_state &= ~TS_CARR_ON; 134825881Ssam if (tp->t_state&TS_ISOPEN) { 134925881Ssam register struct vx_softc *vs; 135025881Ssam register struct vcmds *cp; 135125881Ssam register struct vxcmd *cmdp; 135225881Ssam 135325881Ssam ttyflush(tp, FREAD|FWRITE); 135425881Ssam /* clear all pending trnansmits */ 135525881Ssam vs = &vx_softc[vx]; 135625881Ssam if (tp->t_state&(TS_BUSY|TS_FLUSH) && 135725881Ssam vs->vs_vers == VXV_NEW) { 135825881Ssam int i, cmdfound = 0; 135925881Ssam 136025881Ssam cp = &vs->vs_cmds; 136125881Ssam for (i = cp->v_empty; i != cp->v_fill; ) { 136225881Ssam cmdp = (struct vxcmd *)((long *)cp->cmdbuf[i]-1); 136325881Ssam if ((cmdp->cmd == VXC_XMITDTA || 136425881Ssam cmdp->cmd == VXC_XMITIMM) && 136525881Ssam ((struct vxmit *)cmdp->par)->line == port) { 136625881Ssam cmdfound++; 136725881Ssam cmdp->cmd = VXC_FDTATOX; 136825881Ssam cmdp->par[1] = port; 136925881Ssam } 137025881Ssam if (++i >= VC_CMDBUFL) 137125881Ssam i = 0; 137225881Ssam } 137325881Ssam if (cmdfound) 137425881Ssam tp->t_state &= ~(TS_BUSY|TS_FLUSH); 137525881Ssam /* cmd is already in vioc, have to flush it */ 137625881Ssam else { 137725881Ssam cmdp = vobtain(vs); 137825881Ssam cmdp->cmd = VXC_FDTATOX; 137925881Ssam cmdp->par[1] = port; 138025881Ssam vcmd(vx, (caddr_t)&cmdp->cmd); 138125881Ssam } 138225881Ssam } 138325881Ssam if ((tp->t_flags&NOHANG) == 0) { 138425881Ssam gsignal(tp->t_pgrp, SIGHUP); 138525881Ssam gsignal(tp->t_pgrp, SIGCONT); 138625881Ssam } 138725881Ssam } 138825881Ssam return; 138925881Ssam } 139025881Ssam if ((kp->v_ustat&BRK_CHR) && (tp->t_state&TS_ISOPEN)) { 139125881Ssam (*linesw[tp->t_line].l_rint)(tp->t_intrc & 0377, tp); 139225881Ssam return; 139325881Ssam } 139425881Ssam } 139525881Ssam #endif 1396