add Berkeley specific copyright
[unix-history] / usr / src / sys / tahoe / vba / cy.c
index e0867f1..8b4e850 100644 (file)
@@ -1,4 +1,19 @@
-/*     cy.c    1.9     87/01/11        */
+/*
+ * Copyright (c) 1988 Regents of the University of California.
+ * All rights reserved.
+ *
+ * This code is derived from software contributed to Berkeley by
+ * Computer Consoles Inc.
+ *
+ * Redistribution and use in source and binary forms are permitted
+ * provided that this notice is preserved and that due credit is given
+ * to the University of California at Berkeley. The name of the University
+ * may not be used to endorse or promote products derived from this
+ * software without specific prior written permission. This software
+ * is provided ``as is'' without express or implied warranty.
+ *
+ *     @(#)cy.c        7.1 (Berkeley) %G%
+ */
 
 #include "yc.h"
 #if NCY > 0
 
 #include "yc.h"
 #if NCY > 0
@@ -50,13 +65,6 @@ int  cydebug = 0;
  */
 struct buf ccybuf[NCY];
 
  */
 struct buf ccybuf[NCY];
 
-/*
- * Raw tape operations use rcybuf.  The driver notices when
- * rcybuf is being used and allows the user program to contine
- * after errors and read records not of the standard length.
- */
-struct buf rcybuf[NCY];
-
 int    cyprobe(), cyslave(), cyattach();
 struct buf ycutab[NYC];
 short  yctocy[NYC];
 int    cyprobe(), cyslave(), cyattach();
 struct buf ycutab[NYC];
 short  yctocy[NYC];
@@ -74,24 +82,21 @@ struct      vba_driver cydriver =
 #define        T_3200BPI       0x08            /* unused */
 
 #define        INF     1000000L                /* close to infinity */
 #define        T_3200BPI       0x08            /* unused */
 
 #define        INF     1000000L                /* close to infinity */
-#define        CYMAXIO (32*NBPG)               /* max i/o size */
 
 /*
  * Software state and shared command areas per controller.
  *
 
 /*
  * Software state and shared command areas per controller.
  *
- * The i/o buffer must be defined statically to insure
- * it's address will fit in 20-bits (YECH!!!!!!!!!!!!!!)
+ * The i/o intermediate buffer must be allocated in startup()
+ * so its address will fit in 20-bits (YECH!!!!!!!!!!!!!!).
  */
 struct cy_softc {
  */
 struct cy_softc {
-       struct  pte *cy_map;    /* pte's for mapped buffer i/o */
-       caddr_t cy_utl;         /* mapped virtual address */
        int     cy_bs;          /* controller's buffer size */
        struct  cyscp *cy_scp;  /* system configuration block address */
        struct  cyccb cy_ccb;   /* channel control block */
        struct  cyscb cy_scb;   /* system configuration block */
        struct  cytpb cy_tpb;   /* tape parameter block */
        struct  cytpb cy_nop;   /* nop parameter block for cyintr */
        int     cy_bs;          /* controller's buffer size */
        struct  cyscp *cy_scp;  /* system configuration block address */
        struct  cyccb cy_ccb;   /* channel control block */
        struct  cyscb cy_scb;   /* system configuration block */
        struct  cytpb cy_tpb;   /* tape parameter block */
        struct  cytpb cy_nop;   /* nop parameter block for cyintr */
-       char    cy_buf[CYMAXIO];/* intermediate buffer */
+       struct  vb_buf cy_rbuf; /* vba resources */
 } cy_softc[NCY];
 
 /*
 } cy_softc[NCY];
 
 /*
@@ -164,7 +169,15 @@ cyprobe(reg, vm)
                /*
                 * Allocate page tables.
                 */
                /*
                 * Allocate page tables.
                 */
-               vbmapalloc(btoc(CYMAXIO)+1, &cy->cy_map, &cy->cy_utl);
+               if (cybuf == 0) {
+                       printf("no cy buffer!!!\n");
+                       return (0);
+               }
+               cy->cy_rbuf.vb_rawbuf = cybuf + ctlr * CYMAXIO;
+               if (vbainit(&cy->cy_rbuf, CYMAXIO, VB_20BIT) == 0) {
+                       printf("cy%d: vbainit failed\n", ctlr);
+                       return (0);
+               }
 
                br = 0x13, cvec = 0x80;                 /* XXX */
                return (sizeof (struct cyccb));
 
                br = 0x13, cvec = 0x80;                 /* XXX */
                return (sizeof (struct cyccb));
@@ -217,7 +230,7 @@ cyinit(ctlr, addr)
         * Initialize the system configuration pointer.
         */
        /* make kernel writable */
         * Initialize the system configuration pointer.
         */
        /* make kernel writable */
-       pte = (int *)vtopte((struct proc *)0, btop(cy->cy_scp))
+       pte = (int *)&Sysmap[btop((int)cy->cy_scp &~ KERNBASE)]
        *pte &= ~PG_PROT; *pte |= PG_KW;
        mtpr(TBIS, cy->cy_scp);
        /* load the correct values in the scp */
        *pte &= ~PG_PROT; *pte |= PG_KW;
        mtpr(TBIS, cy->cy_scp);
        /* load the correct values in the scp */
@@ -283,7 +296,6 @@ cyopen(dev, flag)
        register int ycunit;
        register struct vba_device *vi;
        register struct yc_softc *yc;
        register int ycunit;
        register struct vba_device *vi;
        register struct yc_softc *yc;
-       int s;
 
        ycunit = YCUNIT(dev);
        if (ycunit >= NYC || (vi = ycdinfo[ycunit]) == 0 || vi->ui_alive == 0)
 
        ycunit = YCUNIT(dev);
        if (ycunit >= NYC || (vi = ycdinfo[ycunit]) == 0 || vi->ui_alive == 0)
@@ -302,17 +314,19 @@ cyopen(dev, flag)
        }
        cycommand(dev, CY_SENSE, 1);
        if ((yc->yc_status&CYS_OL) == 0) {      /* not on-line */
        }
        cycommand(dev, CY_SENSE, 1);
        if ((yc->yc_status&CYS_OL) == 0) {      /* not on-line */
-               uprintf("yc%d: not online\n", ycunit);
-               return (ENXIO);
+               uprintf("cy%d: not online\n", ycunit);
+               yc->yc_openf = 0;
+               return (EIO);
        }
        if ((flag&FWRITE) && (yc->yc_status&CYS_WP)) {
        }
        if ((flag&FWRITE) && (yc->yc_status&CYS_WP)) {
-               uprintf("yc%d: no write ring\n", ycunit);
-               return (ENXIO);
+               uprintf("cy%d: no write ring\n", ycunit);
+               yc->yc_openf = 0;
+               return (EIO);
        }
        yc->yc_blkno = (daddr_t)0;
        yc->yc_nxrec = INF;
        yc->yc_lastiow = 0;
        }
        yc->yc_blkno = (daddr_t)0;
        yc->yc_nxrec = INF;
        yc->yc_lastiow = 0;
-       yc->yc_blksize = 1024;          /* guess > 0 */
+       yc->yc_blksize = CYMAXIO;               /* guess > 0 */
        yc->yc_blks = 0;
        yc->yc_softerrs = 0;
        yc->yc_ttyp = u.u_ttyp;
        yc->yc_blks = 0;
        yc->yc_softerrs = 0;
        yc->yc_ttyp = u.u_ttyp;
@@ -334,7 +348,8 @@ cyclose(dev, flag)
        struct yc_softc *yc = &yc_softc[YCUNIT(dev)];
 
        if (flag == FWRITE || (flag&FWRITE) && yc->yc_lastiow) {
        struct yc_softc *yc = &yc_softc[YCUNIT(dev)];
 
        if (flag == FWRITE || (flag&FWRITE) && yc->yc_lastiow) {
-               cycommand(dev, CY_WEOF, 2);
+               cycommand(dev, CY_WEOF, 1);     /* can't use count with WEOF */
+               cycommand(dev, CY_WEOF, 1);
                cycommand(dev, CY_SREV, 1);
        }
        if ((minor(dev)&T_NOREWIND) == 0)
                cycommand(dev, CY_SREV, 1);
        }
        if ((minor(dev)&T_NOREWIND) == 0)
@@ -351,6 +366,7 @@ cyclose(dev, flag)
        dlog((LOG_INFO, "%d soft errors in %d blocks\n",
            yc->yc_softerrs, yc->yc_blks));
        yc->yc_openf = 0;
        dlog((LOG_INFO, "%d soft errors in %d blocks\n",
            yc->yc_softerrs, yc->yc_blks));
        yc->yc_openf = 0;
+       return (0);
 }
 
 /*
 }
 
 /*
@@ -410,19 +426,17 @@ cystrategy(bp)
        dlog((LOG_INFO, "cystrategy(%o, %x)\n", bp->b_dev, bp->b_command));
        dp = &ycutab[ycunit];
        bp->av_forw = NULL;
        dlog((LOG_INFO, "cystrategy(%o, %x)\n", bp->b_dev, bp->b_command));
        dp = &ycutab[ycunit];
        bp->av_forw = NULL;
-       bp->b_errcnt = 0;
        vm = ycdinfo[ycunit]->ui_mi;
        /* BEGIN GROT */
        vm = ycdinfo[ycunit]->ui_mi;
        /* BEGIN GROT */
-       if (bp == &rcybuf[CYUNIT(bp->b_dev)]) {
-               if (bp->b_bcount > CYMAXIO) {
+       if (bp->b_flags & B_RAW) {
+               if (bp->b_bcount >= CYMAXIO) {
                        uprintf("cy%d: i/o size too large\n", vm->um_ctlr);
                        uprintf("cy%d: i/o size too large\n", vm->um_ctlr);
-                       bp->b_error = EIO;
+                       bp->b_error = EINVAL;
                        bp->b_resid = bp->b_bcount;
                        bp->b_flags |= B_ERROR;
                        biodone(bp);
                        return;
                }
                        bp->b_resid = bp->b_bcount;
                        bp->b_flags |= B_ERROR;
                        biodone(bp);
                        return;
                }
-               vbasetup(bp, CYMAXIO);
        }
        /* END GROT */
        s = spl3();
        }
        /* END GROT */
        s = spl3();
@@ -503,41 +517,55 @@ loop:
                if (bp->b_command == CY_REW) {
                        vm->um_tab.b_active = SREW;
                        yc->yc_timo = 5*60;
                if (bp->b_command == CY_REW) {
                        vm->um_tab.b_active = SREW;
                        yc->yc_timo = 5*60;
+               } else if (bp->b_command == CY_FSF ||
+                   bp->b_command == CY_BSF) {
+                       vm->um_tab.b_active = SCOM;
+                       yc->yc_timo = 5*60;
                } else {
                        vm->um_tab.b_active = SCOM;
                        yc->yc_timo = imin(imax(10*(int)bp->b_repcnt,60),5*60);
                }
                cy->cy_tpb.tprec = htoms(bp->b_repcnt);
                } else {
                        vm->um_tab.b_active = SCOM;
                        yc->yc_timo = imin(imax(10*(int)bp->b_repcnt,60),5*60);
                }
                cy->cy_tpb.tprec = htoms(bp->b_repcnt);
+               dlog((LOG_INFO, "bpcmd "));
                goto dobpcmd;
        }
        /*
                goto dobpcmd;
        }
        /*
-        * The following checks handle boundary cases for operation
-        * on no-raw tapes.  On raw tapes the initialization of
-        * yc->yc_nxrec by cyphys causes them to be skipped normally
-        * (except in the case of retries).
+        * For raw I/O, save the current block
+        * number in case we have to retry.
         */
         */
-       if (bdbtofsb(bp->b_blkno) > yc->yc_nxrec) {
-               /*
-                * Can't read past known end-of-file.
-                */
-               bp->b_flags |= B_ERROR;
-               bp->b_error = ENXIO;
-               goto next;
-       }
-       if (bdbtofsb(bp->b_blkno) == yc->yc_nxrec && bp->b_flags&B_READ) {
+       if (bp->b_flags & B_RAW) {
+               if (vm->um_tab.b_errcnt == 0) {
+                       yc->yc_blkno = bp->b_blkno;
+                       yc->yc_nxrec = yc->yc_blkno + 1;
+               }
+       } else {
                /*
                /*
-                * Reading at end of file returns 0 bytes.
+                * Handle boundary cases for operation
+                * on non-raw tapes.
                 */
                 */
-               bp->b_resid = bp->b_bcount;
-               clrbuf(bp);
-               goto next;
+               if (bp->b_blkno > yc->yc_nxrec) {
+                       /*
+                        * Can't read past known end-of-file.
+                        */
+                       bp->b_flags |= B_ERROR;
+                       bp->b_error = ENXIO;
+                       goto next;
+               }
+               if (bp->b_blkno == yc->yc_nxrec && bp->b_flags&B_READ) {
+                       /*
+                        * Reading at end of file returns 0 bytes.
+                        */
+                       bp->b_resid = bp->b_bcount;
+                       clrbuf(bp);
+                       goto next;
+               }
+               if ((bp->b_flags&B_READ) == 0)
+                       /*
+                        * Writing sets EOF.
+                        */
+                       yc->yc_nxrec = bp->b_blkno + 1;
        }
        }
-       if ((bp->b_flags&B_READ) == 0)
-               /*
-                * Writing sets EOF.
-                */
-               yc->yc_nxrec = bdbtofsb(bp->b_blkno) + 1;
-       if ((blkno = yc->yc_blkno) == bdbtofsb(bp->b_blkno)) {
+       if ((blkno = yc->yc_blkno) == bp->b_blkno) {
                caddr_t addr;
                int cmd;
 
                caddr_t addr;
                int cmd;
 
@@ -545,17 +573,21 @@ loop:
                 * Choose the appropriate i/o command based on the
                 * transfer size, the estimated block size,
                 * and the controller's internal buffer size.
                 * Choose the appropriate i/o command based on the
                 * transfer size, the estimated block size,
                 * and the controller's internal buffer size.
+                * If the request length is longer than the tape
+                * block length, a buffered read will fail,
+                * thus, we request at most the size that we expect.
+                * We then check for larger records when the read completes.
                 * If we're retrying a read on a raw device because
                 * the original try was a buffer request which failed
                 * due to a record length error, then we force the use
                 * of the raw controller read (YECH!!!!).
                 */
                if (bp->b_flags&B_READ) {
                 * If we're retrying a read on a raw device because
                 * the original try was a buffer request which failed
                 * due to a record length error, then we force the use
                 * of the raw controller read (YECH!!!!).
                 */
                if (bp->b_flags&B_READ) {
-                       if ((bp->b_bcount > cy->cy_bs &&
-                           yc->yc_blksize > cy->cy_bs) || bp->b_errcnt)
-                               cmd = CY_RCOM;
-                       else
+                       if (yc->yc_blksize <= cy->cy_bs &&
+                           vm->um_tab.b_errcnt == 0)
                                cmd = CY_BRCOM;
                                cmd = CY_BRCOM;
+                       else
+                               cmd = CY_RCOM;
                } else {
                        /*
                         * On write error retries erase the
                } else {
                        /*
                         * On write error retries erase the
@@ -571,8 +603,7 @@ loop:
                        cmd = (bp->b_bcount > cy->cy_bs) ? CY_WCOM : CY_BWCOM;
                }
                vm->um_tab.b_active = SIO;
                        cmd = (bp->b_bcount > cy->cy_bs) ? CY_WCOM : CY_BWCOM;
                }
                vm->um_tab.b_active = SIO;
-               addr = (caddr_t)vbastart(bp, cy->cy_buf,
-                   (long *)cy->cy_map, cy->cy_utl);
+               addr = (caddr_t)vbasetup(bp, &cy->cy_rbuf, 1);
                cy->cy_tpb.tpcmd = cmd;
                cy->cy_tpb.tpcontrol = yc->yc_dens;
                if (cmd == CY_RCOM || cmd == CY_WCOM)
                cy->cy_tpb.tpcmd = cmd;
                cy->cy_tpb.tpcontrol = yc->yc_dens;
                if (cmd == CY_RCOM || cmd == CY_WCOM)
@@ -581,8 +612,9 @@ loop:
                cy->cy_tpb.tpcount = 0;
                cyldmba(cy->cy_tpb.tpdata, (caddr_t)addr);
                cy->cy_tpb.tprec = 0;
                cy->cy_tpb.tpcount = 0;
                cyldmba(cy->cy_tpb.tpdata, (caddr_t)addr);
                cy->cy_tpb.tprec = 0;
-               if (cmd == CY_BRCOM && bp->b_bcount > cy->cy_bs)
-                       cy->cy_tpb.tpsize = htoms(cy->cy_bs);
+               if (cmd == CY_BRCOM)
+                       cy->cy_tpb.tpsize = htoms(imin(yc->yc_blksize,
+                           (int)bp->b_bcount));
                else
                        cy->cy_tpb.tpsize = htoms(bp->b_bcount);
                cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
                else
                        cy->cy_tpb.tpsize = htoms(bp->b_bcount);
                cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
@@ -604,14 +636,14 @@ loop:
         * for raw tapes only on error retries.
         */
        vm->um_tab.b_active = SSEEK;
         * for raw tapes only on error retries.
         */
        vm->um_tab.b_active = SSEEK;
-       if (blkno < bdbtofsb(bp->b_blkno)) {
+       if (blkno < bp->b_blkno) {
                bp->b_command = CY_SFORW;
                bp->b_command = CY_SFORW;
-               cy->cy_tpb.tprec = htoms(bdbtofsb(bp->b_blkno) - blkno);
+               cy->cy_tpb.tprec = htoms(bp->b_blkno - blkno);
        } else {
                bp->b_command = CY_SREV;
        } else {
                bp->b_command = CY_SREV;
-               cy->cy_tpb.tprec = htoms(blkno - bdbtofsb(bp->b_blkno));
+               cy->cy_tpb.tprec = htoms(blkno - bp->b_blkno);
        }
        }
-       yc->yc_timo = imin(imax(10 * htoms(cy->cy_tpb.tprec), 60), 5*60);
+       yc->yc_timo = imin(imax((int)(10 * htoms(cy->cy_tpb.tprec)), 60), 5*60);
 dobpcmd:
        /*
         * Do the command in bp.  Reverse direction commands
 dobpcmd:
        /*
         * Do the command in bp.  Reverse direction commands
@@ -622,9 +654,11 @@ dobpcmd:
        if (bp->b_command&CYCW_REV) {
                cy->cy_tpb.tpcmd = bp->b_command &~ CYCW_REV;
                cy->cy_tpb.tpcontrol = yc->yc_dens | CYCW_REV;
        if (bp->b_command&CYCW_REV) {
                cy->cy_tpb.tpcmd = bp->b_command &~ CYCW_REV;
                cy->cy_tpb.tpcontrol = yc->yc_dens | CYCW_REV;
+dlog((LOG_INFO, "cmd %x control %x\n", cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol));
        } else {
                cy->cy_tpb.tpcmd = bp->b_command;
                cy->cy_tpb.tpcontrol = yc->yc_dens;
        } else {
                cy->cy_tpb.tpcmd = bp->b_command;
                cy->cy_tpb.tpcontrol = yc->yc_dens;
+dlog((LOG_INFO, "cmd %x control %x\n", cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol));
        }
        cy->cy_tpb.tpstatus = 0;
        cy->cy_tpb.tpcount = 0;
        }
        cy->cy_tpb.tpstatus = 0;
        cy->cy_tpb.tpcount = 0;
@@ -643,12 +677,10 @@ dobpcmd:
 next:
        /*
         * Done with this operation due to error or the
 next:
        /*
         * Done with this operation due to error or the
-        * fact that it doesn't do anything.  Release VERSAbus
-        * resource (if any), dequeue the transfer and continue
+        * fact that it doesn't do anything.
+        * Dequeue the transfer and continue
         * processing this slave.
         */
         * processing this slave.
         */
-       if (bp == &rcybuf[CYUNIT(bp->b_dev)])
-               vbadone(bp, cy->cy_buf, (long *)cy->cy_map, cy->cy_utl);
        vm->um_tab.b_errcnt = 0;
        dp->b_actf = bp->av_forw;
        biodone(bp);
        vm->um_tab.b_errcnt = 0;
        dp->b_actf = bp->av_forw;
        biodone(bp);
@@ -658,18 +690,18 @@ next:
 /*
  * Cy interrupt routine.
  */
 /*
  * Cy interrupt routine.
  */
-cyintr(cipher)
-       int cipher;
+cyintr(cyunit)
+       int cyunit;
 {
        struct buf *dp;
        register struct buf *bp;
 {
        struct buf *dp;
        register struct buf *bp;
-       register struct vba_ctlr *vm = cyminfo[cipher];
+       register struct vba_ctlr *vm = cyminfo[cyunit];
        register struct cy_softc *cy;
        register struct yc_softc *yc;
        register struct cy_softc *cy;
        register struct yc_softc *yc;
-       int cyunit, err;
+       int err;
        register state;
 
        register state;
 
-       dlog((LOG_INFO, "cyintr(%d)\n", cipher));
+       dlog((LOG_INFO, "cyintr(%d)\n", cyunit));
        /*
         * First, turn off the interrupt from the controller
         * (device uses Multibus non-vectored interrupts...yech).
        /*
         * First, turn off the interrupt from the controller
         * (device uses Multibus non-vectored interrupts...yech).
@@ -684,7 +716,6 @@ cyintr(cipher)
                return;
        }
        bp = dp->b_actf;
                return;
        }
        bp = dp->b_actf;
-       cyunit = CYUNIT(bp->b_dev);
        cy = &cy_softc[cyunit];
        cyuncachetpb(cy);
        yc = &yc_softc[YCUNIT(bp->b_dev)];
        cy = &cy_softc[cyunit];
        cyuncachetpb(cy);
        yc = &yc_softc[YCUNIT(bp->b_dev)];
@@ -740,17 +771,15 @@ cyintr(cipher)
                 * If we were reading raw tape and the only error was that the
                 * record was too long, then we don't consider this an error.
                 */
                 * If we were reading raw tape and the only error was that the
                 * record was too long, then we don't consider this an error.
                 */
-               if (bp == &rcybuf[cyunit] && (bp->b_flags&B_READ) &&
+               if ((bp->b_flags & (B_READ|B_RAW)) == (B_READ|B_RAW) &&
                    err == CYER_STROBE) {
                        /*
                         * Retry reads with the command changed to
                         * a raw read if necessary.  Setting b_errcnt
                         * here causes cystart (above) to force a CY_RCOM.
                         */
                    err == CYER_STROBE) {
                        /*
                         * Retry reads with the command changed to
                         * a raw read if necessary.  Setting b_errcnt
                         * here causes cystart (above) to force a CY_RCOM.
                         */
-                       if (htoms(cy->cy_tpb.tprec) > cy->cy_bs &&
-                           bp->b_bcount > cy->cy_bs && 
-                           yc->yc_blksize <= cy->cy_bs &&
-                           bp->b_errcnt++ == 0) {
+                       if (cy->cy_tpb.tpcmd == CY_BRCOM &&
+                           vm->um_tab.b_errcnt++ == 0) {
                                yc->yc_blkno++;
                                goto opcont;
                        } else
                                yc->yc_blkno++;
                                goto opcont;
                        } else
@@ -760,7 +789,8 @@ cyintr(cipher)
                 * If error is not hard, and this was an i/o operation
                 * retry up to 8 times.
                 */
                 * If error is not hard, and this was an i/o operation
                 * retry up to 8 times.
                 */
-               if (((1<<err)&CYER_SOFT) && state == SIO) {
+               if (state == SIO && (CYMASK(err) &
+                   ((bp->b_flags&B_READ) ? CYER_RSOFT : CYER_WSOFT))) {
                        if (++vm->um_tab.b_errcnt < 7) {
                                yc->yc_blkno++;
                                goto opcont;
                        if (++vm->um_tab.b_errcnt < 7) {
                                yc->yc_blkno++;
                                goto opcont;
@@ -770,7 +800,8 @@ cyintr(cipher)
                         * Hard or non-i/o errors on non-raw tape
                         * cause it to close.
                         */
                         * Hard or non-i/o errors on non-raw tape
                         * cause it to close.
                         */
-                       if (yc->yc_openf > 0 && bp != &rcybuf[cyunit])
+                       if ((bp->b_flags&B_RAW) == 0 &&
+                           yc->yc_openf > 0)
                                yc->yc_openf = -1;
                /*
                 * Couldn't recover from error.
                                yc->yc_openf = -1;
                /*
                 * Couldn't recover from error.
@@ -781,6 +812,24 @@ cyintr(cipher)
                    (err < NCYERROR) ? cyerror[err] : "");
                bp->b_flags |= B_ERROR;
                goto opdone;
                    (err < NCYERROR) ? cyerror[err] : "");
                bp->b_flags |= B_ERROR;
                goto opdone;
+       } else if (cy->cy_tpb.tpcmd == CY_BRCOM) {
+               int reclen = htoms(cy->cy_tpb.tprec);
+
+               /*
+                * If we did a buffered read, check whether the read
+                * was long enough.  If we asked the controller for less
+                * than the user asked for because the previous record
+                * was shorter, update our notion of record size
+                * and retry.  If the record is longer than the buffer,
+                * bump the errcnt so the retry will use direct read.
+                */
+               if (reclen > yc->yc_blksize && bp->b_bcount > yc->yc_blksize) {
+                       yc->yc_blksize = reclen;
+                       if (reclen > cy->cy_bs)
+                               vm->um_tab.b_errcnt++;
+                       yc->yc_blkno++;
+                       goto opcont;
+               }
        }
        /*
         * Advance tape control FSM.
        }
        /*
         * Advance tape control FSM.
@@ -825,7 +874,7 @@ ignoreerr:
                goto opdone;
        
        case SSEEK:
                goto opdone;
        
        case SSEEK:
-               yc->yc_blkno = bdbtofsb(bp->b_blkno);
+               yc->yc_blkno = bp->b_blkno;
                goto opcont;
 
        case SERASE:
                goto opcont;
 
        case SERASE:
@@ -847,8 +896,8 @@ opdone:
         * Save resid and release resources.
         */
        bp->b_resid = bp->b_bcount - htoms(cy->cy_tpb.tpcount);
         * Save resid and release resources.
         */
        bp->b_resid = bp->b_bcount - htoms(cy->cy_tpb.tpcount);
-       if (bp == &rcybuf[CYUNIT(bp->b_dev)])
-               vbadone(bp, cy->cy_buf, (long *)cy->cy_map, cy->cy_utl);
+       if (bp != &ccybuf[cyunit])
+               vbadone(bp, &cy->cy_rbuf);
        biodone(bp);
        /*
         * Circulate slave to end of controller
        biodone(bp);
        /*
         * Circulate slave to end of controller
@@ -896,67 +945,18 @@ cyseteof(bp)
        register struct yc_softc *yc = &yc_softc[YCUNIT(bp->b_dev)];
 
        if (bp == &ccybuf[cyunit]) {
        register struct yc_softc *yc = &yc_softc[YCUNIT(bp->b_dev)];
 
        if (bp == &ccybuf[cyunit]) {
-               if (yc->yc_blkno > bdbtofsb(bp->b_blkno)) {
+               if (yc->yc_blkno > bp->b_blkno) {
                        /* reversing */
                        /* reversing */
-                       yc->yc_nxrec = bdbtofsb(bp->b_blkno) -
-                           htoms(cy->cy_tpb.tpcount);
+                       yc->yc_nxrec = bp->b_blkno - htoms(cy->cy_tpb.tpcount);
                        yc->yc_blkno = yc->yc_nxrec;
                } else {
                        yc->yc_blkno = yc->yc_nxrec;
                } else {
-                       yc->yc_blkno = bdbtofsb(bp->b_blkno) +
-                           htoms(cy->cy_tpb.tpcount);
+                       yc->yc_blkno = bp->b_blkno + htoms(cy->cy_tpb.tpcount);
                        yc->yc_nxrec = yc->yc_blkno - 1;
                }
                return;
        }
        /* eof on read */
                        yc->yc_nxrec = yc->yc_blkno - 1;
                }
                return;
        }
        /* eof on read */
-       yc->yc_nxrec = bdbtofsb(bp->b_blkno);
-}
-
-cyread(dev, uio)
-       dev_t dev;
-       struct uio *uio;
-{
-       int errno;
-
-       errno = cyphys(dev, uio);
-       if (errno)
-               return (errno);
-       return (physio(cystrategy, &rcybuf[CYUNIT(dev)], dev, B_READ, minphys, uio));
-}
-
-cywrite(dev, uio)
-       dev_t dev;
-       struct uio *uio;
-{
-       int errno;
-
-       errno = cyphys(dev, uio);
-       if (errno)
-               return (errno);
-       return (physio(cystrategy, &rcybuf[CYUNIT(dev)], dev, B_WRITE, minphys, uio));
-}
-
-/*
- * Check that a raw device exits.
- * If it does, set up the yc_blkno and yc_nxrec
- * so that the tape will appear positioned correctly.
- */
-cyphys(dev, uio)
-       dev_t dev;
-       struct uio *uio;
-{
-       register int ycunit = YCUNIT(dev);
-       register daddr_t a;
-       register struct yc_softc *yc;
-       register struct vba_device *vi;
-
-       if (ycunit >= NYC || (vi = ycdinfo[ycunit]) == 0 || vi->ui_alive == 0)
-               return (ENXIO);
-       yc = &yc_softc[ycunit];
-       a = bdbtofsb(uio->uio_offset >> DEV_BSHIFT);
-       yc->yc_blkno = a;
-       yc->yc_nxrec = a + 1;
-       return (0);
+       yc->yc_nxrec = bp->b_blkno;
 }
 
 /*ARGSUSED*/
 }
 
 /*ARGSUSED*/
@@ -1064,7 +1064,7 @@ cywait(cp)
  * Load a 20 bit pointer into a Tapemaster pointer.
  */
 cyldmba(reg, value)
  * Load a 20 bit pointer into a Tapemaster pointer.
  */
 cyldmba(reg, value)
-       register caddr_t reg;
+       register u_char *reg;
        caddr_t value;
 {
        register int v = (int)value;
        caddr_t value;
 {
        register int v = (int)value;
@@ -1108,6 +1108,7 @@ cyuncachetpb(cy)
 /*
  * Dump routine.
  */
 /*
  * Dump routine.
  */
+#define        DUMPREC (32*1024)
 cydump(dev)
        dev_t dev;
 {
 cydump(dev)
        dev_t dev;
 {
@@ -1125,7 +1126,7 @@ cydump(dev)
        addr = phys(cyminfo[unit]->um_addr);
        num = maxfree, start = NBPG*2;
        while (num > 0) {
        addr = phys(cyminfo[unit]->um_addr);
        num = maxfree, start = NBPG*2;
        while (num > 0) {
-               bs = num > btoc(CYMAXIO) ? btoc(CYMAXIO) : num;
+               bs = num > btoc(DUMPREC) ? btoc(DUMPREC) : num;
                error = cydwrite(cy, start, bs, addr);
                if (error)
                        return (error);
                error = cydwrite(cy, start, bs, addr);
                if (error)
                        return (error);