1*24003Ssam /* vx.c 1.1 85/07/21 */ 2*24003Ssam 3*24003Ssam #include "vx.h" 4*24003Ssam #if NVX > 0 5*24003Ssam /* 6*24003Ssam * VIOC-X driver 7*24003Ssam */ 8*24003Ssam 9*24003Ssam #include "../h/param.h" 10*24003Ssam #include "../h/ioctl.h" 11*24003Ssam #include "../h/tty.h" 12*24003Ssam #include "../h/dir.h" 13*24003Ssam #include "../h/user.h" 14*24003Ssam #include "../h/map.h" 15*24003Ssam #include "../machine/pte.h" 16*24003Ssam #include "../h/buf.h" 17*24003Ssam #include "../vba/vbavar.h" 18*24003Ssam #include "../h/conf.h" 19*24003Ssam #include "../h/file.h" 20*24003Ssam #include "../h/uio.h" 21*24003Ssam #include "../vba/vioc.h" 22*24003Ssam #ifdef VXPERF 23*24003Ssam #include "../vba/scope.h" 24*24003Ssam #endif VXPERF 25*24003Ssam #include "vbsc.h" 26*24003Ssam #if NVBSC > 0 27*24003Ssam #include "../bsc/bscio.h" 28*24003Ssam #include "../bsc/bsc.h" 29*24003Ssam char bscport[NVXPORTS]; 30*24003Ssam #endif 31*24003Ssam 32*24003Ssam #ifdef BSC_DEBUG 33*24003Ssam #include "../bsc/bscdebug.h" 34*24003Ssam #endif 35*24003Ssam 36*24003Ssam #ifdef VX_DEBUG 37*24003Ssam long vxintr4 = 0; 38*24003Ssam long vxdebug = 0; 39*24003Ssam #include "../vba/vxdebug.h" 40*24003Ssam #endif 41*24003Ssam 42*24003Ssam #define RSPquals 1 43*24003Ssam 44*24003Ssam struct vcx vcx[NVIOCX] ; 45*24003Ssam struct tty vx_tty[NVXPORTS]; 46*24003Ssam extern struct vcmds v_cmds[]; 47*24003Ssam extern long reinit; 48*24003Ssam 49*24003Ssam int vxstart() ; 50*24003Ssam int ttrstrt() ; 51*24003Ssam caddr_t vtoph(); 52*24003Ssam struct vxcmd *vobtain() ; 53*24003Ssam struct vxcmd *nextcmd() ; 54*24003Ssam 55*24003Ssam /* 56*24003Ssam * Driver information for auto-configuration stuff. 57*24003Ssam * (not tested and probably should be changed) 58*24003Ssam */ 59*24003Ssam int vxprobe(), vxattach(), vxrint(); 60*24003Ssam struct vba_device *vxinfo[NVIOCX]; 61*24003Ssam long vxstd[] = { 0 }; 62*24003Ssam struct vba_driver vxdriver = 63*24003Ssam { vxprobe, 0, vxattach, 0, vxstd, "vioc ", vxinfo }; 64*24003Ssam 65*24003Ssam char vxtype[NVIOCX]; /* 0: viox-x/vioc-b; 1: vioc-bop */ 66*24003Ssam char vxbbno = -1; 67*24003Ssam char vxbopno[NVIOCX]; /* BOP board no. if indicated by vxtype[] */ 68*24003Ssam extern vbrall(); 69*24003Ssam 70*24003Ssam 71*24003Ssam vxprobe(reg) 72*24003Ssam caddr_t reg; 73*24003Ssam { 74*24003Ssam register int br, cvec; 75*24003Ssam register struct vblok *vp = (struct vblok *)reg; 76*24003Ssam 77*24003Ssam #ifdef lint 78*24003Ssam br = 0; cvec = br; br = cvec; 79*24003Ssam #endif 80*24003Ssam 81*24003Ssam if(badaddr(vp, 1)) 82*24003Ssam return(0); 83*24003Ssam vp->v_fault = 0 ; 84*24003Ssam vp->v_vioc = V_BSY ; 85*24003Ssam vp->v_hdwre = V_RESET ; /* reset interrupt */ 86*24003Ssam 87*24003Ssam DELAY(4000000); 88*24003Ssam return ( vp->v_fault == VREADY); 89*24003Ssam } 90*24003Ssam 91*24003Ssam vxattach(ui) 92*24003Ssam register struct vba_device *ui; 93*24003Ssam { 94*24003Ssam VIOCBAS[ui->ui_unit] = ui->ui_addr; 95*24003Ssam vxinit(ui->ui_unit,1); 96*24003Ssam } 97*24003Ssam 98*24003Ssam /* 99*24003Ssam * Open a VX line. 100*24003Ssam */ 101*24003Ssam vxopen(dev, flag) 102*24003Ssam { 103*24003Ssam register struct tty *tp; /* pointer to tty struct for port */ 104*24003Ssam register struct vcx *xp; /* pointer to VIOC-X info/cmd buffer */ 105*24003Ssam register d; /* minor device number */ 106*24003Ssam register long jj; 107*24003Ssam 108*24003Ssam 109*24003Ssam d = minor(dev); /* get minor device number */ 110*24003Ssam if (d >= NVXPORTS) /* validate minor device number */ 111*24003Ssam return ENXIO; /* set errno to indicate bad port # */ 112*24003Ssam tp = &vx_tty[d]; /* index the tty structure for port */ 113*24003Ssam 114*24003Ssam xp = &vcx[d>>4]; /* index VIOC-X info/cmd area */ 115*24003Ssam d &= 017; 116*24003Ssam 117*24003Ssam /* If we did not find a board with the correct port number on 118*24003Ssam it, or the entry for the VIOC-X had no ports on it, inform the 119*24003Ssam caller that the port does not exist. */ 120*24003Ssam if(!( xp->v_loport <= d && d <= xp->v_hiport ) /* home? */ 121*24003Ssam || (xp->v_hiport - xp->v_loport)==0) 122*24003Ssam return ENXIO; /* bad minor device number */ 123*24003Ssam tp->t_addr = (caddr_t)xp; /* store address of VIOC-X info */ 124*24003Ssam tp->t_oproc = vxstart; /* store address of startup routine */ 125*24003Ssam tp->t_dev = dev; /* store major/minor device numbers */ 126*24003Ssam d = spl8(); 127*24003Ssam tp->t_state |= TS_WOPEN; /* mark device as waiting for open */ 128*24003Ssam if ((tp->t_state&TS_ISOPEN) == 0) /* is device already open? */ 129*24003Ssam { /* no, open it */ 130*24003Ssam ttychars(tp); /* set default control chars */ 131*24003Ssam if (tp->t_ispeed == 0) /* if no default speeds set them */ 132*24003Ssam { 133*24003Ssam tp->t_ispeed = SSPEED; /* default input baud */ 134*24003Ssam tp->t_ospeed = SSPEED; /* default output baud */ 135*24003Ssam tp->t_flags |= (ODDP|EVENP|ECHO); /* default modes */ 136*24003Ssam } 137*24003Ssam vxparam(dev); /* set parameters for this port */ 138*24003Ssam } 139*24003Ssam splx(d); 140*24003Ssam /* ? if already open for exclusive use open fails unless caller is 141*24003Ssam root. */ 142*24003Ssam if (tp->t_state&TS_XCLUDE && u.u_uid!=0) 143*24003Ssam return EBUSY; /* device is busy, sorry */ 144*24003Ssam 145*24003Ssam /* wait for data carrier detect to go high */ 146*24003Ssam d = spl8(); 147*24003Ssam if( !vcmodem(dev,VMOD_ON) ) 148*24003Ssam while( (tp->t_state&TS_CARR_ON) == 0 ) 149*24003Ssam sleep(&tp->t_canq,TTIPRI); 150*24003Ssam jj= (*linesw[tp->t_line].l_open)(dev,tp); /*let tty.c finish the open */ 151*24003Ssam splx(d); /* 1/2/85 : assures open complete */ 152*24003Ssam return (jj); 153*24003Ssam } 154*24003Ssam 155*24003Ssam /* 156*24003Ssam * Close a VX line. 157*24003Ssam */ 158*24003Ssam vxclose(dev, flag) 159*24003Ssam dev_t dev; 160*24003Ssam int flag; 161*24003Ssam { 162*24003Ssam register struct tty *tp; 163*24003Ssam register d; 164*24003Ssam 165*24003Ssam d = minor(dev) & 0377; 166*24003Ssam tp = &vx_tty[d]; 167*24003Ssam d = spl8(); 168*24003Ssam (*linesw[tp->t_line].l_close)(tp); 169*24003Ssam if ((tp->t_state&TS_ISOPEN) && (tp->t_state&TS_HUPCLS)) 170*24003Ssam if( !vcmodem(dev,VMOD_OFF) ) 171*24003Ssam tp->t_state &= ~TS_CARR_ON; 172*24003Ssam /* wait for the last response */ 173*24003Ssam while(tp->t_state & TS_FLUSH) 174*24003Ssam sleep( (caddr_t)&tp->t_state, TTOPRI ) ; 175*24003Ssam ttyclose(tp); /* let tty.c finish the close */ 176*24003Ssam splx(d); 177*24003Ssam } 178*24003Ssam 179*24003Ssam /* 180*24003Ssam * Read from a VX line. 181*24003Ssam */ 182*24003Ssam vxread(dev, uio) 183*24003Ssam dev_t dev; 184*24003Ssam struct uio *uio; 185*24003Ssam { 186*24003Ssam register struct tty *tp = &vx_tty[minor(dev) & 0377]; 187*24003Ssam return (*linesw[tp->t_line].l_read)(tp, uio); 188*24003Ssam } 189*24003Ssam 190*24003Ssam /* 191*24003Ssam * write on a VX line 192*24003Ssam */ 193*24003Ssam vxwrite(dev, uio) 194*24003Ssam dev_t dev; 195*24003Ssam struct uio *uio; 196*24003Ssam { 197*24003Ssam register struct tty *tp = &vx_tty[minor(dev) & 0377]; 198*24003Ssam return (*linesw[tp->t_line].l_write)(tp, uio); 199*24003Ssam } 200*24003Ssam 201*24003Ssam /* 202*24003Ssam * VIOCX unsolicited interrupt. 203*24003Ssam */ 204*24003Ssam vxrint(n) 205*24003Ssam register n; /* mux number */ 206*24003Ssam { 207*24003Ssam register struct tty *tp; 208*24003Ssam register struct vcx *xp; 209*24003Ssam register short *sp; 210*24003Ssam register struct vblok *kp; 211*24003Ssam register int i, c; 212*24003Ssam short *savsilo; 213*24003Ssam struct silo { 214*24003Ssam char data; 215*24003Ssam char port; 216*24003Ssam }; 217*24003Ssam 218*24003Ssam kp = VBAS(n); 219*24003Ssam xp = &vcx[n]; 220*24003Ssam switch(kp->v_uqual&037) { 221*24003Ssam case 0: 222*24003Ssam break; 223*24003Ssam case 2: 224*24003Ssam printf(" ERR NBR %x\n",kp->v_ustat); 225*24003Ssam vpanic("vc: VC PROC ERR"); 226*24003Ssam vxstreset(n); 227*24003Ssam return(0); 228*24003Ssam case 3: 229*24003Ssam vcmintr(n); 230*24003Ssam return(1); 231*24003Ssam case 4: 232*24003Ssam return(1); 233*24003Ssam default: 234*24003Ssam printf(" ERR NBR %x\n",kp->v_uqual); 235*24003Ssam vpanic("vc: VC UQUAL ERR"); 236*24003Ssam vxstreset(n); 237*24003Ssam return(0); 238*24003Ssam } 239*24003Ssam if(xp->v_vers == V_NEW) { 240*24003Ssam register short *aa ; 241*24003Ssam aa = (short *)kp->v_usdata; 242*24003Ssam sp = (short *)(*aa + (char *)kp) ; 243*24003Ssam } else { 244*24003Ssam c = kp->v_usdata[0] << 6; 245*24003Ssam sp = (short *)((char *)kp + SILOBAS + c); 246*24003Ssam } 247*24003Ssam nextsilo: 248*24003Ssam i = *(savsilo = sp); 249*24003Ssam if (i == 0) return(1); 250*24003Ssam if(xp->v_vers == V_NEW) 251*24003Ssam if( i > xp->v_silosiz ) { 252*24003Ssam printf("vx: %d exceeds silo size\n",i) ; 253*24003Ssam i = xp->v_silosiz; 254*24003Ssam } 255*24003Ssam for(sp++;i > 0;i--,sp++) { 256*24003Ssam c = ((struct silo *)sp)->port & 017; 257*24003Ssam tp = &vx_tty[c+n*16]; 258*24003Ssam if(xp->v_loport > c || c > xp->v_hiport) 259*24003Ssam continue; /* port out of bounds */ 260*24003Ssam if( (tp->t_state & TS_ISOPEN) == 0) { 261*24003Ssam wakeup((caddr_t)&tp->t_rawq); 262*24003Ssam continue; 263*24003Ssam } 264*24003Ssam c = ((struct silo *)sp)->data; 265*24003Ssam switch(((struct silo *)sp)->port&(PERROR|FERROR)) { 266*24003Ssam case PERROR: 267*24003Ssam case PERROR|FERROR: 268*24003Ssam if( (tp->t_flags&(EVENP|ODDP)) == EVENP 269*24003Ssam || (tp->t_flags & (EVENP|ODDP)) == ODDP ) 270*24003Ssam continue; 271*24003Ssam if(!(((struct silo *)sp)->port&FERROR)) 272*24003Ssam break; 273*24003Ssam case FERROR: 274*24003Ssam if(tp->t_flags & RAW) c = 0; 275*24003Ssam else c = tp->t_intrc; 276*24003Ssam } 277*24003Ssam (*linesw[tp->t_line].l_rint)(c, tp); 278*24003Ssam } 279*24003Ssam *savsilo = 0; 280*24003Ssam return(1); 281*24003Ssam } 282*24003Ssam 283*24003Ssam /* 284*24003Ssam * stty/gtty for VX 285*24003Ssam */ 286*24003Ssam vxioctl(dev, cmd, data, flag) 287*24003Ssam int dev; /* major, minor device numbers */ 288*24003Ssam int cmd; /* command */ 289*24003Ssam caddr_t data; 290*24003Ssam int flag; 291*24003Ssam { 292*24003Ssam register struct tty *tp; 293*24003Ssam register error; 294*24003Ssam 295*24003Ssam tp = &vx_tty[minor(dev) & 0377]; 296*24003Ssam error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag); 297*24003Ssam if (error == 0) 298*24003Ssam return error; 299*24003Ssam if((error = ttioctl(tp, cmd, data, flag)) >= 0) 300*24003Ssam { 301*24003Ssam if (cmd==TIOCSETP||cmd==TIOCSETN) 302*24003Ssam vxparam(dev); 303*24003Ssam return error; 304*24003Ssam } else 305*24003Ssam return ENOTTY; 306*24003Ssam } 307*24003Ssam 308*24003Ssam 309*24003Ssam vxparam(dev) 310*24003Ssam dev_t dev; 311*24003Ssam { 312*24003Ssam vxcparam(dev, 1); 313*24003Ssam } 314*24003Ssam 315*24003Ssam /* 316*24003Ssam * Set parameters from open or stty into the VX hardware 317*24003Ssam * registers. 318*24003Ssam */ 319*24003Ssam vxcparam(dev, wait) 320*24003Ssam dev_t dev; /* major, minor device numbers */ 321*24003Ssam int wait; /* nonzero if we should wait for finish */ 322*24003Ssam { 323*24003Ssam register struct tty *tp; 324*24003Ssam register struct vcx *xp; 325*24003Ssam register struct vxcmd *cp; 326*24003Ssam register s; 327*24003Ssam 328*24003Ssam tp = &vx_tty[minor(dev)]; /* pointer to tty structure for port */ 329*24003Ssam xp = (struct vcx *)tp->t_addr; /* pointer to VIOCX info/cmd buffer */ 330*24003Ssam cp = vobtain(xp); 331*24003Ssam s = spl8(); 332*24003Ssam cp->cmd = LPARAX; /* set command to "load parameters" */ 333*24003Ssam cp->par[1] = minor(dev)&017; /* port number */ 334*24003Ssam 335*24003Ssam cp->par[2] = (tp->t_flags&RAW)? 0 : tp->t_startc; /* XON char */ 336*24003Ssam cp->par[3] = (tp->t_flags&RAW)? 0 : tp->t_stopc; /* XOFF char */ 337*24003Ssam 338*24003Ssam if(tp->t_flags&(RAW|LITOUT) || 339*24003Ssam (tp->t_flags&(EVENP|ODDP)) == (EVENP|ODDP)) { 340*24003Ssam cp->par[4] = 0xc0; /* 8 bits of data */ 341*24003Ssam cp->par[7] = 0; /* no parity */ 342*24003Ssam } else { 343*24003Ssam cp->par[4] = 0x40; /* 7 bits of data */ 344*24003Ssam if((tp->t_flags&(EVENP|ODDP)) == ODDP) 345*24003Ssam cp->par[7] = 1; /* odd parity */ 346*24003Ssam else if((tp->t_flags&(EVENP|ODDP)) == EVENP) 347*24003Ssam cp->par[7] = 3; /* even parity */ 348*24003Ssam else 349*24003Ssam cp->par[7] = 0; /* no parity */ 350*24003Ssam } 351*24003Ssam cp->par[5] = 0x4; /* 1 stop bit */ 352*24003Ssam cp->par[6] = tp->t_ospeed; 353*24003Ssam 354*24003Ssam if (vcmd(xp->v_nbr, &cp->cmd) && wait) 355*24003Ssam sleep(cp,TTIPRI); 356*24003Ssam splx(s); 357*24003Ssam } 358*24003Ssam 359*24003Ssam /* 360*24003Ssam * VIOCX command response interrupt. 361*24003Ssam * For transmission, restart output to any active port. 362*24003Ssam * For all other commands, just clean up. 363*24003Ssam */ 364*24003Ssam vxxint(n,cp) 365*24003Ssam register int n; /* VIOC number */ 366*24003Ssam register struct vxcmd *cp; /* command structure */ 367*24003Ssam { 368*24003Ssam register struct vxmit *vp, *pvp; 369*24003Ssam register struct tty *tp; 370*24003Ssam register struct vcx *xp; 371*24003Ssam register struct tty *hp; 372*24003Ssam 373*24003Ssam xp = &vcx[n]; 374*24003Ssam cp = (struct vxcmd *)( (long *)cp - 1); 375*24003Ssam #if NVBSC > 0 376*24003Ssam switch(cp->cmd) { 377*24003Ssam case MDMCTL1: case HUNTMD1: case LPARAX1: 378*24003Ssam vrelease(xp, cp); 379*24003Ssam wakeup(cp); 380*24003Ssam return; 381*24003Ssam } 382*24003Ssam #endif 383*24003Ssam switch(cp->cmd&0xff00) { 384*24003Ssam case LIDENT: /* initialization complete */ 385*24003Ssam if (xp->v_state & V_RESETTING) { 386*24003Ssam vxfnreset(n,cp); 387*24003Ssam vinthandl(n,((V_BSY | RSPquals) << 8) | V_INTR); 388*24003Ssam } 389*24003Ssam cp->cmd++; 390*24003Ssam return; 391*24003Ssam case XMITDTA: case XMITIMM: 392*24003Ssam break; 393*24003Ssam case LPARAX: 394*24003Ssam wakeup(cp); 395*24003Ssam default: /* MDMCTL or FDTATOX */ 396*24003Ssam vrelease(xp, cp); 397*24003Ssam if (xp->v_state & V_RESETTING) { 398*24003Ssam vinthandl(n,((V_BSY | RSPquals) << 8) | V_INTR); 399*24003Ssam } 400*24003Ssam return; 401*24003Ssam } 402*24003Ssam for(vp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizvxmit); 403*24003Ssam vp >= (struct vxmit *)cp->par; 404*24003Ssam vp = (struct vxmit *) ((char *)vp - sizvxmit) ) 405*24003Ssam { 406*24003Ssam tp = &vx_tty[(vp->line & 017)+n*16]; 407*24003Ssam /* cjk buffer bug */ 408*24003Ssam #if NVBSC > 0 409*24003Ssam /* bsc change */ 410*24003Ssam if (tp->t_line == LDISP) { 411*24003Ssam vrelease(xp, cp); 412*24003Ssam bsctxd((vp->line & 017)); 413*24003Ssam return ; 414*24003Ssam } 415*24003Ssam /* End of bsc change */ 416*24003Ssam #endif 417*24003Ssam /* cjk */ 418*24003Ssam pvp = vp; 419*24003Ssam tp->t_state &= ~TS_BUSY; 420*24003Ssam if(tp->t_state & TS_FLUSH) { 421*24003Ssam tp->t_state &= ~TS_FLUSH; 422*24003Ssam wakeup( (caddr_t)&tp->t_state ) ; 423*24003Ssam } 424*24003Ssam else 425*24003Ssam ndflush(&tp->t_outq, vp->bcount+1); 426*24003Ssam } 427*24003Ssam xp->v_xmtcnt--; 428*24003Ssam vrelease(xp,cp); 429*24003Ssam if(xp->v_vers == V_NEW) { 430*24003Ssam vp = pvp; 431*24003Ssam xp->v_actport[(vp->line & 017) - xp->v_loport] |= 1 ; 432*24003Ssam if(vxstart(tp) && (cp = nextcmd(xp)) != NULL) 433*24003Ssam { 434*24003Ssam xp->v_xmtcnt++; 435*24003Ssam vcmd(n, &cp->cmd); 436*24003Ssam return ; 437*24003Ssam } 438*24003Ssam xp->v_actport[(vp->line & 017) - xp->v_loport] = 0 ; 439*24003Ssam return ; 440*24003Ssam } 441*24003Ssam xp->v_actflg = 1; 442*24003Ssam hp = &vx_tty[xp->v_hiport+n*16]; 443*24003Ssam for(tp = &vx_tty[xp->v_loport+n*16];tp <= hp;tp++) 444*24003Ssam if(vxstart(tp) && (cp = nextcmd(xp)) != NULL) 445*24003Ssam { 446*24003Ssam xp->v_xmtcnt++; 447*24003Ssam vcmd(n, &cp->cmd); 448*24003Ssam } 449*24003Ssam if( (cp = nextcmd(xp)) != NULL ) /* command to send ? */ 450*24003Ssam { 451*24003Ssam xp->v_xmtcnt++; 452*24003Ssam vcmd(n,&cp->cmd); 453*24003Ssam } 454*24003Ssam xp->v_actflg = 0; 455*24003Ssam } 456*24003Ssam 457*24003Ssam /* 458*24003Ssam * Force out partial XMIT command after timeout 459*24003Ssam */ 460*24003Ssam vxforce(xp) 461*24003Ssam register struct vcx *xp; 462*24003Ssam { 463*24003Ssam register struct vxcmd *cp; 464*24003Ssam register int s; 465*24003Ssam 466*24003Ssam s = spl8(); 467*24003Ssam if((cp = nextcmd(xp)) != NULL) { 468*24003Ssam xp->v_xmtcnt++; 469*24003Ssam vcmd(xp->v_nbr, &cp->cmd); 470*24003Ssam } 471*24003Ssam splx(s); 472*24003Ssam } 473*24003Ssam 474*24003Ssam /* 475*24003Ssam * Start (restart) transmission on the given VX line. 476*24003Ssam */ 477*24003Ssam vxstart(tp) 478*24003Ssam register struct tty *tp; 479*24003Ssam { 480*24003Ssam register short nch; 481*24003Ssam register struct vcx *xp; 482*24003Ssam register char *outb; 483*24003Ssam register full = 0; 484*24003Ssam int k, s, port; 485*24003Ssam 486*24003Ssam s = spl8(); 487*24003Ssam port = minor(tp->t_dev) & 017; 488*24003Ssam xp = (struct vcx *)tp->t_addr; 489*24003Ssam if (!(tp->t_state&(TS_TIMEOUT|TS_BUSY|TS_TTSTOP))) { 490*24003Ssam if (tp->t_outq.c_cc<=TTLOWAT(tp)) { 491*24003Ssam if (tp->t_state&TS_ASLEEP) { 492*24003Ssam tp->t_state &= ~TS_ASLEEP; 493*24003Ssam wakeup((caddr_t)&tp->t_outq); 494*24003Ssam } 495*24003Ssam if (tp->t_wsel) { 496*24003Ssam selwakeup(tp->t_wsel, tp->t_state & TS_WCOLL); 497*24003Ssam tp->t_wsel = 0; 498*24003Ssam tp->t_state &= ~TS_WCOLL; 499*24003Ssam } 500*24003Ssam } 501*24003Ssam if(tp->t_outq.c_cc == 0) { 502*24003Ssam splx(s); 503*24003Ssam return(0); 504*24003Ssam } 505*24003Ssam #ifdef VXPERF 506*24003Ssam scope_out(3); 507*24003Ssam #endif VXPERF 508*24003Ssam if(!(tp->t_flags&(RAW|LITOUT))) 509*24003Ssam full = 0200; 510*24003Ssam if((nch = ndqb(&tp->t_outq, full)) == 0) { 511*24003Ssam if(full) { 512*24003Ssam nch = getc(&tp->t_outq); 513*24003Ssam timeout(ttrstrt, (caddr_t)tp, (nch&0177) +6); 514*24003Ssam tp->t_state |= TS_TIMEOUT; 515*24003Ssam full = 0; 516*24003Ssam } 517*24003Ssam } else { 518*24003Ssam outb = (char *)tp->t_outq.c_cf; 519*24003Ssam tp->t_state |= TS_BUSY; 520*24003Ssam if(xp->v_vers == V_NEW) 521*24003Ssam k = xp->v_actport[port - xp->v_loport] ; 522*24003Ssam else 523*24003Ssam k = xp->v_actflg ; 524*24003Ssam 525*24003Ssam full = vsetq(xp, port, outb, nch); 526*24003Ssam 527*24003Ssam if( (k&1) == 0 ) { /* not called from vxxint */ 528*24003Ssam if(full || xp->v_xmtcnt == 0) { 529*24003Ssam outb = (char *)(&nextcmd(xp)->cmd); 530*24003Ssam xp->v_xmtcnt++; 531*24003Ssam vcmd(xp->v_nbr, outb ); 532*24003Ssam } else 533*24003Ssam timeout(vxforce,xp,3); 534*24003Ssam } 535*24003Ssam } 536*24003Ssam } 537*24003Ssam splx(s); 538*24003Ssam return(full); /* indicate if max commands or not */ 539*24003Ssam } 540*24003Ssam 541*24003Ssam /* 542*24003Ssam * Stop output on a line. 543*24003Ssam */ 544*24003Ssam vxstop(tp) 545*24003Ssam register struct tty *tp; 546*24003Ssam { 547*24003Ssam register s; 548*24003Ssam 549*24003Ssam s = spl8(); 550*24003Ssam if (tp->t_state & TS_BUSY) { 551*24003Ssam if ((tp->t_state&TS_TTSTOP)==0) { 552*24003Ssam tp->t_state |= TS_FLUSH; 553*24003Ssam } 554*24003Ssam } 555*24003Ssam splx(s); 556*24003Ssam } 557*24003Ssam 558*24003Ssam /* 559*24003Ssam * VIOCX Initialization. Makes free lists of command buffers. 560*24003Ssam * Resets all viocx's. Issues a LIDENT command to each 561*24003Ssam * viocx which establishes interrupt vectors and logical 562*24003Ssam * port numbers 563*24003Ssam */ 564*24003Ssam vxinit(i,wait) 565*24003Ssam register int i; 566*24003Ssam long wait; 567*24003Ssam { 568*24003Ssam register struct vcx *xp; /* ptr to VIOC-X info/cmd buffer */ 569*24003Ssam register struct vblok *kp; /* pointer to VIOC-X control block */ 570*24003Ssam register struct vxcmd *cp; /* pointer to a command buffer */ 571*24003Ssam register char *resp; /* pointer to response buffer */ 572*24003Ssam register int j; 573*24003Ssam register struct vcmds *cpp; 574*24003Ssam char type; 575*24003Ssam register struct bsc *bp; /* bsc change */ 576*24003Ssam extern struct bsc bsc[]; 577*24003Ssam 578*24003Ssam 579*24003Ssam kp = VBAS(i); /* get base adr of cntl blok for VIOC */ 580*24003Ssam 581*24003Ssam xp = &vcx[i]; /* index info/command buffers */ 582*24003Ssam cpp = &v_cmds[i]; 583*24003Ssam type = kp->v_ident; 584*24003Ssam vxtype[i] = 0; /* Type is Viox-x */ 585*24003Ssam switch(type) { 586*24003Ssam case VIOCX: 587*24003Ssam { 588*24003Ssam xp->v_vers = V_OLD ; 589*24003Ssam /* set DCD for printer ports */ 590*24003Ssam for(j = 0;j < 16;j++) 591*24003Ssam if (kp->v_portyp[j] == 4 ) 592*24003Ssam kp->v_dcd |= 1 << j ; 593*24003Ssam } 594*24003Ssam break ; 595*24003Ssam case NWVIOCX: 596*24003Ssam { 597*24003Ssam xp->v_vers = V_NEW ; 598*24003Ssam xp->v_silosiz = kp->v_maxsilo ; 599*24003Ssam /* set DCD for printer ports */ 600*24003Ssam for(j = 0;j < 16;j++) 601*24003Ssam if (kp->v_portyp[j] == 4 ) 602*24003Ssam kp->v_dcd |= 1 << j ; 603*24003Ssam } 604*24003Ssam break ; 605*24003Ssam case PVIOCX: 606*24003Ssam xp->v_vers = V_OLD ; 607*24003Ssam break ; 608*24003Ssam case NPVIOCX: 609*24003Ssam xp->v_vers = V_NEW ; 610*24003Ssam xp->v_silosiz = kp->v_maxsilo ; 611*24003Ssam break ; 612*24003Ssam #if NVBSC > 0 613*24003Ssam case VIOCB: /* old f/w, Bisync board */ 614*24003Ssam printf("%X: %x%x OLD VIOC-B, ", 615*24003Ssam (long)kp, (int)kp->v_ident, 616*24003Ssam (int)kp->v_fault); 617*24003Ssam xp->v_vers = V_OLD ; 618*24003Ssam /* save device specific info */ 619*24003Ssam for(bp = &bsc[0]; bp <= &bsc[NBSC]; bp++) 620*24003Ssam bp->b_devregs = (caddr_t)xp ; 621*24003Ssam printf("%d BSC Ports initialized.\n",NBSC); 622*24003Ssam break ; 623*24003Ssam 624*24003Ssam case NWVIOCB: /* new f/w, Bisync board */ 625*24003Ssam printf("%X: %x%x 16K VIOC-B, ", 626*24003Ssam (long)kp, (int)kp->v_ident, 627*24003Ssam (int)kp->v_fault); 628*24003Ssam xp->v_vers = V_NEW ; 629*24003Ssam xp->v_silosiz = kp->v_maxsilo ; 630*24003Ssam /* save device specific info */ 631*24003Ssam for(bp = &bsc[0]; bp <= &bsc[NBSC]; bp++) 632*24003Ssam bp->b_devregs = (caddr_t)xp ; 633*24003Ssam printf("%d BSC Ports initialized.\n",NBSC); 634*24003Ssam if(CBSIZE > kp->v_maxxmt) 635*24003Ssam printf("vxinit: Warning CBSIZE > maxxmt\n") ; 636*24003Ssam break ; 637*24003Ssam #endif 638*24003Ssam case VBOPID: /* VIOC-BOP */ 639*24003Ssam vxbbno++; 640*24003Ssam vxtype[i] = 1; 641*24003Ssam vxbopno[i] = vxbbno; 642*24003Ssam printf("VIOC-BOP no. %d at %lx\n",vxbopno[i],VIOCBAS[i]); 643*24003Ssam default: 644*24003Ssam return ; /* Not a viocx type */ 645*24003Ssam } 646*24003Ssam xp->v_nbr = -1; /* no number for it yet */ 647*24003Ssam xp->v_maxcmd = xp->v_vers == V_NEW ? 24 : 4; 648*24003Ssam 649*24003Ssam for(j=0; j<NVCXBUFS; j++) /* init all cmd buffers */ 650*24003Ssam { 651*24003Ssam cp = &xp->vx_lst[j]; /* index a buffer */ 652*24003Ssam cp->c_fwd = &xp->vx_lst[j+1]; /* point to next buf */ 653*24003Ssam } 654*24003Ssam xp->vx_avail = &xp->vx_lst[0]; /* set idx to 1st free buf */ 655*24003Ssam cp->c_fwd = (struct vxcmd *)0; /* mark last buf in free list */ 656*24003Ssam 657*24003Ssam cp = vobtain(xp); /* grap the control block */ 658*24003Ssam cp->cmd = LIDENT; /* set command type */ 659*24003Ssam cp->par[0] = i * 4 + VCVECT; /* ack vector */ 660*24003Ssam cp->par[1] = cp->par[0] + 1; /* cmd resp vector */ 661*24003Ssam cp->par[3] = cp->par[0] + 2; /* unsol intr vector */ 662*24003Ssam cp->par[4] = 15; /* max ports, no longer used */ 663*24003Ssam cp->par[5] = 0; /* set 1st port number */ 664*24003Ssam vcmd(i, &cp->cmd); /* initialize the VIOC-X */ 665*24003Ssam 666*24003Ssam if (!wait) return; 667*24003Ssam while(cp->cmd == LIDENT); /* wait for command completion */ 668*24003Ssam 669*24003Ssam /* calculate address of response buffer */ 670*24003Ssam resp = (char *)kp; 671*24003Ssam resp += kp->v_rspoff & 0x3FFF; 672*24003Ssam 673*24003Ssam if(resp[0] != 0 && (resp[0]&0177) != 3) /* did init work? */ 674*24003Ssam { 675*24003Ssam vrelease(xp,cp); /* init failed */ 676*24003Ssam return; /* try next VIOC-X */ 677*24003Ssam } 678*24003Ssam 679*24003Ssam xp->v_loport = cp->par[5]; /* save low port number */ 680*24003Ssam xp->v_hiport = cp->par[7];/* VIOC knows high port numbr */ 681*24003Ssam vrelease(xp,cp); /* done with this control block */ 682*24003Ssam xp->v_nbr = i; /* assign VIOC-X board number */ 683*24003Ssam } 684*24003Ssam 685*24003Ssam /* 686*24003Ssam * Obtain a command buffer 687*24003Ssam */ 688*24003Ssam struct vxcmd * 689*24003Ssam vobtain(xp) 690*24003Ssam register struct vcx *xp; 691*24003Ssam { 692*24003Ssam 693*24003Ssam register struct vxcmd *p; 694*24003Ssam register s; 695*24003Ssam 696*24003Ssam s = spl8(); 697*24003Ssam p = xp->vx_avail; 698*24003Ssam if(p == (struct vxcmd *)0) { 699*24003Ssam #ifdef VX_DEBUG 700*24003Ssam if (vxintr4 & VXNOBUF) vxintr4 &= ~VXNOBUF; 701*24003Ssam #endif 702*24003Ssam vpanic("vx: no buffs"); 703*24003Ssam vxstreset(xp - vcx); 704*24003Ssam splx(s); 705*24003Ssam return(vobtain(xp)); 706*24003Ssam } 707*24003Ssam xp->vx_avail = (xp->vx_avail)->c_fwd; 708*24003Ssam splx(s); 709*24003Ssam return( (struct vxcmd *)p); 710*24003Ssam } 711*24003Ssam 712*24003Ssam /* 713*24003Ssam * Release a command buffer 714*24003Ssam */ 715*24003Ssam vrelease(xp,cp) 716*24003Ssam register struct vcx *xp; 717*24003Ssam register struct vxcmd *cp; 718*24003Ssam { 719*24003Ssam 720*24003Ssam register s; 721*24003Ssam 722*24003Ssam #ifdef VX_DEBUG 723*24003Ssam if (vxintr4 & VXNOBUF) return; 724*24003Ssam #endif 725*24003Ssam s = spl8(); 726*24003Ssam cp->c_fwd = xp->vx_avail; 727*24003Ssam xp->vx_avail = cp; 728*24003Ssam splx(s); 729*24003Ssam } 730*24003Ssam 731*24003Ssam /* 732*24003Ssam * vxcmd - 733*24003Ssam * 734*24003Ssam */ 735*24003Ssam struct vxcmd * 736*24003Ssam nextcmd(xp) 737*24003Ssam register struct vcx *xp; 738*24003Ssam { 739*24003Ssam register struct vxcmd *cp; 740*24003Ssam register int s; 741*24003Ssam 742*24003Ssam s = spl8(); 743*24003Ssam cp = xp->vx_build; 744*24003Ssam xp->vx_build = (struct vxcmd *)0; 745*24003Ssam splx(s); 746*24003Ssam return(cp); 747*24003Ssam } 748*24003Ssam 749*24003Ssam /* 750*24003Ssam * assemble transmits into a multiple command. 751*24003Ssam * up to 8 transmits to 8 lines can be assembled together 752*24003Ssam */ 753*24003Ssam vsetq(xp ,d ,addr, cnt) 754*24003Ssam register struct vcx *xp; 755*24003Ssam caddr_t addr; 756*24003Ssam { 757*24003Ssam 758*24003Ssam register struct vxcmd *cp; 759*24003Ssam register struct vxmit *mp; 760*24003Ssam register char *p; 761*24003Ssam register i; 762*24003Ssam 763*24003Ssam cp = xp->vx_build; 764*24003Ssam if(cp == (struct vxcmd *)0) { 765*24003Ssam cp = vobtain(xp); 766*24003Ssam xp->vx_build = cp; 767*24003Ssam cp->cmd = XMITDTA; 768*24003Ssam } else { 769*24003Ssam if((cp->cmd & 07) == 07) { 770*24003Ssam vpanic("vx: vsetq overflow"); 771*24003Ssam vxstreset(xp->v_nbr); 772*24003Ssam return(0); 773*24003Ssam } 774*24003Ssam cp->cmd++; 775*24003Ssam } 776*24003Ssam 777*24003Ssam mp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizvxmit); 778*24003Ssam mp->bcount = cnt-1; 779*24003Ssam 780*24003Ssam mp->line = d; 781*24003Ssam if((xp->v_vers == V_NEW) && (cnt <= 6)) { 782*24003Ssam cp->cmd = XMITIMM ; 783*24003Ssam p = addr; 784*24003Ssam /* bcopy(addr, &(char *)mp->ostream, cnt) ; */ 785*24003Ssam } else { 786*24003Ssam addr = vtoph(0, (caddr_t)addr) ; /* should be a sys address */ 787*24003Ssam p = (char *)&addr; 788*24003Ssam cnt = sizeof addr; 789*24003Ssam /* mp->ostream = addr ; */ 790*24003Ssam } 791*24003Ssam for(i=0; i<cnt; i++) 792*24003Ssam mp->ostream[i] = *p++; 793*24003Ssam if(xp->v_vers == V_NEW) 794*24003Ssam return(1) ; 795*24003Ssam else 796*24003Ssam return((cp->cmd&07) == 7) ; /* Indicate if full */ 797*24003Ssam } 798*24003Ssam #endif 799