1*24000Ssam /* cy.c 1.1 85/07/21 */ 2*24000Ssam /* cy.c Tahoe version Mar 1983. */ 3*24000Ssam 4*24000Ssam #include "cy.h" 5*24000Ssam #if NCY > 0 /* number of CYPHER tapes in system */ 6*24000Ssam /* 7*24000Ssam * Cypher tape driver 8*24000Ssam * 9*24000Ssam */ 10*24000Ssam #include "../h/param.h" 11*24000Ssam #include "../h/systm.h" 12*24000Ssam #include "../h/vm.h" 13*24000Ssam #include "../h/buf.h" 14*24000Ssam #include "../h/dir.h" 15*24000Ssam #include "../h/conf.h" 16*24000Ssam #include "../h/user.h" 17*24000Ssam #include "../h/file.h" 18*24000Ssam #include "../machine/pte.h" 19*24000Ssam #include "../vba/vbavar.h" 20*24000Ssam #include "../h/mtio.h" 21*24000Ssam #include "../machine/mtpr.h" 22*24000Ssam #include "../h/ioctl.h" 23*24000Ssam #include "../h/cmap.h" 24*24000Ssam #include "../h/uio.h" 25*24000Ssam 26*24000Ssam #include "../vba/cyvar.h" 27*24000Ssam 28*24000Ssam #define NTM 1 /* number of TAPEMASTER controllers */ 29*24000Ssam 30*24000Ssam /* 31*24000Ssam * There is a ccybuf per tape controller. 32*24000Ssam * It is used as the token to pass to the control routines 33*24000Ssam * and also acts as a lock on the slaves on the 34*24000Ssam * controller, since there is only one per controller. 35*24000Ssam * In particular, when the tape is rewinding on close we release 36*24000Ssam * the user process but any further attempts to use the tape drive 37*24000Ssam * before the rewind completes will hang waiting for ccybuf. 38*24000Ssam */ 39*24000Ssam struct buf ccybuf[NTM]; 40*24000Ssam 41*24000Ssam /* 42*24000Ssam * Raw tape operations use rcybuf. The driver 43*24000Ssam * notices when rcybuf is being used and allows the user 44*24000Ssam * program to continue after errors and read records 45*24000Ssam * not of the standard length (BSIZE). 46*24000Ssam */ 47*24000Ssam struct buf rcybuf[NTM]; 48*24000Ssam long cybufused = 0; 49*24000Ssam 50*24000Ssam /* 51*24000Ssam * Driver interface routines and variables. 52*24000Ssam */ 53*24000Ssam int cyprobe(), cyslave(), cyattach(), cydgo(), cyintr(); 54*24000Ssam int cywait(), cyrewind(); 55*24000Ssam unsigned tminphys(); 56*24000Ssam struct vba_ctlr *cyminfo[NTM]; 57*24000Ssam struct vba_device *cydinfo[NCY]; 58*24000Ssam struct buf cyutab[NCY]; 59*24000Ssam short cytotm[NCY]; 60*24000Ssam extern char cyutl[]; 61*24000Ssam long cystd[] = { 0x400000, 0 }; 62*24000Ssam struct vba_driver cydriver = 63*24000Ssam { cyprobe, cyslave, cyattach, cydgo, cystd, "yc", cydinfo, "cy", 64*24000Ssam cyminfo, 0 }; 65*24000Ssam 66*24000Ssam /* bits in minor device */ 67*24000Ssam #define CYUNIT(dev) (minor(dev)&07) /* tape unit number */ 68*24000Ssam #define TMUNIT(dev) (cytotm[CYUNIT(dev)]) /* tape controller number */ 69*24000Ssam #define T_NOREWIND 0x08 /* no rewind bit */ 70*24000Ssam #define T_100IPS 0x10 /* high speed flag */ 71*24000Ssam 72*24000Ssam int pflag; /* probe flag, set every interrupt by cyintr */ 73*24000Ssam 74*24000Ssam #define INF (daddr_t)1000000L 75*24000Ssam extern int hz; 76*24000Ssam 77*24000Ssam struct scp /* SYSTEM CONFIGUREATION POINTER */ 78*24000Ssam { 79*24000Ssam char sysbus ; /* width of system buss 0=8;1=16 */ 80*24000Ssam char nu1 ; 81*24000Ssam char pt_scb[4] ; /* pointer to ->SYSTEM CONFIGUREATION BLOCK */ 82*24000Ssam }; 83*24000Ssam 84*24000Ssam /* absolute address - jumpered on the controller */ 85*24000Ssam #define SCP ((struct scp *)0xc0000c06) 86*24000Ssam 87*24000Ssam struct Scb /* SYSTEM CONFIGUREATION BLOCK */ 88*24000Ssam { 89*24000Ssam char sysblk[1] ; /* 0x03 fixed value code */ 90*24000Ssam char nu2[1] ; 91*24000Ssam char pt_ccb[4] ; /* pointer to ->CHANNEL CONTROL BLOCK */ 92*24000Ssam }Scb; 93*24000Ssam 94*24000Ssam struct ccb /* CHANNEL CONTROL BLOCK */ 95*24000Ssam { 96*24000Ssam char ccw[1] ; /* 0x11 normal; 0x09 clear non_vect interrupt */ 97*24000Ssam char gate[1] ; /* This is "the" GATE */ 98*24000Ssam char pt_tpb[4] ; /* pointer to ->TAPE OPERATION BLOCK or MOVE BLOCK */ 99*24000Ssam }ccb; 100*24000Ssam 101*24000Ssam struct tpb /* TAPE OPERATIONS PARAMETER BLOCK */ 102*24000Ssam { 103*24000Ssam long cmd ; /* COMMAND (input) */ 104*24000Ssam char control[2] ; /* CONTROL (input) */ 105*24000Ssam short count ; /* RETURN COUNT (output) */ 106*24000Ssam short size ; /* BUFFER SIZE (input/output) */ 107*24000Ssam short rec_over ; /* RECORDS/OVERRUN (input/output) */ 108*24000Ssam char pt_data[4] ; /* pointer to ->SOURCE/DEST (input) */ 109*24000Ssam char status[2] ; /* STATUS (output) */ 110*24000Ssam char pt_link[4] ; /* pointer to ->INTERRUPT/PARAMETER BLOCK (input) */ 111*24000Ssam } tpb[NTM]; 112*24000Ssam 113*24000Ssam struct tpb cycool /* tape parameter block to clear interrupts */ 114*24000Ssam = { 115*24000Ssam 0L, /* command */ 116*24000Ssam 0, 0, /* control */ 117*24000Ssam 0, /* count */ 118*24000Ssam 0, /* size */ 119*24000Ssam 0, /* rec_over */ 120*24000Ssam 0, 0, 0, 0, /* pt_data */ 121*24000Ssam 0, 0, /* status */ 122*24000Ssam 0, 0, 0, 0 /* pt_link */ 123*24000Ssam } ; 124*24000Ssam /* 125*24000Ssam * Software state per tape transport. 126*24000Ssam * 127*24000Ssam * 1. A tape drive is a unique-open device; we refuse opens when it is already. 128*24000Ssam * 2. We keep track of the current position on a block tape and seek 129*24000Ssam * before operations by forward/back spacing if necessary. 130*24000Ssam * 3. We remember if the last operation was a write on a tape, so if a tape 131*24000Ssam * is open read write and the last thing done is a write we can 132*24000Ssam * write a standard end of tape mark (two eofs). 133*24000Ssam */ 134*24000Ssam struct cy_softc { 135*24000Ssam char cy_openf; /* lock against multiple opens */ 136*24000Ssam char cy_lastiow; /* last op was a write */ 137*24000Ssam daddr_t cy_blkno; /* block number, for block device tape */ 138*24000Ssam daddr_t cy_nxrec; /* position of end of tape, if known */ 139*24000Ssam daddr_t cy_timo; /* time until timeout expires */ 140*24000Ssam short cy_tact; /* timeout is active */ 141*24000Ssam short cy_count; /* return count of last operation */ 142*24000Ssam char cy_status[2]; /* return status of last operation */ 143*24000Ssam } cy_softc[NTM]; 144*24000Ssam 145*24000Ssam /* 146*24000Ssam * I/O buffer for raw devices. 147*24000Ssam */ 148*24000Ssam char cybuf[TBUFSIZ*NBPG]; /* 10k buffer */ 149*24000Ssam 150*24000Ssam /* 151*24000Ssam * States for um->um_tab.b_active, the per controller state flag. 152*24000Ssam * This is used to sequence control in the driver. 153*24000Ssam */ 154*24000Ssam #define SSEEK 1 /* seeking */ 155*24000Ssam #define SIO 2 /* doing seq i/o */ 156*24000Ssam #define SCOM 3 /* sending control command */ 157*24000Ssam #define SREW 4 /* sending a drive rewind */ 158*24000Ssam 159*24000Ssam /* 160*24000Ssam * Determine if there is a controller for 161*24000Ssam * a cypher at address ctlr_vaddr. 162*24000Ssam * Reset the controller. 163*24000Ssam * Our goal is to make the device interrupt. 164*24000Ssam */ 165*24000Ssam cyprobe(ctlr_vaddr) 166*24000Ssam caddr_t ctlr_vaddr; 167*24000Ssam { 168*24000Ssam int *ip; 169*24000Ssam 170*24000Ssam pflag = 0; /* clear interrupt flag */ 171*24000Ssam if (badcyaddr(ctlr_vaddr + 1)) /* check for versabuss timeout */ 172*24000Ssam return (0); 173*24000Ssam /* 174*24000Ssam * Initialize the system configuration pointer 175*24000Ssam */ 176*24000Ssam ip = (int *)vtopte(0, btop(SCP)); *ip &= ~PG_PROT; *ip |= PG_KW; 177*24000Ssam mtpr(SCP, TBIS); 178*24000Ssam SCP->sysbus = 1; /* system width = 16 bits. */ 179*24000Ssam /* initialize the pointer to the system configuration block */ 180*24000Ssam set_pointer((int)&Scb.sysblk[0], (char *)SCP->pt_scb); 181*24000Ssam /* 182*24000Ssam * Initialize the system configuration block. 183*24000Ssam */ 184*24000Ssam Scb.sysblk[0] = 0x3; /* fixed value */ 185*24000Ssam /* initialize the pointer to the channel control block */ 186*24000Ssam set_pointer((int)&ccb.ccw[0], (char *)Scb.pt_ccb); 187*24000Ssam /* 188*24000Ssam * Initialize the channel control block. 189*24000Ssam */ 190*24000Ssam ccb.ccw[0] = 0x11; /* normal interrupts */ 191*24000Ssam /* initialize the pointer to the tape parameter block */ 192*24000Ssam set_pointer((int)&tpb[0], (char *)ccb.pt_tpb); 193*24000Ssam /* 194*24000Ssam * set the command to be CONFIGURE. 195*24000Ssam */ 196*24000Ssam tpb[0].cmd = CONFIG; 197*24000Ssam tpb[0].control[0] = CW_I; /* interrupt on completion */ 198*24000Ssam tpb[0].control[1] = CW_16bits; 199*24000Ssam ccb.gate[0] = GATE_CLOSED; 200*24000Ssam *ip &= ~PG_PROT; *ip |= PG_KR; 201*24000Ssam mtpr(SCP, TBIS); 202*24000Ssam TM_ATTENTION(ctlr_vaddr, 0xff); /* execute! */ 203*24000Ssam if (cywait()) return(0); 204*24000Ssam else return(1); 205*24000Ssam } 206*24000Ssam 207*24000Ssam /* 208*24000Ssam * Due to a design flaw, we cannot ascertain if the tape 209*24000Ssam * exists or not unless it is on line - ie: unless a tape is 210*24000Ssam * mounted. This is too severe a restriction to bear, 211*24000Ssam * so all units are assumed to exist. 212*24000Ssam */ 213*24000Ssam /*ARGSUSED*/ 214*24000Ssam cyslave(ui, ctlr_vaddr) 215*24000Ssam struct vba_device *ui; 216*24000Ssam caddr_t ctlr_vaddr; 217*24000Ssam { 218*24000Ssam 219*24000Ssam return (1); 220*24000Ssam } 221*24000Ssam 222*24000Ssam /* 223*24000Ssam * Record attachment of the unit to the controller. 224*24000Ssam */ 225*24000Ssam /*ARGSUSED*/ 226*24000Ssam cyattach(ui) 227*24000Ssam struct vba_device *ui; 228*24000Ssam { 229*24000Ssam 230*24000Ssam /* 231*24000Ssam * Cytotm is used in TMUNIT to index the ccybuf and rcybuf 232*24000Ssam * arrays given a cy unit number. 233*24000Ssam */ 234*24000Ssam cytotm[ui->ui_unit] = ui->ui_mi->um_ctlr; 235*24000Ssam } 236*24000Ssam 237*24000Ssam int cytimer(); 238*24000Ssam /* 239*24000Ssam * Open the device. Tapes are unique open 240*24000Ssam * devices, so we refuse if it is already open. 241*24000Ssam * We also check that a tape is available, and 242*24000Ssam * don't block waiting here; if you want to wait 243*24000Ssam * for a tape you should timeout in user code. 244*24000Ssam */ 245*24000Ssam cyopen(dev, flag) 246*24000Ssam dev_t dev; 247*24000Ssam int flag; 248*24000Ssam { 249*24000Ssam register int cyunit, s; 250*24000Ssam register struct vba_device *ui; 251*24000Ssam register struct cy_softc *cy; 252*24000Ssam 253*24000Ssam cyunit = CYUNIT(dev); 254*24000Ssam if (cyunit>=NCY || (cy = &cy_softc[cyunit])->cy_openf || 255*24000Ssam (ui = cydinfo[cyunit]) == 0 || ui->ui_alive == 0) 256*24000Ssam return ENXIO; 257*24000Ssam cycommand(dev, (int)DRIVE_S, 1); /* drive status */ 258*24000Ssam uncache(&tpb[cyunit].status[0]); 259*24000Ssam if ((tpb[cyunit].status[0]&(CS_DR|CS_OL)) != (CS_DR|CS_OL)) { 260*24000Ssam uprintf("cy%d: not online\n", cyunit); 261*24000Ssam return EIO; 262*24000Ssam } 263*24000Ssam if ((flag&FWRITE) && (tpb[cyunit].status[0]&CS_P)) { 264*24000Ssam uprintf("cy%d: no write ring\n", cyunit); 265*24000Ssam return EIO; 266*24000Ssam } 267*24000Ssam cy->cy_openf = 1; 268*24000Ssam cy->cy_blkno = (daddr_t)0; 269*24000Ssam cy->cy_nxrec = INF; 270*24000Ssam cy->cy_lastiow = 0; 271*24000Ssam s = spl8(); 272*24000Ssam if (cy->cy_tact == 0) { 273*24000Ssam cy->cy_timo = INF; 274*24000Ssam cy->cy_tact = 1; 275*24000Ssam timeout(cytimer, (caddr_t)dev, 5*hz); 276*24000Ssam } 277*24000Ssam splx(s); 278*24000Ssam return 0; 279*24000Ssam } 280*24000Ssam 281*24000Ssam /* 282*24000Ssam * Close tape device. 283*24000Ssam * 284*24000Ssam * If tape was open for writing or last operation was 285*24000Ssam * a write, then write two EOF's and backspace over the last one. 286*24000Ssam * Unless this is a non-rewinding special file, rewind the tape. 287*24000Ssam * Make the tape available to others. 288*24000Ssam */ 289*24000Ssam cyclose(dev, flag) 290*24000Ssam register dev_t dev; 291*24000Ssam register flag; 292*24000Ssam { 293*24000Ssam register struct cy_softc *cy = &cy_softc[CYUNIT(dev)]; 294*24000Ssam 295*24000Ssam if (flag == FWRITE || (flag&FWRITE) && cy->cy_lastiow) { 296*24000Ssam cycommand(dev, (int)WRIT_FM, 1); /* write file mark */ 297*24000Ssam cycommand(dev, (int)WRIT_FM, 1); 298*24000Ssam cycommand(dev, (int)SP_BACK, 1); /* space back */ 299*24000Ssam } 300*24000Ssam if ((minor(dev)&T_NOREWIND) == 0) 301*24000Ssam /* 302*24000Ssam * 0 count means don't hang waiting for rewind complete 303*24000Ssam * rather ccybuf stays busy until the operation completes 304*24000Ssam * preventing further opens from completing by 305*24000Ssam * preventing a SENSE operation from completing. 306*24000Ssam */ 307*24000Ssam cycommand(dev, (int)REWD_TA, 0); 308*24000Ssam cy->cy_openf = 0; 309*24000Ssam } 310*24000Ssam 311*24000Ssam int commflag; /* signal cystrategy that it is called from cycommand */ 312*24000Ssam 313*24000Ssam /* 314*24000Ssam * Execute a command on the tape drive 315*24000Ssam * a specified number of times. 316*24000Ssam */ 317*24000Ssam cycommand(dev, com, count) 318*24000Ssam dev_t dev; 319*24000Ssam int com, count; 320*24000Ssam { 321*24000Ssam register struct buf *bp; 322*24000Ssam int s; 323*24000Ssam 324*24000Ssam bp = &ccybuf[TMUNIT(dev)]; 325*24000Ssam s = spl8(); 326*24000Ssam while (bp->b_flags&B_BUSY) { 327*24000Ssam /* 328*24000Ssam * This special check is because B_BUSY never 329*24000Ssam * gets cleared in the non-waiting rewind case. 330*24000Ssam */ 331*24000Ssam if (bp->b_repcnt == 0 && (bp->b_flags&B_DONE)) 332*24000Ssam break; 333*24000Ssam bp->b_flags |= B_WANTED; 334*24000Ssam sleep((caddr_t)bp, PRIBIO); 335*24000Ssam } 336*24000Ssam bp->b_flags = B_BUSY|B_READ; 337*24000Ssam splx(s); 338*24000Ssam bp->b_dev = dev; 339*24000Ssam bp->b_repcnt = count; 340*24000Ssam bp->b_command = com; 341*24000Ssam bp->b_blkno = 0; 342*24000Ssam commflag = 1; 343*24000Ssam cystrategy(bp); 344*24000Ssam commflag = 0; 345*24000Ssam /* 346*24000Ssam * In case of rewind from close, don't wait. 347*24000Ssam * This is the only case where count can be 0. 348*24000Ssam */ 349*24000Ssam if (count == 0) 350*24000Ssam return; 351*24000Ssam iowait(bp); 352*24000Ssam if (bp->b_flags&B_WANTED) 353*24000Ssam wakeup((caddr_t)bp); 354*24000Ssam bp->b_flags &= B_ERROR; 355*24000Ssam } 356*24000Ssam 357*24000Ssam /* 358*24000Ssam * Queue a tape operation. 359*24000Ssam */ 360*24000Ssam cystrategy(bp) 361*24000Ssam register struct buf *bp; 362*24000Ssam { 363*24000Ssam int cyunit = CYUNIT(bp->b_dev); 364*24000Ssam int s; 365*24000Ssam register struct vba_ctlr *um; 366*24000Ssam register struct buf *dp; 367*24000Ssam 368*24000Ssam /* 369*24000Ssam * Put transfer at end of unit queue 370*24000Ssam */ 371*24000Ssam dp = &cyutab[cyunit]; 372*24000Ssam bp->av_forw = NULL; 373*24000Ssam s = spl8(); 374*24000Ssam /* 375*24000Ssam * Next piece of logic takes care of unusual cases when more than 376*24000Ssam * a full block is required. 377*24000Ssam * The driver reads the tape to a temporary buffer and 378*24000Ssam * then moves the amount needed back to the process. 379*24000Ssam * In this case, the flag NOT1K is set. 380*24000Ssam */ 381*24000Ssam 382*24000Ssam if (commflag == 0) 383*24000Ssam buf_setup(bp, 1); 384*24000Ssam um = cydinfo[cyunit]->ui_mi; 385*24000Ssam if (dp->b_actf == NULL) { 386*24000Ssam dp->b_actf = bp; 387*24000Ssam /* 388*24000Ssam * Transport not already active... 389*24000Ssam * put at end of controller queue. 390*24000Ssam */ 391*24000Ssam dp->b_forw = NULL; 392*24000Ssam if (um->um_tab.b_actf == NULL) 393*24000Ssam um->um_tab.b_actf = dp; 394*24000Ssam else 395*24000Ssam um->um_tab.b_actl->b_forw = dp; 396*24000Ssam um->um_tab.b_actl = dp; 397*24000Ssam } else 398*24000Ssam dp->b_actl->av_forw = bp; 399*24000Ssam dp->b_actl = bp; 400*24000Ssam /* 401*24000Ssam * If the controller is not busy, get 402*24000Ssam * it going. 403*24000Ssam */ 404*24000Ssam if (um->um_tab.b_active == 0) 405*24000Ssam cystart(um); 406*24000Ssam splx(s); 407*24000Ssam } 408*24000Ssam 409*24000Ssam /* 410*24000Ssam * Start activity on a cypher controller. 411*24000Ssam */ 412*24000Ssam cystart(um) 413*24000Ssam register struct vba_ctlr *um; 414*24000Ssam { 415*24000Ssam register struct buf *bp, *dp; 416*24000Ssam register struct tpb *tp; 417*24000Ssam register struct cy_softc *cy; 418*24000Ssam register int phadr; 419*24000Ssam int cyunit, timer; 420*24000Ssam daddr_t blkno; 421*24000Ssam caddr_t ctlr_vaddr; 422*24000Ssam ctlr_vaddr = um->um_addr; 423*24000Ssam /* 424*24000Ssam * Look for an idle transport on the controller. 425*24000Ssam */ 426*24000Ssam loop: 427*24000Ssam if ((dp = um->um_tab.b_actf) == NULL) 428*24000Ssam return; 429*24000Ssam if ((bp = dp->b_actf) == NULL) { 430*24000Ssam um->um_tab.b_actf = dp->b_forw; 431*24000Ssam goto loop; 432*24000Ssam } 433*24000Ssam cyunit = CYUNIT(bp->b_dev); 434*24000Ssam cy = &cy_softc[cyunit]; 435*24000Ssam tp = &tpb[cyunit]; 436*24000Ssam /* 437*24000Ssam * Default is that last command was NOT a write command; 438*24000Ssam * if we do a write command we will notice this in cyintr(). 439*24000Ssam */ 440*24000Ssam cy->cy_lastiow = 0; 441*24000Ssam uncache(&tp->status[0]); 442*24000Ssam uncache(&tp->count); 443*24000Ssam cy->cy_count = TM_SHORT(tp->count); 444*24000Ssam cy->cy_status[0] = tp->status[0]; 445*24000Ssam cy->cy_status[1] = tp->status[1]; 446*24000Ssam if (cy->cy_openf < 0 || 447*24000Ssam (bp->b_command != DRIVE_S) && 448*24000Ssam ((tp->status[0]&CS_OL) != CS_OL)) { 449*24000Ssam /* 450*24000Ssam * Have had a hard error on a non-raw tape 451*24000Ssam * or the tape unit is now unavailable 452*24000Ssam * (e.g. taken off line). 453*24000Ssam */ 454*24000Ssam bp->b_flags |= B_ERROR; 455*24000Ssam goto next; 456*24000Ssam } 457*24000Ssam if (bp == &ccybuf[TMUNIT(bp->b_dev)]) { 458*24000Ssam /* 459*24000Ssam * Execute control operation with the specified count. 460*24000Ssam * Set next state; give 5 minutes to complete 461*24000Ssam * rewind, or 10 seconds per iteration (minimum 60 462*24000Ssam * seconds and max 5 minutes) to complete other ops. 463*24000Ssam */ 464*24000Ssam if (bp->b_command == REWD_TA) { 465*24000Ssam um->um_tab.b_active = SREW; 466*24000Ssam cy->cy_timo = 5 * 60; 467*24000Ssam } else { 468*24000Ssam um->um_tab.b_active = SCOM; 469*24000Ssam cy->cy_timo = imin(imax(10*(int)bp->b_repcnt, 60), 5*60); 470*24000Ssam } 471*24000Ssam /* 472*24000Ssam * Prepare parameter block for controller 473*24000Ssam */ 474*24000Ssam tp->cmd = bp->b_command; 475*24000Ssam tp->control[0] = (CW_I | (cyunit<<CW_TSs)); 476*24000Ssam if (minor(bp->b_dev)&T_100IPS) 477*24000Ssam tp->control[1] = (CW_100ips | CW_16bits); 478*24000Ssam else tp->control[1] = (CW_25ips | CW_16bits); 479*24000Ssam if (bp->b_command == SP_BACK) { 480*24000Ssam tp->control[1] |= CW_R; 481*24000Ssam tp->cmd = SPACE; 482*24000Ssam tp->rec_over = TM_SHORT((short)bp->b_repcnt); 483*24000Ssam } 484*24000Ssam if (bp->b_command == SP_FORW) 485*24000Ssam tp->rec_over = TM_SHORT((short)bp->b_repcnt); 486*24000Ssam if (bp->b_command == SRFM_BK) { 487*24000Ssam tp->control[1] |= CW_R; 488*24000Ssam tp->cmd = SERH_FM; 489*24000Ssam tp->rec_over = TM_SHORT((short)bp->b_repcnt); 490*24000Ssam } 491*24000Ssam if (bp->b_command == SRFM_FD) 492*24000Ssam tp->rec_over = TM_SHORT((short)bp->b_repcnt); 493*24000Ssam tp->status[0] = tp->status[1] = 0; 494*24000Ssam tp->count = 0; 495*24000Ssam set_pointer((int)&tpb[cyunit], (char *)ccb.pt_tpb); 496*24000Ssam goto dobpcmd; 497*24000Ssam } 498*24000Ssam /* 499*24000Ssam * The following checks handle boundary cases for operation 500*24000Ssam * on non-raw tapes. On raw tapes the initialization of 501*24000Ssam * cy->cy_nxrec by cyphys causes them to be skipped normally 502*24000Ssam */ 503*24000Ssam if (bdbtofsb(bp->b_blkno) > cy->cy_nxrec) { 504*24000Ssam /* 505*24000Ssam * Can't read past known end-of-file. 506*24000Ssam */ 507*24000Ssam bp->b_flags |= B_ERROR; 508*24000Ssam bp->b_error = ENXIO; 509*24000Ssam goto next; 510*24000Ssam } 511*24000Ssam if (bdbtofsb(bp->b_blkno) == cy->cy_nxrec && 512*24000Ssam bp->b_flags&B_READ) { 513*24000Ssam /* 514*24000Ssam * Reading at end of file returns 0 bytes. 515*24000Ssam */ 516*24000Ssam bp->b_resid = bp->b_bcount; 517*24000Ssam clrbuf(bp); 518*24000Ssam goto next; 519*24000Ssam } 520*24000Ssam if ((bp->b_flags&B_READ) == 0) 521*24000Ssam /* 522*24000Ssam * Writing sets EOF 523*24000Ssam */ 524*24000Ssam cy->cy_nxrec = bdbtofsb(bp->b_blkno) + 1; 525*24000Ssam /* 526*24000Ssam * If the data transfer command is in the correct place, 527*24000Ssam * set up the tape parameter block, and start the i/o. 528*24000Ssam */ 529*24000Ssam if ((blkno = cy->cy_blkno) == bdbtofsb(bp->b_blkno)) { 530*24000Ssam um->um_tab.b_active = SIO; 531*24000Ssam cy->cy_timo = 60; /* premature, but should serve */ 532*24000Ssam 533*24000Ssam phadr = get_ioadr(bp, cybuf, CYmap, cyutl); 534*24000Ssam 535*24000Ssam if ( (bp->b_flags & B_READ) == 0) 536*24000Ssam tp->cmd = WRIT_BU; 537*24000Ssam else tp->cmd = READ_BU; 538*24000Ssam tp->control[0] = (CW_I | (cyunit<<CW_TSs)); 539*24000Ssam if (minor(bp->b_dev)&T_100IPS) 540*24000Ssam tp->control[1] = (CW_100ips | CW_16bits); 541*24000Ssam else tp->control[1] = (CW_25ips | CW_16bits); 542*24000Ssam tp->status[0] = tp->status[1] = 0; 543*24000Ssam tp->count = 0; 544*24000Ssam tp->size = TM_SHORT(bp->b_bcount); 545*24000Ssam set_pointer(phadr, (char *)tp->pt_data); 546*24000Ssam set_pointer((int)&tpb[cyunit], (char *)ccb.pt_tpb); 547*24000Ssam goto dobpcmd; 548*24000Ssam } 549*24000Ssam /* 550*24000Ssam * Tape positioned incorrectly; 551*24000Ssam * set to seek forwards or backwards to the correct spot. 552*24000Ssam */ 553*24000Ssam um->um_tab.b_active = SSEEK; 554*24000Ssam tp->cmd = SPACE; 555*24000Ssam tp->control[0] = (CW_I | (cyunit<<CW_TSs)); 556*24000Ssam if (minor(bp->b_dev)&T_100IPS) 557*24000Ssam tp->control[1] = (CW_100ips | CW_16bits); 558*24000Ssam else tp->control[1] = (CW_25ips | CW_16bits); 559*24000Ssam tp->status[0] = tp->status[1] = 0; 560*24000Ssam set_pointer((int)&tpb[cyunit], (char *)ccb.pt_tpb); 561*24000Ssam if (blkno < bdbtofsb(bp->b_blkno)) 562*24000Ssam tp->rec_over = TM_SHORT((short)(blkno - bdbtofsb(bp->b_blkno))); 563*24000Ssam else { 564*24000Ssam tp->rec_over = TM_SHORT((short)(bdbtofsb(bp->b_blkno) - blkno)); 565*24000Ssam tp->control[1] |= CW_R; 566*24000Ssam } 567*24000Ssam cy->cy_timo = imin(imax(10 * (int)TM_SHORT(tp->rec_over), 60), 5 * 60); 568*24000Ssam dobpcmd: 569*24000Ssam /* 570*24000Ssam * Do the command in bp. 571*24000Ssam */ 572*24000Ssam timer = 8000; /* software tolerance for gate open */ 573*24000Ssam uncache(&ccb.gate[0]); 574*24000Ssam while (ccb.gate[0] != GATE_OPEN) { 575*24000Ssam if (--timer == 0) { 576*24000Ssam ccb.ccw[0] = 0x9; /* forget it...... */ 577*24000Ssam TM_RESET(ctlr_vaddr, 0xff); 578*24000Ssam bp->b_flags |= B_ERROR; 579*24000Ssam goto next; 580*24000Ssam } 581*24000Ssam uncache(&ccb.gate[0]); 582*24000Ssam } 583*24000Ssam ccb.ccw[0] = 0x11; /* normal mode */ 584*24000Ssam ccb.gate[0] = GATE_CLOSED; 585*24000Ssam TM_ATTENTION(ctlr_vaddr, 0xff); /* execute! */ 586*24000Ssam return; 587*24000Ssam 588*24000Ssam next: 589*24000Ssam /* 590*24000Ssam * Done with this operation due to error or 591*24000Ssam * the fact that it doesn't do anything. 592*24000Ssam * dequeue the transfer and continue processing this slave. 593*24000Ssam */ 594*24000Ssam um->um_tab.b_errcnt = 0; 595*24000Ssam dp->b_actf = bp->av_forw; 596*24000Ssam iodone(bp); 597*24000Ssam goto loop; 598*24000Ssam } 599*24000Ssam 600*24000Ssam /* 601*24000Ssam * Kept for historical reasons. Probably not neccessary. 602*24000Ssam */ 603*24000Ssam cydgo(um) 604*24000Ssam struct vba_ctlr *um; 605*24000Ssam { 606*24000Ssam } 607*24000Ssam 608*24000Ssam /* 609*24000Ssam * Cy interrupt routine. 610*24000Ssam */ 611*24000Ssam /*ARGSUSED*/ 612*24000Ssam cyintr(ctlr) 613*24000Ssam int ctlr; 614*24000Ssam { 615*24000Ssam struct buf *dp; 616*24000Ssam register struct buf *bp; 617*24000Ssam register struct tpb *tp; 618*24000Ssam register struct vba_ctlr *um = cyminfo[ctlr]; 619*24000Ssam register struct cy_softc *cy; 620*24000Ssam caddr_t ctlr_vaddr; 621*24000Ssam int cyunit; 622*24000Ssam register state; 623*24000Ssam 624*24000Ssam /* 625*24000Ssam * First we clear the interrupt and close the gate. 626*24000Ssam */ 627*24000Ssam ctlr_vaddr = um->um_addr; 628*24000Ssam ccb.ccw[0] = 0x9; /* clear the interrupt */ 629*24000Ssam ccb.gate[0] = GATE_CLOSED; 630*24000Ssam set_pointer((int)&cycool, (char *)ccb.pt_tpb); 631*24000Ssam cycool.cmd = NO_OP; /* no operation */ 632*24000Ssam cycool.control[0] = 0; /* No INTERRUPTS */ 633*24000Ssam cycool.control[1] = 0; 634*24000Ssam TM_ATTENTION(ctlr_vaddr, 0xff); /* cool it ! */ 635*24000Ssam cywait(); 636*24000Ssam /* 637*24000Ssam * Now we can start handling the interrupt. 638*24000Ssam */ 639*24000Ssam pflag = 1; /* set for the probe routine */ 640*24000Ssam if (intenable == 0) return; /* ignore all interrupts */ 641*24000Ssam if ((dp = um->um_tab.b_actf) == NULL) 642*24000Ssam return; 643*24000Ssam bp = dp->b_actf; 644*24000Ssam cyunit = CYUNIT(bp->b_dev); 645*24000Ssam tp = &tpb[cyunit]; 646*24000Ssam cy = &cy_softc[cyunit]; 647*24000Ssam /* 648*24000Ssam * If last command was a rewind, and tape is still 649*24000Ssam * rewinding, wait for the rewind complete interrupt. 650*24000Ssam */ 651*24000Ssam if (um->um_tab.b_active == SREW) { 652*24000Ssam um->um_tab.b_active = SCOM; 653*24000Ssam /* uncache(&tp->status[1]); */ 654*24000Ssam /* if (tp->status[1]&CS_CC != CS_CC) { */ /* not completed */ 655*24000Ssam /* cy->cy_timo = 5*60; */ /* 5 minutes */ 656*24000Ssam /* return; */ 657*24000Ssam /* } */ 658*24000Ssam } 659*24000Ssam /* 660*24000Ssam * An operation completed... update status 661*24000Ssam */ 662*24000Ssam cy->cy_timo = INF; 663*24000Ssam uncache(&tp->count); 664*24000Ssam uncache(&tp->status[0]); 665*24000Ssam cy->cy_count = TM_SHORT(tp->count); 666*24000Ssam cy->cy_status[0] = tp->status[0]; 667*24000Ssam cy->cy_status[1] = tp->status[1]; 668*24000Ssam if ((bp->b_flags & B_READ) == 0) 669*24000Ssam cy->cy_lastiow = 1; 670*24000Ssam state = um->um_tab.b_active; 671*24000Ssam um->um_tab.b_active = 0; 672*24000Ssam /* 673*24000Ssam * Check for errors. 674*24000Ssam */ 675*24000Ssam if (tp->status[1] & CS_ERm) { 676*24000Ssam /* 677*24000Ssam * If we hit the end of the tape file, update our position. 678*24000Ssam */ 679*24000Ssam if (tp->status[0] & CS_FM) 680*24000Ssam { 681*24000Ssam cyseteof(bp); /* set blkno and nxrec */ 682*24000Ssam state = SCOM; 683*24000Ssam goto opdone; 684*24000Ssam } 685*24000Ssam /* If reading raw device and block was too short ignore the 686*24000Ssam * error and let the user program decide what to do. 687*24000Ssam */ 688*24000Ssam if ((tp->status[0] & ER_TOF) && /* (bp->b_flags & B_PHYS) && */ 689*24000Ssam (bp->b_flags & B_READ)) goto cont; 690*24000Ssam cy->cy_openf = -1; /* cause to close */ 691*24000Ssam printf("cy%d: hard error bn %d er=%x\n", cyunit, 692*24000Ssam bp->b_blkno, tp->status[1]&CS_ERm); 693*24000Ssam bp->b_flags |= B_ERROR; 694*24000Ssam goto opdone; 695*24000Ssam } 696*24000Ssam /* 697*24000Ssam * If we were reading block tape and the record 698*24000Ssam * was too long, we consider this an error. 699*24000Ssam */ 700*24000Ssam cont: 701*24000Ssam uncache(&tp->count); 702*24000Ssam uncache(&tp->cmd); 703*24000Ssam if (bp != &rcybuf[TMUNIT(bp->b_dev)] && (tp->cmd == READ_BU) && 704*24000Ssam bp->b_bcount < TM_SHORT(tp->count)) { 705*24000Ssam cy->cy_openf = -1; /* cause to close */ 706*24000Ssam printf("cy%d: error - tape block too long \n", cyunit); 707*24000Ssam bp->b_flags |= B_ERROR; 708*24000Ssam goto opdone; 709*24000Ssam } 710*24000Ssam /* 711*24000Ssam * No errors. 712*24000Ssam * Advance tape control FSM. 713*24000Ssam */ 714*24000Ssam switch (state) { 715*24000Ssam 716*24000Ssam case SIO: 717*24000Ssam /* 718*24000Ssam * Read/write increments tape block number 719*24000Ssam */ 720*24000Ssam cy->cy_blkno++; 721*24000Ssam end_transfer(bp, cybuf, CYmap, cyutl); 722*24000Ssam goto opdone; 723*24000Ssam 724*24000Ssam case SCOM: 725*24000Ssam /* 726*24000Ssam * For forward/backward space record update current position. 727*24000Ssam */ 728*24000Ssam if (bp == &ccybuf[TMUNIT(bp->b_dev)]) 729*24000Ssam switch (bp->b_command) { 730*24000Ssam 731*24000Ssam case SP_FORW: 732*24000Ssam cy->cy_blkno += bp->b_repcnt; 733*24000Ssam break; 734*24000Ssam 735*24000Ssam case SP_BACK: 736*24000Ssam cy->cy_blkno -= bp->b_repcnt; 737*24000Ssam break; 738*24000Ssam } 739*24000Ssam goto opdone; 740*24000Ssam 741*24000Ssam case SSEEK: 742*24000Ssam cy->cy_blkno = bdbtofsb(bp->b_blkno); 743*24000Ssam goto opcont; 744*24000Ssam 745*24000Ssam default: 746*24000Ssam panic("cyintr"); 747*24000Ssam } 748*24000Ssam opdone: 749*24000Ssam /* 750*24000Ssam * Reset error count and remove 751*24000Ssam * from device queue. 752*24000Ssam */ 753*24000Ssam um->um_tab.b_errcnt = 0; 754*24000Ssam dp->b_actf = bp->av_forw; 755*24000Ssam uncache(&tp->count); 756*24000Ssam bp->b_resid = bp->b_bcount - TM_SHORT(tp->count); 757*24000Ssam iodone(bp); 758*24000Ssam /* 759*24000Ssam * Circulate slave to end of controller 760*24000Ssam * queue to give other slaves a chance. 761*24000Ssam */ 762*24000Ssam um->um_tab.b_actf = dp->b_forw; 763*24000Ssam if (dp->b_actf) { 764*24000Ssam dp->b_forw = NULL; 765*24000Ssam if (um->um_tab.b_actf == NULL) 766*24000Ssam um->um_tab.b_actf = dp; 767*24000Ssam else 768*24000Ssam um->um_tab.b_actl->b_forw = dp; 769*24000Ssam um->um_tab.b_actl = dp; 770*24000Ssam } 771*24000Ssam if (um->um_tab.b_actf == 0) 772*24000Ssam return; 773*24000Ssam opcont: 774*24000Ssam cystart(um); 775*24000Ssam } 776*24000Ssam 777*24000Ssam cytimer(dev) 778*24000Ssam int dev; 779*24000Ssam { 780*24000Ssam register struct cy_softc *cy = &cy_softc[CYUNIT(dev)]; 781*24000Ssam int s; 782*24000Ssam 783*24000Ssam if (cy->cy_timo != INF && (cy->cy_timo -= 5) < 0) { 784*24000Ssam printf("cy%d: lost interrupt\n", CYUNIT(dev)); 785*24000Ssam cy->cy_timo = INF; 786*24000Ssam s = spl8(); 787*24000Ssam cyintr(TMUNIT(dev)); 788*24000Ssam splx(s); 789*24000Ssam return; 790*24000Ssam } 791*24000Ssam if (cy->cy_timo != INF ) timeout(cytimer, (caddr_t)dev, 5*hz); 792*24000Ssam } 793*24000Ssam 794*24000Ssam cyseteof(bp) 795*24000Ssam register struct buf *bp; 796*24000Ssam { 797*24000Ssam register int cyunit = CYUNIT(bp->b_dev); 798*24000Ssam register struct cy_softc *cy = &cy_softc[cyunit]; 799*24000Ssam register struct tpb *tp; 800*24000Ssam 801*24000Ssam tp = &tpb[cyunit]; 802*24000Ssam uncache(&tp->rec_over); 803*24000Ssam if (bp == &ccybuf[TMUNIT(bp->b_dev)]) { 804*24000Ssam if (cy->cy_blkno > bdbtofsb(bp->b_blkno)) { 805*24000Ssam /* reversing */ 806*24000Ssam cy->cy_nxrec = bdbtofsb(bp->b_blkno) - (int)TM_SHORT(tp->rec_over); 807*24000Ssam cy->cy_blkno = cy->cy_nxrec; 808*24000Ssam } else { 809*24000Ssam /* spacing forward */ 810*24000Ssam cy->cy_blkno = bdbtofsb(bp->b_blkno) + (int)TM_SHORT(tp->rec_over); 811*24000Ssam cy->cy_nxrec = cy->cy_blkno - 1; 812*24000Ssam } 813*24000Ssam return; 814*24000Ssam } 815*24000Ssam /* eof on read */ 816*24000Ssam cy->cy_nxrec = bdbtofsb(bp->b_blkno); 817*24000Ssam } 818*24000Ssam 819*24000Ssam cyread(dev, uio) 820*24000Ssam dev_t dev; 821*24000Ssam struct uio *uio; 822*24000Ssam { 823*24000Ssam register error; 824*24000Ssam 825*24000Ssam error = cyphys(dev, uio); 826*24000Ssam if (error) 827*24000Ssam return error; 828*24000Ssam while (cybufused) sleep (&cybufused, PRIBIO+1); 829*24000Ssam cybufused = 1; 830*24000Ssam error = physio(cystrategy, &rcybuf[TMUNIT(dev)], dev, B_READ, tminphys, uio); 831*24000Ssam cybufused = 0; 832*24000Ssam wakeup (&cybufused); 833*24000Ssam return error; 834*24000Ssam } 835*24000Ssam 836*24000Ssam cywrite(dev, uio) 837*24000Ssam dev_t dev; 838*24000Ssam struct uio *uio; 839*24000Ssam { 840*24000Ssam register error; 841*24000Ssam 842*24000Ssam error = cyphys(dev, uio); 843*24000Ssam if (error) 844*24000Ssam return error; 845*24000Ssam while (cybufused) sleep (&cybufused, PRIBIO+1); 846*24000Ssam cybufused = 1; 847*24000Ssam error = physio(cystrategy, &rcybuf[TMUNIT(dev)], dev, B_WRITE, tminphys, uio); 848*24000Ssam cybufused = 0; 849*24000Ssam wakeup (&cybufused); 850*24000Ssam return error; 851*24000Ssam } 852*24000Ssam 853*24000Ssam 854*24000Ssam cyreset(uban) 855*24000Ssam int uban; 856*24000Ssam { 857*24000Ssam register struct vba_ctlr *um; 858*24000Ssam register cy0f, cyunit; 859*24000Ssam register struct vba_device *ui; 860*24000Ssam register struct buf *dp; 861*24000Ssam 862*24000Ssam for (cy0f = 0; cy0f < NTM; cy0f++) { 863*24000Ssam if ((um = cyminfo[cy0f]) == 0 || um->um_alive == 0 || 864*24000Ssam um->um_vbanum != uban) 865*24000Ssam continue; 866*24000Ssam printf(" cy%d", cy0f); 867*24000Ssam um->um_tab.b_active = 0; 868*24000Ssam um->um_tab.b_actf = um->um_tab.b_actl = 0; 869*24000Ssam for (cyunit = 0; cyunit < NCY; cyunit++) { 870*24000Ssam if ((ui = cydinfo[cyunit]) == 0 || ui->ui_mi != um || 871*24000Ssam ui->ui_alive == 0) 872*24000Ssam continue; 873*24000Ssam dp = &cyutab[cyunit]; 874*24000Ssam dp->b_active = 0; 875*24000Ssam dp->b_forw = 0; 876*24000Ssam dp->b_command = DRIVE_R; 877*24000Ssam if (um->um_tab.b_actf == NULL) 878*24000Ssam um->um_tab.b_actf = dp; 879*24000Ssam else 880*24000Ssam um->um_tab.b_actl->b_forw = dp; 881*24000Ssam um->um_tab.b_actl = dp; 882*24000Ssam if (cy_softc[cyunit].cy_openf > 0) 883*24000Ssam cy_softc[cyunit].cy_openf = -1; 884*24000Ssam } 885*24000Ssam cystart(um); 886*24000Ssam } 887*24000Ssam } 888*24000Ssam 889*24000Ssam 890*24000Ssam cyioctl(dev, cmd, data, flag) 891*24000Ssam caddr_t data; 892*24000Ssam dev_t dev; 893*24000Ssam { 894*24000Ssam int cyunit = CYUNIT(dev); 895*24000Ssam register struct cy_softc *cy = &cy_softc[cyunit]; 896*24000Ssam register struct buf *bp = &ccybuf[TMUNIT(dev)]; 897*24000Ssam register callcount; 898*24000Ssam int fcount; 899*24000Ssam struct mtop *mtop; 900*24000Ssam struct mtget *mtget; 901*24000Ssam /* we depend of the values and order of the MT codes here */ 902*24000Ssam static cyops[] = 903*24000Ssam {WRIT_FM, SRFM_FD, SRFM_BK, SP_FORW, SP_BACK, REWD_TA, OFF_UNL, NO_OP}; 904*24000Ssam 905*24000Ssam switch (cmd) { 906*24000Ssam case MTIOCTOP: /* tape operation */ 907*24000Ssam mtop = (struct mtop *)data; 908*24000Ssam switch(mtop->mt_op) { 909*24000Ssam case MTWEOF: 910*24000Ssam callcount = mtop->mt_count; 911*24000Ssam fcount = 1; 912*24000Ssam break; 913*24000Ssam case MTFSF: case MTBSF: 914*24000Ssam callcount = mtop->mt_count; 915*24000Ssam fcount = INF; 916*24000Ssam break; 917*24000Ssam case MTFSR: case MTBSR: 918*24000Ssam callcount = 1; 919*24000Ssam fcount = mtop->mt_count; 920*24000Ssam break; 921*24000Ssam case MTREW: case MTOFFL: case MTNOP: 922*24000Ssam callcount = 1; 923*24000Ssam fcount = 1; 924*24000Ssam break; 925*24000Ssam default: 926*24000Ssam return ENXIO; 927*24000Ssam } 928*24000Ssam if (callcount <= 0 || fcount <= 0) 929*24000Ssam return EINVAL; 930*24000Ssam while (--callcount >= 0) { 931*24000Ssam cycommand(dev, cyops[mtop->mt_op], fcount); 932*24000Ssam if ((bp->b_flags&B_ERROR) || cy->cy_status[1]&CS_ERm) 933*24000Ssam break; 934*24000Ssam } 935*24000Ssam return geterror(bp); 936*24000Ssam case MTIOCGET: 937*24000Ssam mtget = (struct mtget *)data; 938*24000Ssam mtget->mt_dsreg = cy->cy_status[0]; 939*24000Ssam mtget->mt_erreg = cy->cy_status[1]; 940*24000Ssam mtget->mt_resid = cy->cy_count; 941*24000Ssam mtget->mt_type = MT_ISCY; 942*24000Ssam break; 943*24000Ssam default: 944*24000Ssam return ENXIO; 945*24000Ssam } 946*24000Ssam return 0; 947*24000Ssam } 948*24000Ssam 949*24000Ssam 950*24000Ssam 951*24000Ssam /* 952*24000Ssam * Check that a raw device exists. 953*24000Ssam * If it does, set up cy_blkno and cy_nxrec 954*24000Ssam * so that the tape will appear positioned correctly. 955*24000Ssam */ 956*24000Ssam cyphys(dev, uio) 957*24000Ssam dev_t dev; 958*24000Ssam struct uio *uio; 959*24000Ssam { 960*24000Ssam register int cyunit = CYUNIT(dev); 961*24000Ssam register daddr_t a; 962*24000Ssam register struct cy_softc *cy; 963*24000Ssam register struct vba_device *ui; 964*24000Ssam 965*24000Ssam if (cyunit >= NCY || (ui=cydinfo[cyunit]) == 0 || ui->ui_alive == 0) 966*24000Ssam return ENXIO; 967*24000Ssam cy = &cy_softc[cyunit]; 968*24000Ssam a = bdbtofsb(uio->uio_offset >> PGSHIFT); 969*24000Ssam cy->cy_blkno = a; 970*24000Ssam cy->cy_nxrec = a + 1; 971*24000Ssam return 0; 972*24000Ssam } 973*24000Ssam 974*24000Ssam /* 975*24000Ssam * Set a TAPEMASTER pointer (first parameter), into the 976*24000Ssam * 4 bytes array pointed by the second parameter. 977*24000Ssam */ 978*24000Ssam set_pointer(pointer, dest) 979*24000Ssam int pointer; 980*24000Ssam char * dest; 981*24000Ssam { 982*24000Ssam *dest++ = pointer & 0xff; /* low byte - offset */ 983*24000Ssam *dest++ = (pointer >> 8) & 0xff; /* high byte - offset */ 984*24000Ssam *dest++ = 0; 985*24000Ssam *dest = (pointer & 0xf0000) >> 12; /* base */ 986*24000Ssam } 987*24000Ssam 988*24000Ssam cydump(dev) 989*24000Ssam dev_t dev; 990*24000Ssam { 991*24000Ssam register struct vba_device *ui; 992*24000Ssam register struct tpb *tp; 993*24000Ssam int cyunit = CYUNIT(dev); 994*24000Ssam int blk, num; 995*24000Ssam int start; 996*24000Ssam 997*24000Ssam start = 0x800; 998*24000Ssam num = maxfree; 999*24000Ssam tp = &tpb[cyunit]; 1000*24000Ssam if (cyunit >= NCY || (ui=cydinfo[cyunit]) == 0 || ui->ui_alive == 0) 1001*24000Ssam return(ENXIO); 1002*24000Ssam if (cywait) return(EFAULT); 1003*24000Ssam while (num > 0) { 1004*24000Ssam blk = num > TBUFSIZ ? TBUFSIZ : num; 1005*24000Ssam bcopy(start*NBPG, cybuf, blk*NBPG); 1006*24000Ssam tp->cmd = WRIT_BU; 1007*24000Ssam tp->control[0] = cyunit<<CW_TSs; 1008*24000Ssam tp->control[1] = (CW_100ips | CW_16bits); 1009*24000Ssam tp->status[0] = tp->status[1] = 0; 1010*24000Ssam tp->size = TM_SHORT(blk*NBPG); 1011*24000Ssam set_pointer((int)cybuf, (char *)tp->pt_data); 1012*24000Ssam set_pointer((int)&tpb[cyunit], (char *)ccb.pt_tpb); 1013*24000Ssam ccb.gate[0] = GATE_CLOSED; 1014*24000Ssam TM_ATTENTION(cyaddr, 0xff); /* execute! */ 1015*24000Ssam start += blk; 1016*24000Ssam num -= blk; 1017*24000Ssam if (cywait) return(EFAULT); 1018*24000Ssam uncache(&tp->status[1]); 1019*24000Ssam if (tp->status[1]&CS_ERm) /* error */ 1020*24000Ssam return (EIO); 1021*24000Ssam } 1022*24000Ssam cyeof(tp, cyunit); 1023*24000Ssam if (cywait) return(EFAULT); 1024*24000Ssam cyeof(tp, cyunit); 1025*24000Ssam if (cywait) return(EFAULT); 1026*24000Ssam uncache(&tp->status[1]); 1027*24000Ssam if (tp->status[1]&CS_ERm) /* error */ 1028*24000Ssam return (EIO); 1029*24000Ssam cyrewind(tp, cyunit); 1030*24000Ssam return (0); 1031*24000Ssam } 1032*24000Ssam 1033*24000Ssam cywait() 1034*24000Ssam { 1035*24000Ssam register cnt; 1036*24000Ssam 1037*24000Ssam cnt = 5000; /* 5 seconds timeout */ 1038*24000Ssam do { 1039*24000Ssam --cnt; 1040*24000Ssam DELAY(1000); 1041*24000Ssam uncache(&ccb.gate[0]); 1042*24000Ssam } 1043*24000Ssam while (cnt>0 && ccb.gate[0] == GATE_CLOSED); 1044*24000Ssam if (cnt == 0) return(1); /* timeout */ 1045*24000Ssam else return(0); 1046*24000Ssam } 1047*24000Ssam 1048*24000Ssam cyeof(tp, unit) 1049*24000Ssam register struct tpb *tp; 1050*24000Ssam int unit; 1051*24000Ssam { 1052*24000Ssam tp->cmd = WRIT_FM; 1053*24000Ssam tp->control[0] = unit<<CW_TSs; 1054*24000Ssam tp->control[1] = (CW_100ips | CW_16bits); 1055*24000Ssam tp->status[0] = tp->status[1] = 0; 1056*24000Ssam tp->rec_over = TM_SHORT(1); 1057*24000Ssam set_pointer((int)&tpb[unit], (char *)ccb.pt_tpb); 1058*24000Ssam ccb.gate[0] = GATE_CLOSED; 1059*24000Ssam TM_ATTENTION(cyaddr, 0xff); /* execute! */ 1060*24000Ssam } 1061*24000Ssam 1062*24000Ssam 1063*24000Ssam cyrewind(tp, unit) 1064*24000Ssam register struct tpb *tp; 1065*24000Ssam int unit; 1066*24000Ssam { 1067*24000Ssam tp->cmd = REWD_TA; 1068*24000Ssam tp->control[0] = unit<<CW_TSs; 1069*24000Ssam tp->control[1] = (CW_100ips | CW_16bits); 1070*24000Ssam tp->status[0] = tp->status[1] = 0; 1071*24000Ssam set_pointer((int)&tpb[unit], (char *)ccb.pt_tpb); 1072*24000Ssam ccb.gate[0] = GATE_CLOSED; 1073*24000Ssam TM_ATTENTION(cyaddr, 0xff); /* execute! */ 1074*24000Ssam } 1075*24000Ssam 1076*24000Ssam unsigned 1077*24000Ssam tminphys(bp) 1078*24000Ssam register struct buf *bp; 1079*24000Ssam { 1080*24000Ssam 1081*24000Ssam if (bp->b_bcount > sizeof cybuf) 1082*24000Ssam bp->b_bcount = sizeof cybuf; 1083*24000Ssam } 1084*24000Ssam #endif 1085