1*25675Ssam /* vx.c 1.2 86/01/05 */ 224003Ssam 324003Ssam #include "vx.h" 424003Ssam #if NVX > 0 524003Ssam /* 624003Ssam * VIOC-X driver 724003Ssam */ 8*25675Ssam #include "../tahoe/pte.h" 924003Ssam 1024003Ssam #include "../h/param.h" 1124003Ssam #include "../h/ioctl.h" 1224003Ssam #include "../h/tty.h" 1324003Ssam #include "../h/dir.h" 1424003Ssam #include "../h/user.h" 1524003Ssam #include "../h/map.h" 1624003Ssam #include "../h/buf.h" 1724003Ssam #include "../h/conf.h" 1824003Ssam #include "../h/file.h" 1924003Ssam #include "../h/uio.h" 20*25675Ssam #include "../h/proc.h" 21*25675Ssam #include "../h/vm.h" 22*25675Ssam 23*25675Ssam #include "../tahoevba/vbavar.h" 24*25675Ssam #include "../tahoevba/vioc.h" 2524003Ssam #ifdef VXPERF 26*25675Ssam #include "../tahoevba/scope.h" 2724003Ssam #endif VXPERF 2824003Ssam #include "vbsc.h" 2924003Ssam #if NVBSC > 0 3024003Ssam #include "../bsc/bscio.h" 3124003Ssam #include "../bsc/bsc.h" 3224003Ssam char bscport[NVXPORTS]; 3324003Ssam #endif 3424003Ssam 3524003Ssam #ifdef BSC_DEBUG 3624003Ssam #include "../bsc/bscdebug.h" 3724003Ssam #endif 3824003Ssam 3924003Ssam #ifdef VX_DEBUG 4024003Ssam long vxintr4 = 0; 4124003Ssam long vxdebug = 0; 4224003Ssam #include "../vba/vxdebug.h" 4324003Ssam #endif 4424003Ssam 4524003Ssam #define RSPquals 1 4624003Ssam 4724003Ssam struct vcx vcx[NVIOCX] ; 4824003Ssam struct tty vx_tty[NVXPORTS]; 4924003Ssam extern struct vcmds v_cmds[]; 5024003Ssam extern long reinit; 5124003Ssam 5224003Ssam int vxstart() ; 5324003Ssam int ttrstrt() ; 5424003Ssam struct vxcmd *vobtain() ; 5524003Ssam struct vxcmd *nextcmd() ; 5624003Ssam 5724003Ssam /* 5824003Ssam * Driver information for auto-configuration stuff. 5924003Ssam * (not tested and probably should be changed) 6024003Ssam */ 6124003Ssam int vxprobe(), vxattach(), vxrint(); 6224003Ssam struct vba_device *vxinfo[NVIOCX]; 6324003Ssam long vxstd[] = { 0 }; 6424003Ssam struct vba_driver vxdriver = 65*25675Ssam { vxprobe, 0, vxattach, 0, vxstd, "vx", vxinfo }; 6624003Ssam 6724003Ssam char vxtype[NVIOCX]; /* 0: viox-x/vioc-b; 1: vioc-bop */ 6824003Ssam char vxbbno = -1; 6924003Ssam char vxbopno[NVIOCX]; /* BOP board no. if indicated by vxtype[] */ 7024003Ssam extern vbrall(); 7124003Ssam 7224003Ssam 7324003Ssam vxprobe(reg) 7424003Ssam caddr_t reg; 7524003Ssam { 7624003Ssam register int br, cvec; 7724003Ssam register struct vblok *vp = (struct vblok *)reg; 7824003Ssam 7924003Ssam #ifdef lint 8024003Ssam br = 0; cvec = br; br = cvec; 81*25675Ssam vackint(0); vunsol(0); vcmdrsp(0); vxfreset(0); 8224003Ssam #endif 8324003Ssam 84*25675Ssam if (badaddr((caddr_t)vp, 1)) 85*25675Ssam return (0); 86*25675Ssam vp->v_fault = 0; 87*25675Ssam vp->v_vioc = V_BSY; 88*25675Ssam vp->v_hdwre = V_RESET; /* reset interrupt */ 8924003Ssam DELAY(4000000); 90*25675Ssam if (vp->v_fault != VREADY) 91*25675Ssam return (0); 92*25675Ssam return (sizeof (*vp)); 9324003Ssam } 9424003Ssam 9524003Ssam vxattach(ui) 9624003Ssam register struct vba_device *ui; 9724003Ssam { 98*25675Ssam 9924003Ssam VIOCBAS[ui->ui_unit] = ui->ui_addr; 100*25675Ssam vxinit(ui->ui_unit,(long)1); 10124003Ssam } 10224003Ssam 10324003Ssam /* 10424003Ssam * Open a VX line. 10524003Ssam */ 106*25675Ssam /*ARGSUSED*/ 10724003Ssam vxopen(dev, flag) 10824003Ssam { 10924003Ssam register struct tty *tp; /* pointer to tty struct for port */ 11024003Ssam register struct vcx *xp; /* pointer to VIOC-X info/cmd buffer */ 11124003Ssam register d; /* minor device number */ 11224003Ssam register long jj; 11324003Ssam 11424003Ssam 11524003Ssam d = minor(dev); /* get minor device number */ 11624003Ssam if (d >= NVXPORTS) /* validate minor device number */ 11724003Ssam return ENXIO; /* set errno to indicate bad port # */ 11824003Ssam tp = &vx_tty[d]; /* index the tty structure for port */ 11924003Ssam 12024003Ssam xp = &vcx[d>>4]; /* index VIOC-X info/cmd area */ 12124003Ssam d &= 017; 12224003Ssam 12324003Ssam /* If we did not find a board with the correct port number on 12424003Ssam it, or the entry for the VIOC-X had no ports on it, inform the 12524003Ssam caller that the port does not exist. */ 12624003Ssam if(!( xp->v_loport <= d && d <= xp->v_hiport ) /* home? */ 12724003Ssam || (xp->v_hiport - xp->v_loport)==0) 12824003Ssam return ENXIO; /* bad minor device number */ 12924003Ssam tp->t_addr = (caddr_t)xp; /* store address of VIOC-X info */ 13024003Ssam tp->t_oproc = vxstart; /* store address of startup routine */ 13124003Ssam tp->t_dev = dev; /* store major/minor device numbers */ 13224003Ssam d = spl8(); 13324003Ssam tp->t_state |= TS_WOPEN; /* mark device as waiting for open */ 13424003Ssam if ((tp->t_state&TS_ISOPEN) == 0) /* is device already open? */ 13524003Ssam { /* no, open it */ 13624003Ssam ttychars(tp); /* set default control chars */ 13724003Ssam if (tp->t_ispeed == 0) /* if no default speeds set them */ 13824003Ssam { 13924003Ssam tp->t_ispeed = SSPEED; /* default input baud */ 14024003Ssam tp->t_ospeed = SSPEED; /* default output baud */ 14124003Ssam tp->t_flags |= (ODDP|EVENP|ECHO); /* default modes */ 14224003Ssam } 14324003Ssam vxparam(dev); /* set parameters for this port */ 14424003Ssam } 14524003Ssam splx(d); 14624003Ssam /* ? if already open for exclusive use open fails unless caller is 14724003Ssam root. */ 14824003Ssam if (tp->t_state&TS_XCLUDE && u.u_uid!=0) 14924003Ssam return EBUSY; /* device is busy, sorry */ 15024003Ssam 15124003Ssam /* wait for data carrier detect to go high */ 15224003Ssam d = spl8(); 15324003Ssam if( !vcmodem(dev,VMOD_ON) ) 15424003Ssam while( (tp->t_state&TS_CARR_ON) == 0 ) 155*25675Ssam sleep((caddr_t)&tp->t_canq,TTIPRI); 15624003Ssam jj= (*linesw[tp->t_line].l_open)(dev,tp); /*let tty.c finish the open */ 15724003Ssam splx(d); /* 1/2/85 : assures open complete */ 15824003Ssam return (jj); 15924003Ssam } 16024003Ssam 16124003Ssam /* 16224003Ssam * Close a VX line. 16324003Ssam */ 164*25675Ssam /*ARGSUSED*/ 16524003Ssam vxclose(dev, flag) 16624003Ssam dev_t dev; 16724003Ssam int flag; 16824003Ssam { 16924003Ssam register struct tty *tp; 17024003Ssam register d; 17124003Ssam 17224003Ssam d = minor(dev) & 0377; 17324003Ssam tp = &vx_tty[d]; 17424003Ssam d = spl8(); 17524003Ssam (*linesw[tp->t_line].l_close)(tp); 17624003Ssam if ((tp->t_state&TS_ISOPEN) && (tp->t_state&TS_HUPCLS)) 17724003Ssam if( !vcmodem(dev,VMOD_OFF) ) 17824003Ssam tp->t_state &= ~TS_CARR_ON; 17924003Ssam /* wait for the last response */ 18024003Ssam while(tp->t_state & TS_FLUSH) 18124003Ssam sleep( (caddr_t)&tp->t_state, TTOPRI ) ; 18224003Ssam ttyclose(tp); /* let tty.c finish the close */ 18324003Ssam splx(d); 18424003Ssam } 18524003Ssam 18624003Ssam /* 18724003Ssam * Read from a VX line. 18824003Ssam */ 18924003Ssam vxread(dev, uio) 19024003Ssam dev_t dev; 19124003Ssam struct uio *uio; 19224003Ssam { 19324003Ssam register struct tty *tp = &vx_tty[minor(dev) & 0377]; 19424003Ssam return (*linesw[tp->t_line].l_read)(tp, uio); 19524003Ssam } 19624003Ssam 19724003Ssam /* 19824003Ssam * write on a VX line 19924003Ssam */ 20024003Ssam vxwrite(dev, uio) 20124003Ssam dev_t dev; 20224003Ssam struct uio *uio; 20324003Ssam { 20424003Ssam register struct tty *tp = &vx_tty[minor(dev) & 0377]; 20524003Ssam return (*linesw[tp->t_line].l_write)(tp, uio); 20624003Ssam } 20724003Ssam 20824003Ssam /* 20924003Ssam * VIOCX unsolicited interrupt. 21024003Ssam */ 21124003Ssam vxrint(n) 21224003Ssam register n; /* mux number */ 21324003Ssam { 21424003Ssam register struct tty *tp; 21524003Ssam register struct vcx *xp; 21624003Ssam register short *sp; 21724003Ssam register struct vblok *kp; 21824003Ssam register int i, c; 21924003Ssam short *savsilo; 22024003Ssam struct silo { 22124003Ssam char data; 22224003Ssam char port; 22324003Ssam }; 22424003Ssam 22524003Ssam kp = VBAS(n); 22624003Ssam xp = &vcx[n]; 22724003Ssam switch(kp->v_uqual&037) { 22824003Ssam case 0: 22924003Ssam break; 23024003Ssam case 2: 23124003Ssam printf(" ERR NBR %x\n",kp->v_ustat); 23224003Ssam vpanic("vc: VC PROC ERR"); 23324003Ssam vxstreset(n); 23424003Ssam return(0); 23524003Ssam case 3: 23624003Ssam vcmintr(n); 23724003Ssam return(1); 23824003Ssam case 4: 23924003Ssam return(1); 24024003Ssam default: 24124003Ssam printf(" ERR NBR %x\n",kp->v_uqual); 24224003Ssam vpanic("vc: VC UQUAL ERR"); 24324003Ssam vxstreset(n); 24424003Ssam return(0); 24524003Ssam } 24624003Ssam if(xp->v_vers == V_NEW) { 24724003Ssam register short *aa ; 24824003Ssam aa = (short *)kp->v_usdata; 24924003Ssam sp = (short *)(*aa + (char *)kp) ; 25024003Ssam } else { 25124003Ssam c = kp->v_usdata[0] << 6; 25224003Ssam sp = (short *)((char *)kp + SILOBAS + c); 25324003Ssam } 25424003Ssam i = *(savsilo = sp); 25524003Ssam if (i == 0) return(1); 25624003Ssam if(xp->v_vers == V_NEW) 25724003Ssam if( i > xp->v_silosiz ) { 25824003Ssam printf("vx: %d exceeds silo size\n",i) ; 25924003Ssam i = xp->v_silosiz; 26024003Ssam } 26124003Ssam for(sp++;i > 0;i--,sp++) { 26224003Ssam c = ((struct silo *)sp)->port & 017; 26324003Ssam tp = &vx_tty[c+n*16]; 26424003Ssam if(xp->v_loport > c || c > xp->v_hiport) 26524003Ssam continue; /* port out of bounds */ 26624003Ssam if( (tp->t_state & TS_ISOPEN) == 0) { 26724003Ssam wakeup((caddr_t)&tp->t_rawq); 26824003Ssam continue; 26924003Ssam } 27024003Ssam c = ((struct silo *)sp)->data; 27124003Ssam switch(((struct silo *)sp)->port&(PERROR|FERROR)) { 27224003Ssam case PERROR: 27324003Ssam case PERROR|FERROR: 27424003Ssam if( (tp->t_flags&(EVENP|ODDP)) == EVENP 27524003Ssam || (tp->t_flags & (EVENP|ODDP)) == ODDP ) 27624003Ssam continue; 27724003Ssam if(!(((struct silo *)sp)->port&FERROR)) 27824003Ssam break; 27924003Ssam case FERROR: 28024003Ssam if(tp->t_flags & RAW) c = 0; 28124003Ssam else c = tp->t_intrc; 28224003Ssam } 28324003Ssam (*linesw[tp->t_line].l_rint)(c, tp); 28424003Ssam } 28524003Ssam *savsilo = 0; 28624003Ssam return(1); 28724003Ssam } 28824003Ssam 28924003Ssam /* 29024003Ssam * stty/gtty for VX 29124003Ssam */ 29224003Ssam vxioctl(dev, cmd, data, flag) 29324003Ssam int dev; /* major, minor device numbers */ 29424003Ssam int cmd; /* command */ 29524003Ssam caddr_t data; 29624003Ssam int flag; 29724003Ssam { 29824003Ssam register struct tty *tp; 29924003Ssam register error; 30024003Ssam 30124003Ssam tp = &vx_tty[minor(dev) & 0377]; 30224003Ssam error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag); 30324003Ssam if (error == 0) 30424003Ssam return error; 30524003Ssam if((error = ttioctl(tp, cmd, data, flag)) >= 0) 30624003Ssam { 30724003Ssam if (cmd==TIOCSETP||cmd==TIOCSETN) 30824003Ssam vxparam(dev); 30924003Ssam return error; 31024003Ssam } else 31124003Ssam return ENOTTY; 31224003Ssam } 31324003Ssam 31424003Ssam 31524003Ssam vxparam(dev) 31624003Ssam dev_t dev; 31724003Ssam { 31824003Ssam vxcparam(dev, 1); 31924003Ssam } 32024003Ssam 32124003Ssam /* 32224003Ssam * Set parameters from open or stty into the VX hardware 32324003Ssam * registers. 32424003Ssam */ 32524003Ssam vxcparam(dev, wait) 32624003Ssam dev_t dev; /* major, minor device numbers */ 32724003Ssam int wait; /* nonzero if we should wait for finish */ 32824003Ssam { 32924003Ssam register struct tty *tp; 33024003Ssam register struct vcx *xp; 33124003Ssam register struct vxcmd *cp; 33224003Ssam register s; 33324003Ssam 33424003Ssam tp = &vx_tty[minor(dev)]; /* pointer to tty structure for port */ 33524003Ssam xp = (struct vcx *)tp->t_addr; /* pointer to VIOCX info/cmd buffer */ 33624003Ssam cp = vobtain(xp); 33724003Ssam s = spl8(); 33824003Ssam cp->cmd = LPARAX; /* set command to "load parameters" */ 33924003Ssam cp->par[1] = minor(dev)&017; /* port number */ 34024003Ssam 34124003Ssam cp->par[2] = (tp->t_flags&RAW)? 0 : tp->t_startc; /* XON char */ 34224003Ssam cp->par[3] = (tp->t_flags&RAW)? 0 : tp->t_stopc; /* XOFF char */ 34324003Ssam 34424003Ssam if(tp->t_flags&(RAW|LITOUT) || 34524003Ssam (tp->t_flags&(EVENP|ODDP)) == (EVENP|ODDP)) { 34624003Ssam cp->par[4] = 0xc0; /* 8 bits of data */ 34724003Ssam cp->par[7] = 0; /* no parity */ 34824003Ssam } else { 34924003Ssam cp->par[4] = 0x40; /* 7 bits of data */ 35024003Ssam if((tp->t_flags&(EVENP|ODDP)) == ODDP) 35124003Ssam cp->par[7] = 1; /* odd parity */ 35224003Ssam else if((tp->t_flags&(EVENP|ODDP)) == EVENP) 35324003Ssam cp->par[7] = 3; /* even parity */ 35424003Ssam else 35524003Ssam cp->par[7] = 0; /* no parity */ 35624003Ssam } 35724003Ssam cp->par[5] = 0x4; /* 1 stop bit */ 35824003Ssam cp->par[6] = tp->t_ospeed; 35924003Ssam 360*25675Ssam if (vcmd(xp->v_nbr, (caddr_t)&cp->cmd) && wait) 361*25675Ssam sleep((caddr_t)cp,TTIPRI); 36224003Ssam splx(s); 36324003Ssam } 36424003Ssam 36524003Ssam /* 36624003Ssam * VIOCX command response interrupt. 36724003Ssam * For transmission, restart output to any active port. 36824003Ssam * For all other commands, just clean up. 36924003Ssam */ 37024003Ssam vxxint(n,cp) 37124003Ssam register int n; /* VIOC number */ 37224003Ssam register struct vxcmd *cp; /* command structure */ 37324003Ssam { 37424003Ssam register struct vxmit *vp, *pvp; 37524003Ssam register struct tty *tp; 37624003Ssam register struct vcx *xp; 37724003Ssam register struct tty *hp; 37824003Ssam 37924003Ssam xp = &vcx[n]; 38024003Ssam cp = (struct vxcmd *)( (long *)cp - 1); 38124003Ssam #if NVBSC > 0 38224003Ssam switch(cp->cmd) { 38324003Ssam case MDMCTL1: case HUNTMD1: case LPARAX1: 38424003Ssam vrelease(xp, cp); 38524003Ssam wakeup(cp); 38624003Ssam return; 38724003Ssam } 38824003Ssam #endif 38924003Ssam switch(cp->cmd&0xff00) { 39024003Ssam case LIDENT: /* initialization complete */ 39124003Ssam if (xp->v_state & V_RESETTING) { 39224003Ssam vxfnreset(n,cp); 39324003Ssam vinthandl(n,((V_BSY | RSPquals) << 8) | V_INTR); 39424003Ssam } 39524003Ssam cp->cmd++; 39624003Ssam return; 39724003Ssam case XMITDTA: case XMITIMM: 39824003Ssam break; 39924003Ssam case LPARAX: 400*25675Ssam wakeup((caddr_t)cp); 40124003Ssam default: /* MDMCTL or FDTATOX */ 40224003Ssam vrelease(xp, cp); 40324003Ssam if (xp->v_state & V_RESETTING) { 40424003Ssam vinthandl(n,((V_BSY | RSPquals) << 8) | V_INTR); 40524003Ssam } 40624003Ssam return; 40724003Ssam } 40824003Ssam for(vp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizvxmit); 40924003Ssam vp >= (struct vxmit *)cp->par; 41024003Ssam vp = (struct vxmit *) ((char *)vp - sizvxmit) ) 41124003Ssam { 41224003Ssam tp = &vx_tty[(vp->line & 017)+n*16]; 41324003Ssam /* cjk buffer bug */ 41424003Ssam #if NVBSC > 0 41524003Ssam /* bsc change */ 41624003Ssam if (tp->t_line == LDISP) { 41724003Ssam vrelease(xp, cp); 41824003Ssam bsctxd((vp->line & 017)); 41924003Ssam return ; 42024003Ssam } 42124003Ssam /* End of bsc change */ 42224003Ssam #endif 42324003Ssam /* cjk */ 42424003Ssam pvp = vp; 42524003Ssam tp->t_state &= ~TS_BUSY; 42624003Ssam if(tp->t_state & TS_FLUSH) { 42724003Ssam tp->t_state &= ~TS_FLUSH; 42824003Ssam wakeup( (caddr_t)&tp->t_state ) ; 42924003Ssam } 43024003Ssam else 43124003Ssam ndflush(&tp->t_outq, vp->bcount+1); 43224003Ssam } 43324003Ssam xp->v_xmtcnt--; 43424003Ssam vrelease(xp,cp); 43524003Ssam if(xp->v_vers == V_NEW) { 43624003Ssam vp = pvp; 43724003Ssam xp->v_actport[(vp->line & 017) - xp->v_loport] |= 1 ; 43824003Ssam if(vxstart(tp) && (cp = nextcmd(xp)) != NULL) 43924003Ssam { 44024003Ssam xp->v_xmtcnt++; 441*25675Ssam vcmd(n, (caddr_t)&cp->cmd); 44224003Ssam return ; 44324003Ssam } 44424003Ssam xp->v_actport[(vp->line & 017) - xp->v_loport] = 0 ; 44524003Ssam return ; 44624003Ssam } 44724003Ssam xp->v_actflg = 1; 44824003Ssam hp = &vx_tty[xp->v_hiport+n*16]; 44924003Ssam for(tp = &vx_tty[xp->v_loport+n*16];tp <= hp;tp++) 45024003Ssam if(vxstart(tp) && (cp = nextcmd(xp)) != NULL) 45124003Ssam { 45224003Ssam xp->v_xmtcnt++; 453*25675Ssam vcmd(n, (caddr_t)&cp->cmd); 45424003Ssam } 45524003Ssam if( (cp = nextcmd(xp)) != NULL ) /* command to send ? */ 45624003Ssam { 45724003Ssam xp->v_xmtcnt++; 458*25675Ssam vcmd(n, (caddr_t)&cp->cmd); 45924003Ssam } 46024003Ssam xp->v_actflg = 0; 46124003Ssam } 46224003Ssam 46324003Ssam /* 46424003Ssam * Force out partial XMIT command after timeout 46524003Ssam */ 46624003Ssam vxforce(xp) 46724003Ssam register struct vcx *xp; 46824003Ssam { 46924003Ssam register struct vxcmd *cp; 47024003Ssam register int s; 47124003Ssam 47224003Ssam s = spl8(); 47324003Ssam if((cp = nextcmd(xp)) != NULL) { 47424003Ssam xp->v_xmtcnt++; 475*25675Ssam vcmd(xp->v_nbr, (caddr_t)&cp->cmd); 47624003Ssam } 47724003Ssam splx(s); 47824003Ssam } 47924003Ssam 48024003Ssam /* 48124003Ssam * Start (restart) transmission on the given VX line. 48224003Ssam */ 48324003Ssam vxstart(tp) 48424003Ssam register struct tty *tp; 48524003Ssam { 486*25675Ssam register short n; 48724003Ssam register struct vcx *xp; 48824003Ssam register char *outb; 48924003Ssam register full = 0; 49024003Ssam int k, s, port; 49124003Ssam 49224003Ssam s = spl8(); 49324003Ssam port = minor(tp->t_dev) & 017; 49424003Ssam xp = (struct vcx *)tp->t_addr; 49524003Ssam if (!(tp->t_state&(TS_TIMEOUT|TS_BUSY|TS_TTSTOP))) { 49624003Ssam if (tp->t_outq.c_cc<=TTLOWAT(tp)) { 49724003Ssam if (tp->t_state&TS_ASLEEP) { 49824003Ssam tp->t_state &= ~TS_ASLEEP; 49924003Ssam wakeup((caddr_t)&tp->t_outq); 50024003Ssam } 50124003Ssam if (tp->t_wsel) { 50224003Ssam selwakeup(tp->t_wsel, tp->t_state & TS_WCOLL); 50324003Ssam tp->t_wsel = 0; 50424003Ssam tp->t_state &= ~TS_WCOLL; 50524003Ssam } 50624003Ssam } 50724003Ssam if(tp->t_outq.c_cc == 0) { 50824003Ssam splx(s); 50924003Ssam return(0); 51024003Ssam } 51124003Ssam #ifdef VXPERF 51224003Ssam scope_out(3); 51324003Ssam #endif VXPERF 51424003Ssam if(!(tp->t_flags&(RAW|LITOUT))) 51524003Ssam full = 0200; 516*25675Ssam if((n = ndqb(&tp->t_outq, full)) == 0) { 51724003Ssam if(full) { 518*25675Ssam n = getc(&tp->t_outq); 519*25675Ssam timeout(ttrstrt, (caddr_t)tp, (n&0177) +6); 52024003Ssam tp->t_state |= TS_TIMEOUT; 52124003Ssam full = 0; 52224003Ssam } 52324003Ssam } else { 52424003Ssam outb = (char *)tp->t_outq.c_cf; 52524003Ssam tp->t_state |= TS_BUSY; 52624003Ssam if(xp->v_vers == V_NEW) 52724003Ssam k = xp->v_actport[port - xp->v_loport] ; 52824003Ssam else 52924003Ssam k = xp->v_actflg ; 53024003Ssam 531*25675Ssam full = vsetq(xp, port, outb, n); 53224003Ssam 53324003Ssam if( (k&1) == 0 ) { /* not called from vxxint */ 53424003Ssam if(full || xp->v_xmtcnt == 0) { 53524003Ssam outb = (char *)(&nextcmd(xp)->cmd); 53624003Ssam xp->v_xmtcnt++; 53724003Ssam vcmd(xp->v_nbr, outb ); 53824003Ssam } else 539*25675Ssam timeout(vxforce,(caddr_t)xp,3); 54024003Ssam } 54124003Ssam } 54224003Ssam } 54324003Ssam splx(s); 54424003Ssam return(full); /* indicate if max commands or not */ 54524003Ssam } 54624003Ssam 54724003Ssam /* 54824003Ssam * Stop output on a line. 54924003Ssam */ 55024003Ssam vxstop(tp) 55124003Ssam register struct tty *tp; 55224003Ssam { 55324003Ssam register s; 55424003Ssam 55524003Ssam s = spl8(); 55624003Ssam if (tp->t_state & TS_BUSY) { 55724003Ssam if ((tp->t_state&TS_TTSTOP)==0) { 55824003Ssam tp->t_state |= TS_FLUSH; 55924003Ssam } 56024003Ssam } 56124003Ssam splx(s); 56224003Ssam } 56324003Ssam 56424003Ssam /* 56524003Ssam * VIOCX Initialization. Makes free lists of command buffers. 56624003Ssam * Resets all viocx's. Issues a LIDENT command to each 56724003Ssam * viocx which establishes interrupt vectors and logical 56824003Ssam * port numbers 56924003Ssam */ 57024003Ssam vxinit(i,wait) 57124003Ssam register int i; 57224003Ssam long wait; 57324003Ssam { 57424003Ssam register struct vcx *xp; /* ptr to VIOC-X info/cmd buffer */ 57524003Ssam register struct vblok *kp; /* pointer to VIOC-X control block */ 57624003Ssam register struct vxcmd *cp; /* pointer to a command buffer */ 57724003Ssam register char *resp; /* pointer to response buffer */ 57824003Ssam register int j; 57924003Ssam char type; 580*25675Ssam #if NVBSC > 0 58124003Ssam register struct bsc *bp; /* bsc change */ 58224003Ssam extern struct bsc bsc[]; 583*25675Ssam #endif 58424003Ssam 58524003Ssam 58624003Ssam kp = VBAS(i); /* get base adr of cntl blok for VIOC */ 58724003Ssam 58824003Ssam xp = &vcx[i]; /* index info/command buffers */ 58924003Ssam type = kp->v_ident; 59024003Ssam vxtype[i] = 0; /* Type is Viox-x */ 59124003Ssam switch(type) { 59224003Ssam case VIOCX: 59324003Ssam { 59424003Ssam xp->v_vers = V_OLD ; 59524003Ssam /* set DCD for printer ports */ 59624003Ssam for(j = 0;j < 16;j++) 59724003Ssam if (kp->v_portyp[j] == 4 ) 59824003Ssam kp->v_dcd |= 1 << j ; 59924003Ssam } 60024003Ssam break ; 60124003Ssam case NWVIOCX: 60224003Ssam { 60324003Ssam xp->v_vers = V_NEW ; 60424003Ssam xp->v_silosiz = kp->v_maxsilo ; 60524003Ssam /* set DCD for printer ports */ 60624003Ssam for(j = 0;j < 16;j++) 60724003Ssam if (kp->v_portyp[j] == 4 ) 60824003Ssam kp->v_dcd |= 1 << j ; 60924003Ssam } 61024003Ssam break ; 61124003Ssam case PVIOCX: 61224003Ssam xp->v_vers = V_OLD ; 61324003Ssam break ; 61424003Ssam case NPVIOCX: 61524003Ssam xp->v_vers = V_NEW ; 61624003Ssam xp->v_silosiz = kp->v_maxsilo ; 61724003Ssam break ; 61824003Ssam #if NVBSC > 0 61924003Ssam case VIOCB: /* old f/w, Bisync board */ 62024003Ssam printf("%X: %x%x OLD VIOC-B, ", 62124003Ssam (long)kp, (int)kp->v_ident, 62224003Ssam (int)kp->v_fault); 62324003Ssam xp->v_vers = V_OLD ; 62424003Ssam /* save device specific info */ 62524003Ssam for(bp = &bsc[0]; bp <= &bsc[NBSC]; bp++) 62624003Ssam bp->b_devregs = (caddr_t)xp ; 62724003Ssam printf("%d BSC Ports initialized.\n",NBSC); 62824003Ssam break ; 62924003Ssam 63024003Ssam case NWVIOCB: /* new f/w, Bisync board */ 63124003Ssam printf("%X: %x%x 16K VIOC-B, ", 63224003Ssam (long)kp, (int)kp->v_ident, 63324003Ssam (int)kp->v_fault); 63424003Ssam xp->v_vers = V_NEW ; 63524003Ssam xp->v_silosiz = kp->v_maxsilo ; 63624003Ssam /* save device specific info */ 63724003Ssam for(bp = &bsc[0]; bp <= &bsc[NBSC]; bp++) 63824003Ssam bp->b_devregs = (caddr_t)xp ; 63924003Ssam printf("%d BSC Ports initialized.\n",NBSC); 64024003Ssam if(CBSIZE > kp->v_maxxmt) 64124003Ssam printf("vxinit: Warning CBSIZE > maxxmt\n") ; 64224003Ssam break ; 64324003Ssam #endif 64424003Ssam case VBOPID: /* VIOC-BOP */ 64524003Ssam vxbbno++; 64624003Ssam vxtype[i] = 1; 64724003Ssam vxbopno[i] = vxbbno; 64824003Ssam printf("VIOC-BOP no. %d at %lx\n",vxbopno[i],VIOCBAS[i]); 64924003Ssam default: 65024003Ssam return ; /* Not a viocx type */ 65124003Ssam } 65224003Ssam xp->v_nbr = -1; /* no number for it yet */ 65324003Ssam xp->v_maxcmd = xp->v_vers == V_NEW ? 24 : 4; 65424003Ssam 65524003Ssam for(j=0; j<NVCXBUFS; j++) /* init all cmd buffers */ 65624003Ssam { 65724003Ssam cp = &xp->vx_lst[j]; /* index a buffer */ 65824003Ssam cp->c_fwd = &xp->vx_lst[j+1]; /* point to next buf */ 65924003Ssam } 66024003Ssam xp->vx_avail = &xp->vx_lst[0]; /* set idx to 1st free buf */ 66124003Ssam cp->c_fwd = (struct vxcmd *)0; /* mark last buf in free list */ 66224003Ssam 66324003Ssam cp = vobtain(xp); /* grap the control block */ 66424003Ssam cp->cmd = LIDENT; /* set command type */ 66524003Ssam cp->par[0] = i * 4 + VCVECT; /* ack vector */ 66624003Ssam cp->par[1] = cp->par[0] + 1; /* cmd resp vector */ 66724003Ssam cp->par[3] = cp->par[0] + 2; /* unsol intr vector */ 66824003Ssam cp->par[4] = 15; /* max ports, no longer used */ 66924003Ssam cp->par[5] = 0; /* set 1st port number */ 670*25675Ssam vcmd(i, (caddr_t)&cp->cmd); /* initialize the VIOC-X */ 67124003Ssam 67224003Ssam if (!wait) return; 67324003Ssam while(cp->cmd == LIDENT); /* wait for command completion */ 67424003Ssam 67524003Ssam /* calculate address of response buffer */ 67624003Ssam resp = (char *)kp; 67724003Ssam resp += kp->v_rspoff & 0x3FFF; 67824003Ssam 67924003Ssam if(resp[0] != 0 && (resp[0]&0177) != 3) /* did init work? */ 68024003Ssam { 68124003Ssam vrelease(xp,cp); /* init failed */ 68224003Ssam return; /* try next VIOC-X */ 68324003Ssam } 68424003Ssam 68524003Ssam xp->v_loport = cp->par[5]; /* save low port number */ 68624003Ssam xp->v_hiport = cp->par[7];/* VIOC knows high port numbr */ 68724003Ssam vrelease(xp,cp); /* done with this control block */ 68824003Ssam xp->v_nbr = i; /* assign VIOC-X board number */ 68924003Ssam } 69024003Ssam 69124003Ssam /* 69224003Ssam * Obtain a command buffer 69324003Ssam */ 69424003Ssam struct vxcmd * 69524003Ssam vobtain(xp) 69624003Ssam register struct vcx *xp; 69724003Ssam { 69824003Ssam 69924003Ssam register struct vxcmd *p; 70024003Ssam register s; 70124003Ssam 70224003Ssam s = spl8(); 70324003Ssam p = xp->vx_avail; 70424003Ssam if(p == (struct vxcmd *)0) { 70524003Ssam #ifdef VX_DEBUG 70624003Ssam if (vxintr4 & VXNOBUF) vxintr4 &= ~VXNOBUF; 70724003Ssam #endif 70824003Ssam vpanic("vx: no buffs"); 70924003Ssam vxstreset(xp - vcx); 71024003Ssam splx(s); 71124003Ssam return(vobtain(xp)); 71224003Ssam } 71324003Ssam xp->vx_avail = (xp->vx_avail)->c_fwd; 71424003Ssam splx(s); 71524003Ssam return( (struct vxcmd *)p); 71624003Ssam } 71724003Ssam 71824003Ssam /* 71924003Ssam * Release a command buffer 72024003Ssam */ 72124003Ssam vrelease(xp,cp) 72224003Ssam register struct vcx *xp; 72324003Ssam register struct vxcmd *cp; 72424003Ssam { 72524003Ssam 72624003Ssam register s; 72724003Ssam 72824003Ssam #ifdef VX_DEBUG 72924003Ssam if (vxintr4 & VXNOBUF) return; 73024003Ssam #endif 73124003Ssam s = spl8(); 73224003Ssam cp->c_fwd = xp->vx_avail; 73324003Ssam xp->vx_avail = cp; 73424003Ssam splx(s); 73524003Ssam } 73624003Ssam 73724003Ssam /* 73824003Ssam * vxcmd - 73924003Ssam * 74024003Ssam */ 74124003Ssam struct vxcmd * 74224003Ssam nextcmd(xp) 74324003Ssam register struct vcx *xp; 74424003Ssam { 74524003Ssam register struct vxcmd *cp; 74624003Ssam register int s; 74724003Ssam 74824003Ssam s = spl8(); 74924003Ssam cp = xp->vx_build; 75024003Ssam xp->vx_build = (struct vxcmd *)0; 75124003Ssam splx(s); 75224003Ssam return(cp); 75324003Ssam } 75424003Ssam 75524003Ssam /* 75624003Ssam * assemble transmits into a multiple command. 75724003Ssam * up to 8 transmits to 8 lines can be assembled together 75824003Ssam */ 759*25675Ssam vsetq(xp ,d ,addr, n) 76024003Ssam register struct vcx *xp; 76124003Ssam caddr_t addr; 76224003Ssam { 76324003Ssam 76424003Ssam register struct vxcmd *cp; 76524003Ssam register struct vxmit *mp; 76624003Ssam register char *p; 76724003Ssam register i; 76824003Ssam 76924003Ssam cp = xp->vx_build; 77024003Ssam if(cp == (struct vxcmd *)0) { 77124003Ssam cp = vobtain(xp); 77224003Ssam xp->vx_build = cp; 77324003Ssam cp->cmd = XMITDTA; 77424003Ssam } else { 77524003Ssam if((cp->cmd & 07) == 07) { 77624003Ssam vpanic("vx: vsetq overflow"); 77724003Ssam vxstreset(xp->v_nbr); 77824003Ssam return(0); 77924003Ssam } 78024003Ssam cp->cmd++; 78124003Ssam } 78224003Ssam 78324003Ssam mp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizvxmit); 784*25675Ssam mp->bcount = n-1; 78524003Ssam 78624003Ssam mp->line = d; 787*25675Ssam if((xp->v_vers == V_NEW) && (n <= 6)) { 78824003Ssam cp->cmd = XMITIMM ; 78924003Ssam p = addr; 790*25675Ssam /* bcopy(addr, &(char *)mp->ostream, n) ; */ 79124003Ssam } else { 792*25675Ssam addr = (caddr_t)vtoph((struct proc *)0, (unsigned)addr); 793*25675Ssam /* should be a sys address */ 79424003Ssam p = (char *)&addr; 795*25675Ssam n = sizeof addr; 79624003Ssam /* mp->ostream = addr ; */ 79724003Ssam } 798*25675Ssam for(i=0; i<n; i++) 79924003Ssam mp->ostream[i] = *p++; 80024003Ssam if(xp->v_vers == V_NEW) 80124003Ssam return(1) ; 80224003Ssam else 80324003Ssam return((cp->cmd&07) == 7) ; /* Indicate if full */ 80424003Ssam } 80524003Ssam #endif 806