X-Git-Url: https://git.subgeniuskitty.com/unix-history/.git/blobdiff_plain/4db7c84e2e96010f2474115d135571bc6655ff15..3155ebd21da2cb4d3370481297ceabe7c5c3a0d0:/usr/src/sys/tahoe/vba/vx.c diff --git a/usr/src/sys/tahoe/vba/vx.c b/usr/src/sys/tahoe/vba/vx.c index be7a171972..6247fe435b 100644 --- a/usr/src/sys/tahoe/vba/vx.c +++ b/usr/src/sys/tahoe/vba/vx.c @@ -1,4 +1,4 @@ -/* vx.c 1.5 86/01/12 */ +/* vx.c 1.6 86/01/13 */ #include "vx.h" #if NVX > 0 @@ -23,61 +23,85 @@ #include "uio.h" #include "proc.h" #include "vm.h" +#include "kernel.h" #include "../tahoevba/vbavar.h" -#include "../tahoevba/vioc.h" +#include "../tahoevba/vxreg.h" #include "../tahoevba/scope.h" #include "vbsc.h" #if NVBSC > 0 #include "../tahoebsc/bscio.h" #include "../tahoebsc/bsc.h" -char bscport[NVXPORTS]; -#endif - #ifdef BSC_DEBUG #include "../tahoebsc/bscdebug.h" #endif -#ifdef VX_DEBUG -long vxintr4 = 0; -long vxdebug = 0; -#include "../tahoevba/vxdebug.h" +char bscport[NVX*16]; #endif -#define RSPquals 1 +#ifdef VX_DEBUG +long vxintr4 = 0; +#define VXERR4 1 +#define VXNOBUF 2 +long vxdebug = 0; +#define VXVCM 1 +#define VXVCC 2 +#define VXVCX 4 +#include "../tahoesna/snadebug.h" +#endif -struct vcx vcx[NVIOCX] ; -struct tty vx_tty[NVXPORTS]; -extern struct vcmds v_cmds[]; -extern long reinit; +/* + * Interrupt type bits passed to vinthandl(). + */ +#define CMDquals 0 /* command completed interrupt */ +#define RSPquals 1 /* command response interrupt */ +#define UNSquals 2 /* unsolicited interrupt */ -int vxstart() ; -int ttrstrt() ; -struct vxcmd *vobtain() ; -struct vxcmd *nextcmd() ; +struct tty vx_tty[NVX*16]; +int vxstart(), ttrstrt(); +struct vxcmd *vobtain(), *nextcmd(); /* * Driver information for auto-configuration stuff. - * (not tested and probably should be changed) */ int vxprobe(), vxattach(), vxrint(); -struct vba_device *vxinfo[NVIOCX]; +struct vba_device *vxinfo[NVX]; long vxstd[] = { 0 }; struct vba_driver vxdriver = { vxprobe, 0, vxattach, 0, vxstd, "vx", vxinfo }; -char vxtype[NVIOCX]; /* 0: viox-x/vioc-b; 1: vioc-bop */ -char vxbbno = -1; -char vxbopno[NVIOCX]; /* BOP board no. if indicated by vxtype[] */ -int vxivec[NVIOCX]; /* interrupt vector base */ -extern vbrall(); +struct vx_softc { + u_char vs_type; /* 0: viox-x/vioc-b, 1: vioc-bop */ + u_char vs_bop; /* bop board # for vioc-bop's */ + u_char vs_loport; /* low port nbr */ + u_char vs_hiport; /* high port nbr */ + u_short vs_nbr; /* viocx number */ + u_short vs_maxcmd; /* max number of concurrent cmds */ + u_short vs_silosiz; /* silo size */ + short vs_vers; /* vioc/pvioc version */ +#define VXV_OLD 0 /* PVIOCX | VIOCX */ +#define VXV_NEW 1 /* NPVIOCX | NVIOCX */ + short vs_xmtcnt; /* xmit commands pending */ + short vs_brkreq; /* send break requests pending */ + short vs_active; /* active port bit array or flag */ + short vs_state; /* controller state */ +#define VXS_READY 0 /* ready for commands */ +#define VXS_RESET 1 /* in process of reseting */ + caddr_t vs_mricmd; /* most recent issued cmd */ + u_int vs_ivec; /* interrupt vector base */ + struct vxcmd *vs_avail;/* next available command buffer */ + struct vxcmd *vs_build; + struct vxcmd vs_lst[NVCXBUFS]; + struct vcmds vs_cmds; +} vx_softc[NVX]; vxprobe(reg, vi) caddr_t reg; struct vba_device *vi; { register int br, cvec; /* must be r12, r11 */ - register struct vblok *vp = (struct vblok *)reg; + register struct vxdevice *vp = (struct vxdevice *)reg; + register struct vx_softc *vs; #ifdef lint br = 0; cvec = br; br = cvec; @@ -89,8 +113,9 @@ vxprobe(reg, vi) vp->v_vioc = V_BSY; vp->v_hdwre = V_RESET; /* reset interrupt */ DELAY(4000000); - if (vp->v_fault != VREADY) + if (vp->v_fault != VXF_READY) return (0); + vs = &vx_softc[vi->ui_unit]; #ifdef notdef /* * Align vioc interrupt vector base to 4 vector @@ -99,20 +124,18 @@ vxprobe(reg, vi) */ if ((vi->ui_hd->vh_lastiv -= 3) > 0xff) vi->ui_hd->vh_lastiv = 0xff; - vxivec[vi->ui_unit] = vi->ui_hd->vh_lastiv = - vi->ui_hd->vh_lastiv &~ 0x3; + vs->vs_ivec = vi->ui_hd->vh_lastiv = vi->ui_hd->vh_lastiv &~ 0x3; #else - vxivec[vi->ui_unit] = 0x40+vi->ui_unit*4; + vs->vs_ivec = 0x40+vi->ui_unit*4; #endif - br = 0x18, cvec = vxivec[vi->ui_unit]; /* XXX */ - return (sizeof (*vp)); + br = 0x18, cvec = vs->vs_ivec; /* XXX */ + return (sizeof (struct vxdevice)); } vxattach(vi) register struct vba_device *vi; { - VIOCBAS[vi->ui_unit] = vi->ui_addr; vxinit(vi->ui_unit, (long)1); } @@ -121,57 +144,46 @@ vxattach(vi) */ /*ARGSUSED*/ vxopen(dev, flag) + dev_t dev; + int flag; { register struct tty *tp; /* pointer to tty struct for port */ - register struct vcx *xp; /* pointer to VIOC-X info/cmd buffer */ - register d; /* minor device number */ - register long jj; - - - d = minor(dev); /* get minor device number */ - if (d >= NVXPORTS) /* validate minor device number */ - return ENXIO; /* set errno to indicate bad port # */ - tp = &vx_tty[d]; /* index the tty structure for port */ - - xp = &vcx[d>>4]; /* index VIOC-X info/cmd area */ - d &= 017; - - /* If we did not find a board with the correct port number on - it, or the entry for the VIOC-X had no ports on it, inform the - caller that the port does not exist. */ - if(!( xp->v_loport <= d && d <= xp->v_hiport ) /* home? */ - || (xp->v_hiport - xp->v_loport)==0) - return ENXIO; /* bad minor device number */ - tp->t_addr = (caddr_t)xp; /* store address of VIOC-X info */ - tp->t_oproc = vxstart; /* store address of startup routine */ - tp->t_dev = dev; /* store major/minor device numbers */ - d = spl8(); - tp->t_state |= TS_WOPEN; /* mark device as waiting for open */ - if ((tp->t_state&TS_ISOPEN) == 0) /* is device already open? */ - { /* no, open it */ - ttychars(tp); /* set default control chars */ - if (tp->t_ispeed == 0) /* if no default speeds set them */ - { - tp->t_ispeed = SSPEED; /* default input baud */ - tp->t_ospeed = SSPEED; /* default output baud */ - tp->t_flags |= (ODDP|EVENP|ECHO); /* default modes */ + register struct vx_softc *vs; + register struct vba_device *vi; + int unit, vx, s, error; + + unit = minor(dev); + vx = unit >> 4; + if (unit >= NVX*16 || (vi = vxinfo[vx])== 0 || vi->ui_alive == 0) + return (ENXIO); + tp = &vx_tty[unit]; + if (tp->t_state&TS_XCLUDE && u.u_uid != 0) + return (EBUSY); + vs = &vx_softc[vx]; +#ifdef notdef + if (unit < vs->vs_loport || vs->vs_hiport < unit) /* ??? */ + return (ENXIO); +#endif + tp->t_addr = (caddr_t)vs; + tp->t_oproc = vxstart; + tp->t_dev = dev; + s = spl8(); + tp->t_state |= TS_WOPEN; + if ((tp->t_state&TS_ISOPEN) == 0) { + ttychars(tp); + if (tp->t_ispeed == 0) { + tp->t_ispeed = SSPEED; + tp->t_ospeed = SSPEED; + tp->t_flags |= ODDP|EVENP|ECHO; } - vxparam(dev); /* set parameters for this port */ + vxparam(dev); } - splx(d); - /* ? if already open for exclusive use open fails unless caller is - root. */ - if (tp->t_state&TS_XCLUDE && u.u_uid!=0) - return EBUSY; /* device is busy, sorry */ - - /* wait for data carrier detect to go high */ - d = spl8(); - if( !vcmodem(dev,VMOD_ON) ) - while( (tp->t_state&TS_CARR_ON) == 0 ) - sleep((caddr_t)&tp->t_canq,TTIPRI); - jj= (*linesw[tp->t_line].l_open)(dev,tp); /*let tty.c finish the open */ - splx(d); /* 1/2/85 : assures open complete */ - return (jj); + if (!vcmodem(dev, VMOD_ON)) + while ((tp->t_state&TS_CARR_ON) == 0) + sleep((caddr_t)&tp->t_canq, TTIPRI); + error = (*linesw[tp->t_line].l_open)(dev,tp); + splx(s); + return (error); } /* @@ -179,24 +191,24 @@ vxopen(dev, flag) */ /*ARGSUSED*/ vxclose(dev, flag) -dev_t dev; -int flag; + dev_t dev; + int flag; { register struct tty *tp; - register d; + int unit, s; - d = minor(dev) & 0377; - tp = &vx_tty[d]; - d = spl8(); + unit = minor(dev); + tp = &vx_tty[unit]; + s = spl8(); (*linesw[tp->t_line].l_close)(tp); - if ((tp->t_state&TS_ISOPEN) && (tp->t_state&TS_HUPCLS)) - if( !vcmodem(dev,VMOD_OFF) ) + if ((tp->t_state & (TS_ISOPEN|TS_HUPCLS)) == (TS_ISOPEN|TS_HUPCLS)) + if (!vcmodem(dev, VMOD_OFF)) tp->t_state &= ~TS_CARR_ON; /* wait for the last response */ - while(tp->t_state & TS_FLUSH) - sleep( (caddr_t)&tp->t_state, TTOPRI ) ; - ttyclose(tp); /* let tty.c finish the close */ - splx(d); + while (tp->t_state&TS_FLUSH) + sleep((caddr_t)&tp->t_state, TTOPRI); + ttyclose(tp); + splx(s); } /* @@ -206,8 +218,9 @@ vxread(dev, uio) dev_t dev; struct uio *uio; { - register struct tty *tp = &vx_tty[minor(dev) & 0377]; - return (*linesw[tp->t_line].l_read)(tp, uio); + struct tty *tp = &vx_tty[minor(dev)]; + + return ((*linesw[tp->t_line].l_read)(tp, uio)); } /* @@ -217,120 +230,126 @@ vxwrite(dev, uio) dev_t dev; struct uio *uio; { - register struct tty *tp = &vx_tty[minor(dev) & 0377]; - return (*linesw[tp->t_line].l_write)(tp, uio); + register struct tty *tp = &vx_tty[minor(dev)]; + + return ((*linesw[tp->t_line].l_write)(tp, uio)); } /* * VIOCX unsolicited interrupt. */ -vxrint(n) -register n; /* mux number */ +vxrint(vx) + register vx; { - register struct tty *tp; - register struct vcx *xp; - register short *sp; - register struct vblok *kp; - register int i, c; - short *savsilo; - struct silo { - char data; - char port; - }; - - kp = VBAS(n); - xp = &vcx[n]; - switch(kp->v_uqual&037) { + register struct tty *tp, *tp0; + register struct vxdevice *addr; + register struct vx_softc *vs; + struct vba_device *vi; + register int nc, c; + register struct silo { + char data, port; + } *sp; + short *osp; + int overrun = 0; + + vi = vxinfo[vx]; + if (vi == 0 || vi->ui_alive == 0) + return; + addr = (struct vxdevice *)vi->ui_addr; + switch (addr->v_uqual&037) { case 0: break; case 2: - printf(" ERR NBR %x\n",kp->v_ustat); - vpanic("vc: VC PROC ERR"); - vxstreset(n); - return(0); + printf("vx%d: vc proc err, ustat %x\n", addr->v_ustat); + vxstreset(vx); + return (0); case 3: - vcmintr(n); - return(1); + vcmintr(vx); + return (1); case 4: - return(1); + return (1); default: - printf(" ERR NBR %x\n",kp->v_uqual); - vpanic("vc: VC UQUAL ERR"); - vxstreset(n); - return(0); - } - if(xp->v_vers == V_NEW) { - register short *aa ; - aa = (short *)kp->v_usdata; - sp = (short *)(*aa + (char *)kp) ; - } else { - c = kp->v_usdata[0] << 6; - sp = (short *)((char *)kp + SILOBAS + c); - } - i = *(savsilo = sp); - if (i == 0) return(1); - if(xp->v_vers == V_NEW) - if( i > xp->v_silosiz ) { - printf("vx: %d exceeds silo size\n",i) ; - i = xp->v_silosiz; - } - for(sp++;i > 0;i--,sp++) { - c = ((struct silo *)sp)->port & 017; - tp = &vx_tty[c+n*16]; - if(xp->v_loport > c || c > xp->v_hiport) - continue; /* port out of bounds */ - if( (tp->t_state & TS_ISOPEN) == 0) { + printf("vx%d: vc uqual err, uqual %x\n", addr->v_uqual); + vxstreset(vx); + return (0); + } + vs = &vx_softc[vx]; + if (vs->vs_vers == VXV_NEW) + sp = (struct silo *)((caddr_t)addr + *(short *)addr->v_usdata); + else + sp = (struct silo *)((caddr_t)addr+VX_SILO+(addr->v_usdata[0]<<6)); + nc = *(osp = (short *)sp); + if (nc == 0) + return (1); + if (vs->vs_vers == VXV_NEW && nc > vs->vs_silosiz) { + printf("vx%d: %d exceeds silo size\n", nc); + nc = vs->vs_silosiz; + } + tp0 = &vx_tty[vx*16]; + sp = (struct silo *)(((short *)sp)+1); + for (; nc > 0; nc--, sp = (struct silo *)(((short *)sp)+1)) { + c = sp->port & 017; + if (vs->vs_loport > c || c > vs->vs_hiport) + continue; + tp = tp0 + c; + if( (tp->t_state&TS_ISOPEN) == 0) { wakeup((caddr_t)&tp->t_rawq); continue; } - c = ((struct silo *)sp)->data; - switch(((struct silo *)sp)->port&(PERROR|FERROR)) { - case PERROR: - case PERROR|FERROR: - if( (tp->t_flags&(EVENP|ODDP)) == EVENP - || (tp->t_flags & (EVENP|ODDP)) == ODDP ) + c = sp->data; + if ((sp->port&VX_RO) == VX_RO && !overrun) { + printf("vx%d: receiver overrun\n", vi->ui_unit); + overrun = 1; + continue; + } + if (sp->port&VX_PE) + if ((tp->t_flags&(EVENP|ODDP)) == EVENP || + (tp->t_flags&(EVENP|ODDP)) == ODDP) continue; - if(!(((struct silo *)sp)->port&FERROR)) - break; - case FERROR: - if(tp->t_flags & RAW) c = 0; - else c = tp->t_intrc; + if (sp->port&VX_FE) { + /* + * At framing error (break) generate + * a null (in raw mode, for getty), or a + * interrupt (in cooked/cbreak mode). + */ + if (tp->t_flags&RAW) + c = 0; + else + c = tp->t_intrc; } (*linesw[tp->t_line].l_rint)(c, tp); } - *savsilo = 0; - return(1); + *osp = 0; + return (1); } /* - * stty/gtty for VX + * Ioctl for VX. */ vxioctl(dev, cmd, data, flag) -int dev; /* major, minor device numbers */ -int cmd; /* command */ -caddr_t data; -int flag; + dev_t dev; + caddr_t data; { - register struct tty *tp; - register error; + register struct tty *tp; + int error; - tp = &vx_tty[minor(dev) & 0377]; + tp = &vx_tty[minor(dev)]; error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag); if (error == 0) - return error; - if((error = ttioctl(tp, cmd, data, flag)) >= 0) - { - if (cmd==TIOCSETP||cmd==TIOCSETN) + return (error); + error = ttioctl(tp, cmd, data, flag); + if (error >= 0) { + if (cmd == TIOCSETP || cmd == TIOCSETN) vxparam(dev); - return error; - } else - return ENOTTY; + return (error); + } + return (ENOTTY); } - vxparam(dev) -dev_t dev; + dev_t dev; { + vxcparam(dev, 1); } @@ -339,31 +358,29 @@ dev_t dev; * registers. */ vxcparam(dev, wait) -dev_t dev; /* major, minor device numbers */ -int wait; /* nonzero if we should wait for finish */ + dev_t dev; + int wait; { - register struct tty *tp; - register struct vcx *xp; - register struct vxcmd *cp; - register s; + register struct tty *tp; + register struct vx_softc *vs; + register struct vxcmd *cp; + int s; - tp = &vx_tty[minor(dev)]; /* pointer to tty structure for port */ - xp = (struct vcx *)tp->t_addr; /* pointer to VIOCX info/cmd buffer */ - cp = vobtain(xp); + tp = &vx_tty[minor(dev)]; + vs = (struct vx_softc *)tp->t_addr; + cp = vobtain(vs); s = spl8(); - cp->cmd = LPARAX; /* set command to "load parameters" */ + cp->cmd = VXC_LPARAX; /* set command to "load parameters" */ cp->par[1] = minor(dev)&017; /* port number */ - - cp->par[2] = (tp->t_flags&RAW)? 0 : tp->t_startc; /* XON char */ - cp->par[3] = (tp->t_flags&RAW)? 0 : tp->t_stopc; /* XOFF char */ - - if(tp->t_flags&(RAW|LITOUT) || - (tp->t_flags&(EVENP|ODDP)) == (EVENP|ODDP)) { + cp->par[2] = (tp->t_flags&RAW) ? 0 : tp->t_startc; /* XON char */ + cp->par[3] = (tp->t_flags&RAW) ? 0 : tp->t_stopc; /* XOFF char */ + if (tp->t_flags&(RAW|LITOUT) || + (tp->t_flags&(EVENP|ODDP)) == (EVENP|ODDP)) { cp->par[4] = 0xc0; /* 8 bits of data */ cp->par[7] = 0; /* no parity */ } else { cp->par[4] = 0x40; /* 7 bits of data */ - if((tp->t_flags&(EVENP|ODDP)) == ODDP) + if ((tp->t_flags&(EVENP|ODDP)) == ODDP) cp->par[7] = 1; /* odd parity */ else if((tp->t_flags&(EVENP|ODDP)) == EVENP) cp->par[7] = 3; /* even parity */ @@ -372,8 +389,7 @@ int wait; /* nonzero if we should wait for finish */ } cp->par[5] = 0x4; /* 1 stop bit */ cp->par[6] = tp->t_ospeed; - - if (vcmd(xp->v_nbr, (caddr_t)&cp->cmd) && wait) + if (vcmd(vs->vs_nbr, (caddr_t)&cp->cmd) && wait) sleep((caddr_t)cp,TTIPRI); splx(s); } @@ -383,112 +399,107 @@ int wait; /* nonzero if we should wait for finish */ * For transmission, restart output to any active port. * For all other commands, just clean up. */ -vxxint(n,cp) -register int n; /* VIOC number */ -register struct vxcmd *cp; /* command structure */ +vxxint(vx, cp) + register int vx; + register struct vxcmd *cp; { - register struct vxmit *vp, *pvp; - register struct tty *tp; - register struct vcx *xp; - register struct tty *hp; + register struct vxmit *vp, *pvp; + register struct tty *tp, *tp0; + register struct vx_softc *vs; + register struct tty *hp; - xp = &vcx[n]; - cp = (struct vxcmd *)( (long *)cp - 1); + vs = &vx_softc[vx]; + cp = (struct vxcmd *)((long *)cp-1); #if NVBSC > 0 - switch(cp->cmd) { - case MDMCTL1: case HUNTMD1: case LPARAX1: - vrelease(xp, cp); - wakeup(cp); + if (cp->cmd == VXC_MDMCTL1 || cp->cmd == VXC_HUNTMD1 || + cp->cmd == VXC_LPARAX1) { + vrelease(vs, cp); + wakeup((caddr_t)cp); return; } #endif - switch(cp->cmd&0xff00) { - case LIDENT: /* initialization complete */ - if (xp->v_state & V_RESETTING) { - vxfnreset(n,cp); - vinthandl(n,((V_BSY | RSPquals) << 8) | V_INTR); + switch (cp->cmd&0xff00) { + + case VXC_LIDENT: /* initialization complete */ + if (vs->vs_state == VXS_RESET) { + vxfnreset(vx, cp); + vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR); } cp->cmd++; return; - case XMITDTA: case XMITIMM: + + case VXC_XMITDTA: + case VXC_XMITIMM: break; - case LPARAX: + + case VXC_LPARAX: wakeup((caddr_t)cp); - default: /* MDMCTL or FDTATOX */ - vrelease(xp, cp); - if (xp->v_state & V_RESETTING) { - vinthandl(n,((V_BSY | RSPquals) << 8) | V_INTR); - } + /* fall thru... */ + default: /* VXC_MDMCTL or VXC_FDTATOX */ + vrelease(vs, cp); + if (vs->vs_state == VXS_RESET) + vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR); return; } - for(vp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizvxmit); - vp >= (struct vxmit *)cp->par; - vp = (struct vxmit *) ((char *)vp - sizvxmit) ) - { - tp = &vx_tty[(vp->line & 017)+n*16]; -/* cjk buffer bug */ + tp0 = &vx_tty[vx*16]; + vp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit)); + for (; vp >= (struct vxmit *)cp->par; vp--) { + tp = tp0 + (vp->line & 017); #if NVBSC > 0 - /* bsc change */ if (tp->t_line == LDISP) { vrelease(xp, cp); - bsctxd((vp->line & 017)); - return ; + bsctxd(vp->line & 017); + return; } - /* End of bsc change */ #endif -/* cjk */ pvp = vp; tp->t_state &= ~TS_BUSY; - if(tp->t_state & TS_FLUSH) { + if (tp->t_state & TS_FLUSH) { tp->t_state &= ~TS_FLUSH; - wakeup( (caddr_t)&tp->t_state ) ; - } - else + wakeup((caddr_t)&tp->t_state); + } else ndflush(&tp->t_outq, vp->bcount+1); } - xp->v_xmtcnt--; - vrelease(xp,cp); - if(xp->v_vers == V_NEW) { + vs->vs_xmtcnt--; + vrelease(vs, cp); + if (vs->vs_vers == VXV_NEW) { vp = pvp; - xp->v_actport[(vp->line & 017) - xp->v_loport] |= 1 ; - if(vxstart(tp) && (cp = nextcmd(xp)) != NULL) - { - xp->v_xmtcnt++; - vcmd(n, (caddr_t)&cp->cmd); - return ; + vs->vs_active |= 1 << ((vp->line & 017) - vs->vs_loport); + if (vxstart(tp) && (cp = nextcmd(vs)) != NULL) { + vs->vs_xmtcnt++; + vcmd(vx, (caddr_t)&cp->cmd); + return; } - xp->v_actport[(vp->line & 017) - xp->v_loport] = 0 ; - return ; - } - xp->v_actflg = 1; - hp = &vx_tty[xp->v_hiport+n*16]; - for(tp = &vx_tty[xp->v_loport+n*16];tp <= hp;tp++) - if(vxstart(tp) && (cp = nextcmd(xp)) != NULL) - { - xp->v_xmtcnt++; - vcmd(n, (caddr_t)&cp->cmd); + vs->vs_active &= ~(1 << ((vp->line & 017) - vs->vs_loport)); + } else { + vs->vs_active = 1; + tp0 = &vx_tty[vx*16 + vs->vs_hiport]; + for(tp = &vx_tty[vx*16 + vs->vs_loport]; tp <= tp0; tp++) + if (vxstart(tp) && (cp = nextcmd(vs)) != NULL) { + vs->vs_xmtcnt++; + vcmd(vx, (caddr_t)&cp->cmd); + } + if ((cp = nextcmd(vs)) != NULL) { /* command to send? */ + vs->vs_xmtcnt++; + vcmd(vx, (caddr_t)&cp->cmd); } - if( (cp = nextcmd(xp)) != NULL ) /* command to send ? */ - { - xp->v_xmtcnt++; - vcmd(n, (caddr_t)&cp->cmd); + vs->vs_active = 0; } - xp->v_actflg = 0; } /* * Force out partial XMIT command after timeout */ -vxforce(xp) -register struct vcx *xp; +vxforce(vs) + register struct vx_softc *vs; { - register struct vxcmd *cp; - register int s; + register struct vxcmd *cp; + int s; s = spl8(); - if((cp = nextcmd(xp)) != NULL) { - xp->v_xmtcnt++; - vcmd(xp->v_nbr, (caddr_t)&cp->cmd); + if ((cp = nextcmd(vs)) != NULL) { + vs->vs_xmtcnt++; + vcmd(vs->vs_nbr, (caddr_t)&cp->cmd); } splx(s); } @@ -497,19 +508,19 @@ register struct vcx *xp; * Start (restart) transmission on the given VX line. */ vxstart(tp) -register struct tty *tp; + register struct tty *tp; { register short n; - register struct vcx *xp; + register struct vx_softc *vs; register char *outb; register full = 0; int k, s, port; s = spl8(); port = minor(tp->t_dev) & 017; - xp = (struct vcx *)tp->t_addr; - if (!(tp->t_state&(TS_TIMEOUT|TS_BUSY|TS_TTSTOP))) { - if (tp->t_outq.c_cc<=TTLOWAT(tp)) { + vs = (struct vx_softc *)tp->t_addr; + if ((tp->t_state&(TS_TIMEOUT|TS_BUSY|TS_TTSTOP)) == 0) { + if (tp->t_outq.c_cc <= TTLOWAT(tp)) { if (tp->t_state&TS_ASLEEP) { tp->t_state &= ~TS_ASLEEP; wakeup((caddr_t)&tp->t_outq); @@ -520,234 +531,200 @@ register struct tty *tp; tp->t_state &= ~TS_WCOLL; } } - if(tp->t_outq.c_cc == 0) { + if (tp->t_outq.c_cc == 0) { splx(s); - return(0); + return (0); } scope_out(3); - if(!(tp->t_flags&(RAW|LITOUT))) + if ((tp->t_flags&(RAW|LITOUT)) == 0) full = 0200; - if((n = ndqb(&tp->t_outq, full)) == 0) { - if(full) { + if ((n = ndqb(&tp->t_outq, full)) == 0) { + if (full) { n = getc(&tp->t_outq); - timeout(ttrstrt, (caddr_t)tp, (n&0177) +6); + timeout(ttrstrt, (caddr_t)tp, (n&0177)+6); tp->t_state |= TS_TIMEOUT; full = 0; } } else { outb = (char *)tp->t_outq.c_cf; tp->t_state |= TS_BUSY; - if(xp->v_vers == V_NEW) - k = xp->v_actport[port - xp->v_loport] ; + if (vs->vs_vers == VXV_NEW) + k = vs->vs_active & (1 << (port-vs->vs_loport)); else - k = xp->v_actflg ; - - full = vsetq(xp, port, outb, n); - - if( (k&1) == 0 ) { /* not called from vxxint */ - if(full || xp->v_xmtcnt == 0) { - outb = (char *)(&nextcmd(xp)->cmd); - xp->v_xmtcnt++; - vcmd(xp->v_nbr, outb ); + k = vs->vs_active; + full = vsetq(vs, port, outb, n); + if ((k&1) == 0) { /* not called from vxxint */ + if (full || vs->vs_xmtcnt == 0) { + outb = (char *)(&nextcmd(vs)->cmd); + vs->vs_xmtcnt++; + vcmd(vs->vs_nbr, outb); } else - timeout(vxforce,(caddr_t)xp,3); + timeout(vxforce, (caddr_t)vs, 3); } } } splx(s); - return(full); /* indicate if max commands or not */ + return (full); /* indicate if max commands or not */ } /* * Stop output on a line. */ vxstop(tp) -register struct tty *tp; + register struct tty *tp; { - register s; + int s; s = spl8(); - if (tp->t_state & TS_BUSY) { - if ((tp->t_state&TS_TTSTOP)==0) { + if (tp->t_state&TS_BUSY) + if ((tp->t_state&TS_TTSTOP) == 0) tp->t_state |= TS_FLUSH; - } - } splx(s); } +static int vxbbno = -1; /* * VIOCX Initialization. Makes free lists of command buffers. * Resets all viocx's. Issues a LIDENT command to each * viocx which establishes interrupt vectors and logical * port numbers */ -vxinit(i,wait) -register int i; -long wait; -{ - register struct vcx *xp; /* ptr to VIOC-X info/cmd buffer */ - register struct vblok *kp; /* pointer to VIOC-X control block */ - register struct vxcmd *cp; /* pointer to a command buffer */ - register char *resp; /* pointer to response buffer */ - register int j; +vxinit(vx, wait) + register int vx; + int wait; +{ + register struct vx_softc *vs; + register struct vxdevice *addr; + register struct vxcmd *cp; + register char *resp; + register int j; char type; -#if NVBSC > 0 - register struct bsc *bp; /* bsc change */ - extern struct bsc bsc[]; -#endif + vs = &vx_softc[vx]; + vs->vs_type = 0; /* viox-x by default */ + addr = (struct vxdevice *)(((struct vba_device *)vxinfo[vx])->ui_addr); + type = addr->v_ident; + vs->vs_vers = (type&VXT_NEW) ? VXV_NEW : VXV_OLD; + if (vs->vs_vers == VXV_NEW) + vs->vs_silosiz = addr->v_maxsilo; + switch (type) { + + case VXT_VIOCX: + case VXT_VIOCX|VXT_NEW: + /* set dcd for printer ports */ + for (j = 0;j < 16;j++) + if (addr->v_portyp[j] == 4) + addr->v_dcd |= 1 << j; + break; - kp = VBAS(i); /* get base adr of cntl blok for VIOC */ - - xp = &vcx[i]; /* index info/command buffers */ - type = kp->v_ident; - vxtype[i] = 0; /* Type is Viox-x */ - switch(type) { - case VIOCX: - { - xp->v_vers = V_OLD ; - /* set DCD for printer ports */ - for(j = 0;j < 16;j++) - if (kp->v_portyp[j] == 4 ) - kp->v_dcd |= 1 << j ; - } - break ; - case NWVIOCX: - { - xp->v_vers = V_NEW ; - xp->v_silosiz = kp->v_maxsilo ; - /* set DCD for printer ports */ - for(j = 0;j < 16;j++) - if (kp->v_portyp[j] == 4 ) - kp->v_dcd |= 1 << j ; - } - break ; - case PVIOCX: - xp->v_vers = V_OLD ; - break ; - case NPVIOCX: - xp->v_vers = V_NEW ; - xp->v_silosiz = kp->v_maxsilo ; - break ; + case VXT_PVIOCX: + case VXT_PVIOCX|VXT_NEW: + break; #if NVBSC > 0 - case VIOCB: /* old f/w, Bisync board */ - printf("%X: %x%x OLD VIOC-B, ", - (long)kp, (int)kp->v_ident, - (int)kp->v_fault); - xp->v_vers = V_OLD ; - /* save device specific info */ - for(bp = &bsc[0]; bp <= &bsc[NBSC]; bp++) - bp->b_devregs = (caddr_t)xp ; - printf("%d BSC Ports initialized.\n",NBSC); - break ; - - case NWVIOCB: /* new f/w, Bisync board */ - printf("%X: %x%x 16K VIOC-B, ", - (long)kp, (int)kp->v_ident, - (int)kp->v_fault); - xp->v_vers = V_NEW ; - xp->v_silosiz = kp->v_maxsilo ; - /* save device specific info */ - for(bp = &bsc[0]; bp <= &bsc[NBSC]; bp++) - bp->b_devregs = (caddr_t)xp ; - printf("%d BSC Ports initialized.\n",NBSC); - if(CBSIZE > kp->v_maxxmt) - printf("vxinit: Warning CBSIZE > maxxmt\n") ; - break ; + case VX_VIOCB: /* old f/w bisync */ + case VX_VIOCB|VXT_NEW: { /* new f/w bisync */ + register struct bsc *bp; + extern struct bsc bsc[]; + + printf("%X: %x%x %s VIOC-B, ", (long)addr, (int)addr->v_ident, + (int)addr->v_fault, vs->vs_vers == VXV_OLD ? "old" : "16k"); + for (bp = &bsc[0]; bp <= &bsc[NBSC]; bp++) + bp->b_devregs = (caddr_t)vs; + printf("%d BSC Ports initialized.\n", NBSC); + break; + if (vs->vs_vers == VXV_NEW && CBSIZE > addr->v_maxxmt) + printf("vxinit: Warning CBSIZE > maxxmt\n"); + break; #endif - case VBOPID: /* VIOC-BOP */ - vxbbno++; - vxtype[i] = 1; - vxbopno[i] = vxbbno; - printf("VIOC-BOP no. %d at %lx\n",vxbopno[i],VIOCBAS[i]); - default: - return ; /* Not a viocx type */ - } - xp->v_nbr = -1; /* no number for it yet */ - xp->v_maxcmd = xp->v_vers == V_NEW ? 24 : 4; + case VXT_VIOCBOP: /* VIOC-BOP */ + vs->vs_type = 1; + vs->vs_bop = ++vxbbno; + printf("VIOC-BOP no. %d at %x\n", vs->vs_bop, addr); - for(j=0; jvx_lst[j]; /* index a buffer */ - cp->c_fwd = &xp->vx_lst[j+1]; /* point to next buf */ + default: /* unknown viocx type */ + printf("vx%d: unknown type %x\n", vx, type); + return; + } + vs->vs_nbr = -1; + vs->vs_maxcmd = vs->vs_vers == VXV_NEW ? 24 : 4; + /* init all cmd buffers */ + for (j = 0; j < NVCXBUFS; j++) { + cp = &vs->vs_lst[j]; /* index a buffer */ + cp->c_fwd = &vs->vs_lst[j+1]; /* point to next buf */ } - xp->vx_avail = &xp->vx_lst[0]; /* set idx to 1st free buf */ + vs->vs_avail = &vs->vs_lst[0]; /* set idx to 1st free buf */ cp->c_fwd = (struct vxcmd *)0; /* mark last buf in free list */ - cp = vobtain(xp); /* grap the control block */ - cp->cmd = LIDENT; /* set command type */ - cp->par[0] = vxivec[i]; /* ack vector */ + cp = vobtain(vs); /* grab the control block */ + cp->cmd = VXC_LIDENT; /* set command type */ + cp->par[0] = vs->vs_ivec; /* ack vector */ cp->par[1] = cp->par[0]+1; /* cmd resp vector */ cp->par[3] = cp->par[0]+2; /* unsol intr vector */ - cp->par[4] = 15; /* max ports, no longer used */ - cp->par[5] = 0; /* set 1st port number */ - vcmd(i, (caddr_t)&cp->cmd); /* initialize the VIOC-X */ - - if (!wait) return; - for (j = 0; cp->cmd == LIDENT && j < 4000000; j++) + cp->par[4] = 15; /* max ports, no longer used */ + cp->par[5] = 0; /* set 1st port number */ + vcmd(vx, (caddr_t)&cp->cmd); /* initialize the VIOC-X */ + if (!wait) + return; + for (j = 0; cp->cmd == VXC_LIDENT && j < 4000000; j++) ; if (j >= 4000000) - printf("vx%d: didn't respond to LIDENT\n", i); + printf("vx%d: didn't respond to LIDENT\n", vx); /* calculate address of response buffer */ - resp = (char *)kp; - resp += kp->v_rspoff & 0x3FFF; - - if(resp[0] != 0 && (resp[0]&0177) != 3) /* did init work? */ - { - vrelease(xp,cp); /* init failed */ - return; /* try next VIOC-X */ + resp = (char *)addr + (addr->v_rspoff&0x3fff); + if (resp[0] != 0 && (resp[0]&0177) != 3) { /* did init work? */ + vrelease(vs, cp); + return; } - - xp->v_loport = cp->par[5]; /* save low port number */ - xp->v_hiport = cp->par[7];/* VIOC knows high port numbr */ - vrelease(xp,cp); /* done with this control block */ - xp->v_nbr = i; /* assign VIOC-X board number */ + vs->vs_loport = cp->par[5]; + vs->vs_hiport = cp->par[7]; + vrelease(vs, cp); + vs->vs_nbr = vx; /* assign VIOC-X board number */ } /* * Obtain a command buffer */ -struct vxcmd * -vobtain(xp) -register struct vcx *xp; +struct vxcmd * +vobtain(vs) + register struct vx_softc *vs; { - - register struct vxcmd *p; - register s; + register struct vxcmd *p; + int s; s = spl8(); - p = xp->vx_avail; - if(p == (struct vxcmd *)0) { + p = vs->vs_avail; + if (p == (struct vxcmd *)0) { #ifdef VX_DEBUG - if (vxintr4 & VXNOBUF) vxintr4 &= ~VXNOBUF; + if (vxintr4&VXNOBUF) + vxintr4 &= ~VXNOBUF; #endif - vpanic("vx: no buffs"); - vxstreset(xp - vcx); + printf("vx%d: no buffers\n", vs - vx_softc); + vxstreset(vs - vx_softc); splx(s); - return(vobtain(xp)); + return (vobtain(vs)); } - xp->vx_avail = (xp->vx_avail)->c_fwd; + vs->vs_avail = vs->vs_avail->c_fwd; splx(s); - return( (struct vxcmd *)p); + return ((struct vxcmd *)p); } /* * Release a command buffer */ -vrelease(xp,cp) -register struct vcx *xp; -register struct vxcmd *cp; +vrelease(vs, cp) + register struct vx_softc *vs; + register struct vxcmd *cp; { - - register s; + int s; #ifdef VX_DEBUG - if (vxintr4 & VXNOBUF) return; + if (vxintr4&VXNOBUF) + return; #endif s = spl8(); - cp->c_fwd = xp->vx_avail; - xp->vx_avail = cp; + cp->c_fwd = vs->vs_avail; + vs->vs_avail = cp; splx(s); } @@ -755,54 +732,51 @@ register struct vxcmd *cp; * vxcmd - * */ -struct vxcmd * -nextcmd(xp) -register struct vcx *xp; +struct vxcmd * +nextcmd(vs) + register struct vx_softc *vs; { - register struct vxcmd *cp; - register int s; + register struct vxcmd *cp; + int s; s = spl8(); - cp = xp->vx_build; - xp->vx_build = (struct vxcmd *)0; + cp = vs->vs_build; + vs->vs_build = (struct vxcmd *)0; splx(s); - return(cp); + return (cp); } /* * assemble transmits into a multiple command. * up to 8 transmits to 8 lines can be assembled together */ -vsetq(xp ,d ,addr, n) -register struct vcx *xp; -caddr_t addr; +vsetq(vs ,d ,addr, n) + register struct vx_softc *vs; + caddr_t addr; { - - register struct vxcmd *cp; - register struct vxmit *mp; - register char *p; + register struct vxcmd *cp; + register struct vxmit *mp; + register char *p; register i; - cp = xp->vx_build; - if(cp == (struct vxcmd *)0) { - cp = vobtain(xp); - xp->vx_build = cp; - cp->cmd = XMITDTA; + cp = vs->vs_build; + if (cp == (struct vxcmd *)0) { + cp = vobtain(vs); + vs->vs_build = cp; + cp->cmd = VXC_XMITDTA; } else { - if((cp->cmd & 07) == 07) { - vpanic("vx: vsetq overflow"); - vxstreset(xp->v_nbr); - return(0); + if ((cp->cmd & 07) == 07) { + printf("vx%d: setq overflow\n", vs-vx_softc); + vxstreset(vs->vs_nbr); + return (0); } cp->cmd++; } - - mp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizvxmit); + mp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit)); mp->bcount = n-1; - mp->line = d; - if((xp->v_vers == V_NEW) && (n <= 6)) { - cp->cmd = XMITIMM ; + if (vs->vs_vers == VXV_NEW && n <= 6) { + cp->cmd = VXC_XMITIMM; p = addr; /* bcopy(addr, &(char *)mp->ostream, n) ; */ } else { @@ -812,11 +786,600 @@ caddr_t addr; n = sizeof addr; /* mp->ostream = addr ; */ } - for(i=0; iostream[i] = *p++; - if(xp->v_vers == V_NEW) - return(1) ; - else - return((cp->cmd&07) == 7) ; /* Indicate if full */ + if (vs->vs_vers == VXV_NEW) + return (vs->vs_vers == VXV_NEW ? 1 : (cp->cmd&07) == 7); +} + +/* + * Write a command out to the VIOC + */ +vcmd(vx, cmdad) + register int vx; + register caddr_t cmdad; +{ + register struct vcmds *cp; + register struct vx_softc *vs; + int s; + + s = spl8(); + vs = &vx_softc[vx]; + if (vs->vs_state == VXS_RESET && cmdad != NULL) { + /* + * When the vioc is resetting, don't process + * anything other than LIDENT commands. + */ + register struct vxcmd *cmdp = (struct vxcmd *) + ((char *)cmdad - sizeof (cmdp->c_fwd)); + + if (cmdp->cmd != VXC_LIDENT) { + vrelease(vs, cmdp); + return (0); + } + } + cp = &vs->vs_cmds; + if (cmdad != (caddr_t)0) { + cp->cmdbuf[cp->v_fill] = cmdad; + if (++cp->v_fill >= VC_CMDBUFL) + cp->v_fill = 0; + if (cp->v_fill == cp->v_empty) { + printf("vx%d: cmd q overflow\n", vx); + vxstreset(vx); + splx(s); + return (0); + } + cp->v_cmdsem++; + } + if (cp->v_cmdsem && cp->v_curcnt < vs->vs_maxcmd) { + cp->v_cmdsem--; + cp->v_curcnt++; + vinthandl(vx, ((V_BSY|CMDquals) << 8)|V_INTR); + } + splx(s); + return (1); +} + +/* + * VIOC acknowledge interrupt. The VIOC has received the new + * command. If no errors, the new command becomes one of 16 (max) + * current commands being executed. + */ +vackint(vx) + register vx; +{ + register struct vxdevice *vp; + register struct vcmds *cp; + struct vx_softc *vs; + int s; + + scope_out(5); + vs = &vx_softc[vx]; + if (vs->vs_type) { /* Its a BOP */ +#ifdef SNA_DEBUG + extern vbrall(); + + if (snadebug & SVIOC) + printf("vx%d: vack interrupt from BOP\n", vx); + vbrall(vx); /* Int. from BOP, port 0 */ +#endif + return; + } + s = spl8(); + vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; + cp = &vs->vs_cmds; + if (vp->v_vcid & V_ERR) { + register char *resp; + register i; + printf("vx%d INTR ERR type %x v_dcd %x\n", vx, + vp->v_vcid & 07, vp->v_dcd & 0xff); + /* resp = (char *)vp + (vp->v_rspoff & 0x7FFF); */ + resp = (char *)vs->vs_mricmd; + for (i = 0; i < 16; i++) + printf("%x ", resp[i]&0xff); + printf("\n"); + splx(s); + vxstreset(vx); + return; + } + if ((vp->v_hdwre&017) == CMDquals) { +#ifdef VX_DEBUG + if (vxintr4 & VXERR4) { /* causes VIOC INTR ERR 4 */ + register struct vxcmd *cp1; + register struct vxcmd *cp0 = (struct vxcmd *) + ((long)cp->cmdbuf[cp->v_empty] - 4); + + if (cp0->cmd == VXC_XMITDTA || cp0->cmd == VXC_XMITIMM) { + cp1 = vobtain(vs); + *cp1 = *cp0; + vxintr4 &= ~VXERR4; + (void) vcmd(vx, &cp1->cmd); + } + } +#endif + cp->v_curcmd[vp->v_vcid & VCMDLEN-1] = cp->cmdbuf[cp->v_empty]; + if (++cp->v_empty >= VC_CMDBUFL) + cp->v_empty = 0; + } + if (++cp->v_itrempt >= VC_IQLEN) + cp->v_itrempt = 0; + vintempt(vx); + splx(s); + (void) vcmd(vx, (caddr_t)0); /* queue next cmd, if any */ +} + +/* + * Command Response interrupt. The Vioc has completed + * a command. The command may now be returned to + * the appropriate device driver. + */ +vcmdrsp(vx) + register vx; +{ + register struct vxdevice *vp; + register struct vcmds *cp; + register caddr_t cmd; + register struct vx_softc *vs; + register char *resp; + register k; + register int s; + + scope_out(6); + vs = &vx_softc[vx]; + if (vs->vs_type) { /* Its a BOP */ + printf("vx%d: vcmdrsp interrupt\n", vx); + return; + } + s = spl8(); + vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; + cp = &vs->vs_cmds; + resp = (char *)vp + (vp->v_rspoff&0x7fff); + if (((k = resp[1])&V_UNBSY) == 0) { + printf("vx%d: cmdresp debug\n", vx); + splx(s); + vxstreset(vx); + return; + } + k &= VCMDLEN-1; + cmd = cp->v_curcmd[k]; + cp->v_curcmd[k] = (caddr_t)0; + cp->v_curcnt--; + k = *((short *)&resp[4]); /* cmd operation code */ + if ((k&0xff00) == VXC_LIDENT) /* want hiport number */ + for (k = 0; k < VRESPLEN; k++) + cmd[k] = resp[k+4]; + resp[1] = 0; + vxxint(vx, (struct vxcmd *)cmd); + if (vs->vs_state == VXS_READY) + vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR); + splx(s); +} + +/* + * Unsolicited interrupt. + */ +vunsol(vx) + register vx; +{ + register struct vxdevice *vp; + struct vx_softc *vs; + int s; + + scope_out(1); + vs = &vx_softc[vx]; + if (vs->vs_type) { /* Its a BOP */ + printf("vx%d: vunsol from BOP\n", vx); + return; + } + s = spl8(); + vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; + if (vp->v_uqual&V_UNBSY) { + vxrint(vx); + vinthandl(vx, ((V_BSY|UNSquals) << 8)|V_INTR); +#ifdef notdef + } else { + printf("vx%d: unsolicited interrupt error\n", vx); + splx(s); + vxstreset(vx); +#endif + } + splx(s); +} + +/* + * Enqueue an interrupt + */ +vinthandl(vx, item) + register int vx; + register item; +{ + register struct vcmds *cp; + int empty; + + cp = &vx_softc[vx].vs_cmds; + empty = cp->v_itrfill == cp->v_itrempt; + cp->v_itrqueu[cp->v_itrfill] = item; + if (++cp->v_itrfill >= VC_IQLEN) + cp->v_itrfill = 0; + if (cp->v_itrfill == cp->v_itrempt) { + printf("vx%d: interrupt q overflow\n", vx); + vxstreset(vx); + } else if (empty) + vintempt(vx); +} + +vintempt(vx) + register int vx; +{ + register struct vcmds *cp; + register struct vxdevice *vp; + register short item; + register short *intr; + + vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; + if (vp->v_vioc&V_BSY) + return; + cp = &vx_softc[vx].vs_cmds; + if (cp->v_itrempt == cp->v_itrfill) + return; + item = cp->v_itrqueu[cp->v_itrempt]; + intr = (short *)&vp->v_vioc; + switch ((item >> 8)&03) { + + case CMDquals: { /* command */ + int phys; + + if (cp->v_empty == cp->v_fill || vp->v_vcbsy&V_BSY) + break; + vx_softc[vx].vs_mricmd = (caddr_t)cp->cmdbuf[cp->v_empty]; + phys = vtoph((struct proc *)0, + (unsigned)cp->cmdbuf[cp->v_empty]); + vp->v_vcp[0] = ((short *)&phys)[0]; + vp->v_vcp[1] = ((short *)&phys)[1]; + vp->v_vcbsy = V_BSY; + *intr = item; + scope_out(4); + break; + } + + case RSPquals: /* command response */ + *intr = item; + scope_out(7); + break; + + case UNSquals: /* unsolicited interrupt */ + vp->v_uqual = 0; + *intr = item; + scope_out(2); + break; + } +} + +/* + * Start a reset on a vioc after error (hopefully) + */ +vxstreset(vx) + register vx; +{ + register struct vx_softc *vs; + register struct vxdevice *vp; + register struct vxcmd *cp; + register int j; + extern int vxinreset(); + int s; + + s = spl8() ; + vs = &vx_softc[vx]; + if (vs->vs_state == VXS_RESET) { /* avoid recursion */ + splx(s); + return; + } + vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; + /* + * Zero out the vioc structures, mark the vioc as being + * reset, reinitialize the free command list, reset the vioc + * and start a timer to check on the progress of the reset. + */ + bzero((caddr_t)vs, (unsigned)sizeof (*vs)); + + /* + * Setting VXS_RESET prevents others from issuing + * commands while allowing currently queued commands to + * be passed to the VIOC. + */ + vs->vs_state = VXS_RESET; + /* init all cmd buffers */ + for (j = 0; j < NVCXBUFS; j++) { + cp = &vs->vs_lst[j]; /* index a buffer */ + cp->c_fwd = &vs->vs_lst[j+1]; /* point to next buf */ + } + vs->vs_avail = &vs->vs_lst[0]; /* set idx to 1st free buf */ + cp->c_fwd = (struct vxcmd *)0; /* mark last buf in free list */ + printf("vx%d: reset...", vx); + vp->v_fault = 0; + vp->v_vioc = V_BSY; + vp->v_hdwre = V_RESET; /* reset interrupt */ + timeout(vxinreset, (caddr_t)vx, hz*5); + splx(s); +} + +/* continue processing a reset on a vioc after an error (hopefully) */ +vxinreset(vx) + int vx; +{ + register struct vxdevice *vp; + int s = spl8(); + + vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; + /* + * See if the vioc has reset. + */ + if (vp->v_fault != VXF_READY) { + printf("failed\n"); + splx(s); + return; + } + /* + * Send a LIDENT to the vioc and mess with carrier flags + * on parallel printer ports. + */ + vxinit(vx, (long)0); + splx(s); +} + +/* + * Restore modem control, parameters and restart output. + * Since the vioc can handle no more then 24 commands at a time + * and we could generate as many as 48 commands, we must do this in + * phases, issuing no more then 16 commands at a time. + */ +/* finish the reset on the vioc after an error (hopefully) */ +vxfnreset(vx, cp) + register int vx; + register struct vxcmd *cp; +{ + register struct vx_softc *vs; + register struct vxdevice *vp ; + register struct tty *tp, *tp0; + register int i; +#ifdef notdef + register int on; +#endif + extern int vxrestart(); + int s = spl8(); + + vs = &vx_softc[vx]; + vs->vs_loport = cp->par[5]; + vs->vs_hiport = cp->par[7]; + vrelease(vs, cp); + vs->vs_nbr = vx; /* assign VIOC-X board number */ + vs->vs_state = VXS_READY; + + vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; + vp->v_vcid = 0; + + /* + * Restore modem information and control. + */ + tp0 = &vx_tty[vx*16]; + for (i = vs->vs_loport; i <= vs->vs_hiport; i++) { + tp = tp0 + i; + if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) { + tp->t_state &= ~TS_CARR_ON; + vcmodem(tp->t_dev, VMOD_ON); + if (tp->t_state&TS_CARR_ON) + wakeup((caddr_t)&tp->t_canq); + else if (tp->t_state & TS_ISOPEN) { + ttyflush(tp, FREAD|FWRITE); + if (tp->t_state&TS_FLUSH) + wakeup((caddr_t)&tp->t_state); + if ((tp->t_flags&NOHANG) == 0) { + gsignal(tp->t_pgrp, SIGHUP); + gsignal(tp->t_pgrp, SIGCONT); + } + } + } + /* + * If carrier has changed while we were resetting, + * take appropriate action. + */ +#ifdef notdef + on = vp->v_dcd & 1<t_state&TS_CARR_ON) == 0) { + tp->t_state |= TS_CARR_ON; + wakeup((caddr_t)&tp->t_canq); + } else if (!on && tp->t_state&TS_CARR_ON) { + tp->t_state &= ~TS_CARR_ON; + if (tp->t_state & TS_ISOPEN) { + ttyflush(tp, FREAD|FWRITE); + if (tp->t_state&TS_FLUSH) + wakeup((caddr_t)&tp->t_state); + if ((tp->t_flags&NOHANG) == 0) { + gsignal(tp->t_pgrp, SIGHUP); + gsignal(tp->t_pgrp, SIGCONT); + } + } + } +#endif + } + vs->vs_state = VXS_RESET; + timeout(vxrestart, (caddr_t)vx, hz); + splx(s); +} + +/* + * Restore a particular aspect of the VIOC. + */ +vxrestart(vx) + int vx; +{ + register struct tty *tp, *tp0; + register struct vx_softc *vs; + register int i, cnt; + int s = spl8(); + + cnt = vx >> 8; + vx &= 0xff; + vs = &vx_softc[vx]; + vs->vs_state = VXS_READY; + tp0 = &vx_tty[vx*16]; + for (i = vs->vs_loport; i <= vs->vs_hiport; i++) { + tp = tp0 + i; + if (cnt != 0) { + tp->t_state &= ~(TS_BUSY|TS_TIMEOUT); + if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) + vxstart(tp); /* restart pending output */ + } else { + if (tp->t_state&(TS_WOPEN|TS_ISOPEN)) + vxcparam(tp->t_dev, 0); + } + } + if (cnt == 0) { + vs->vs_state = VXS_RESET; + timeout(vxrestart, (caddr_t)(vx + 1*256), hz); + } else + printf("done\n"); + splx(s); +} + +vxreset(dev) + dev_t dev; +{ + + vxstreset(minor(dev) >> 4); /* completes asynchronously */ +} + +vxfreset(vx) + register int vx; +{ + struct vba_device *vi; + + if ((unsigned)vx > NVX || (vi = vxinfo[vx]) == 0 || vi->ui_addr == 0) + return (ENODEV); + vx_softc[vx].vs_state = VXS_READY; + vxstreset(vx); + return (0); /* completes asynchronously */ +} + +vcmodem(dev, flag) + dev_t dev; +{ + struct tty *tp; + register struct vxcmd *cp; + register struct vx_softc *vs; + register struct vxdevice *kp; + register port; + int unit; + + unit = minor(dev); + tp = &vx_tty[unit]; + vs = (struct vx_softc *)tp->t_addr; + cp = vobtain(vs); + kp = (struct vxdevice *)((struct vba_device *)vxinfo[vs->vs_nbr])->ui_addr; + + port = unit & 017; + /* + * Issue MODEM command + */ + cp->cmd = VXC_MDMCTL; + cp->par[0] = (flag == VMOD_ON) ? V_ENAB : V_DISAB; + cp->par[1] = port; + vcmd(vs->vs_nbr, (caddr_t)&cp->cmd); + port -= vs->vs_loport; + if ((kp->v_dcd >> port) & 1) { + if (flag == VMOD_ON) + tp->t_state |= TS_CARR_ON; + return (1); + } + return (0); +} + +/* + * VCMINTR called when an unsolicited interrup occurs signaling + * some change of modem control state. + */ +vcmintr(vx) + register vx; +{ + register struct vxdevice *kp; + register struct tty *tp; + register port; + + kp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; + port = kp->v_usdata[0] & 017; + tp = &vx_tty[vx*16+port]; +#if NVBSC > 0 + /* + * Check for change in DSR for BISYNC port. + */ + if (bscport[vx*16+port]&BISYNC) { + if (kp->v_ustat&DSR_CHG) { + register struct vx_softc *xp; + register struct bsc *bp; + extern struct bsc bsc[]; + + vs = (struct vx_softc *)tp->t_addr; + bp = &bsc[minor(tp->t_dev)] ; + bp->b_hlflgs &= ~BSC_DSR ; + if (kp->v_ustat & DSR_ON) + bp->b_hlflgs |= BSC_DSR ; + printf("BSC DSR Chg: %x\n", kp->v_ustat&DSR_CHG);/*XXX*/ + } + return; + } +#endif + if ((kp->v_ustat&DCD_ON) && ((tp->t_state&TS_CARR_ON) == 0)) { + tp->t_state |= TS_CARR_ON; + wakeup((caddr_t)&tp->t_canq); + return; + } + if ((kp->v_ustat&DCD_OFF) && (tp->t_state&TS_CARR_ON)) { + tp->t_state &= ~TS_CARR_ON; + if (tp->t_state&TS_ISOPEN) { + register struct vx_softc *vs; + register struct vcmds *cp; + register struct vxcmd *cmdp; + + ttyflush(tp, FREAD|FWRITE); + /* clear all pending trnansmits */ + vs = &vx_softc[vx]; + if (tp->t_state&(TS_BUSY|TS_FLUSH) && + vs->vs_vers == VXV_NEW) { + int i, cmdfound = 0; + + cp = &vs->vs_cmds; + for (i = cp->v_empty; i != cp->v_fill; ) { + cmdp = (struct vxcmd *)((long *)cp->cmdbuf[i]-1); + if ((cmdp->cmd == VXC_XMITDTA || + cmdp->cmd == VXC_XMITIMM) && + ((struct vxmit *)cmdp->par)->line == port) { + cmdfound++; + cmdp->cmd = VXC_FDTATOX; + cmdp->par[1] = port; + } + if (++i >= VC_CMDBUFL) + i = 0; + } + if (cmdfound) + tp->t_state &= ~(TS_BUSY|TS_FLUSH); + /* cmd is already in vioc, have to flush it */ + else { + cmdp = vobtain(vs); + cmdp->cmd = VXC_FDTATOX; + cmdp->par[1] = port; + vcmd(vx, (caddr_t)&cmdp->cmd); + } + } + if ((tp->t_flags&NOHANG) == 0) { + gsignal(tp->t_pgrp, SIGHUP); + gsignal(tp->t_pgrp, SIGCONT); + } + } + return; + } + if ((kp->v_ustat&BRK_CHR) && (tp->t_state&TS_ISOPEN)) { + (*linesw[tp->t_line].l_rint)(tp->t_intrc & 0377, tp); + return; + } } #endif