1*25675Ssam /* cy.c 1.2 86/01/05 */ 224000Ssam 324000Ssam #include "cy.h" 4*25675Ssam #if NCY > 0 524000Ssam /* 6*25675Ssam * Cipher Tapemaster driver. 724000Ssam */ 8*25675Ssam int cydebug = 0; 924000Ssam 10*25675Ssam #include "../tahoe/mtpr.h" 11*25675Ssam #include "../tahoe/pte.h" 1224000Ssam 13*25675Ssam #include "param.h" 14*25675Ssam #include "systm.h" 15*25675Ssam #include "vm.h" 16*25675Ssam #include "buf.h" 17*25675Ssam #include "file.h" 18*25675Ssam #include "dir.h" 19*25675Ssam #include "user.h" 20*25675Ssam #include "proc.h" 21*25675Ssam #include "signal.h" 22*25675Ssam #include "uio.h" 23*25675Ssam #include "ioctl.h" 24*25675Ssam #include "mtio.h" 25*25675Ssam #include "errno.h" 26*25675Ssam #include "cmap.h" 2724000Ssam 28*25675Ssam #include "../tahoevba/vbavar.h" 29*25675Ssam #include "../tahoevba/cyreg.h" 3024000Ssam 31*25675Ssam #define MAXCONTROLLERS 4 32*25675Ssam #define MAX_BLOCKSIZE (TBUFSIZ*NBPG) 33*25675Ssam #define NUM_UNIT (NCY * 4) 3424000Ssam 35*25675Ssam #define TRUE 1 36*25675Ssam #define FALSE 0 3724000Ssam 38*25675Ssam #define RETRY 1 39*25675Ssam #define EXTEND 2 40*25675Ssam #define FATAL 3 4124000Ssam 42*25675Ssam #define MAINTAIN_POSITION 0 43*25675Ssam #define DONT_MAINTAIN_POSITION 1 4424000Ssam 45*25675Ssam #define PROCESSED 0x80000000 46*25675Ssam #define SLEEPING 0x80000000 47*25675Ssam #define b_cmd av_back /* only unused word in request */ 4824000Ssam 49*25675Ssam extern int cywrite_filemark(), cysearch_fm_forw(), cysearch_fm_back(); 50*25675Ssam extern int cy_space_forw(), cy_space_back(), cyrewind_tape_ta(); 51*25675Ssam extern int cyrewind_tape_unl(), cydrive_status(), cyrewind_tape_ov(); 52*25675Ssam extern int cyraw_read(), cyraw_write(), cybuf_read(), cybuf_write(); 53*25675Ssam extern int cywait_until_ready(), cywrite_0_fm(), cywrite_1_fm(); 54*25675Ssam extern int cywrite_2_fm(), cyno_op(), cywrite_eov(); 55*25675Ssam 56*25675Ssam static int (*cmd_tbl[15])() = { 57*25675Ssam cywrite_filemark, 58*25675Ssam #define DO_W_FM 0 59*25675Ssam cysearch_fm_forw, 60*25675Ssam #define DO_SFMF 1 61*25675Ssam cysearch_fm_back, 62*25675Ssam #define DO_SFMB 2 63*25675Ssam cy_space_forw, 64*25675Ssam #define DO_SPF 3 65*25675Ssam cy_space_back, 66*25675Ssam #define DO_SPB 4 67*25675Ssam cyrewind_tape_ta, 68*25675Ssam #define DO_RWTA 5 69*25675Ssam cyrewind_tape_unl, 70*25675Ssam #define DO_RWUN 6 71*25675Ssam cydrive_status, 72*25675Ssam #define DO_STAT 7 73*25675Ssam cyrewind_tape_ov, 74*25675Ssam #define DO_RWOV 8 75*25675Ssam cywait_until_ready, 76*25675Ssam #define DO_WAIT 9 77*25675Ssam cywrite_eov, 78*25675Ssam #define DO_WEOV 10 79*25675Ssam cyraw_read, 80*25675Ssam #define DO_RRD 11 81*25675Ssam cyraw_write, 82*25675Ssam #define DO_RWT 12 83*25675Ssam cybuf_read, 84*25675Ssam #define DO_BRD 13 85*25675Ssam cybuf_write 86*25675Ssam #define DO_BWT 14 8724000Ssam }; 8824000Ssam 8924000Ssam 90*25675Ssam extern int cyprobe(), cyslave(), cyattach(), cydgo(); 91*25675Ssam extern unsigned cyminsize(); 92*25675Ssam #if NCY > 0 93*25675Ssam extern char cy0utl[]; 94*25675Ssam #endif 95*25675Ssam #if NCY > 1 96*25675Ssam extern char cy1utl[]; 97*25675Ssam #endif 98*25675Ssam static fmt_scp *scp_ptrs[MAXCONTROLLERS] = 99*25675Ssam { (fmt_scp *)0xc0000c06, (fmt_scp *)0xc0000c16, }; 100*25675Ssam struct vba_ctlr *cyminfo[NCY]; 101*25675Ssam struct vba_device *cydinfo[NUM_UNIT]; 102*25675Ssam struct vba_driver cydriver = { 103*25675Ssam cyprobe, cyslave, cyattach, cydgo, (long *)scp_ptrs, 104*25675Ssam "yc", cydinfo, "cy", cyminfo 105*25675Ssam }; 10624000Ssam 10724000Ssam /* 108*25675Ssam * Per-controller data structure. 10924000Ssam */ 110*25675Ssam typedef struct { 111*25675Ssam struct pte *map; 112*25675Ssam char *utl; 113*25675Ssam int (*interupt_path)(); 114*25675Ssam label_t environ; /* Environment variable for longjmps */ 115*25675Ssam struct buf *my_request; 116*25675Ssam struct buf *wakeup_request; 117*25675Ssam short bs; /* buffer size */ 118*25675Ssam fmt_ccb ccb; /* Channel control blocks */ 119*25675Ssam fmt_scb scb; /* System configuration blocks */ 120*25675Ssam fmt_tpb tpb; /* Tape parameter blocks */ 121*25675Ssam fmt_tpb last; /* Tape parameter blocks */ 122*25675Ssam fmt_tpb noop; /* Tape parameter blocks */ 123*25675Ssam long rawbuf[MAX_BLOCKSIZE/sizeof(long)+1]; 124*25675Ssam } ctlr_tab; 12524000Ssam 126*25675Ssam extern int cy_normal_path(); 127*25675Ssam ctlr_tab ctlr_info[NCY] = { 128*25675Ssam #if NCY > 0 129*25675Ssam {CY0map, cy0utl, cy_normal_path}, 130*25675Ssam #endif 131*25675Ssam #if NCY > 1 132*25675Ssam {CY1map, cy1utl, cy_normal_path}, 133*25675Ssam #endif 134*25675Ssam }; 13524000Ssam 13624000Ssam /* 137*25675Ssam * Per-drive information. 13824000Ssam */ 139*25675Ssam typedef struct { 140*25675Ssam int (*cleanup)(); 141*25675Ssam struct buf u_queue; 142*25675Ssam struct buf rawbp; 143*25675Ssam long blkno; 144*25675Ssam long file_number; 145*25675Ssam short last_control; 146*25675Ssam short last_status; 147*25675Ssam short last_resid; 148*25675Ssam unsigned long bad_count; 149*25675Ssam unsigned control_proto: 16; 150*25675Ssam unsigned error_count : 8; 151*25675Ssam unsigned open : 1; 152*25675Ssam unsigned eof : 1; 153*25675Ssam unsigned bot : 1; 154*25675Ssam unsigned eot : 1; 155*25675Ssam char *message; 156*25675Ssam } unit_tab; 157*25675Ssam unit_tab unit_info[NUM_UNIT]; 15824000Ssam 159*25675Ssam cyprobe(ctlr_vaddr) 160*25675Ssam register caddr_t ctlr_vaddr; 161*25675Ssam { 162*25675Ssam static int ctlr = -1; /* XXX */ 163*25675Ssam 164*25675Ssam ctlr++; 165*25675Ssam if (badcyaddr(ctlr_vaddr + 1) || 166*25675Ssam !cy_init_controller(ctlr_vaddr, ctlr, 1)) 167*25675Ssam return (0); 168*25675Ssam return (sizeof (caddr_t)); /* XXX */ 169*25675Ssam } 170*25675Ssam 17124000Ssam /* 172*25675Ssam * Initialize the controller after a controller reset or during autoconfigure. 173*25675Ssam * All of the system control blocks are initialized and the controller is 174*25675Ssam * asked to configure itself for later use. 175*25675Ssam * 176*25675Ssam * If the print value is true cy_first_TM_attention will anounce 177*25675Ssam * the type of controller we are (Tapemasher) and will print the size 178*25675Ssam * of the internal controller buffer. 17924000Ssam */ 180*25675Ssam cy_init_controller(ctlr_vaddr, ctlr, print) 181*25675Ssam register caddr_t ctlr_vaddr; 182*25675Ssam register int ctlr, print; 18324000Ssam { 184*25675Ssam register int *pte; 185*25675Ssam register fmt_scp *SCP; 186*25675Ssam register fmt_scb *SCB; 187*25675Ssam register fmt_ccb *CCB; 188*25675Ssam register ctlr_tab *ci; 18924000Ssam 19024000Ssam /* 191*25675Ssam * Initialize the system configuration pointer. 19224000Ssam */ 193*25675Ssam SCP = scp_ptrs[ctlr]; 194*25675Ssam /* make kernel writable */ 195*25675Ssam pte = (int *)vtopte((struct proc *)0, btop(SCP)); 196*25675Ssam *pte &= ~PG_PROT; *pte |= PG_KW; 197*25675Ssam mtpr(TBIS, SCP); 198*25675Ssam /* load the correct values in the scp */ 199*25675Ssam SCP->bus_size = _16_BITS; 200*25675Ssam load_mbus_addr((caddr_t)&ctlr_info[ctlr].scb, SCP->scb_ptr); 201*25675Ssam /* put it back to read-only */ 202*25675Ssam *pte &= ~PG_PROT; *pte |= PG_KR; 203*25675Ssam mtpr(TBIS, SCP); 204*25675Ssam 20524000Ssam /* 206*25675Ssam * Init system configuration block. 20724000Ssam */ 208*25675Ssam SCB = &ctlr_info[ctlr].scb; 209*25675Ssam SCB->fixed_value = 0x3; 210*25675Ssam /* set pointer to the channel control block */ 211*25675Ssam load_mbus_addr((caddr_t)&ctlr_info[ctlr].ccb, SCB->ccb_ptr); 212*25675Ssam 21324000Ssam /* 214*25675Ssam * Initialize the chanel control block. 21524000Ssam */ 216*25675Ssam CCB = &ctlr_info[ctlr].ccb; 217*25675Ssam CCB->ccw = CLEAR_INTERUPT; 218*25675Ssam CCB->gate = GATE_OPEN; 219*25675Ssam /* set pointer to the tape parameter block */ 220*25675Ssam load_mbus_addr((caddr_t)&ctlr_info[ctlr].tpb, CCB->tpb_ptr); 221*25675Ssam 22224000Ssam /* 223*25675Ssam * Issue a noop cmd and get the internal buffer size for buffered i/o. 22424000Ssam */ 225*25675Ssam ci = &ctlr_info[ctlr]; 226*25675Ssam /* set command to be CONFIGURE */ 227*25675Ssam ci->tpb.cmd = NO_OP; 228*25675Ssam ci->tpb.control = CW_16bits; 229*25675Ssam ci->ccb.gate = GATE_CLOSED; 230*25675Ssam CY_ATTENTION(ctlr_vaddr); /* execute! */ 231*25675Ssam if (cywait(&ci->ccb) || (ci->tpb.status & CS_ERm)) { 232*25675Ssam printf("yc%d: time-out during init\n", ctlr); 233*25675Ssam return (0); 234*25675Ssam } 235*25675Ssam ci->tpb.cmd = CONFIG; 236*25675Ssam ci->tpb.control = CW_16bits; 237*25675Ssam ci->ccb.gate = GATE_CLOSED; 238*25675Ssam CY_ATTENTION(ctlr_vaddr); /* execute! */ 239*25675Ssam if (cywait(&ci->ccb) || (ci->tpb.status & CS_ERm)) { 240*25675Ssam cyprint_err("Tapemaster configuration failure", 241*25675Ssam 0, ci->tpb.status); 242*25675Ssam return (0); 243*25675Ssam } 244*25675Ssam uncache(&ci->tpb.count); 245*25675Ssam ci->bs = MULTIBUS_SHORT(ci->tpb.count); 246*25675Ssam if (print) 247*25675Ssam printf("yc%d: %dKb buffer\n", ctlr, ci->bs/1024); 248*25675Ssam return (1); 24924000Ssam } 25024000Ssam 25124000Ssam /* 252*25675Ssam * Check to see if a drive is attached to a controller. 253*25675Ssam * Since we can only tell that a drive is there if a tape is loaded and 254*25675Ssam * the drive is placed online, we always indicate the slave is present. 25524000Ssam */ 256*25675Ssam cyslave(vi, addr) 257*25675Ssam struct vba_device *vi; 258*25675Ssam caddr_t addr; 25924000Ssam { 26024000Ssam 261*25675Ssam #ifdef lint 262*25675Ssam vi = vi; addr = addr; 263*25675Ssam #endif 26424000Ssam return (1); 26524000Ssam } 26624000Ssam 267*25675Ssam cyattach(dev_info) 268*25675Ssam struct vba_device *dev_info; 269*25675Ssam { 270*25675Ssam register unit_tab *ui = &unit_info[dev_info->ui_unit]; 271*25675Ssam register struct buf *cq = &dev_info->ui_mi->um_tab; 272*25675Ssam register struct buf *uq = cq->b_forw; 273*25675Ssam register struct buf *start_queue = uq; 274*25675Ssam 275*25675Ssam /* Add unit to controllers queue */ 276*25675Ssam if (cq->b_forw == NULL) { 277*25675Ssam cq->b_forw = &ui->u_queue; 278*25675Ssam ui->u_queue.b_forw = &ui->u_queue; 279*25675Ssam } else { 280*25675Ssam while(uq->b_forw != start_queue) 281*25675Ssam uq = uq->b_forw; 282*25675Ssam ui->u_queue.b_forw = start_queue; 283*25675Ssam uq->b_forw = &ui->u_queue; 284*25675Ssam } 285*25675Ssam ui->cleanup = cyno_op; 286*25675Ssam ui->last_status = 0; 287*25675Ssam ui->last_control = 0; 288*25675Ssam ui->file_number = 0; 289*25675Ssam ui->bad_count = 0; 290*25675Ssam ui->blkno = 0; 291*25675Ssam ui->open = FALSE; 292*25675Ssam ui->bot = TRUE; 293*25675Ssam ui->eot = FALSE; 294*25675Ssam ui->eof = FALSE; 295*25675Ssam ui->message = NULL; 296*25675Ssam } 297*25675Ssam 298*25675Ssam cydgo() 299*25675Ssam { 300*25675Ssam 301*25675Ssam } 302*25675Ssam 303*25675Ssam /* macro to pack the unit number into Tapemaster format */ 304*25675Ssam #define UNIT(unit) \ 305*25675Ssam (((cydinfo[unit]->ui_slave & 1) << 11) | \ 306*25675Ssam ((cydinfo[unit]->ui_slave & 2) << 9) | \ 307*25675Ssam ((cydinfo[unit]->ui_slave & 4) >> 2)) 308*25675Ssam 309*25675Ssam cyopen(dev, flag) 310*25675Ssam register int flag; 311*25675Ssam register dev_t dev; 312*25675Ssam { 313*25675Ssam register int unit = CYUNIT(dev); 314*25675Ssam register unit_tab *ui; 315*25675Ssam 316*25675Ssam if (unit >= NUM_UNIT || cydinfo[unit] == 0 || 317*25675Ssam (ui = &unit_info[unit])->open) 318*25675Ssam return (ENXIO); 319*25675Ssam ui->control_proto = UNIT(unit) | CW_INTR | CW_16bits; 320*25675Ssam ui->blkno = 0; 321*25675Ssam ui->bad_count = 0; 322*25675Ssam ui->eof = 0; 323*25675Ssam ui->open = 1; 324*25675Ssam cycmd(dev, DO_WAIT, 1); /* wait for tape to rewind */ 325*25675Ssam if ((ui->last_status&CS_OL) == 0) { /* not on-line */ 326*25675Ssam ui->open = 0; 327*25675Ssam return (ENXIO); 328*25675Ssam } 329*25675Ssam if ((flag&FWRITE) && (ui->last_status&CS_P)) { 330*25675Ssam uprintf("cy%d: write protected\n", unit); 331*25675Ssam ui->open = 0; 332*25675Ssam return (ENXIO); 333*25675Ssam } 334*25675Ssam if (ui->last_status&CS_LP) { 335*25675Ssam ui->file_number = 0; 336*25675Ssam ui->bot = 1; 337*25675Ssam ui->eof = ui->eot = 0; 338*25675Ssam } 339*25675Ssam return (0); 340*25675Ssam } 341*25675Ssam 342*25675Ssam cyclose(dev, flag) 343*25675Ssam register dev_t dev; 344*25675Ssam register flag; 345*25675Ssam { 346*25675Ssam register int unit = CYUNIT(dev); 347*25675Ssam register unit_tab *ui = &unit_info[unit]; 348*25675Ssam 349*25675Ssam if (ui->last_status&CS_OL) { 350*25675Ssam if ((flag&FWRITE) && (minor(dev)&T_NOREWIND)) 351*25675Ssam cycmd(dev, DO_WEOV, 1); 352*25675Ssam else if ((minor(dev) & T_NOREWIND) == 0) 353*25675Ssam cycmd(dev, DO_RWOV, 1); 354*25675Ssam } 355*25675Ssam if (ui->bad_count != 0) { 356*25675Ssam #ifdef notdef 357*25675Ssam ui->bad_count *= 889; 358*25675Ssam uprintf("cy%d: Warning - %d.%dcm of tape were used for recovering bad spots.\n", unit, ui->bad_count/100, ui->bad_count%100); 359*25675Ssam #endif 360*25675Ssam ui->bad_count = 0; 361*25675Ssam } 362*25675Ssam ui->open = 0; 363*25675Ssam } 364*25675Ssam 36524000Ssam /* 366*25675Ssam * Cycmd is used internally to implement all the ioctl functions. 367*25675Ssam * We duplicate the code in physio 368*25675Ssam * that is used for syncronizing the processes (sleep / wakeup) so 369*25675Ssam * that we can treat our internal command requests exactly like 370*25675Ssam * regular reads and writes. They get put on the controller queue, 371*25675Ssam * start processes them and iodone is called to wake us up on completion. 372*25675Ssam * 373*25675Ssam * We don't call physio directly because it expects data to be moved 374*25675Ssam * and has a lot more overhead than we really need. 37524000Ssam */ 376*25675Ssam cycmd(dev, command, count) 377*25675Ssam register dev_t dev; 378*25675Ssam register int command, count; 37924000Ssam { 380*25675Ssam register int unit = CYUNIT(dev); 381*25675Ssam register unit_tab *ui = &unit_info[unit]; 382*25675Ssam register struct buf *uq; 383*25675Ssam int s; 384*25675Ssam 385*25675Ssam s = spl3(); 386*25675Ssam while (ui->rawbp.b_flags & B_BUSY) { 387*25675Ssam ui->rawbp.b_flags |= B_WANTED; 388*25675Ssam sleep((caddr_t)&ui->rawbp, PRIBIO+1); 389*25675Ssam } 390*25675Ssam splx(s); 391*25675Ssam /* load the request queue element */ 392*25675Ssam ui->rawbp.b_error = 0; 393*25675Ssam ui->rawbp.b_dev = dev; 394*25675Ssam ui->rawbp.b_cmd = (struct buf *)command; 395*25675Ssam ui->rawbp.b_bcount = count; 396*25675Ssam ui->rawbp.b_flags = B_PHYS | B_BUSY; 397*25675Ssam s = spl3(); 398*25675Ssam uq = &ui->u_queue; 399*25675Ssam ui->rawbp.av_forw = NULL; 400*25675Ssam if (uq->av_forw == NULL) 401*25675Ssam uq->av_forw = &ui->rawbp; 402*25675Ssam else 403*25675Ssam uq->av_back->av_forw = &ui->rawbp; 404*25675Ssam uq->av_back = &ui->rawbp; 405*25675Ssam cystart(cydinfo[unit]->ui_mi, &ui->rawbp, s); 40624000Ssam 407*25675Ssam /* wait for operation to complete */ 408*25675Ssam while ((ui->rawbp.b_flags&B_DONE) == 0) 409*25675Ssam sleep((caddr_t)&ui->rawbp, PRIBIO); 410*25675Ssam ui->rawbp.b_flags &= ~(B_PHYS | B_BUSY); 411*25675Ssam if (ui->rawbp.b_flags & B_WANTED) 412*25675Ssam wakeup((caddr_t)&ui->rawbp); 413*25675Ssam return (geterror(&ui->rawbp)); 41424000Ssam } 41524000Ssam 416*25675Ssam cystrategy(bp) 417*25675Ssam register struct buf *bp; 418*25675Ssam { 419*25675Ssam register int unit = CYUNIT(bp->b_dev); 420*25675Ssam register unit_tab *ui = &unit_info[unit]; 421*25675Ssam register struct buf *uq; 422*25675Ssam int s; 423*25675Ssam 424*25675Ssam /* check the validity of the request */ 425*25675Ssam if (bp->b_bcount > MAX_BLOCKSIZE) { 426*25675Ssam uprintf("cy%d: Maximum block size is %dk!\n", 427*25675Ssam unit, MAX_BLOCKSIZE/1024); 428*25675Ssam bp->b_error = EIO; 429*25675Ssam bp->b_resid = bp->b_bcount; 430*25675Ssam bp->b_flags |= B_ERROR; 431*25675Ssam iodone(bp); 432*25675Ssam return; 433*25675Ssam } 434*25675Ssam vbasetup(bp, MAX_BLOCKSIZE); 435*25675Ssam if (bp->b_flags & B_PHYS) 436*25675Ssam bp->b_cmd = (struct buf *)(bp->b_flags&B_READ? DO_RRD : DO_RWT); 437*25675Ssam else 438*25675Ssam bp->b_cmd = (struct buf *)(bp->b_flags&B_READ? DO_BRD : DO_BWT); 439*25675Ssam /* place request on queue and start it */ 440*25675Ssam s = spl3(); 441*25675Ssam uq = &ui->u_queue; 442*25675Ssam bp->av_forw = NULL; 443*25675Ssam if (uq->av_forw == NULL) 444*25675Ssam uq->av_forw = bp; 445*25675Ssam else 446*25675Ssam uq->av_back->av_forw = bp; 447*25675Ssam uq->av_back = bp; 448*25675Ssam cystart(cydinfo[unit]->ui_mi, bp, s); 449*25675Ssam } 450*25675Ssam 451*25675Ssam struct buf *cyget_next(); 452*25675Ssam int cystart_timeout(); 45324000Ssam /* 454*25675Ssam * Cystart is called once for every request that is placed on a 455*25675Ssam * controller's queue. Start is responsible for fetching requests for 456*25675Ssam * a controller queue, starting the operation, and waiting for completion, 457*25675Ssam * and releasing the buf structure back to UNIX or cycmd, before fetching 458*25675Ssam * the next request. 459*25675Ssam * 460*25675Ssam * The controller's queue looks like this: 461*25675Ssam * 462*25675Ssam * +---------------------------------------+ 463*25675Ssam * | | 464*25675Ssam * +-----------+ | +-----------+ +-----------+ | 465*25675Ssam * | b_forw |---+-->| b_forw |--~ ~-->| b_forw |--+ 466*25675Ssam * +-----------+ +-----------+ +-----------+ 467*25675Ssam * | b_back | | ......... | | ......... | 468*25675Ssam * +-----------+ +-----------+ +-----------+ 469*25675Ssam * | ......... | First unit queue Last unit queue 470*25675Ssam * +-----------+ element element 471*25675Ssam * head of controller queue 472*25675Ssam * (cyminfo[ctlr].um_tab) 47324000Ssam */ 474*25675Ssam cystart(vi, bp, s) 475*25675Ssam register struct vba_ctlr *vi; 476*25675Ssam register struct buf *bp; 47724000Ssam { 478*25675Ssam int unit = CYUNIT(bp->b_dev), ctlr = vi->um_ctlr; 479*25675Ssam register struct buf *next, *cq = &vi->um_tab; 480*25675Ssam register unit_tab *ui = &unit_info[unit]; 481*25675Ssam register ctlr_tab *ci = &ctlr_info[ctlr]; 48224000Ssam 483*25675Ssam if (cq->b_active&SLEEPING) { 484*25675Ssam untimeout(cystart_timeout, (caddr_t)cq); 485*25675Ssam cystart_timeout(cq); 48624000Ssam } 487*25675Ssam if (cq->b_active) { 488*25675Ssam sleep((caddr_t)bp, PRIBIO-1); 489*25675Ssam if (bp->b_flags&PROCESSED) { 490*25675Ssam if (ui->message) { 491*25675Ssam uprintf("cy%d: %s\n", unit, ui->message); 492*25675Ssam ui->message = 0; 493*25675Ssam } 494*25675Ssam bp->b_flags &= ~PROCESSED; 495*25675Ssam iodone(bp); 496*25675Ssam return; 497*25675Ssam } 49824000Ssam } 499*25675Ssam cq->b_active = 1; 500*25675Ssam splx(s); 501*25675Ssam ci->my_request = bp; 502*25675Ssam cydo_my_command(ctlr, cq, ci); 503*25675Ssam if (ui->message) { 504*25675Ssam uprintf("cy%d: %s\n", unit, ui->message); 505*25675Ssam ui->message = 0; 50624000Ssam } 507*25675Ssam bp->b_flags &= ~PROCESSED; 508*25675Ssam iodone(bp); 509*25675Ssam if ((next = cyget_next(cq)) != NULL) 510*25675Ssam wakeup((caddr_t)next); 511*25675Ssam else 512*25675Ssam cq->b_active = 0; 51324000Ssam } 51424000Ssam 51524000Ssam /* 516*25675Ssam * Cystart_timeout wakes up the start routine after it's 3 517*25675Ssam * second wait time is up or when a new command enters the queue. 518*25675Ssam * The timer is used to give up the processor while all drives 519*25675Ssam * on the queue are rewinding and we need to wait for them to be dome. 52024000Ssam */ 521*25675Ssam cystart_timeout(cq) 522*25675Ssam register struct buf *cq; 52324000Ssam { 52424000Ssam 525*25675Ssam cq->b_active &= ~SLEEPING; 526*25675Ssam wakeup((caddr_t)cq); 527*25675Ssam } 528*25675Ssam 529*25675Ssam /* 530*25675Ssam * Cydo_my command scans the request queues once for a 531*25675Ssam * particular controller and calls the appropriate processing routine 532*25675Ssam * each time we find a request that can be started. 533*25675Ssam */ 534*25675Ssam cydo_my_command(ctlr, cq, ci) 535*25675Ssam register struct buf *cq; 536*25675Ssam register ctlr_tab *ci; 537*25675Ssam { 538*25675Ssam register struct buf *next; 539*25675Ssam 540*25675Ssam while ((next = cyget_next(cq)) != NULL) { 541*25675Ssam if (cq->b_forw->b_active&SLEEPING) { 542*25675Ssam cq->b_active |= SLEEPING; 543*25675Ssam timeout(cystart_timeout, (caddr_t)cq, 1*60); 544*25675Ssam sleep((caddr_t)cq, PRIBIO); 545*25675Ssam continue; 546*25675Ssam } 547*25675Ssam if (setjmp(&ctlr_info[ctlr].environ)) 548*25675Ssam cydone(cq); 549*25675Ssam else { 550*25675Ssam register int cmd = (int)next->b_cmd; 551*25675Ssam 552*25675Ssam (*cmd_tbl[cmd])(next, cq); 553*25675Ssam } 554*25675Ssam if (next->b_flags & PROCESSED) { 555*25675Ssam if (ci->my_request == next) 556*25675Ssam break; 557*25675Ssam wakeup((caddr_t)next); 558*25675Ssam } 55924000Ssam } 56024000Ssam } 56124000Ssam 562*25675Ssam struct buf * 563*25675Ssam cyget_next(cq) 564*25675Ssam register struct buf *cq; 565*25675Ssam { 566*25675Ssam register struct buf *bp, *uq, *next = NULL; 56724000Ssam 568*25675Ssam cq->b_forw = cq->b_forw->b_forw; 569*25675Ssam uq = cq->b_forw; 570*25675Ssam do { 571*25675Ssam if ((bp = uq->av_forw) != NULL) { 572*25675Ssam if ((uq->b_active&SLEEPING) == 0) { 573*25675Ssam cq->b_forw = uq; 574*25675Ssam return (bp); 575*25675Ssam } 576*25675Ssam next = uq; 577*25675Ssam } 578*25675Ssam uq = uq->b_forw; 579*25675Ssam } while(uq != cq->b_forw); 580*25675Ssam if (next != NULL) { 581*25675Ssam cq->b_forw = next; 582*25675Ssam return (next->av_forw); 583*25675Ssam } 584*25675Ssam return (NULL); 585*25675Ssam } 586*25675Ssam 58724000Ssam /* 588*25675Ssam * Mark the current command on the controller's q completed and remove it. 58924000Ssam */ 590*25675Ssam cydone(cq) 591*25675Ssam struct buf *cq; 59224000Ssam { 593*25675Ssam register struct buf *uq = cq->b_forw; 59424000Ssam int s; 59524000Ssam 596*25675Ssam uq->av_forw->b_flags |= PROCESSED; 597*25675Ssam s = spl3(); 598*25675Ssam if ((uq->av_forw = uq->av_forw->av_forw) == NULL) 599*25675Ssam uq->av_back = NULL; 60024000Ssam splx(s); 60124000Ssam } 60224000Ssam 60324000Ssam /* 604*25675Ssam * The following routines implement the individual commands. 605*25675Ssam * 606*25675Ssam * Each command is responsible for a few things. 1) Each has to keep 607*25675Ssam * track of special cases that are related to the individual command and 608*25675Ssam * the previous commands sequence, 2) each is required to call iodone when 609*25675Ssam * command is actually finished, 3) it must use cyexecute to actually 610*25675Ssam * start the controller, and 4) they are required to keep the tape in 611*25675Ssam * a consistant state so that other commands will not be messed up. 61224000Ssam */ 613*25675Ssam 614*25675Ssam /* 615*25675Ssam * Read requests from the raw device. 616*25675Ssam * The special cases are: 617*25675Ssam * 1) we can not read after a write. (writting defines end of file) 618*25675Ssam * 2) reading past end of file returns 0 bytes; 619*25675Ssam */ 620*25675Ssam cyraw_read(bp, cq) 62124000Ssam register struct buf *bp; 622*25675Ssam struct buf *cq; 62324000Ssam { 624*25675Ssam int unit = CYUNIT(bp->b_dev); 625*25675Ssam register unit_tab *ui = &unit_info[unit]; 626*25675Ssam register ctlr_tab *ci = &ctlr_info[cydinfo[unit]->ui_ctlr]; 627*25675Ssam int addr, lock_flag, command; 62824000Ssam 629*25675Ssam if (ui->cleanup != cyno_op || ui->eof) { 630*25675Ssam bp->b_resid = bp->b_bcount; 631*25675Ssam bp->b_error = ENXIO, bp->b_flags |= B_ERROR; 632*25675Ssam cydone(cq); 633*25675Ssam return; 634*25675Ssam } 635*25675Ssam if (bp->b_bcount > ci->bs) 636*25675Ssam command = READ_TA, lock_flag = CW_LOCK; 637*25675Ssam else 638*25675Ssam command = READ_BU, lock_flag = 0; 639*25675Ssam ui->blkno++; 640*25675Ssam addr = vbastart(bp, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl); 641*25675Ssam cyexecute(command, bp->b_bcount, addr, lock_flag, unit, 10, FALSE); 642*25675Ssam vbadone(bp, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl); 643*25675Ssam cydone(cq); 644*25675Ssam } 645*25675Ssam 64624000Ssam /* 647*25675Ssam * Write requests from the raw device. 648*25675Ssam * The special cases are: 649*25675Ssam * 1) we don't allow writes after end of tape is reached. 65024000Ssam */ 651*25675Ssam cyraw_write(bp, cq) 652*25675Ssam register struct buf *bp; 653*25675Ssam struct buf *cq; 654*25675Ssam { 655*25675Ssam int unit = CYUNIT(bp->b_dev); 656*25675Ssam register unit_tab *ui = &unit_info[CYUNIT(unit)]; 657*25675Ssam register ctlr_tab *ci = &ctlr_info[cydinfo[unit]->ui_ctlr]; 658*25675Ssam int addr, lock_flag, command; 65924000Ssam 660*25675Ssam if (ui->eot) { 661*25675Ssam bp->b_resid = bp->b_bcount; 662*25675Ssam bp->b_error = ENXIO, bp->b_flags |= B_ERROR; 663*25675Ssam longjmp(&ci->environ); 664*25675Ssam } 665*25675Ssam ui->cleanup = cywrite_2_fm; 666*25675Ssam if (bp->b_bcount > ci->bs) 667*25675Ssam command = WRIT_TA, lock_flag = CW_LOCK; 668*25675Ssam else 669*25675Ssam command = WRIT_BU, lock_flag = 0; 670*25675Ssam ui->blkno++; 671*25675Ssam addr = vbastart(bp, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl); 672*25675Ssam cyexecute(command, bp->b_bcount, addr, lock_flag, unit, 10, FALSE); 673*25675Ssam vbadone(bp, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl); 674*25675Ssam cydone(cq); 67524000Ssam } 67624000Ssam 67724000Ssam /* 678*25675Ssam * Write a filemark on a tape. 67924000Ssam */ 680*25675Ssam cywrite_filemark(bp, cq) 681*25675Ssam register struct buf *bp; 682*25675Ssam struct buf *cq; 68324000Ssam { 684*25675Ssam int unit = CYUNIT(bp->b_dev); 685*25675Ssam register unit_tab *ui = &unit_info[CYUNIT(unit)]; 686*25675Ssam 687*25675Ssam if (bp->b_bcount == 0) { 688*25675Ssam cydone(cq); 68924000Ssam return; 69024000Ssam } 691*25675Ssam bp->b_bcount--; 692*25675Ssam if (ui->cleanup == cywrite_1_fm) 693*25675Ssam ui->cleanup = cywrite_0_fm; 694*25675Ssam if (ui->cleanup == cywrite_2_fm || ui->cleanup == cyno_op) 695*25675Ssam ui->cleanup = cywrite_1_fm; 696*25675Ssam ui->file_number++; 697*25675Ssam ui->eof = 1; 698*25675Ssam ui->blkno = 0; 699*25675Ssam cyexecute(WRIT_FM, (long)1, 0, 0, unit, 10, FALSE); 700*25675Ssam } 701*25675Ssam 702*25675Ssam /* 703*25675Ssam ** cysearch_fm_forw is the ioctl to search for a filemark in the 704*25675Ssam ** forward direction on tape. 705*25675Ssam ** 706*25675Ssam ** Since only one device can be active on a given controller at any 707*25675Ssam ** given instant in time, we try to be nice and let onther devices on 708*25675Ssam ** this controller be scheduled after we space over each record. This will 709*25675Ssam ** at least give the apperance of overlapped operations on the controller. 710*25675Ssam ** 711*25675Ssam ** The special cases are: 712*25675Ssam ** 1) if the last command was a write the we can't search. 713*25675Ssam */ 714*25675Ssam 715*25675Ssam cysearch_fm_forw(request, cq) 716*25675Ssam register struct buf *request; 717*25675Ssam register struct buf *cq; 718*25675Ssam { 719*25675Ssam register int unit = CYUNIT(request->b_dev); 720*25675Ssam register unit_tab *ui = &unit_info[CYUNIT(unit)]; 721*25675Ssam register int ctlr = cydinfo[unit]->ui_ctlr; 722*25675Ssam register ctlr_tab *ci = &ctlr_info[ctlr]; 723*25675Ssam 724*25675Ssam if((ui->cleanup != cyno_op) || ui->eot) { 725*25675Ssam request->b_resid = request->b_bcount; 726*25675Ssam request->b_error = ENXIO, request->b_flags |= B_ERROR; 727*25675Ssam longjmp(&ci->environ); 72824000Ssam } 729*25675Ssam if(request->b_bcount && !ui->eot) { 730*25675Ssam if(!ui->eot) { 731*25675Ssam ui->blkno++; 732*25675Ssam cyexecute(SPAC_FM, (long)1, 0, 0, unit, 5, FALSE); 733*25675Ssam if(!(ui->eof || ui->eot)) 734*25675Ssam return; 73524000Ssam } 736*25675Ssam request->b_bcount--; 737*25675Ssam ui->eof = FALSE; 738*25675Ssam if(!ui->eot) { 739*25675Ssam ui->file_number++; 740*25675Ssam ui->blkno = 0; 741*25675Ssam return; 74224000Ssam } 74324000Ssam } 744*25675Ssam if(ui->eot) { 745*25675Ssam request->b_resid = request->b_bcount; 746*25675Ssam request->b_flags |= B_ERROR, request->b_error = ENXIO; 74724000Ssam } 748*25675Ssam cydone(cq); 749*25675Ssam } 750*25675Ssam 751*25675Ssam 752*25675Ssam /* 753*25675Ssam ** cysearch_fm_back is the ioctl to search for a filemark in the 754*25675Ssam ** reverse direction on tape. 755*25675Ssam ** 756*25675Ssam ** Since only one device can be active on a given controller at any 757*25675Ssam ** given instant in time, we try to be nice and let onther devices on 758*25675Ssam ** this controller be scheduled after we space over each record. This will 759*25675Ssam ** at least give the apperance of overlapped operations on the controller. 760*25675Ssam ** 761*25675Ssam ** The special cases are: 762*25675Ssam ** 1) can't search past begining of tape. 763*25675Ssam ** 2) if the lasr operation was a write data then we need to add 764*25675Ssam ** an end of volume record before we start searching. 765*25675Ssam */ 766*25675Ssam 767*25675Ssam cysearch_fm_back(request, cq) 768*25675Ssam register struct buf *request; 769*25675Ssam register struct buf *cq; 770*25675Ssam { 771*25675Ssam register int unit = CYUNIT(request->b_dev); 772*25675Ssam register unit_tab *ui = &unit_info[CYUNIT(unit)]; 773*25675Ssam 774*25675Ssam if(!ui->bot) { 775*25675Ssam (*ui->cleanup)(unit, MAINTAIN_POSITION); 776*25675Ssam if(ui->blkno == 0) 777*25675Ssam request->b_bcount++; 778*25675Ssam ui->blkno = 0xffffffff; 779*25675Ssam if(request->b_bcount && !ui->bot) { 780*25675Ssam cyexecute(SPAC_FM, (long)1, 0, CW_REV, unit, 6, FALSE); 781*25675Ssam if(ui->eof) { 782*25675Ssam ui->eof = FALSE; 783*25675Ssam ui->file_number--; 784*25675Ssam request->b_bcount--; 785*25675Ssam } 786*25675Ssam return; 787*25675Ssam } 788*25675Ssam if(ui->bot) { 789*25675Ssam ui->file_number = 0; 790*25675Ssam if(request->b_bcount) { 791*25675Ssam request->b_resid = request->b_bcount; 792*25675Ssam request->b_error = ENXIO; 793*25675Ssam request->b_flags |= B_ERROR; 794*25675Ssam } 795*25675Ssam } 796*25675Ssam else { 797*25675Ssam request->b_cmd = (struct buf *)DO_SFMF; 798*25675Ssam request->b_bcount = 1; 799*25675Ssam return; 800*25675Ssam } 80124000Ssam } 802*25675Ssam ui->blkno = 0; 803*25675Ssam ui->eof = FALSE; 804*25675Ssam cydone(cq); 805*25675Ssam } 80624000Ssam 80724000Ssam 808*25675Ssam /* 809*25675Ssam ** cy_space_forw is used to search forward a given number of records on 810*25675Ssam ** tape. 811*25675Ssam ** 812*25675Ssam ** Since only one device can be active on a given controller at any 813*25675Ssam ** given instant in time, we try to be nice and let onther devices on 814*25675Ssam ** this controller be scheduled after we space over each record. This will 815*25675Ssam ** at least give the apperance of overlapped operations on the controller. 816*25675Ssam ** 817*25675Ssam ** The special cases are: 818*25675Ssam ** 1) we can't space over a filemark. 819*25675Ssam ** 2) if the last command was a write data or filemark we can't space forward. 820*25675Ssam */ 821*25675Ssam 822*25675Ssam cy_space_forw(request, cq) 823*25675Ssam register struct buf *request; 824*25675Ssam register struct buf *cq; 825*25675Ssam { 826*25675Ssam register int unit = CYUNIT(request->b_dev); 827*25675Ssam register unit_tab *ui = &unit_info[CYUNIT(unit)]; 828*25675Ssam register int ctlr = cydinfo[unit]->ui_ctlr; 829*25675Ssam register ctlr_tab *ci = &ctlr_info[ctlr]; 830*25675Ssam 831*25675Ssam if((ui->cleanup != cyno_op) || ui->eof) { 832*25675Ssam request->b_resid = request->b_bcount; 833*25675Ssam request->b_error = ENXIO, request->b_flags |= B_ERROR; 834*25675Ssam longjmp(&ci->environ); 83524000Ssam } 836*25675Ssam if(request->b_bcount) { 837*25675Ssam ui->blkno++; 838*25675Ssam cyexecute(SPAC_FM, (long)1, 0, 0, unit, 10, FALSE); 839*25675Ssam if(!ui->eof && request->b_bcount) { 840*25675Ssam request->b_bcount--; 841*25675Ssam return; 842*25675Ssam } 84324000Ssam } 844*25675Ssam if(ui->eof) { 845*25675Ssam request->b_resid = request->b_bcount; 846*25675Ssam request->b_error = ENXIO, request->b_flags |= B_ERROR; 847*25675Ssam } 848*25675Ssam cydone(cq); 849*25675Ssam } 850*25675Ssam 851*25675Ssam 852*25675Ssam /* 853*25675Ssam ** Cy_space_back spaces backward a given number of records. 854*25675Ssam ** 855*25675Ssam ** Since only one device can be active on a given controller at any 856*25675Ssam ** given instant in time, we try to be nice and let onther devices on 857*25675Ssam ** this controller be scheduled after we space over each record. This will 858*25675Ssam ** at least give the apperance of overlapped operations on the controller. 859*25675Ssam ** 860*25675Ssam ** The special cases are: 861*25675Ssam ** 1) we can't space over a filemark. 862*25675Ssam ** 2) we can't space past the beginning of tape. 863*25675Ssam ** 3) if the last operation was a write data then we need to add 864*25675Ssam ** an end of volume record before we start searching. 865*25675Ssam */ 866*25675Ssam 867*25675Ssam cy_space_back(request, cq) 868*25675Ssam register struct buf *request; 869*25675Ssam register struct buf *cq; 870*25675Ssam { 871*25675Ssam register int unit = CYUNIT(request->b_dev); 872*25675Ssam register unit_tab *ui = &unit_info[CYUNIT(unit)]; 873*25675Ssam 874*25675Ssam if(!ui->bot) { 875*25675Ssam (*ui->cleanup)(unit, MAINTAIN_POSITION); 876*25675Ssam if(request->b_bcount+1 && !ui->bot && !ui->eof) { 877*25675Ssam request->b_bcount--; 878*25675Ssam ui->blkno--; 879*25675Ssam cyexecute(SPACE, (long)1, 0, CW_REV, unit, 15, FALSE); 880*25675Ssam return; 88124000Ssam } 882*25675Ssam if(!ui->bot) { 883*25675Ssam request->b_bcount = 1; 884*25675Ssam cy_space_forw(request, cq); 885*25675Ssam } 886*25675Ssam ui->eof = FALSE; 88724000Ssam } 888*25675Ssam cydone(cq); 889*25675Ssam } 89024000Ssam 891*25675Ssam /* 892*25675Ssam * Rewind tape and wait for completion. 893*25675Ssam * An overlapped rewind is issued and then we change the command type to 894*25675Ssam * a wait for ready ioctl. Wait for ready contains the logic to poll 895*25675Ssam * without blocking anything in the system, until the drive becomes ready or 896*25675Ssam * drops off line whichever comes first. 897*25675Ssam */ 898*25675Ssam /*ARGSUSED*/ 899*25675Ssam cyrewind_tape_ta(bp, cq) 900*25675Ssam struct buf *bp, *cq; 901*25675Ssam { 902*25675Ssam 903*25675Ssam cyrewind_tape(bp, REWD_OV); 904*25675Ssam bp->b_cmd = (struct buf *)DO_WAIT; 90524000Ssam } 90624000Ssam 90724000Ssam /* 908*25675Ssam * Do an overlapped rewind and then unload the tape. 909*25675Ssam * This feature is handled by the individual tape drive and 910*25675Ssam * in some cases can not be performed. 91124000Ssam */ 912*25675Ssam cyrewind_tape_unl(bp, cq) 913*25675Ssam struct buf *bp, *cq; 91424000Ssam { 915*25675Ssam 916*25675Ssam cyrewind_tape(bp, OFF_UNL); 917*25675Ssam cydone(cq); 91824000Ssam } 91924000Ssam 92024000Ssam /* 921*25675Ssam * Do an overlapped rewind. 92224000Ssam */ 923*25675Ssam cyrewind_tape_ov(bp, cq) 924*25675Ssam struct buf *bp, *cq; 92524000Ssam { 926*25675Ssam 927*25675Ssam cyrewind_tape(bp, REWD_OV); 928*25675Ssam cydone(cq); 929*25675Ssam } 930*25675Ssam 931*25675Ssam /* 932*25675Ssam * Common code for all rewind commands. 933*25675Ssam * The special cases are: 934*25675Ssam * 3) if the last operation was a write data then we need to add 935*25675Ssam * an end of volume record before we start searching. 936*25675Ssam */ 937*25675Ssam cyrewind_tape(bp, cmd) 93824000Ssam register struct buf *bp; 939*25675Ssam int cmd; 940*25675Ssam { 941*25675Ssam register int unit = CYUNIT(bp->b_dev); 942*25675Ssam register unit_tab *ui = &unit_info[unit]; 94324000Ssam 944*25675Ssam (*ui->cleanup)(unit, DONT_MAINTAIN_POSITION); 945*25675Ssam ui->blkno = 0; 946*25675Ssam ui->eof = FALSE; 947*25675Ssam ui->bot = TRUE; 948*25675Ssam ui->eot = FALSE; 949*25675Ssam ui->file_number = 0; 950*25675Ssam bp->b_resid = 0; 951*25675Ssam ui->cleanup = cyno_op; 952*25675Ssam cyexecute(cmd, (long)0, 0, 0, unit, cmd == REWD_OV ? 10 : 10*60, 0); 953*25675Ssam } 954*25675Ssam 955*25675Ssam /* 956*25675Ssam ** Cywait_until_ready is used to wait for rewinds to complete. 957*25675Ssam ** We check the status and if the tape is still rewinding we re-enter ourself 958*25675Ssam ** on the activity queue to give other requests a chance to execute before we 959*25675Ssam ** check the status again. One other thing is that we only want to check 960*25675Ssam ** the status every five seconds. so we set a timer for five seconds and 961*25675Ssam ** check the time left every time we enter this routine. If there is still 962*25675Ssam ** time left then we simply reinsert ourself on the queue again and wait 963*25675Ssam ** until next time .. 964*25675Ssam */ 965*25675Ssam cywait_until_ready(request, cq) 966*25675Ssam register struct buf *request; 967*25675Ssam register struct buf *cq; 968*25675Ssam { 969*25675Ssam extern int cywait_timeout(); 970*25675Ssam register int unit = CYUNIT(request->b_dev); 971*25675Ssam register unit_tab *ui = &unit_info[unit]; 972*25675Ssam 973*25675Ssam cyexecute(DRIVE_S, (long)0, 0, 0, unit, 10, FALSE); 974*25675Ssam if((!(ui->last_status & CS_OL)) || (ui->last_status & CS_RDY)) { 975*25675Ssam cydone(cq); 97624000Ssam return; 97724000Ssam } 978*25675Ssam cq->b_forw->b_active |= SLEEPING; 979*25675Ssam timeout(cywait_timeout, (caddr_t)cq->b_forw, 2*60); 980*25675Ssam } 981*25675Ssam 982*25675Ssam /* 983*25675Ssam * Reset the timing flag for nice_wait after 3 seconds. 984*25675Ssam * This makes this drive eligible for scheduling again. 985*25675Ssam */ 986*25675Ssam cywait_timeout(uq) 987*25675Ssam struct buf *uq; 988*25675Ssam { 989*25675Ssam 990*25675Ssam uq->b_active &= ~SLEEPING; 991*25675Ssam } 992*25675Ssam 993*25675Ssam /* 994*25675Ssam * Process a status ioctl request. 995*25675Ssam * It depends entirly on the interupt routines to load the last_XXX 996*25675Ssam * registers in unit_info[]. 997*25675Ssam */ 998*25675Ssam cydrive_status(bp, cq) 999*25675Ssam struct buf *bp, *cq; 1000*25675Ssam { 1001*25675Ssam 1002*25675Ssam cyexecute(DRIVE_S, (long)0, 0, 0, CYUNIT(bp->b_dev), 10, FALSE); 1003*25675Ssam cydone(cq); 1004*25675Ssam } 1005*25675Ssam 1006*25675Ssam /* 1007*25675Ssam ** cybuf_read handles the read requests from the block device. 1008*25675Ssam ** 1009*25675Ssam ** The special cases are: 1010*25675Ssam ** 1) we can not read after a write. (writting defines end of file) 1011*25675Ssam ** 2) reading past end of file returns 0 bytes; 1012*25675Ssam ** 3) if we are mispositioned we have to seek to the correct block. 1013*25675Ssam ** 4) we can hit end of tape while seeking. 1014*25675Ssam ** 5) we want to be nice to other processes while seeking so we 1015*25675Ssam ** break the request up into smaller requests. 1016*25675Ssam ** 6) returns error if the block was larger than requested. 1017*25675Ssam */ 1018*25675Ssam cybuf_read(request, cq) 1019*25675Ssam register struct buf *request; 1020*25675Ssam register struct buf *cq; 1021*25675Ssam { 1022*25675Ssam register int unit = CYUNIT(request->b_dev); 1023*25675Ssam register unit_tab *ui = &unit_info[CYUNIT(unit)]; 1024*25675Ssam register int ctlr = cydinfo[unit]->ui_ctlr; 1025*25675Ssam register ctlr_tab *ci = &ctlr_info[ctlr]; 1026*25675Ssam register int addr, command, bus_lock; 1027*25675Ssam 1028*25675Ssam cydebug = 1; 1029*25675Ssam if(cyseek(request, cq)) { 1030*25675Ssam if(ui->cleanup != cyno_op) { 1031*25675Ssam clrbuf(request); 1032*25675Ssam longjmp(&ci->environ); 103324000Ssam } 1034*25675Ssam if(request->b_bcount > ci->bs) 1035*25675Ssam command = READ_TA, bus_lock = CW_LOCK; 1036*25675Ssam else 1037*25675Ssam command = READ_BU, bus_lock = 0; 1038*25675Ssam ui->blkno++; 1039*25675Ssam addr = vbastart(request, (caddr_t)ci->rawbuf, (long *)ci->map, 1040*25675Ssam ci->utl); 1041*25675Ssam cyexecute(command,request->b_bcount,addr,bus_lock,unit,8,FALSE); 1042*25675Ssam vbadone(request, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl); 1043*25675Ssam cydone(cq); 104424000Ssam } 1045*25675Ssam } 1046*25675Ssam 1047*25675Ssam 1048*25675Ssam /* 1049*25675Ssam ** cybuf_write handles the write requests from the block device. 1050*25675Ssam ** 1051*25675Ssam ** The special cases are: 1052*25675Ssam ** 1) if we are mispositioned we have to seek to the correct block. 1053*25675Ssam ** 2) we can hit end of tape while seeking. 1054*25675Ssam ** 3) we want to be nice to other processes while seeking so we 1055*25675Ssam ** break the request up into smaller requests. 1056*25675Ssam ** 4) we don't allow writes after end of tape is reached. 1057*25675Ssam */ 1058*25675Ssam 1059*25675Ssam cybuf_write(request, cq) 1060*25675Ssam register struct buf *request; 1061*25675Ssam register struct buf *cq; 1062*25675Ssam { 1063*25675Ssam register int unit = CYUNIT(request->b_dev); 1064*25675Ssam register unit_tab *ui = &unit_info[CYUNIT(unit)]; 1065*25675Ssam register int ctlr = cydinfo[unit]->ui_ctlr; 1066*25675Ssam register ctlr_tab *ci = &ctlr_info[ctlr]; 1067*25675Ssam register int addr, command, bus_lock; 1068*25675Ssam 1069*25675Ssam if(ui->eot && (request->b_blkno >= ui->blkno)) { 1070*25675Ssam request->b_error = ENXIO, request->b_flags |= B_ERROR; 1071*25675Ssam request->b_resid = request->b_bcount; 1072*25675Ssam longjmp(&ci->environ); 107324000Ssam } 1074*25675Ssam if(cyseek(request, cq)) { 1075*25675Ssam ui->cleanup = cywrite_2_fm; 1076*25675Ssam ui->blkno++; 1077*25675Ssam if(request->b_bcount > ci->bs) 1078*25675Ssam command = WRIT_TA, bus_lock = CW_LOCK; 1079*25675Ssam else 1080*25675Ssam command = WRIT_BU, bus_lock = 0; 1081*25675Ssam addr = vbastart(request, (caddr_t)ci->rawbuf, (long *)ci->map, 1082*25675Ssam ci->utl); 1083*25675Ssam load_mbus_addr((caddr_t)addr, (short *)&ci->tpb.data_ptr); 1084*25675Ssam cyexecute(command,request->b_bcount,addr,bus_lock,unit,5,FALSE); 1085*25675Ssam vbadone(request, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl); 1086*25675Ssam cydone(cq); 1087*25675Ssam } 1088*25675Ssam } 108924000Ssam 109024000Ssam 1091*25675Ssam /* 1092*25675Ssam ** cyseek is used by the block device to position the tape correctly 1093*25675Ssam ** before each read or write request. 1094*25675Ssam ** 1095*25675Ssam ** The special cases are: 1096*25675Ssam ** 1) we can hit end of tape while seeking. 1097*25675Ssam ** 2) we want to be nice to other processes while seeking so we 1098*25675Ssam ** break the request up into smaller requests. 1099*25675Ssam */ 1100*25675Ssam cyseek(request, cq) 1101*25675Ssam register struct buf *request; 1102*25675Ssam register struct buf *cq; 1103*25675Ssam { 1104*25675Ssam register int unit = CYUNIT(request->b_dev); 1105*25675Ssam register unit_tab *ui = &unit_info[CYUNIT(unit)]; 1106*25675Ssam register int ctlr = cydinfo[unit]->ui_ctlr; 1107*25675Ssam register ctlr_tab *ci = &ctlr_info[ctlr]; 110824000Ssam 1109*25675Ssam #ifdef lint 1110*25675Ssam cq = cq; 1111*25675Ssam #endif 1112*25675Ssam if(request->b_blkno < ui->blkno) { 1113*25675Ssam register int count; 111424000Ssam 1115*25675Ssam (*ui->cleanup)(unit, MAINTAIN_POSITION); 1116*25675Ssam count = ((request->b_blkno+1) == ui->blkno) ? 2 : 1; 1117*25675Ssam ui->blkno -= count; 1118*25675Ssam cyexecute(SPAC_FM, (long)1, 0, CW_REV, unit, 10, FALSE); 1119*25675Ssam if(!ui->eof) 1120*25675Ssam return FALSE; 1121*25675Ssam ui->eof = FALSE; 1122*25675Ssam request->b_blkno = ui->blkno + 1; 1123*25675Ssam } 1124*25675Ssam if(request->b_blkno > ui->blkno) { 1125*25675Ssam if((ui->cleanup != cyno_op) || ui->eof || ui->eot) { 1126*25675Ssam request->b_resid = request->b_bcount; 1127*25675Ssam request->b_error = ENXIO, request->b_flags |= B_ERROR; 1128*25675Ssam longjmp(&ci->environ); 112924000Ssam } 1130*25675Ssam ui->blkno++; 1131*25675Ssam cyexecute(SPAC_FM, (long)1, 0, 0, unit, 10, FALSE); 1132*25675Ssam return FALSE; 1133*25675Ssam } 1134*25675Ssam return TRUE; 1135*25675Ssam } 113624000Ssam 113724000Ssam 1138*25675Ssam /* 1139*25675Ssam */ 1140*25675Ssam 1141*25675Ssam cywrite_eov(request, cq) 1142*25675Ssam register struct buf *request; 1143*25675Ssam register struct buf *cq; 1144*25675Ssam { 1145*25675Ssam extern int cyno_op(); 1146*25675Ssam register int unit = CYUNIT(request->b_dev); 1147*25675Ssam register unit_tab *ui = &unit_info[CYUNIT(unit)]; 1148*25675Ssam 1149*25675Ssam if(ui->cleanup != cyno_op) { 1150*25675Ssam (*ui->cleanup)(unit, DONT_MAINTAIN_POSITION); 1151*25675Ssam cyexecute(SPACE, (long)2, 0, CW_REV, unit, 10, FALSE); 1152*25675Ssam cyexecute(SPACE, (long)1, 0, 0, unit, 10, FALSE); 1153*25675Ssam unit_info[unit].cleanup = cyno_op; 1154*25675Ssam ui->blkno = 0; 115524000Ssam } 1156*25675Ssam cydone(cq); 1157*25675Ssam } 1158*25675Ssam 1159*25675Ssam 1160*25675Ssam /* 1161*25675Ssam ** Do nothing 1162*25675Ssam */ 1163*25675Ssam /*ARGSUSED*/ 1164*25675Ssam cyno_op(unit, action) 1165*25675Ssam int unit, action; 1166*25675Ssam { 1167*25675Ssam } 1168*25675Ssam 1169*25675Ssam 1170*25675Ssam /* 1171*25675Ssam ** Write 0 file marks to tape 1172*25675Ssam */ 1173*25675Ssam /*ARGSUSED*/ 1174*25675Ssam cywrite_0_fm(unit, action) 1175*25675Ssam int unit, action; 1176*25675Ssam { 1177*25675Ssam unit_info[unit].cleanup = cyno_op; 1178*25675Ssam } 1179*25675Ssam 1180*25675Ssam 1181*25675Ssam /* 1182*25675Ssam ** Write 1 file mark to tape 1183*25675Ssam */ 1184*25675Ssam 1185*25675Ssam cywrite_1_fm(unit, action) 1186*25675Ssam int unit, action; 1187*25675Ssam { 1188*25675Ssam 1189*25675Ssam cyexecute(WRIT_FM, (long)1, 0, 0, unit, 5, FALSE); 1190*25675Ssam if(action == MAINTAIN_POSITION) { 1191*25675Ssam cyexecute(SPACE, (long)2, 0, CW_REV, unit, 10, FALSE); 1192*25675Ssam cyexecute(SPACE, (long)1, 0, 0, unit, 10, FALSE); 119324000Ssam } 1194*25675Ssam unit_info[unit].cleanup = cyno_op; 119524000Ssam } 119624000Ssam 1197*25675Ssam 1198*25675Ssam /* 1199*25675Ssam ** Write 2 file marks to tape 1200*25675Ssam */ 1201*25675Ssam 1202*25675Ssam cywrite_2_fm(unit, action) 1203*25675Ssam int unit, action; 120424000Ssam { 120524000Ssam 1206*25675Ssam cyexecute(WRIT_FM, (long)1, 0, 0, unit, 5, FALSE); 1207*25675Ssam cyexecute(WRIT_FM, (long)1, 0, 0, unit, 5, FALSE); 1208*25675Ssam if(action == MAINTAIN_POSITION) { 1209*25675Ssam cyexecute(SPACE, (long)3, 0, CW_REV, unit, 10, FALSE); 1210*25675Ssam cyexecute(SPACE, (long)1, 0, 0, unit, 2, FALSE); 121124000Ssam } 1212*25675Ssam unit_info[unit].cleanup = cyno_op; 121324000Ssam } 121424000Ssam 1215*25675Ssam 1216*25675Ssam extern int cytimeout(); 1217*25675Ssam extern int cy_normal_path(); 1218*25675Ssam /* 1219*25675Ssam ** Cyexecute is used to start all commands to the controller. We 1220*25675Ssam ** do all common code here before starting. 1221*25675Ssam */ 1222*25675Ssam 1223*25675Ssam cyexecute(command, count, addr, control_flags, unit, time, interupt_routine) 1224*25675Ssam register int command; 1225*25675Ssam long count; 1226*25675Ssam int addr, control_flags, unit, time, interupt_routine; 122724000Ssam { 1228*25675Ssam register int priority; 1229*25675Ssam register int ctlr = cydinfo[unit]->ui_ctlr; 1230*25675Ssam register unit_tab *ui = &unit_info[unit]; 1231*25675Ssam register ctlr_tab *ci = &ctlr_info[ctlr]; 1232*25675Ssam register struct buf *request = ui->u_queue.av_forw; 123324000Ssam 1234*25675Ssam ci->tpb.cmd = command; 1235*25675Ssam ci->tpb.control = ui->control_proto | control_flags; 1236*25675Ssam ci->tpb.status = ci->tpb.count = (short)0; 1237*25675Ssam load_mbus_addr((caddr_t)addr, (short *)&ci->tpb.data_ptr); 1238*25675Ssam switch(command) { 1239*25675Ssam case READ_BU: 1240*25675Ssam case READ_TA: 1241*25675Ssam case WRIT_BU: 1242*25675Ssam case WRIT_TA: 1243*25675Ssam ci->tpb.size = MULTIBUS_SHORT((short)count); 1244*25675Ssam ci->tpb.rec_over = (short)0; 1245*25675Ssam break; 1246*25675Ssam default: 1247*25675Ssam ci->tpb.size = (short)0; 1248*25675Ssam ci->tpb.rec_over = MULTIBUS_SHORT((short)count); 1249*25675Ssam break; 1250*25675Ssam } 1251*25675Ssam load_mbus_addr((caddr_t)0, ci->tpb.link_ptr); 1252*25675Ssam if(!interupt_routine) 1253*25675Ssam ci->last = ci->tpb; 1254*25675Ssam /* 1255*25675Ssam gag! but it the last possible moment to wait 1256*25675Ssam for this controller to get out of it's own way..... 1257*25675Ssam */ 1258*25675Ssam uncache(&ci->ccb.gate); 1259*25675Ssam while(ci->ccb.gate == GATE_CLOSED) 1260*25675Ssam uncache(&ci->ccb.gate); 1261*25675Ssam load_mbus_addr((caddr_t)&ci->tpb, ci->ccb.tpb_ptr); 1262*25675Ssam ci->ccb.ccw = NORMAL_INTERUPT; 1263*25675Ssam ci->ccb.gate = GATE_CLOSED; 1264*25675Ssam if(!interupt_routine) 1265*25675Ssam ci->interupt_path = cy_normal_path; 1266*25675Ssam timeout(cytimeout, (caddr_t)ctlr, time*60); 1267*25675Ssam priority = spl3(); 1268*25675Ssam CY_ATTENTION(cyminfo[ctlr]->um_addr); 1269*25675Ssam if(!interupt_routine) { 1270*25675Ssam sleep((caddr_t)ci, PRIBIO+3); 1271*25675Ssam splx(priority); 1272*25675Ssam if(request->b_flags & B_ERROR) { 1273*25675Ssam if((command == READ_BU) || (command == READ_TA) || 1274*25675Ssam (command == WRIT_BU) || (command == WRIT_TA)) 1275*25675Ssam vbadone(request, (caddr_t)ci->rawbuf, 1276*25675Ssam (long *)ci->map,ci->utl); 1277*25675Ssam longjmp(&ci->environ); 127824000Ssam } 127924000Ssam return; 1280*25675Ssam } 1281*25675Ssam splx(priority); 128224000Ssam } 128324000Ssam 1284*25675Ssam 1285*25675Ssam /* 1286*25675Ssam ** cytimeout is the interupt timeout routine. We assume that a 1287*25675Ssam ** particular command has gone astray, so we completely reset the controller, 1288*25675Ssam ** and call the interupt routine to help us clean up. Before the interupt 1289*25675Ssam ** routine is called we jam a controller timeout value in the status register 1290*25675Ssam ** to fake out the calling routines. 1291*25675Ssam */ 1292*25675Ssam 1293*25675Ssam cytimeout(ctlr) 1294*25675Ssam register int ctlr; 129524000Ssam { 1296*25675Ssam register int priority = spl3(); 1297*25675Ssam register char *ctlr_vaddr = cyminfo[ctlr]->um_addr; 1298*25675Ssam register int tmp_stat; 129924000Ssam 1300*25675Ssam uncache(&ctlr_info[ctlr].tpb.status); 1301*25675Ssam tmp_stat = ctlr_info[ctlr].tpb.status; 1302*25675Ssam CY_RESET(ctlr_vaddr); 1303*25675Ssam cy_init_controller(ctlr_vaddr, ctlr, 0); 1304*25675Ssam splx(priority); 1305*25675Ssam ctlr_info[ctlr].tpb = ctlr_info[ctlr].last; 1306*25675Ssam ctlr_info[ctlr].tpb.status = (tmp_stat & ~CS_ERm) | CS_OL | ER_TIMOUT; 1307*25675Ssam cyintr(ctlr); 130824000Ssam } 130924000Ssam 1310*25675Ssam /* 1311*25675Ssam ** Cyintr is the interupt routine for the Tapemaster controller. 1312*25675Ssam ** 1313*25675Ssam ** Due to controller problems, the first thing we have to do is turn 1314*25675Ssam ** off the Tapemaster interupting mechanism. If we don't we will be flooded 1315*25675Ssam ** with bogus interupts and the system will spend all it's time processing 1316*25675Ssam ** them. To Turn the interupts off we issue a NOOP command with the 'turn 1317*25675Ssam ** off interupts' code in the ccb. 1318*25675Ssam ** 1319*25675Ssam ** take note that since this command TURNS OFF the interupts it 1320*25675Ssam ** itself CANNOT interupt... This means that polling must be done 1321*25675Ssam ** at sometime to make sure that tis command is completed. The polling 1322*25675Ssam ** is done before the next command is issued to reduce polling (halting 1323*25675Ssam ** UNIX) time. 1324*25675Ssam ** 1325*25675Ssam ** After we turn off interupts we uncache all the values in the tpb 1326*25675Ssam ** and call the correct processing routine. This routine can be for normal 1327*25675Ssam ** interupts or for interupts generated during a retry operation. 1328*25675Ssam */ 1329*25675Ssam 1330*25675Ssam cyintr(ctlr) 1331*25675Ssam register int ctlr; 133224000Ssam { 1333*25675Ssam extern int cytimeout(); 1334*25675Ssam register ctlr_tab *ci = &ctlr_info[ctlr]; 133524000Ssam 1336*25675Ssam untimeout(cytimeout, (caddr_t)ctlr); 1337*25675Ssam /* turn off interupts for the stupid controller */ 1338*25675Ssam ci->ccb.ccw = CLEAR_INTERUPT; 1339*25675Ssam ci->noop.cmd = NO_OP; 1340*25675Ssam ci->noop.control = (short)0; 1341*25675Ssam load_mbus_addr((caddr_t)&ci->noop, ci->ccb.tpb_ptr); 1342*25675Ssam ci->ccb.gate = GATE_CLOSED; 1343*25675Ssam CY_ATTENTION(cyminfo[ctlr]->um_addr); 1344*25675Ssam uncache_tpb(ci); 1345*25675Ssam (*ci->interupt_path)(ctlr); 134624000Ssam } 134724000Ssam 134824000Ssam 1349*25675Ssam /* 1350*25675Ssam ** This is the portion of the interupt routine that processes all 1351*25675Ssam ** normal cases i.e. non retry cases. We check the operations status 1352*25675Ssam ** if it is retryable we set the interupt path to the retry routines and 1353*25675Ssam ** start the backward spaceing. when the spacing is done the retry logic 1354*25675Ssam ** will be called and this routine will be skipped entirely. 1355*25675Ssam ** 1356*25675Ssam ** If the command is ok or not retryable we set the status accordingly 1357*25675Ssam ** and wakeup cyexecute to continue processing. 1358*25675Ssam */ 1359*25675Ssam 1360*25675Ssam cy_normal_path(ctlr) 1361*25675Ssam register int ctlr; 136224000Ssam { 1363*25675Ssam extern int cy_retry_path(); 1364*25675Ssam extern int cy_extended_gap_path(); 1365*25675Ssam register int error; 1366*25675Ssam register struct buf *cq = &cyminfo[ctlr]->um_tab; 1367*25675Ssam register struct buf *uq = cq->b_forw; 1368*25675Ssam register struct buf *request = uq->av_forw; 1369*25675Ssam register int unit = CYUNIT(request->b_dev); 1370*25675Ssam register unit_tab *ui = &unit_info[unit]; 1371*25675Ssam register ctlr_tab *ci = &ctlr_info[ctlr]; 137224000Ssam 1373*25675Ssam if (error = cydecode_error(unit, ci->tpb.status)) { 1374*25675Ssam if(error != FATAL) { 1375*25675Ssam if (error == RETRY) 1376*25675Ssam ci->interupt_path = cy_retry_path; 137724000Ssam else 1378*25675Ssam ci->interupt_path = cy_extended_gap_path; 1379*25675Ssam cyexecute(SPACE, (long)2, 0, CW_REV, unit, 5, TRUE); 1380*25675Ssam return; 138124000Ssam } 138224000Ssam } 1383*25675Ssam request->b_resid=request->b_bcount-MULTIBUS_SHORT(ci->tpb.count); 1384*25675Ssam ui->error_count = 0; 1385*25675Ssam ui->last_resid = request->b_resid; 1386*25675Ssam ui->last_status = ci->tpb.status; 1387*25675Ssam ui->last_control = ci->tpb.control; 1388*25675Ssam if (error == FATAL) 1389*25675Ssam request->b_flags |= B_ERROR, request->b_error = EIO; 1390*25675Ssam wakeup((caddr_t)ci); 139124000Ssam } 139224000Ssam 139324000Ssam 1394*25675Ssam /* 1395*25675Ssam ** Cy_retry_path finishes up the retry sequence for the tape. 1396*25675Ssam ** If we were going in the reverse direction it means that we have to 1397*25675Ssam ** space forward to correctly position ourselfs in back of the tape gap 1398*25675Ssam ** instead of in front of it. If we were going forward it means that 1399*25675Ssam ** we are positioned correctly and we can actually restart the instruction 1400*25675Ssam ** that failed before. 1401*25675Ssam */ 1402*25675Ssam 1403*25675Ssam cy_retry_path(ctlr) 1404*25675Ssam register int ctlr; 140524000Ssam { 1406*25675Ssam extern int cy_do_again_path(); 1407*25675Ssam register struct buf *cq = &cyminfo[ctlr]->um_tab; 1408*25675Ssam register struct buf *uq = cq->b_forw; 1409*25675Ssam register struct buf *request = uq->av_forw; 1410*25675Ssam register int unit = CYUNIT(request->b_dev); 1411*25675Ssam register ctlr_tab *ci = &ctlr_info[ctlr]; 141224000Ssam 1413*25675Ssam if(!(ci->tpb.status & CS_OL)) { 1414*25675Ssam ci->interupt_path = cy_normal_path; 1415*25675Ssam cy_normal_path(ctlr); 1416*25675Ssam return; 1417*25675Ssam } 1418*25675Ssam if(ci->tpb.control & CW_REV) { 1419*25675Ssam if(!(ci->tpb.status & CS_LP)) { 1420*25675Ssam ci->interupt_path = cy_do_again_path; 1421*25675Ssam cyexecute(SPACE, (long)1, 0, 0, unit, 5, TRUE); 1422*25675Ssam return; 142324000Ssam } 1424*25675Ssam cy_do_again_path(ctlr); 1425*25675Ssam } 1426*25675Ssam } 1427*25675Ssam 1428*25675Ssam 1429*25675Ssam /* 1430*25675Ssam ** 1431*25675Ssam */ 1432*25675Ssam 1433*25675Ssam cy_extended_gap_path(ctlr) 1434*25675Ssam register int ctlr; 1435*25675Ssam { 1436*25675Ssam extern int cy_do_again_path(); 1437*25675Ssam register ctlr_tab *ci = &ctlr_info[ctlr]; 1438*25675Ssam register struct buf *cq = &cyminfo[ctlr]->um_tab; 1439*25675Ssam register struct buf *uq = cq->b_forw; 1440*25675Ssam register struct buf *request = uq->av_forw; 1441*25675Ssam register int unit = CYUNIT(request->b_dev); 1442*25675Ssam 1443*25675Ssam if(!(ci->tpb.status & CS_OL)) { 1444*25675Ssam ci->interupt_path = cy_normal_path; 1445*25675Ssam cy_normal_path(ctlr); 1446*25675Ssam return; 1447*25675Ssam } 1448*25675Ssam if(ci->tpb.control & CW_REV) { 1449*25675Ssam if(!(ci->tpb.status & CS_LP)) { 1450*25675Ssam cyexecute(SPACE, (long)1, 0, 0, unit, 5, TRUE); 1451*25675Ssam return; 145224000Ssam } 145324000Ssam } 1454*25675Ssam ci->interupt_path = cy_do_again_path; 1455*25675Ssam cyexecute(ERASE_F, (long)unit_info[unit].error_count, 0, 0, 1456*25675Ssam unit, 5, TRUE); 145724000Ssam } 145824000Ssam 145924000Ssam 1460*25675Ssam /* 1461*25675Ssam ** 1462*25675Ssam */ 146324000Ssam 1464*25675Ssam cy_do_again_path(ctlr) 1465*25675Ssam register int ctlr; 1466*25675Ssam { 1467*25675Ssam extern int cy_normal_path(); 1468*25675Ssam register ctlr_tab *ci = &ctlr_info[ctlr]; 1469*25675Ssam 1470*25675Ssam if(!(ci->tpb.status & CS_OL)) { 1471*25675Ssam ci->interupt_path = cy_normal_path; 1472*25675Ssam cy_normal_path(ctlr); 1473*25675Ssam return; 1474*25675Ssam } 1475*25675Ssam ci->tpb = ci->last; 1476*25675Ssam uncache(&ci->ccb.gate); 1477*25675Ssam while(ci->ccb.gate == GATE_CLOSED) 1478*25675Ssam uncache(&ci->ccb.gate); 1479*25675Ssam load_mbus_addr((caddr_t)&ci->tpb, ci->ccb.tpb_ptr); 1480*25675Ssam ci->ccb.ccw = NORMAL_INTERUPT; 1481*25675Ssam ci->ccb.gate = GATE_CLOSED; 1482*25675Ssam ci->interupt_path = cy_normal_path; 1483*25675Ssam CY_ATTENTION(cyminfo[ctlr]->um_addr); 1484*25675Ssam } 1485*25675Ssam 1486*25675Ssam 148724000Ssam /* 1488*25675Ssam ** for each longword in the tpb we call uncache to purge it from 1489*25675Ssam ** the cache. This is done so that we can correctly access tpb data 1490*25675Ssam ** that was placed there by the controller. 1491*25675Ssam */ 1492*25675Ssam 1493*25675Ssam uncache_tpb(ci) 1494*25675Ssam ctlr_tab *ci; 149524000Ssam { 1496*25675Ssam register long *ptr = (long *)&ci->tpb; 1497*25675Ssam register int i; 149824000Ssam 1499*25675Ssam for(i=0; i<((sizeof(fmt_tpb)+sizeof(long)-1)/sizeof(long)); i++) 1500*25675Ssam uncache(ptr++); 150124000Ssam } 150224000Ssam 1503*25675Ssam 150424000Ssam /* 1505*25675Ssam ** Cyprint_error is the common printing routine for all messages 1506*25675Ssam ** that need to print the tape status along with it. This is so we 1507*25675Ssam ** we can save space, have consistant messages, and we can send the messages 1508*25675Ssam ** to the correct places. 1509*25675Ssam */ 1510*25675Ssam 1511*25675Ssam cyprint_err(message, unit, status) 1512*25675Ssam register char *message; 1513*25675Ssam register int unit, status; 151424000Ssam { 1515*25675Ssam status &= 0xffff; 1516*25675Ssam printf("cy%d: %s! Status = %x\n", unit, message, status); 151724000Ssam } 151824000Ssam 1519*25675Ssam /* 1520*25675Ssam ** Decode the error to determine whether the previous command was 1521*25675Ssam ** ok, retryable, or fatal and return the value. If it was a hardware 1522*25675Ssam ** problem we print the message to the console, otherwise we print it 1523*25675Ssam ** to the user's terminal later when execute returns. 1524*25675Ssam */ 1525*25675Ssam 1526*25675Ssam cydecode_error(unit, status) 1527*25675Ssam register int unit, status; 1528*25675Ssam { 1529*25675Ssam register unit_tab *ui = &unit_info[unit]; 1530*25675Ssam register ctlr_tab *ci = &ctlr_info[cydinfo[unit]->ui_ctlr]; 1531*25675Ssam 1532*25675Ssam if(!(status & CS_OL) && (ci->tpb.cmd != OFF_UNL)) { 1533*25675Ssam ui->message = "Drive is not on-line"; 1534*25675Ssam cyprint_err(ui->message, unit, status); 1535*25675Ssam return FATAL; 1536*25675Ssam } 1537*25675Ssam ui->bot = ((status & CS_LP) != 0); 1538*25675Ssam ui->eof = ((status & CS_FM) != 0); 1539*25675Ssam switch(status & CS_ERm) { 1540*25675Ssam case ER_EOT: 1541*25675Ssam if(ci->tpb.control & CW_REV) { 1542*25675Ssam ui->bot = TRUE; 1543*25675Ssam ui->eot = FALSE; 1544*25675Ssam } 1545*25675Ssam else if(!ui->eot){ 1546*25675Ssam ui->message = "End of tape"; 1547*25675Ssam ui->bot = FALSE; 1548*25675Ssam ui->eot = TRUE; 1549*25675Ssam } 1550*25675Ssam case 0 : 1551*25675Ssam case ER_FM: 1552*25675Ssam case ER_NOSTRM: 1553*25675Ssam return 0; 1554*25675Ssam case ER_TIMOUT: 1555*25675Ssam case ER_TIMOUT1: 1556*25675Ssam case ER_TIMOUT2: 1557*25675Ssam case ER_TIMOUT3: 1558*25675Ssam case ER_TIMOUT4: 1559*25675Ssam ui->message = "Drive timed out during transfer"; 1560*25675Ssam cyprint_err(ui->message, unit, status); 1561*25675Ssam return FATAL; 1562*25675Ssam case ER_NEX: 1563*25675Ssam ui->message = 1564*25675Ssam "Controller referenced non-existant system memory"; 1565*25675Ssam cyprint_err(ui->message, unit, status); 1566*25675Ssam return FATAL; 1567*25675Ssam case ER_DIAG: 1568*25675Ssam case ER_JUMPER: 1569*25675Ssam ui->message = "Controller diagnostics failed"; 1570*25675Ssam cyprint_err(ui->message, unit, status); 1571*25675Ssam return FATAL; 1572*25675Ssam case ER_STROBE: 1573*25675Ssam if (ci->tpb.cmd == READ_BU) { 1574*25675Ssam ci->last.cmd = READ_TA; 1575*25675Ssam return RETRY; 1576*25675Ssam } 1577*25675Ssam if(ci->tpb.cmd == READ_TA) 1578*25675Ssam return 0; 1579*25675Ssam ui->message = "Unsatisfactory media found"; 1580*25675Ssam return FATAL; 1581*25675Ssam case ER_FIFO: 1582*25675Ssam case ER_NOTRDY: 1583*25675Ssam ui->error_count = 1; 1584*25675Ssam return RETRY; 1585*25675Ssam case ER_PROT: 1586*25675Ssam ui->message = "Tape is write protected"; 1587*25675Ssam return FATAL; 1588*25675Ssam case ER_CHKSUM: 1589*25675Ssam ui->message = "Checksum error in controller proms"; 1590*25675Ssam cyprint_err(ui->message, unit, status); 1591*25675Ssam return FATAL; 1592*25675Ssam case ER_HARD: 1593*25675Ssam ui->error_count++; 1594*25675Ssam if((ci->tpb.cmd == WRIT_TA) || 1595*25675Ssam (ci->tpb.cmd == WRIT_BU) || 1596*25675Ssam (ci->tpb.cmd == WRIT_FM)) { 1597*25675Ssam ui->bad_count++; 1598*25675Ssam return EXTEND; 1599*25675Ssam } 1600*25675Ssam ui->message = "Unrecoverable media error during read"; 1601*25675Ssam return FATAL; 1602*25675Ssam case ER_PARITY: 1603*25675Ssam if(++ui->error_count < 8) 1604*25675Ssam return RETRY; 1605*25675Ssam ui->message = "Unrecoverable tape parity error"; 1606*25675Ssam return FATAL; 1607*25675Ssam case ER_BLANK: 1608*25675Ssam ui->message="Blank tape found (data expected)"; 1609*25675Ssam return FATAL; 1610*25675Ssam case ER_HDWERR: 1611*25675Ssam default: 1612*25675Ssam ui->message = "Unrecoverble hardware error"; 1613*25675Ssam cyprint_err(ui->message, unit, status); 1614*25675Ssam return FATAL; 1615*25675Ssam } 1616*25675Ssam } 1617*25675Ssam 1618*25675Ssam cyread(dev, uio) 1619*25675Ssam dev_t dev; 1620*25675Ssam struct uio *uio; 1621*25675Ssam { 1622*25675Ssam unit_tab *ui = &unit_info[CYUNIT(dev)]; 1623*25675Ssam 1624*25675Ssam return (physio(cystrategy, &ui->rawbp, dev, B_READ, cyminsize, uio)); 1625*25675Ssam } 1626*25675Ssam 1627*25675Ssam 1628*25675Ssam cywrite(dev, uio) 1629*25675Ssam dev_t dev; 1630*25675Ssam struct uio *uio; 1631*25675Ssam { 1632*25675Ssam unit_tab *ui = &unit_info[CYUNIT(dev)]; 1633*25675Ssam 1634*25675Ssam return (physio(cystrategy,&ui->rawbp, dev, B_WRITE, cyminsize, uio)); 1635*25675Ssam } 1636*25675Ssam 1637*25675Ssam /*ARGSUSED*/ 1638*25675Ssam cyioctl(dev, cmd, data, flag) 1639*25675Ssam dev_t dev; 1640*25675Ssam caddr_t data; 1641*25675Ssam { 1642*25675Ssam 1643*25675Ssam switch (cmd) { 1644*25675Ssam 1645*25675Ssam case MTIOCTOP: { 1646*25675Ssam struct mtop *mp = (struct mtop *)data; 1647*25675Ssam 1648*25675Ssam if (mp->mt_op <= DO_WAIT) 1649*25675Ssam return (cycmd(dev, (int)mp->mt_op, (int)mp->mt_count)); 1650*25675Ssam return (EIO); 1651*25675Ssam } 1652*25675Ssam 1653*25675Ssam case MTIOCGET: { 1654*25675Ssam register unit_tab *ui = &unit_info[CYUNIT(dev)]; 1655*25675Ssam register struct mtget *mp = (struct mtget *)data; 1656*25675Ssam 1657*25675Ssam mp->mt_type = MT_ISCY; 1658*25675Ssam mp->mt_dsreg = ui->last_control; 1659*25675Ssam mp->mt_erreg = ui->last_status; 1660*25675Ssam mp->mt_resid = ui->last_resid; 1661*25675Ssam mp->mt_fileno = ui->file_number; 1662*25675Ssam mp->mt_blkno = ui->blkno; 1663*25675Ssam cycmd(dev, DO_STAT, 1); 1664*25675Ssam break; 1665*25675Ssam } 1666*25675Ssam 1667*25675Ssam default: 1668*25675Ssam return (ENXIO); 1669*25675Ssam } 1670*25675Ssam return (0); 1671*25675Ssam } 1672*25675Ssam 1673*25675Ssam /* 1674*25675Ssam * Dump routine. 1675*25675Ssam */ 167624000Ssam cydump(dev) 1677*25675Ssam dev_t dev; 167824000Ssam { 1679*25675Ssam register int unit = CYUNIT(dev); 1680*25675Ssam register int ctlr = cydinfo[unit]->ui_ctlr; 1681*25675Ssam register unit_tab *ui = &unit_info[unit]; 1682*25675Ssam register ctlr_tab *ci = &ctlr_info[ctlr]; 1683*25675Ssam register int blk_siz; 1684*25675Ssam register int num = maxfree; 1685*25675Ssam register int start = 0x800; 168624000Ssam 1687*25675Ssam if ((unit >= NCY) || cydinfo[unit]) 168824000Ssam return(ENXIO); 1689*25675Ssam ui->control_proto = CW_LOCK | CW_25ips | CW_16bits; 1690*25675Ssam if (cywait(&ci->ccb)) 1691*25675Ssam return(EFAULT); 169224000Ssam while (num > 0) { 1693*25675Ssam blk_siz = num > TBUFSIZ ? TBUFSIZ : num; 1694*25675Ssam bcopy((caddr_t)(start*NBPG), (caddr_t)ci->rawbuf, 1695*25675Ssam (unsigned)(blk_siz*NBPG)); 1696*25675Ssam ci->tpb.cmd = WRIT_TA; 1697*25675Ssam ci->tpb.control = ui->control_proto; 1698*25675Ssam ci->tpb.status = 0; 1699*25675Ssam ci->tpb.size = MULTIBUS_SHORT(blk_siz*NBPG); 1700*25675Ssam load_mbus_addr((caddr_t)0, ci->tpb.link_ptr); 1701*25675Ssam load_mbus_addr((caddr_t)ci->rawbuf, (short *)&ci->tpb.data_ptr); 1702*25675Ssam load_mbus_addr((caddr_t)&ci->tpb, ci->ccb.tpb_ptr); 1703*25675Ssam ci->ccb.gate = GATE_CLOSED; 1704*25675Ssam CY_ATTENTION(cyminfo[ctlr]->um_addr); 1705*25675Ssam start += blk_siz; 1706*25675Ssam num -= blk_siz; 1707*25675Ssam if (cywait(&ci->ccb)) 1708*25675Ssam return(EFAULT); 1709*25675Ssam uncache(&ci->tpb); 1710*25675Ssam if (ci->tpb.status&CS_ERm) /* error */ 171124000Ssam return (EIO); 171224000Ssam } 1713*25675Ssam for(num=0; num<2; num++) { 1714*25675Ssam ci->tpb.cmd = WRIT_FM; 1715*25675Ssam ci->tpb.control = ui->control_proto; 1716*25675Ssam ci->tpb.status = ci->tpb.size = 0; 1717*25675Ssam ci->tpb.count = MULTIBUS_SHORT(1); 1718*25675Ssam load_mbus_addr((caddr_t)0, ci->tpb.link_ptr); 1719*25675Ssam load_mbus_addr((caddr_t)ci->rawbuf, (short *)&ci->tpb.data_ptr); 1720*25675Ssam load_mbus_addr((caddr_t)&ci->tpb, ci->ccb.tpb_ptr); 1721*25675Ssam ci->ccb.gate = GATE_CLOSED; 1722*25675Ssam CY_ATTENTION(cyminfo[ctlr]->um_addr); 1723*25675Ssam if (cywait(&ci->ccb)) 1724*25675Ssam return(EFAULT); 1725*25675Ssam uncache(&ci->tpb); 1726*25675Ssam if (ci->tpb.status&CS_ERm) /* error */ 1727*25675Ssam return (EIO); 1728*25675Ssam } 1729*25675Ssam ci->tpb.cmd = REWD_OV; 1730*25675Ssam ci->tpb.control = ui->control_proto; 1731*25675Ssam ci->tpb.status = ci->tpb.size = 0; 1732*25675Ssam ci->tpb.count = MULTIBUS_SHORT(1); 1733*25675Ssam load_mbus_addr((caddr_t)0, ci->tpb.link_ptr); 1734*25675Ssam load_mbus_addr((caddr_t)ci->rawbuf, (short *)&ci->tpb.data_ptr); 1735*25675Ssam load_mbus_addr((caddr_t)&ci->tpb, ci->ccb.tpb_ptr); 1736*25675Ssam ci->ccb.gate = GATE_CLOSED; 1737*25675Ssam CY_ATTENTION(cyminfo[ctlr]->um_addr); 1738*25675Ssam if (cywait(&ci->ccb)) 1739*25675Ssam return EFAULT; 1740*25675Ssam uncache(&ci->tpb); 1741*25675Ssam return 0; 174224000Ssam } 174324000Ssam 1744*25675Ssam /* 1745*25675Ssam * Poll until the controller is ready. 1746*25675Ssam */ 1747*25675Ssam cywait(cp) 1748*25675Ssam register fmt_ccb *cp; 174924000Ssam { 1750*25675Ssam register int i = 5000; 175124000Ssam 1752*25675Ssam uncache(&cp->gate); 1753*25675Ssam while (i-- > 0 && cp->gate == GATE_CLOSED) { 175424000Ssam DELAY(1000); 1755*25675Ssam uncache(&cp->gate); 175624000Ssam } 1757*25675Ssam return (i <= 0); 175824000Ssam } 175924000Ssam 1760*25675Ssam /* 1761*25675Ssam * Load a 20 bit pointer into the i/o registers. 1762*25675Ssam */ 1763*25675Ssam load_mbus_addr(in, out) 1764*25675Ssam caddr_t in; 1765*25675Ssam short *out; 176624000Ssam { 1767*25675Ssam register int tmp_in = (int)in; 1768*25675Ssam register char *out_ptr = (char *)out; 1769*25675Ssam 1770*25675Ssam *out_ptr++ = (char)(tmp_in & 0xff); 1771*25675Ssam *out_ptr++ = (char)((tmp_in >> 8) & 0xff); 1772*25675Ssam *out_ptr++ = (char)0; 1773*25675Ssam *out_ptr++ = (char)((tmp_in & 0xf0000) >> 12); 177424000Ssam } 177524000Ssam 1776*25675Ssam /* 1777*25675Ssam ** CYMINSIZE s supposed to adjust the buffer size for any raw i/o. 1778*25675Ssam ** since tapes can not read the tail end of partial blocks we ignore 1779*25675Ssam ** this request and strategy will return an appropriate error message later. 1780*25675Ssam ** 1781*25675Ssam ** If this is not done UNIX will lose data that is on the tape. 1782*25675Ssam */ 1783*25675Ssam unsigned 1784*25675Ssam cyminsize(bp) 1785*25675Ssam struct buf *bp; 178624000Ssam { 1787*25675Ssam if (bp->b_bcount > MAX_BLOCKSIZE) 1788*25675Ssam bp->b_bcount = MAX_BLOCKSIZE; 178924000Ssam } 179024000Ssam 1791*25675Ssam /* 1792*25675Ssam * Unconditionally reset all controllers to their initial state. 1793*25675Ssam */ 1794*25675Ssam cyreset(vba) 1795*25675Ssam int vba; 179624000Ssam { 1797*25675Ssam register caddr_t addr; 1798*25675Ssam register int ctlr; 179924000Ssam 1800*25675Ssam for (ctlr = 0; ctlr < NCY; ctlr++) 1801*25675Ssam if (cyminfo[ctlr] && cyminfo[ctlr]->um_vbanum == vba) { 1802*25675Ssam addr = cyminfo[ctlr]->um_addr; 1803*25675Ssam CY_RESET(addr); 1804*25675Ssam if (!cy_init_controller(addr, ctlr, 0)) { 1805*25675Ssam printf("cy%d: reset failed\n", ctlr); 1806*25675Ssam cyminfo[ctlr] = NULL; 1807*25675Ssam } 1808*25675Ssam } 180924000Ssam } 181024000Ssam #endif 1811