changes for var. length sockaddrs; new routing; mv common ether input
[unix-history] / usr / src / sys / tahoe / vba / cy.c
index ec7aca7..5a2123d 100644 (file)
@@ -1,15 +1,37 @@
-/*     cy.c    1.6     86/01/27        */
+/*
+ * 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 the above copyright notice and this paragraph are
+ * duplicated in all such forms and that any documentation,
+ * advertising materials, and other materials related to such
+ * distribution and use acknowledge that the software was developed
+ * by the University of California, 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'' AND WITHOUT ANY EXPRESS OR
+ * IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED
+ * WARRANTIES OF MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE.
+ *
+ *     @(#)cy.c        7.2 (Berkeley) %G%
+ */
 
 #include "yc.h"
 #if NCY > 0
 /*
  * Cipher Tapemaster driver.
  */
 
 #include "yc.h"
 #if NCY > 0
 /*
  * Cipher Tapemaster driver.
  */
+#define CYDEBUG
+#ifdef CYDEBUG
 int    cydebug = 0;
 int    cydebug = 0;
-#define        dlog    if (cydebug) log
-
-#include "../tahoe/mtpr.h"
-#include "../tahoe/pte.h"
+#define        dlog(params)    if (cydebug) log params
+#else
+#define dlog(params)   /* */
+#endif
 
 #include "param.h"
 #include "systm.h"
 
 #include "param.h"
 #include "systm.h"
@@ -27,6 +49,11 @@ int  cydebug = 0;
 #include "cmap.h"
 #include "kernel.h"
 #include "syslog.h"
 #include "cmap.h"
 #include "kernel.h"
 #include "syslog.h"
+#include "tty.h"
+
+#include "../tahoe/cpu.h"
+#include "../tahoe/mtpr.h"
+#include "../tahoe/pte.h"
 
 #include "../tahoevba/vbavar.h"
 #define        CYERROR
 
 #include "../tahoevba/vbavar.h"
 #define        CYERROR
@@ -43,13 +70,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];
@@ -63,28 +83,25 @@ struct      vba_driver cydriver =
 #define        YCUNIT(dev)     (minor(dev)&03)
 #define        CYUNIT(dev)     (yctocy[YCUNIT(dev)])
 #define        T_NOREWIND      0x04
 #define        YCUNIT(dev)     (minor(dev)&03)
 #define        CYUNIT(dev)     (yctocy[YCUNIT(dev)])
 #define        T_NOREWIND      0x04
-#define        T_1600BPI       0x08
-#define        T_3200BPI       0x10
+#define        T_1600BPI       0x00            /* pseudo */
+#define        T_3200BPI       0x08            /* unused */
 
 #define        INF     1000000L                /* close to infinity */
 
 #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 */
        int     cy_bs;          /* controller's buffer size */
-       char    cy_buf[CYMAXIO];/* intermediate buffer */
        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 */
        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 */
+       struct  vb_buf cy_rbuf; /* vba resources */
 } cy_softc[NCY];
 
 /*
 } cy_softc[NCY];
 
 /*
@@ -102,6 +119,9 @@ struct      yc_softc {
        struct  tty *yc_ttyp;   /* user's tty for errors */
        daddr_t yc_blkno;       /* block number, for block device tape */
        daddr_t yc_nxrec;       /* position of end of tape, if known */
        struct  tty *yc_ttyp;   /* user's tty for errors */
        daddr_t yc_blkno;       /* block number, for block device tape */
        daddr_t yc_nxrec;       /* position of end of tape, if known */
+       int     yc_blksize;     /* current tape blocksize estimate */
+       int     yc_blks;        /* number of I/O operations since open */
+       int     yc_softerrs;    /* number of soft I/O errors since open */
 } yc_softc[NYC];
 
 /*
 } yc_softc[NYC];
 
 /*
@@ -125,20 +145,49 @@ cyprobe(reg, vm)
        struct vba_ctlr *vm;
 {
        register br, cvec;                      /* must be r12, r11 */
        struct vba_ctlr *vm;
 {
        register br, cvec;                      /* must be r12, r11 */
-       struct cy_softc *cy;
+       register struct cy_softc *cy;
+       int ctlr = vm->um_ctlr;
 
 
+#ifdef lint
+       br = 0; cvec = br; br = cvec;
+       cyintr(0);
+#endif
        if (badcyaddr(reg+1))
                return (0);
        if (badcyaddr(reg+1))
                return (0);
-       if (vm->um_ctlr > NCYSCP || cyscp[vm->um_ctlr] == 0)    /* XXX */
-               return (0);                                     /* XXX */
-       cy_softc[vm->um_ctlr].cy_scp = cyscp[vm->um_ctlr];      /* XXX */
+       if (ctlr > NCYSCP || cyscp[ctlr] == 0)          /* XXX */
+               return (0);
+       cy = &cy_softc[ctlr];
+       cy->cy_scp = cyscp[ctlr];                       /* XXX */
        /*
         * Tapemaster controller must have interrupt handler
         * disable interrupt, so we'll just kludge things
         * (stupid multibus non-vectored interrupt crud).
         */
        /*
         * Tapemaster controller must have interrupt handler
         * disable interrupt, so we'll just kludge things
         * (stupid multibus non-vectored interrupt crud).
         */
-       br = 0x13, cvec = 0x80;                                 /* XXX */
-       return (sizeof (struct cyccb));
+       if (cyinit(ctlr, reg)) {
+               uncache(&cy->cy_tpb.tpcount);
+               cy->cy_bs = htoms(cy->cy_tpb.tpcount);
+               /*
+                * Setup nop parameter block for clearing interrupts.
+                */
+               cy->cy_nop.tpcmd = CY_NOP;
+               cy->cy_nop.tpcontrol = 0;
+               /*
+                * Allocate page tables.
+                */
+               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));
+       } else
+               return (0);
 }
 
 /*
 }
 
 /*
@@ -165,20 +214,8 @@ cyattach(vi)
 
        yctocy[vi->ui_unit] = ctlr;
        cy = &cy_softc[ctlr];
 
        yctocy[vi->ui_unit] = ctlr;
        cy = &cy_softc[ctlr];
-       if (cy->cy_bs == 0 && cyinit(ctlr)) {
-               uncache(&cy->cy_tpb.tpcount);
-               cy->cy_bs = htoms(cy->cy_tpb.tpcount);
-               printf("cy%d: %dkb buffer\n", ctlr, cy->cy_bs/1024);
-               /*
-                * Setup nop parameter block for clearing interrupts.
-                */
-               cy->cy_nop.tpcmd = CY_NOP;
-               cy->cy_nop.tpcontrol = 0;
-               /*
-                * Allocate page tables.
-                */
-               vbmapalloc(btoc(CYMAXIO)+1, &cy->cy_map, &cy->cy_utl);
-       }
+       if (vi->ui_slave == 0 && cy->cy_bs)
+               printf("; %dkb buffer", cy->cy_bs/1024);
 }
 
 /*
 }
 
 /*
@@ -187,18 +224,18 @@ cyattach(vi)
  * are initialized and the controller is asked to configure
  * itself for later use.
  */
  * are initialized and the controller is asked to configure
  * itself for later use.
  */
-cyinit(ctlr)
+cyinit(ctlr, addr)
        int ctlr;
        int ctlr;
+       register caddr_t addr;
 {
        register struct cy_softc *cy = &cy_softc[ctlr];
 {
        register struct cy_softc *cy = &cy_softc[ctlr];
-       register caddr_t addr = cyminfo[ctlr]->um_addr;
        register int *pte;
 
        /*
         * Initialize the system configuration pointer.
         */
        /* make kernel writable */
        register int *pte;
 
        /*
         * 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 */
@@ -211,7 +248,7 @@ cyinit(ctlr)
        /*
         * Init system configuration block.
         */
        /*
         * Init system configuration block.
         */
-       cy->cy_scb.csb_fixed = 0x3;
+       cy->cy_scb.csb_fixed = CSB_FIXED;
        /* set pointer to the channel control block */
        cyldmba(cy->cy_scb.csb_ccb, (caddr_t)&cy->cy_ccb);
 
        /* set pointer to the channel control block */
        cyldmba(cy->cy_scb.csb_ccb, (caddr_t)&cy->cy_ccb);
 
@@ -264,38 +301,40 @@ 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)
                return (ENXIO);
        if ((yc = &yc_softc[ycunit])->yc_openf)
                return (EBUSY);
 
        ycunit = YCUNIT(dev);
        if (ycunit >= NYC || (vi = ycdinfo[ycunit]) == 0 || vi->ui_alive == 0)
                return (ENXIO);
        if ((yc = &yc_softc[ycunit])->yc_openf)
                return (EBUSY);
+       yc->yc_openf = 1;
 #define        PACKUNIT(vi) \
     (((vi->ui_slave&1)<<11)|((vi->ui_slave&2)<<9)|((vi->ui_slave&4)>>2))
        /* no way to select density */
        yc->yc_dens = PACKUNIT(vi)|CYCW_IE|CYCW_16BITS;
 #define        PACKUNIT(vi) \
     (((vi->ui_slave&1)<<11)|((vi->ui_slave&2)<<9)|((vi->ui_slave&4)>>2))
        /* no way to select density */
        yc->yc_dens = PACKUNIT(vi)|CYCW_IE|CYCW_16BITS;
+       if (yc->yc_tact == 0) {
+               yc->yc_timo = INF;
+               yc->yc_tact = 1;
+               timeout(cytimer, (caddr_t)dev, 5*hz);
+       }
        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_openf = 1;
        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 = CYMAXIO;               /* guess > 0 */
+       yc->yc_blks = 0;
+       yc->yc_softerrs = 0;
        yc->yc_ttyp = u.u_ttyp;
        yc->yc_ttyp = u.u_ttyp;
-       s = splclock();
-       if (yc->yc_tact == 0) {
-               yc->yc_timo = INF;
-               yc->yc_tact = 1;
-               timeout(cytimer, (caddr_t)dev, 5*hz);
-       }
-       splx(s);
        return (0);
 }
 
        return (0);
 }
 
@@ -309,12 +348,13 @@ cyopen(dev, flag)
  */
 cyclose(dev, flag)
        dev_t dev;
  */
 cyclose(dev, flag)
        dev_t dev;
-       register int flag;
+       int flag;
 {
 {
-       register struct yc_softc *yc = &yc_softc[YCUNIT(dev)];
+       struct yc_softc *yc = &yc_softc[YCUNIT(dev)];
 
        if (flag == FWRITE || (flag&FWRITE) && yc->yc_lastiow) {
 
        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)
@@ -325,7 +365,13 @@ cyclose(dev, flag)
                 * a CY_SENSE from completing.
                 */
                cycommand(dev, CY_REW, 0);
                 * a CY_SENSE from completing.
                 */
                cycommand(dev, CY_REW, 0);
+       if (yc->yc_blks > 10 && yc->yc_softerrs > yc->yc_blks / 10)
+               log(LOG_INFO, "yc%d: %d soft errors in %d blocks\n",
+                   YCUNIT(dev), yc->yc_softerrs, yc->yc_blks);
+       dlog((LOG_INFO, "%d soft errors in %d blocks\n",
+           yc->yc_softerrs, yc->yc_blks));
        yc->yc_openf = 0;
        yc->yc_openf = 0;
+       return (0);
 }
 
 /*
 }
 
 /*
@@ -335,14 +381,13 @@ cycommand(dev, com, count)
        dev_t dev;
        int com, count;
 {
        dev_t dev;
        int com, count;
 {
-       register int unit = CYUNIT(dev);
        register struct buf *bp;
        int s;
        
        bp = &ccybuf[CYUNIT(dev)];
        s = spl3();
        register struct buf *bp;
        int s;
        
        bp = &ccybuf[CYUNIT(dev)];
        s = spl3();
-       dlog(LOG_INFO, "cycommand(%o, %x, %d), b_flags %x\n",
-           dev, com, count, bp->b_flags);
+       dlog((LOG_INFO, "cycommand(%o, %x, %d), b_flags %x\n",
+           dev, com, count, bp->b_flags));
        while (bp->b_flags&B_BUSY) {
                /*
                 * This special check is because B_BUSY never
        while (bp->b_flags&B_BUSY) {
                /*
                 * This special check is because B_BUSY never
@@ -366,7 +411,7 @@ cycommand(dev, com, count)
         */
        if (count == 0)
                return;
         */
        if (count == 0)
                return;
-       iowait(bp);
+       biowait(bp);
        if (bp->b_flags&B_WANTED)
                wakeup((caddr_t)bp);
        bp->b_flags &= B_ERROR;
        if (bp->b_flags&B_WANTED)
                wakeup((caddr_t)bp);
        bp->b_flags &= B_ERROR;
@@ -383,21 +428,20 @@ cystrategy(bp)
        /*
         * Put transfer at end of unit queue.
         */
        /*
         * Put transfer at end of unit queue.
         */
-       dlog(LOG_INFO, "cystrategy(%o, %x)\n", bp->b_dev, bp->b_command);
+       dlog((LOG_INFO, "cystrategy(%o, %x)\n", bp->b_dev, bp->b_command));
        dp = &ycutab[ycunit];
        bp->av_forw = NULL;
        vm = ycdinfo[ycunit]->ui_mi;
        /* BEGIN GROT */
        dp = &ycutab[ycunit];
        bp->av_forw = NULL;
        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;
                        bp->b_resid = bp->b_bcount;
                        bp->b_flags |= B_ERROR;
-                       iodone(bp);
+                       biodone(bp);
                        return;
                }
                        return;
                }
-               vbasetup(bp, CYMAXIO);
        }
        /* END GROT */
        s = spl3();
        }
        /* END GROT */
        s = spl3();
@@ -432,11 +476,10 @@ cystart(vm)
        register struct buf *bp, *dp;
        register struct yc_softc *yc;
        register struct cy_softc *cy;
        register struct buf *bp, *dp;
        register struct yc_softc *yc;
        register struct cy_softc *cy;
-       register struct vba_device *vi;
        int ycunit;
        daddr_t blkno;
 
        int ycunit;
        daddr_t blkno;
 
-       dlog(LOG_INFO, "cystart()\n");
+       dlog((LOG_INFO, "cystart()\n"));
        /*
         * Look for an idle transport on the controller.
         */
        /*
         * Look for an idle transport on the controller.
         */
@@ -462,8 +505,8 @@ loop:
                 * or the tape unit is now unavailable (e.g.
                 * taken off line).
                 */
                 * or the tape unit is now unavailable (e.g.
                 * taken off line).
                 */
-               dlog(LOG_INFO, "openf %d command %x status %b\n",
-                   yc->yc_openf, bp->b_command, cy->cy_tpb.tpstatus, CYS_BITS);
+               dlog((LOG_INFO, "openf %d command %x status %b\n",
+                  yc->yc_openf, bp->b_command, cy->cy_tpb.tpstatus, CYS_BITS));
                bp->b_flags |= B_ERROR;
                goto next;
        }
                bp->b_flags |= B_ERROR;
                goto next;
        }
@@ -479,57 +522,77 @@ 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;
 
                /*
                 * Choose the appropriate i/o command based on the
                caddr_t addr;
                int cmd;
 
                /*
                 * Choose the appropriate i/o command based on the
-                * transfer size and the controller's internal buffer.
+                * 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 || 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
@@ -545,8 +608,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)
@@ -555,7 +617,11 @@ 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;
-               cy->cy_tpb.tpsize = htoms(bp->b_bcount);
+               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);
                do
                        uncache(&cy->cy_ccb.cbgate);
                cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
                do
                        uncache(&cy->cy_ccb.cbgate);
@@ -563,9 +629,9 @@ loop:
                cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
                cy->cy_ccb.cbcw = CBCW_IE;
                cy->cy_ccb.cbgate = GATE_CLOSED;
                cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
                cy->cy_ccb.cbcw = CBCW_IE;
                cy->cy_ccb.cbgate = GATE_CLOSED;
-               dlog(LOG_INFO, "CY_GO(%x) cmd %x control %x size %d\n",
+               dlog((LOG_INFO, "CY_GO(%x) cmd %x control %x size %d\n",
                    vm->um_addr, cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol,
                    vm->um_addr, cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol,
-                   htoms(cy->cy_tpb.tpsize));
+                   htoms(cy->cy_tpb.tpsize)));
                CY_GO(vm->um_addr);
                return;
        }
                CY_GO(vm->um_addr);
                return;
        }
@@ -575,14 +641,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
@@ -593,9 +659,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;
@@ -606,58 +674,56 @@ dobpcmd:
        cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
        cy->cy_ccb.cbcw = CBCW_IE;
        cy->cy_ccb.cbgate = GATE_CLOSED;
        cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
        cy->cy_ccb.cbcw = CBCW_IE;
        cy->cy_ccb.cbgate = GATE_CLOSED;
-       dlog(LOG_INFO, "CY_GO(%x) cmd %x control %x rec %d\n",
+       dlog((LOG_INFO, "CY_GO(%x) cmd %x control %x rec %d\n",
            vm->um_addr, cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol,
            vm->um_addr, cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol,
-           htoms(cy->cy_tpb.tprec));
+           htoms(cy->cy_tpb.tprec)));
        CY_GO(vm->um_addr);
        return;
 next:
        /*
         * Done with this operation due to error or the
        CY_GO(vm->um_addr);
        return;
 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;
        vm->um_tab.b_errcnt = 0;
        dp->b_actf = bp->av_forw;
-       iodone(bp);
+       biodone(bp);
        goto loop;
 }
 
 /*
  * Cy interrupt routine.
  */
        goto loop;
 }
 
 /*
  * 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).
         */
        cy = &cy_softc[vm->um_ctlr];
        cy->cy_ccb.cbcw = CBCW_CLRINT;
        /*
         * First, turn off the interrupt from the controller
         * (device uses Multibus non-vectored interrupts...yech).
         */
        cy = &cy_softc[vm->um_ctlr];
        cy->cy_ccb.cbcw = CBCW_CLRINT;
-       cyldmba(cy->cy_ccb.cbtpb, &cy->cy_nop);
+       cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_nop);
        cy->cy_ccb.cbgate = GATE_CLOSED;
        CY_GO(vm->um_addr);
        if ((dp = vm->um_tab.b_actf) == NULL) {
        cy->cy_ccb.cbgate = GATE_CLOSED;
        CY_GO(vm->um_addr);
        if ((dp = vm->um_tab.b_actf) == NULL) {
-               dlog(LOG_ERR, "cy%d: stray interrupt", vm->um_ctlr);
+               dlog((LOG_ERR, "cy%d: stray interrupt", vm->um_ctlr));
                return;
        }
        bp = dp->b_actf;
                return;
        }
        bp = dp->b_actf;
-       cyunit = CYUNIT(bp->b_dev);
        cy = &cy_softc[cyunit];
        cyuncachetpb(cy);
        cy = &cy_softc[cyunit];
        cyuncachetpb(cy);
+       yc = &yc_softc[YCUNIT(bp->b_dev)];
        /*
         * If last command was a rewind and tape is
         * still moving, wait for the operation to complete.
        /*
         * If last command was a rewind and tape is
         * still moving, wait for the operation to complete.
@@ -672,14 +738,13 @@ cyintr(cipher)
        /*
         * An operation completed...record status.
         */
        /*
         * An operation completed...record status.
         */
-       yc = &yc_softc[YCUNIT(bp->b_dev)];
        yc->yc_timo = INF;
        yc->yc_control = cy->cy_tpb.tpcontrol;
        yc->yc_status = cy->cy_tpb.tpstatus;
        yc->yc_resid = bp->b_bcount - htoms(cy->cy_tpb.tpcount);
        yc->yc_timo = INF;
        yc->yc_control = cy->cy_tpb.tpcontrol;
        yc->yc_status = cy->cy_tpb.tpstatus;
        yc->yc_resid = bp->b_bcount - htoms(cy->cy_tpb.tpcount);
-       dlog(LOG_INFO, "cmd %x control %b status %b resid %d\n",
+       dlog((LOG_INFO, "cmd %x control %b status %b resid %d\n",
            cy->cy_tpb.tpcmd, yc->yc_control, CYCW_BITS,
            cy->cy_tpb.tpcmd, yc->yc_control, CYCW_BITS,
-           yc->yc_status, CYS_BITS, yc->yc_resid);
+           yc->yc_status, CYS_BITS, yc->yc_resid));
        if ((bp->b_flags&B_READ) == 0)
                yc->yc_lastiow = 1;
        state = vm->um_tab.b_active;
        if ((bp->b_flags&B_READ) == 0)
                yc->yc_lastiow = 1;
        state = vm->um_tab.b_active;
@@ -689,7 +754,7 @@ cyintr(cipher)
         */
        if (cy->cy_tpb.tpstatus&CYS_ERR) {
                err = cy->cy_tpb.tpstatus&CYS_ERR;
         */
        if (cy->cy_tpb.tpstatus&CYS_ERR) {
                err = cy->cy_tpb.tpstatus&CYS_ERR;
-               dlog(LOG_INFO, "error %d\n", err);
+               dlog((LOG_INFO, "error %d\n", err));
                /*
                 * If we hit the end of tape file, update our position.
                 */
                /*
                 * If we hit the end of tape file, update our position.
                 */
@@ -711,23 +776,26 @@ 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) {
                        /*
                    err == CYER_STROBE) {
                        /*
-                        * Retry reads once with the command changed to
-                        * a raw read (if possible).  Setting b_errcnt
+                        * Retry reads with the command changed to
+                        * a raw read if necessary.  Setting b_errcnt
                         * here causes cystart (above) to force a CY_RCOM.
                         */
                         * here causes cystart (above) to force a CY_RCOM.
                         */
-                       if (bp->b_errcnt++ != 0)
+                       if (cy->cy_tpb.tpcmd == CY_BRCOM &&
+                           vm->um_tab.b_errcnt++ == 0) {
+                               yc->yc_blkno++;
+                               goto opcont;
+                       } else
                                goto ignoreerr;
                                goto ignoreerr;
-                       yc->yc_blkno++;
-                       goto opcont;
                }
                /*
                 * 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;
@@ -737,19 +805,36 @@ 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.
                 */
                tprintf(yc->yc_ttyp,
                                yc->yc_openf = -1;
                /*
                 * Couldn't recover from error.
                 */
                tprintf(yc->yc_ttyp,
-                   "yc%d: hard error bn%d status=%b", YCUNIT(bp->b_dev),
-                   bp->b_blkno, yc->yc_status, CYS_BITS);
-               if (err < NCYERROR)
-                       tprintf(yc->yc_ttyp, ", %s", cyerror[err]);
-               tprintf(yc->yc_ttyp, "\n");
+                   "yc%d: hard error bn%d status=%b, %s\n", YCUNIT(bp->b_dev),
+                   bp->b_blkno, yc->yc_status, CYS_BITS,
+                   (err < NCYERROR) ? cyerror[err] : "");
                bp->b_flags |= B_ERROR;
                goto opdone;
                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.
@@ -769,26 +854,32 @@ ignoreerr:
                 * Read/write increments tape block number.
                 */
                yc->yc_blkno++;
                 * Read/write increments tape block number.
                 */
                yc->yc_blkno++;
+               yc->yc_blks++;
+               if (vm->um_tab.b_errcnt || yc->yc_status & CYS_CR)
+                       yc->yc_softerrs++;
+               yc->yc_blksize = htoms(cy->cy_tpb.tpcount);
+               dlog((LOG_ERR, "blocksize %d", yc->yc_blksize));
                goto opdone;
 
        case SCOM:
                /*
                 * For forward/backward space record update current position.
                 */
                goto opdone;
 
        case SCOM:
                /*
                 * For forward/backward space record update current position.
                 */
-               if (bp == &ccybuf[CYUNIT(bp->b_dev)]) switch (bp->b_command) {
+               if (bp == &ccybuf[CYUNIT(bp->b_dev)])
+                       switch ((int)bp->b_command) {
 
 
-               case CY_SFORW:
-                       yc->yc_blkno -= bp->b_repcnt;
-                       break;
+                       case CY_SFORW:
+                               yc->yc_blkno -= bp->b_repcnt;
+                               break;
 
 
-               case CY_SREV:
-                       yc->yc_blkno += bp->b_repcnt;
-                       break;
-               }
+                       case CY_SREV:
+                               yc->yc_blkno += bp->b_repcnt;
+                               break;
+                       }
                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:
@@ -810,9 +901,9 @@ 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);
-       iodone(bp);
+       if (bp != &ccybuf[cyunit])
+               vbadone(bp, &cy->cy_rbuf);
+       biodone(bp);
        /*
         * Circulate slave to end of controller
         * queue to give other slaves a chance.
        /*
         * Circulate slave to end of controller
         * queue to give other slaves a chance.
@@ -837,6 +928,10 @@ cytimer(dev)
        register struct yc_softc *yc = &yc_softc[YCUNIT(dev)];
        int s;
 
        register struct yc_softc *yc = &yc_softc[YCUNIT(dev)];
        int s;
 
+       if (yc->yc_openf == 0 && yc->yc_timo == INF) {
+               yc->yc_tact = 0;
+               return;
+       }
        if (yc->yc_timo != INF && (yc->yc_timo -= 5) < 0) {
                printf("yc%d: lost interrupt\n", YCUNIT(dev));
                yc->yc_timo = INF;
        if (yc->yc_timo != INF && (yc->yc_timo -= 5) < 0) {
                printf("yc%d: lost interrupt\n", YCUNIT(dev));
                yc->yc_timo = INF;
@@ -855,67 +950,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*/
@@ -932,7 +978,7 @@ cyioctl(dev, cmd, data, flag)
        struct mtget *mtget;
        /* we depend of the values and order of the MT codes here */
        static cyops[] =
        struct mtget *mtget;
        /* we depend of the values and order of the MT codes here */
        static cyops[] =
-       {CY_WEOF,CY_SFORW,CY_SREV,CY_SFORW,CY_SREV,CY_REW,CY_OFFL,CY_SENSE};
+       {CY_WEOF,CY_FSF,CY_BSF,CY_SFORW,CY_SREV,CY_REW,CY_OFFL,CY_SENSE};
 
        switch (cmd) {
 
 
        switch (cmd) {
 
@@ -941,7 +987,15 @@ cyioctl(dev, cmd, data, flag)
                switch (op = mtop->mt_op) {
 
                case MTWEOF:
                switch (op = mtop->mt_op) {
 
                case MTWEOF:
+                       callcount = mtop->mt_count;
+                       fcount = 1;
+                       break;
+
                case MTFSR: case MTBSR:
                case MTFSR: case MTBSR:
+                       callcount = 1;
+                       fcount = mtop->mt_count;
+                       break;
+
                case MTFSF: case MTBSF:
                        callcount = mtop->mt_count;
                        fcount = 1;
                case MTFSF: case MTBSF:
                        callcount = mtop->mt_count;
                        fcount = 1;
@@ -958,6 +1012,7 @@ cyioctl(dev, cmd, data, flag)
                if (callcount <= 0 || fcount <= 0)
                        return (EINVAL);
                while (--callcount >= 0) {
                if (callcount <= 0 || fcount <= 0)
                        return (EINVAL);
                while (--callcount >= 0) {
+#ifdef notdef
                        /*
                         * Gagh, this controller is the pits...
                         */
                        /*
                         * Gagh, this controller is the pits...
                         */
@@ -967,7 +1022,11 @@ cyioctl(dev, cmd, data, flag)
                                while ((bp->b_flags&B_ERROR) == 0 &&
                                 (yc->yc_status&(CYS_EOT|CYS_BOT|CYS_FM)) == 0);
                        } else
                                while ((bp->b_flags&B_ERROR) == 0 &&
                                 (yc->yc_status&(CYS_EOT|CYS_BOT|CYS_FM)) == 0);
                        } else
+#endif
                                cycommand(dev, cyops[op], fcount);
                                cycommand(dev, cyops[op], fcount);
+                       dlog((LOG_INFO,
+                           "cyioctl: status %x, b_flags %x, resid %d\n",
+                           yc->yc_status, bp->b_flags, bp->b_resid));
                        if ((bp->b_flags&B_ERROR) ||
                            (yc->yc_status&(CYS_BOT|CYS_EOT)))
                                break;
                        if ((bp->b_flags&B_ERROR) ||
                            (yc->yc_status&(CYS_BOT|CYS_EOT)))
                                break;
@@ -1007,14 +1066,13 @@ cywait(cp)
 }
 
 /*
 }
 
 /*
- * Load a 20 bit pointer into an i/o register.
+ * Load a 20 bit pointer into a Tapemaster pointer.
  */
  */
-cyldmba(wreg, value)
-       short *wreg;
+cyldmba(reg, value)
+       register u_char *reg;
        caddr_t value;
 {
        register int v = (int)value;
        caddr_t value;
 {
        register int v = (int)value;
-       register caddr_t reg = (caddr_t)wreg;
 
        *reg++ = v;
        *reg++ = v >> 8;
 
        *reg++ = v;
        *reg++ = v >> 8;
@@ -1035,7 +1093,7 @@ cyreset(vba)
                if (cyminfo[ctlr] && cyminfo[ctlr]->um_vbanum == vba) {
                        addr = cyminfo[ctlr]->um_addr;
                        CY_RESET(addr);
                if (cyminfo[ctlr] && cyminfo[ctlr]->um_vbanum == vba) {
                        addr = cyminfo[ctlr]->um_addr;
                        CY_RESET(addr);
-                       if (!cyinit(ctlr)) {
+                       if (!cyinit(ctlr, addr)) {
                                printf("cy%d: reset failed\n", ctlr);
                                cyminfo[ctlr] = NULL;
                        }
                                printf("cy%d: reset failed\n", ctlr);
                                cyminfo[ctlr] = NULL;
                        }
@@ -1055,13 +1113,14 @@ cyuncachetpb(cy)
 /*
  * Dump routine.
  */
 /*
  * Dump routine.
  */
+#define        DUMPREC (32*1024)
 cydump(dev)
        dev_t dev;
 {
        register struct cy_softc *cy;
        register int bs, num, start;
        register caddr_t addr;
 cydump(dev)
        dev_t dev;
 {
        register struct cy_softc *cy;
        register int bs, num, start;
        register caddr_t addr;
-       int unit = CYUNIT(dev), ctlr, error;
+       int unit = CYUNIT(dev), error;
 
        if (unit >= NCY || cyminfo[unit] == 0 ||
            (cy = &cy_softc[unit])->cy_bs == 0 || YCUNIT(dev) >= NYC)
 
        if (unit >= NCY || cyminfo[unit] == 0 ||
            (cy = &cy_softc[unit])->cy_bs == 0 || YCUNIT(dev) >= NYC)
@@ -1069,10 +1128,10 @@ cydump(dev)
        if (cywait(&cy->cy_ccb))
                return (EFAULT);
 #define        phys(a) ((caddr_t)((int)(a)&~0xc0000000))
        if (cywait(&cy->cy_ccb))
                return (EFAULT);
 #define        phys(a) ((caddr_t)((int)(a)&~0xc0000000))
-       addr = phys(cyminfo[ctlr]->um_addr);
+       addr = phys(cyminfo[unit]->um_addr);
        num = maxfree, start = NBPG*2;
        while (num > 0) {
        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);