1*24002Ssam /* vxc.c 1.1 85/07/21 */ 2*24002Ssam 3*24002Ssam #include "vx.h" 4*24002Ssam #if NVX > 0 5*24002Ssam /* 6*24002Ssam * VIOC driver 7*24002Ssam */ 8*24002Ssam #include "../h/param.h" 9*24002Ssam #include "../h/file.h" 10*24002Ssam #include "../h/ioctl.h" 11*24002Ssam #include "../h/tty.h" 12*24002Ssam #include "../h/errno.h" 13*24002Ssam #include "../h/time.h" 14*24002Ssam #include "../h/kernel.h" 15*24002Ssam #include "../vba/vioc.h" 16*24002Ssam #include "../sna/snadebug.h" 17*24002Ssam #ifdef VXPERF 18*24002Ssam #include "../vba/scope.h" 19*24002Ssam #endif VXPERF 20*24002Ssam 21*24002Ssam #define CMDquals 0 22*24002Ssam #define RSPquals 1 23*24002Ssam #define UNSquals 2 24*24002Ssam 25*24002Ssam long reinit = 0; 26*24002Ssam extern struct vcx vcx[] ; 27*24002Ssam extern struct tty vx_tty[]; 28*24002Ssam struct vcmds v_cmds[NVIOCX] ; 29*24002Ssam 30*24002Ssam extern char vxtype[]; 31*24002Ssam extern char vxbbno; 32*24002Ssam extern char vxbopno[]; 33*24002Ssam #ifdef SNA_DEBUG 34*24002Ssam extern vbrall(); 35*24002Ssam #endif SNA_DEBUG 36*24002Ssam extern struct vxcmd *vobtain(); 37*24002Ssam 38*24002Ssam #ifdef VX_DEBUG 39*24002Ssam #include "../vba/vxdebug.h" 40*24002Ssam #endif 41*24002Ssam 42*24002Ssam /* 43*24002Ssam * Write a command out to the VIOC 44*24002Ssam */ 45*24002Ssam vcmd(n, cmdad) 46*24002Ssam register int n ; 47*24002Ssam register caddr_t cmdad ; /* command address */ 48*24002Ssam { 49*24002Ssam 50*24002Ssam register struct vcmds *cp ; 51*24002Ssam register struct vcx *xp; 52*24002Ssam int s ; 53*24002Ssam 54*24002Ssam s = spl8() ; 55*24002Ssam cp = &v_cmds[n] ; 56*24002Ssam xp = &vcx[n]; 57*24002Ssam if (xp->v_state&V_RESETTING && cmdad != NULL) { 58*24002Ssam /* 59*24002Ssam * When the vioc is resetting, don't process 60*24002Ssam * anything other than LIDENT commands. 61*24002Ssam */ 62*24002Ssam register struct vxcmd *cp = (struct vxcmd *) 63*24002Ssam ((char *)cmdad - sizeof(cp->c_fwd)); 64*24002Ssam if (cp->cmd != LIDENT) { 65*24002Ssam vrelease(xp, cp); 66*24002Ssam return(0); 67*24002Ssam } 68*24002Ssam } 69*24002Ssam if (cmdad != (caddr_t) 0) { 70*24002Ssam cp->cmdbuf[cp->v_fill] = cmdad ; 71*24002Ssam if( ++cp->v_fill >= VC_CMDBUFL ) cp->v_fill = 0 ; 72*24002Ssam if(cp->v_fill == cp->v_empty) { 73*24002Ssam vpanic("vc: CMD Q OVFLO") ; 74*24002Ssam vxstreset(n); 75*24002Ssam splx(s); 76*24002Ssam return(0); 77*24002Ssam } 78*24002Ssam cp->v_cmdsem++; 79*24002Ssam } 80*24002Ssam if(cp->v_cmdsem && cp->v_curcnt < vcx[n].v_maxcmd) { 81*24002Ssam cp->v_cmdsem--; 82*24002Ssam cp->v_curcnt++; 83*24002Ssam vinthandl(n, ((V_BSY | CMDquals) << 8) | V_INTR ) ; 84*24002Ssam } 85*24002Ssam splx(s) ; 86*24002Ssam } 87*24002Ssam 88*24002Ssam /* 89*24002Ssam * VIOC acknowledge interrupt. The VIOC has received the new 90*24002Ssam * command. If no errors, the new command becomes one of 16 (max) 91*24002Ssam * current commands being executed. 92*24002Ssam */ 93*24002Ssam vackint(n) 94*24002Ssam register n ; /* VIOC number */ 95*24002Ssam { 96*24002Ssam 97*24002Ssam register struct vblok *vp ; 98*24002Ssam register struct vcmds *cp ; 99*24002Ssam register s; 100*24002Ssam 101*24002Ssam #ifdef VXPERF 102*24002Ssam scope_out(5); 103*24002Ssam #endif VXPERF 104*24002Ssam if (vxtype[n]) { /* Its a BOP */ 105*24002Ssam #ifdef SNA_DEBUG 106*24002Ssam if (snadebug & SVIOC) 107*24002Ssam printf("vack: interrupt from BOP at VIOC%d,1st vector.\n",n); 108*24002Ssam vbrall(n); /* Int. from BOP, port 0 */ 109*24002Ssam #endif 110*24002Ssam return; 111*24002Ssam } 112*24002Ssam s = spl8(); 113*24002Ssam vp = VBAS(n) ; 114*24002Ssam cp = &v_cmds[n] ; 115*24002Ssam if( vp->v_vcid & V_ERR ) { 116*24002Ssam register char *resp; 117*24002Ssam register i; 118*24002Ssam printf ("INTR ERR type = %x VIOC = %x, v_dcd: %lx\n", 119*24002Ssam vp->v_vcid & 07, n, vp->v_dcd & 0xff); 120*24002Ssam /* resp = (char *)vp + (vp->v_rspoff & 0x7FFF); */ 121*24002Ssam resp = (char *)(&vcx[n])->v_mricmd; 122*24002Ssam for(i=0; i<16; i++) 123*24002Ssam printf("%x ", resp[i]&0xff); 124*24002Ssam vpanic( "\nvcc: vackint") ; 125*24002Ssam splx(s); 126*24002Ssam vxstreset(n); 127*24002Ssam return ; 128*24002Ssam } else 129*24002Ssam if((vp->v_hdwre&017) == CMDquals) { 130*24002Ssam #ifdef VX_DEBUG 131*24002Ssam if (vxintr4 & VXERR4) { /* causes VIOC INTR ERR 4 */ 132*24002Ssam register struct vxcmd *cp1; 133*24002Ssam register struct vxcmd *cp0 = (struct vxcmd *) 134*24002Ssam ((long)cp->cmdbuf[cp->v_empty] - 4); 135*24002Ssam if ((cp0->cmd == XMITDTA) || (cp0->cmd == XMITIMM)) { 136*24002Ssam cp1 = vobtain(&vcx[n]); 137*24002Ssam *cp1 = *cp0; 138*24002Ssam vxintr4 &= ~VXERR4; 139*24002Ssam vcmd(n,&cp1->cmd); 140*24002Ssam } 141*24002Ssam } 142*24002Ssam #endif 143*24002Ssam cp->v_curcmd[vp->v_vcid & VCMDLEN-1] = cp->cmdbuf[cp->v_empty] ; 144*24002Ssam if( ++cp->v_empty >= VC_CMDBUFL ) cp->v_empty = 0 ; 145*24002Ssam } 146*24002Ssam if( ++cp->v_itrempt >= VC_IQLEN ) cp->v_itrempt = 0 ; 147*24002Ssam vintempt(n) ; 148*24002Ssam splx(s); 149*24002Ssam vcmd(n, 0); /* queue next cmd, if any */ 150*24002Ssam } 151*24002Ssam 152*24002Ssam /* 153*24002Ssam * Command Response interrupt. The Vioc has completed 154*24002Ssam * a command. The command may now be returned to 155*24002Ssam * the appropriate device driver . 156*24002Ssam */ 157*24002Ssam vcmdrsp(n) 158*24002Ssam register n ; 159*24002Ssam { 160*24002Ssam 161*24002Ssam register struct vblok *vp ; 162*24002Ssam register struct vcmds *cp ; 163*24002Ssam register caddr_t cmd ; 164*24002Ssam register char *resp ; 165*24002Ssam register k ; 166*24002Ssam register int s ; 167*24002Ssam 168*24002Ssam #ifdef VXPERF 169*24002Ssam scope_out(6); 170*24002Ssam #endif VXPERF 171*24002Ssam if (vxtype[n]) { /* Its a BOP */ 172*24002Ssam printf("vcmdrsp: stray interrupt from BOP at VIOC%d...\n",n); 173*24002Ssam return; 174*24002Ssam } 175*24002Ssam s = spl8(); 176*24002Ssam vp = VBAS(n) ; 177*24002Ssam cp = &v_cmds[n] ; 178*24002Ssam resp = (char *)vp; 179*24002Ssam resp += vp->v_rspoff & 0x7FFF; 180*24002Ssam 181*24002Ssam if( (k=resp[1]) & V_UNBSY ) { 182*24002Ssam k &= VCMDLEN-1; 183*24002Ssam cmd = cp->v_curcmd[k]; 184*24002Ssam cp->v_curcmd[k] = (caddr_t)0; 185*24002Ssam cp->v_curcnt--; 186*24002Ssam k = *((short *)&resp[4]); /* cmd operation code */ 187*24002Ssam if((k & 0xFF00) == LIDENT) { /* want hiport number */ 188*24002Ssam for(k=0; k<VRESPLEN; k++) 189*24002Ssam cmd[k] = resp[k+4]; 190*24002Ssam } 191*24002Ssam resp[1] = 0; 192*24002Ssam vxxint(n, cmd) ; 193*24002Ssam if ((&vcx[n])->v_state == V_RESETTING) return; 194*24002Ssam } 195*24002Ssam else { 196*24002Ssam vpanic( "vc, cmdresp debug") ; 197*24002Ssam splx(s); 198*24002Ssam vxstreset(n); 199*24002Ssam return; 200*24002Ssam } 201*24002Ssam 202*24002Ssam vinthandl(n, ( (V_BSY | RSPquals) << 8 ) | V_INTR ) ; 203*24002Ssam splx(s); 204*24002Ssam 205*24002Ssam } 206*24002Ssam 207*24002Ssam 208*24002Ssam /* 209*24002Ssam * Unsolicited interrupt. 210*24002Ssam */ 211*24002Ssam vunsol(n) 212*24002Ssam register(n) ; 213*24002Ssam { 214*24002Ssam 215*24002Ssam register struct vblok *vp ; 216*24002Ssam register s; 217*24002Ssam 218*24002Ssam #ifdef VXPERF 219*24002Ssam scope_out(1); 220*24002Ssam #endif VXPERF 221*24002Ssam if (vxtype[n]) { /* Its a BOP */ 222*24002Ssam printf("vunsol: stray interrupt from BOP at VIOC%d...\n",n); 223*24002Ssam return; 224*24002Ssam } 225*24002Ssam s = spl8(); 226*24002Ssam vp = VBAS(n) ; 227*24002Ssam if(vp->v_uqual & V_UNBSY) { 228*24002Ssam vxrint(n) ; 229*24002Ssam vinthandl(n, ( (V_BSY | UNSquals) << 8 ) | V_INTR ) ; 230*24002Ssam splx(s); 231*24002Ssam } 232*24002Ssam else { 233*24002Ssam vpanic("vc: UNSOL INT ERR") ; 234*24002Ssam splx(s); 235*24002Ssam vxstreset(n); 236*24002Ssam } 237*24002Ssam } 238*24002Ssam 239*24002Ssam /* 240*24002Ssam * Enqueue an interrupt 241*24002Ssam */ 242*24002Ssam vinthandl(n, item) 243*24002Ssam register int n ; 244*24002Ssam register item ; 245*24002Ssam { 246*24002Ssam 247*24002Ssam register struct vcmds *cp ; 248*24002Ssam register int empflag = 0 ; 249*24002Ssam 250*24002Ssam cp = &v_cmds[n] ; 251*24002Ssam if( cp->v_itrfill == cp->v_itrempt ) empflag++ ; 252*24002Ssam cp->v_itrqueu[cp->v_itrfill] = item ; 253*24002Ssam if( ++cp->v_itrfill >= VC_IQLEN ) cp->v_itrfill = 0 ; 254*24002Ssam if(cp->v_itrfill == cp->v_itrempt) { 255*24002Ssam vpanic( "vc: INT Q OVFLO" ) ; 256*24002Ssam vxstreset(n); 257*24002Ssam } 258*24002Ssam else if( empflag ) vintempt(n) ; 259*24002Ssam } 260*24002Ssam 261*24002Ssam vintempt(n) 262*24002Ssam register int n ; 263*24002Ssam { 264*24002Ssam register struct vcmds *cp ; 265*24002Ssam register struct vblok *vp ; 266*24002Ssam register short item ; 267*24002Ssam register short *intr ; 268*24002Ssam 269*24002Ssam vp = VBAS(n) ; 270*24002Ssam if(vp->v_vioc & V_BSY) return ; 271*24002Ssam cp = &v_cmds[n] ; 272*24002Ssam if(cp->v_itrempt == cp->v_itrfill) return ; 273*24002Ssam item = cp->v_itrqueu[cp->v_itrempt] ; 274*24002Ssam intr = (short *)&vp->v_vioc ; 275*24002Ssam switch( (item >> 8) & 03 ) { 276*24002Ssam 277*24002Ssam case CMDquals: /* command */ 278*24002Ssam { 279*24002Ssam int phys; 280*24002Ssam 281*24002Ssam if(cp->v_empty == cp->v_fill || vp->v_vcbsy&V_BSY) 282*24002Ssam break; 283*24002Ssam (&vcx[n])->v_mricmd = (caddr_t)cp->cmdbuf[cp->v_empty]; 284*24002Ssam phys = vtoph(0, cp->cmdbuf[cp->v_empty]) ; /* should be a sys address */ 285*24002Ssam vp->v_vcp[0] = ((short *)&phys)[0]; 286*24002Ssam vp->v_vcp[1] = ((short *)&phys)[1]; 287*24002Ssam vp->v_vcbsy = V_BSY ; 288*24002Ssam *intr = item ; 289*24002Ssam } 290*24002Ssam #ifdef VXPERF 291*24002Ssam scope_out(4); 292*24002Ssam #endif VXPERF 293*24002Ssam break ; 294*24002Ssam 295*24002Ssam case RSPquals: /* command response */ 296*24002Ssam *intr = item ; 297*24002Ssam #ifdef VXPERF 298*24002Ssam scope_out(7); 299*24002Ssam #endif VXPERF 300*24002Ssam break ; 301*24002Ssam 302*24002Ssam case UNSquals: /* unsolicited interrupt */ 303*24002Ssam vp->v_uqual = 0 ; 304*24002Ssam *intr = item ; 305*24002Ssam #ifdef VXPERF 306*24002Ssam scope_out(2); 307*24002Ssam #endif VXPERF 308*24002Ssam break ; 309*24002Ssam } 310*24002Ssam } 311*24002Ssam 312*24002Ssam 313*24002Ssam /* start a reset on a vioc after error (hopefully) */ 314*24002Ssam vxstreset(n) 315*24002Ssam register n; 316*24002Ssam { 317*24002Ssam register struct vcx *xp; 318*24002Ssam register struct vblok *vp ; 319*24002Ssam register struct vxcmd *cp; 320*24002Ssam register int j; 321*24002Ssam extern int vxinreset(); 322*24002Ssam int s ; 323*24002Ssam 324*24002Ssam s = spl8() ; 325*24002Ssam vp = VBAS(n); 326*24002Ssam xp = &vcx[n]; 327*24002Ssam 328*24002Ssam if (xp->v_state&V_RESETTING) 329*24002Ssam /* 330*24002Ssam * Avoid infinite recursion. 331*24002Ssam */ 332*24002Ssam return; 333*24002Ssam 334*24002Ssam /* 335*24002Ssam * Zero out the vioc structures, mark the vioc as being 336*24002Ssam * reset, reinitialize the free command list, reset the vioc 337*24002Ssam * and start a timer to check on the progress of the reset. 338*24002Ssam */ 339*24002Ssam bzero(&v_cmds[n], sizeof(struct vcmds)); 340*24002Ssam bzero(xp, sizeof(struct vcx)); 341*24002Ssam 342*24002Ssam /* 343*24002Ssam * Setting V_RESETTING prevents others from issuing 344*24002Ssam * commands while allowing currently queued commands to 345*24002Ssam * be passed to the VIOC. 346*24002Ssam */ 347*24002Ssam xp->v_state |= V_RESETTING; 348*24002Ssam for(j=0; j<NVCXBUFS; j++) /* init all cmd buffers */ 349*24002Ssam { 350*24002Ssam cp = &xp->vx_lst[j]; /* index a buffer */ 351*24002Ssam cp->c_fwd = &xp->vx_lst[j+1]; /* point to next buf */ 352*24002Ssam } 353*24002Ssam xp->vx_avail = &xp->vx_lst[0]; /* set idx to 1st free buf */ 354*24002Ssam cp->c_fwd = (struct vxcmd *)0; /* mark last buf in free list */ 355*24002Ssam 356*24002Ssam printf("resetting VIOC %x .. ", n); 357*24002Ssam 358*24002Ssam vp->v_fault = 0 ; 359*24002Ssam vp->v_vioc = V_BSY ; 360*24002Ssam vp->v_hdwre = V_RESET ; /* reset interrupt */ 361*24002Ssam 362*24002Ssam timeout(vxinreset, (caddr_t)n, hz*5); 363*24002Ssam splx(s); 364*24002Ssam return; 365*24002Ssam } 366*24002Ssam 367*24002Ssam /* continue processing a reset on a vioc after an error (hopefully) */ 368*24002Ssam vxinreset(vioc) 369*24002Ssam caddr_t vioc; 370*24002Ssam { 371*24002Ssam register struct vcx *xp; 372*24002Ssam register struct vblok *vp ; 373*24002Ssam register int n = (int)vioc; 374*24002Ssam int s = spl8(); 375*24002Ssam printf("vxinreset "); 376*24002Ssam 377*24002Ssam vp = VBAS(n); 378*24002Ssam xp = &vcx[n]; 379*24002Ssam 380*24002Ssam /* 381*24002Ssam * See if the vioc has reset. 382*24002Ssam */ 383*24002Ssam if (vp->v_fault != VREADY) { 384*24002Ssam printf("failed\n"); 385*24002Ssam splx(s); 386*24002Ssam return; 387*24002Ssam } 388*24002Ssam 389*24002Ssam /* 390*24002Ssam * Send a LIDENT to the vioc and mess with carrier flags 391*24002Ssam * on parallel printer ports. 392*24002Ssam */ 393*24002Ssam vxinit(n, 0); 394*24002Ssam splx(s); 395*24002Ssam } 396*24002Ssam 397*24002Ssam /* 398*24002Ssam * Restore modem control, parameters and restart output. 399*24002Ssam * Since the vioc can handle no more then 24 commands at a time 400*24002Ssam * and we could generate as many as 48 commands, we must do this in 401*24002Ssam * phases, issuing no more then 16 commands at a time. 402*24002Ssam */ 403*24002Ssam /* finish the reset on the vioc after an error (hopefully) */ 404*24002Ssam vxfnreset(n, cp) 405*24002Ssam register int n; 406*24002Ssam register struct vxcmd *cp; 407*24002Ssam { 408*24002Ssam register struct vcx *xp; 409*24002Ssam register struct vblok *vp ; 410*24002Ssam register struct tty *tp; 411*24002Ssam register int i; 412*24002Ssam register int on; 413*24002Ssam extern int vxrestart(); 414*24002Ssam int s = spl8(); 415*24002Ssam printf("vxfnreset "); 416*24002Ssam 417*24002Ssam vp = VBAS(n); 418*24002Ssam xp = &vcx[n]; 419*24002Ssam 420*24002Ssam xp->v_loport = cp->par[5]; /* save low port number */ 421*24002Ssam xp->v_hiport = cp->par[7];/* VIOC knows high port numbr */ 422*24002Ssam vrelease(xp,cp); /* done with this control block */ 423*24002Ssam xp->v_nbr = n; /* assign VIOC-X board number */ 424*24002Ssam 425*24002Ssam xp->v_state &= ~V_RESETTING; 426*24002Ssam 427*24002Ssam vp->v_vcid = 0; 428*24002Ssam 429*24002Ssam /* 430*24002Ssam * Restore modem information and control. 431*24002Ssam */ 432*24002Ssam for(i=xp->v_loport; i<=xp->v_hiport; i++) { 433*24002Ssam tp = &vx_tty[i+n*16]; 434*24002Ssam if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) { 435*24002Ssam tp->t_state &= ~TS_CARR_ON; 436*24002Ssam vcmodem(tp->t_dev, VMOD_ON); 437*24002Ssam if (tp->t_state&TS_CARR_ON) { 438*24002Ssam wakeup((caddr_t)&tp->t_canq) ; 439*24002Ssam } 440*24002Ssam else { 441*24002Ssam if(tp->t_state & TS_ISOPEN) { 442*24002Ssam ttyflush(tp, FREAD|FWRITE); 443*24002Ssam if(tp->t_state&TS_FLUSH) 444*24002Ssam wakeup((caddr_t)&tp->t_state) ; 445*24002Ssam if((tp->t_flags&NOHANG)==0) { 446*24002Ssam gsignal(tp->t_pgrp, SIGHUP) ; 447*24002Ssam gsignal(tp->t_pgrp, SIGCONT); 448*24002Ssam } 449*24002Ssam } 450*24002Ssam } 451*24002Ssam } 452*24002Ssam /* 453*24002Ssam * If carrier has changed while we were resetting, 454*24002Ssam * take appropriate action. 455*24002Ssam */ 456*24002Ssam /* 457*24002Ssam on = vp->v_dcd & 1<<i; 458*24002Ssam if (on && (tp->t_state&TS_CARR_ON) == 0) { 459*24002Ssam tp->t_state |= TS_CARR_ON ; 460*24002Ssam wakeup((caddr_t)&tp->t_canq) ; 461*24002Ssam } else if (!on && tp->t_state&TS_CARR_ON) { 462*24002Ssam tp->t_state &= ~TS_CARR_ON ; 463*24002Ssam if(tp->t_state & TS_ISOPEN) { 464*24002Ssam ttyflush(tp, FREAD|FWRITE); 465*24002Ssam if(tp->t_state&TS_FLUSH) 466*24002Ssam wakeup((caddr_t)&tp->t_state) ; 467*24002Ssam if((tp->t_flags&NOHANG)==0) { 468*24002Ssam gsignal(tp->t_pgrp, SIGHUP) ; 469*24002Ssam gsignal(tp->t_pgrp, SIGCONT); 470*24002Ssam } 471*24002Ssam } 472*24002Ssam } 473*24002Ssam */ 474*24002Ssam } 475*24002Ssam 476*24002Ssam xp->v_state |= V_RESETTING; 477*24002Ssam 478*24002Ssam timeout(vxrestart, (caddr_t)n, hz); 479*24002Ssam splx(s); 480*24002Ssam } 481*24002Ssam 482*24002Ssam /* 483*24002Ssam * Restore a particular aspect of the VIOC. 484*24002Ssam */ 485*24002Ssam vxrestart(vioc) 486*24002Ssam caddr_t vioc; 487*24002Ssam { 488*24002Ssam register struct tty *tp, *tp0; 489*24002Ssam register struct vcx *xp; 490*24002Ssam register int i, cnt; 491*24002Ssam register int n = (int)vioc; 492*24002Ssam int s = spl8(); 493*24002Ssam 494*24002Ssam cnt = n>>8; 495*24002Ssam printf("vxrestart %d ",cnt); 496*24002Ssam n &= 0xff; 497*24002Ssam 498*24002Ssam tp0 = &vx_tty[n*16]; 499*24002Ssam xp = &vcx[n]; 500*24002Ssam 501*24002Ssam xp->v_state &= ~V_RESETTING; 502*24002Ssam 503*24002Ssam for(i=xp->v_loport; i<=xp->v_hiport; i++) { 504*24002Ssam tp = tp0 + i; 505*24002Ssam if (cnt != 0) { 506*24002Ssam tp->t_state &= ~(TS_BUSY|TS_TIMEOUT); 507*24002Ssam if(tp->t_state&(TS_ISOPEN|TS_WOPEN)) /* restart pending output */ 508*24002Ssam vxstart(tp); 509*24002Ssam } else { 510*24002Ssam if (tp->t_state&(TS_WOPEN|TS_ISOPEN)) 511*24002Ssam vxcparam(tp->t_dev, 0); 512*24002Ssam } 513*24002Ssam } 514*24002Ssam 515*24002Ssam if (cnt == 0) { 516*24002Ssam xp->v_state |= V_RESETTING; 517*24002Ssam timeout(vxrestart, (caddr_t)(n + 1*256), hz); 518*24002Ssam } else 519*24002Ssam printf("done\n"); 520*24002Ssam splx(s); 521*24002Ssam } 522*24002Ssam 523*24002Ssam vxreset(dev) 524*24002Ssam dev_t dev; 525*24002Ssam { 526*24002Ssam vxstreset(minor(dev)>>4); /* completes asynchronously */ 527*24002Ssam } 528*24002Ssam 529*24002Ssam vxfreset(n) 530*24002Ssam register int n; 531*24002Ssam { 532*24002Ssam register struct vblok *vp; 533*24002Ssam 534*24002Ssam if (n < 0 || n > NVX || VBAS(n) == NULL) 535*24002Ssam return(ENODEV); 536*24002Ssam vcx[n].v_state &= ~V_RESETTING; 537*24002Ssam vxstreset(n); 538*24002Ssam return(0); /* completes asynchronously */ 539*24002Ssam } 540*24002Ssam #endif 541*24002Ssam 542