from Keith Muller;
[unix-history] / usr / src / sys / tahoe / vba / vd.c
index 63709a7..31f9597 100644 (file)
@@ -2,6 +2,9 @@
  * Copyright (c) 1988 Regents of the University of California.
  * All rights reserved.
  *
  * 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,
  * 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,
@@ -14,7 +17,7 @@
  * IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED
  * WARRANTIES OF MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE.
  *
  * IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED
  * WARRANTIES OF MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE.
  *
- *     @(#)vd.c        7.5 (Berkeley) %G%
+ *     @(#)vd.c        7.9 (Berkeley) %G%
  */
 
 #include "dk.h"
  */
 
 #include "dk.h"
@@ -73,6 +76,8 @@ struct vdsoftc {
 #define        VD_STARTED      0x2     /* start command issued */
 #define        VD_DOSEEKS      0x4     /* should overlap seeks */
 #define        VD_SCATGATH     0x8     /* can do scatter-gather commands (correctly) */
 #define        VD_STARTED      0x2     /* start command issued */
 #define        VD_DOSEEKS      0x4     /* should overlap seeks */
 #define        VD_SCATGATH     0x8     /* can do scatter-gather commands (correctly) */
+#define        VD_LOCKED       0x10    /* locked for direct controller access */
+#define        VD_WAIT         0x20    /* someone needs direct controller access */
        u_short vd_type;        /* controller type */
        u_short vd_wticks;      /* timeout */
        struct  mdcb vd_mdcb;   /* master command block */
        u_short vd_type;        /* controller type */
        u_short vd_wticks;      /* timeout */
        struct  mdcb vd_mdcb;   /* master command block */
@@ -159,7 +164,7 @@ vdprobe(reg, vm)
                vdaddr->vdtcf_dcb = AM_ENPDA;
                vdaddr->vdtcf_trail = AM_ENPDA;
                vdaddr->vdtcf_data = AM_ENPDA;
                vdaddr->vdtcf_dcb = AM_ENPDA;
                vdaddr->vdtcf_trail = AM_ENPDA;
                vdaddr->vdtcf_data = AM_ENPDA;
-               vdaddr->vdccf = CCF_SEN | CCF_DER | CCF_STS |
+               vdaddr->vdccf = CCF_SEN | CCF_DIU | CCF_STS |
                    XMD_32BIT | BSZ_16WRD |
                    CCF_ENP | CCF_EPE | CCF_EDE | CCF_ECE | CCF_ERR;
        }
                    XMD_32BIT | BSZ_16WRD |
                    CCF_ENP | CCF_EPE | CCF_EDE | CCF_ECE | CCF_ERR;
        }
@@ -167,7 +172,7 @@ vdprobe(reg, vm)
        vd->vd_dcbphys = vtoph((struct proc *)0, (unsigned)&vd->vd_dcb);
        vm->um_addr = reg;              /* XXX */
        s = spl7();
        vd->vd_dcbphys = vtoph((struct proc *)0, (unsigned)&vd->vd_dcb);
        vm->um_addr = reg;              /* XXX */
        s = spl7();
-       if (!vdcmd(vm, VDOP_INIT, 10) || !vdcmd(vm, VDOP_DIAG, 10)) {
+       if (!vdcmd(vm, VDOP_INIT, 10, 0) || !vdcmd(vm, VDOP_DIAG, 10, 0)) {
                printf("vd%d: %s cmd failed\n", vm->um_ctlr,
                    vd->vd_dcb.opcode == VDOP_INIT ? "init" : "diag");
                splx(s);
                printf("vd%d: %s cmd failed\n", vm->um_ctlr,
                    vd->vd_dcb.opcode == VDOP_INIT ? "init" : "diag");
                splx(s);
@@ -175,7 +180,7 @@ vdprobe(reg, vm)
        }
        if (vd->vd_type == VDTYPE_SMDE) {
                vd->vd_dcb.trail.idtrail.date = 0;
        }
        if (vd->vd_type == VDTYPE_SMDE) {
                vd->vd_dcb.trail.idtrail.date = 0;
-               if (vdcmd(vm, VDOP_IDENT, 10)) {
+               if (vdcmd(vm, VDOP_IDENT, 10, 0)) {
                        uncache(&vd->vd_dcb.trail.idtrail.date);
                        if (vd->vd_dcb.trail.idtrail.date != 0)
                                vd->vd_flags |= VD_SCATGATH;
                        uncache(&vd->vd_dcb.trail.idtrail.date);
                        if (vd->vd_dcb.trail.idtrail.date != 0)
                                vd->vd_flags |= VD_SCATGATH;
@@ -212,9 +217,19 @@ vdslave(vi, vdaddr)
        struct vdsoftc *vd = &vdsoftc[vi->ui_ctlr];
 
        if ((vd->vd_flags&VD_INIT) == 0) {
        struct vdsoftc *vd = &vdsoftc[vi->ui_ctlr];
 
        if ((vd->vd_flags&VD_INIT) == 0) {
-               printf("vd%d: %s controller%s\n", vi->ui_ctlr,
-                   vd->vd_type == VDTYPE_VDDC ? "VDDC" : "SMDE",
-                   (vd->vd_flags & VD_SCATGATH) ? " with scatter-gather" : "");
+               printf("vd%d: %s controller", vi->ui_ctlr,
+                   vd->vd_type == VDTYPE_VDDC ? "VDDC" : "SMDE");
+               if (vd->vd_flags & VD_SCATGATH) {
+                       char rev[5];
+
+                       bcopy((caddr_t)&vd->vd_dcb.trail.idtrail.rev, rev,
+                           sizeof(vd->vd_dcb.trail.idtrail.rev));
+                       printf(" firmware rev %s (%d-%d-%d)", rev,
+                           (vd->vd_dcb.trail.idtrail.date >> 8) & 0xff,
+                           vd->vd_dcb.trail.idtrail.date & 0xff,
+                           (vd->vd_dcb.trail.idtrail.date >> 16) & 0xffff);
+               }
+               printf("\n");
                vd->vd_flags |= VD_INIT;
        }
 
                vd->vd_flags |= VD_INIT;
        }
 
@@ -232,6 +247,7 @@ vdslave(vi, vdaddr)
        lp->d_ntracks = 23;
        lp->d_ncylinders = 850;
        lp->d_secpercyl = 66*23;
        lp->d_ntracks = 23;
        lp->d_ncylinders = 850;
        lp->d_secpercyl = 66*23;
+       lp->d_rpm = 3600;
        lp->d_npartitions = 1;
        lp->d_partitions[0].p_offset = 0;
        lp->d_partitions[0].p_size = LABELSECTOR + 1;
        lp->d_npartitions = 1;
        lp->d_partitions[0].p_offset = 0;
        lp->d_partitions[0].p_size = LABELSECTOR + 1;
@@ -410,20 +426,24 @@ vdinit(dev, flags)
                        dk->dk_state = OPENRAW;
                }
 #ifdef COMPAT_42
                        dk->dk_state = OPENRAW;
                }
 #ifdef COMPAT_42
+               vdlock(vi->ui_ctlr);
                if (vdmaptype(vi, lp))
                        dk->dk_state = OPEN;
                if (vdmaptype(vi, lp))
                        dk->dk_state = OPEN;
+               vdunlock(vi->ui_ctlr);
 #endif
        } else {
                /*
                 * Now that we have the label, configure
                 * the correct drive parameters.
                 */
 #endif
        } else {
                /*
                 * Now that we have the label, configure
                 * the correct drive parameters.
                 */
+               vdlock(vi->ui_ctlr);
                if (vdreset_drive(vi))
                        dk->dk_state = OPEN;
                else {
                        dk->dk_state = CLOSED;
                        error = ENXIO;
                }
                if (vdreset_drive(vi))
                        dk->dk_state = OPEN;
                else {
                        dk->dk_state = CLOSED;
                        error = ENXIO;
                }
+               vdunlock(vi->ui_ctlr);
        }
 #ifndef SECSIZE
        vd_setsecsize(dk, lp);
        }
 #ifndef SECSIZE
        vd_setsecsize(dk, lp);
@@ -680,7 +700,7 @@ setupaddr:
 
        case VDOP_RAS:
        case VDOP_GAW:
 
        case VDOP_RAS:
        case VDOP_GAW:
-               vd->vd_dcb.trailcnt += vba_sgsetup(bp, &vd->vd_rbuf,
+               vd->vd_dcb.trailcnt += vd_sgsetup(bp, &vd->vd_rbuf,
                    &vd->vd_dcb.trail.sgtrail);
                break;
        }
                    &vd->vd_dcb.trail.sgtrail);
                break;
        }
@@ -731,6 +751,42 @@ setupaddr:
        VDGO(vm->um_addr, vd->vd_mdcbphys, vd->vd_type);
 }
 
        VDGO(vm->um_addr, vd->vd_mdcbphys, vd->vd_type);
 }
 
+/*
+ * Wait for controller to finish current operation
+ * so that direct controller accesses can be done.
+ */
+vdlock(ctlr)
+{
+       register struct vba_ctlr *vm = vdminfo[ctlr];
+       register struct vdsoftc *vd = &vdsoftc[ctlr];
+       int s;
+
+       s = spl7();
+       while (vm->um_tab.b_active || vd->vd_flags & VD_LOCKED) {
+               vd->vd_flags |= VD_WAIT;
+               sleep((caddr_t)vd, PRIBIO);
+       }
+       vd->vd_flags |= VD_LOCKED;
+       splx(s);
+}
+
+/*
+ * Continue normal operations after pausing for 
+ * munging the controller directly.
+ */
+vdunlock(ctlr)
+{
+       register struct vba_ctlr *vm = vdminfo[ctlr];
+       register struct vdsoftc *vd = &vdsoftc[ctlr];
+
+       vd->vd_flags &= ~VD_LOCKED;
+       if (vd->vd_flags & VD_WAIT) {
+               vd->vd_flags &= ~VD_WAIT;
+               wakeup((caddr_t)vd);
+       } else if (vm->um_tab.b_actf || vm->um_tab.b_seekf)
+               vdstart(vm);
+}
+
 #define        DONTCARE (DCBS_DSE|DCBS_DSL|DCBS_TOP|DCBS_TOM|DCBS_FAIL|DCBS_DONE)
 /*
  * Handle a disk interrupt.
 #define        DONTCARE (DCBS_DSE|DCBS_DSL|DCBS_TOP|DCBS_TOM|DCBS_FAIL|DCBS_DONE)
 /*
  * Handle a disk interrupt.
@@ -840,7 +896,10 @@ vdintr(ctlr)
         * If there are devices ready to
         * transfer, start the controller.
         */
         * If there are devices ready to
         * transfer, start the controller.
         */
-       if (vm->um_tab.b_actf || vm->um_tab.b_seekf)
+       if (vd->vd_flags & VD_WAIT) {
+               vd->vd_flags &= ~VD_WAIT;
+               wakeup((caddr_t)vd);
+       } else if (vm->um_tab.b_actf || vm->um_tab.b_seekf)
                vdstart(vm);
 }
 
                vdstart(vm);
 }
 
@@ -938,7 +997,9 @@ vdioctl(dev, cmd, data, flag)
                    (dk->dk_state == OPENRAW) ? 0 : dk->dk_openpart)) == 0) {
                        int wlab;
 
                    (dk->dk_state == OPENRAW) ? 0 : dk->dk_openpart)) == 0) {
                        int wlab;
 
-                       dk->dk_state = OPEN;
+                       if (error == 0 && dk->dk_state == OPENRAW &&
+                           vdreset_drive(vddinfo[unit]))
+                               dk->dk_state = OPEN;
                        /* simulate opening partition 0 so write succeeds */
                        dk->dk_openpart |= (1 << 0);            /* XXX */
                        wlab = dk->dk_wlabel;
                        /* simulate opening partition 0 so write succeeds */
                        dk->dk_openpart |= (1 << 0);            /* XXX */
                        wlab = dk->dk_wlabel;
@@ -1140,7 +1201,7 @@ vdreset_ctlr(vm)
                vdaddr->vdccf = CCF_STS | XMD_32BIT | BSZ_16WRD |
                    CCF_ENP | CCF_EPE | CCF_EDE | CCF_ECE | CCF_ERR;
        }
                vdaddr->vdccf = CCF_STS | XMD_32BIT | BSZ_16WRD |
                    CCF_ENP | CCF_EPE | CCF_EDE | CCF_ECE | CCF_ERR;
        }
-       if (!vdcmd(vm, VDOP_INIT, 10) || !vdcmd(vm, VDOP_DIAG, 10)) {
+       if (!vdcmd(vm, VDOP_INIT, 10, 0) || !vdcmd(vm, VDOP_DIAG, 10, 0)) {
                printf("%s cmd failed\n",
                    vd->vd_dcb.opcode == VDOP_INIT ? "init" : "diag");
                return;
                printf("%s cmd failed\n",
                    vd->vd_dcb.opcode == VDOP_INIT ? "init" : "diag");
                return;
@@ -1181,6 +1242,20 @@ top:
                printf(" during config\n");
                return (0);
        }
                printf(" during config\n");
                return (0);
        }
+/*
+uncache(&vd->vd_dcb.err_code);
+printf("vdreset_drive %d, error %b, ecode %x, status %x => ",
+   vi->ui_unit, vd->vd_dcb.operrsta, VDERRBITS, vd->vd_dcb.err_code,
+   vdaddr->vdstatus[vi->ui_slave]);
+uncache(&vdaddr->vdstatus[vi->ui_slave]);
+printf("%x =>", vdaddr->vdstatus[vi->ui_slave]);
+{ int status = vd->vd_dcb.operrsta;
+vdcmd(vm, VDOP_STATUS, 5, vi->ui_slave);
+vd->vd_dcb.operrsta = status;
+}
+uncache(&vdaddr->vdstatus[vi->ui_slave]);
+printf("%x\n", vdaddr->vdstatus[vi->ui_slave]);
+*/
        if (vd->vd_dcb.operrsta & VDERR_HARD) {
                if (vd->vd_type == VDTYPE_SMDE) {
                        if (lp->d_devflags == 0) {
        if (vd->vd_dcb.operrsta & VDERR_HARD) {
                if (vd->vd_type == VDTYPE_SMDE) {
                        if (lp->d_devflags == 0) {
@@ -1204,7 +1279,7 @@ top:
                        vd->vd_flags |= VD_STARTED;
                        started = (vdcmd(vm, VDOP_START, 10) == 1);
                        DELAY(62000000);
                        vd->vd_flags |= VD_STARTED;
                        started = (vdcmd(vm, VDOP_START, 10) == 1);
                        DELAY(62000000);
-                       printf("done");
+                       printf("done\n");
                        lp->d_devflags = 0;
                        if (started)
                                goto top;
                        lp->d_devflags = 0;
                        if (started)
                                goto top;
@@ -1218,7 +1293,7 @@ top:
 /*
  * Perform a command w/o trailer.
  */
 /*
  * Perform a command w/o trailer.
  */
-vdcmd(vm, cmd, t)
+vdcmd(vm, cmd, t, slave)
        register struct vba_ctlr *vm;
 {
        register struct vdsoftc *vd = &vdsoftc[vm->um_ctlr];
        register struct vba_ctlr *vm;
 {
        register struct vdsoftc *vd = &vdsoftc[vm->um_ctlr];
@@ -1227,7 +1302,7 @@ vdcmd(vm, cmd, t)
        vd->vd_dcb.intflg = DCBINT_NONE;
        vd->vd_dcb.nxtdcb = (struct dcb *)0;    /* end of chain */
        vd->vd_dcb.operrsta = 0;
        vd->vd_dcb.intflg = DCBINT_NONE;
        vd->vd_dcb.nxtdcb = (struct dcb *)0;    /* end of chain */
        vd->vd_dcb.operrsta = 0;
-       vd->vd_dcb.devselect = 0;
+       vd->vd_dcb.devselect = slave;
        vd->vd_dcb.trailcnt = 0;
        vd->vd_mdcb.mdcb_head = (struct dcb *)vd->vd_dcbphys;
        vd->vd_mdcb.mdcb_status = 0;
        vd->vd_dcb.trailcnt = 0;
        vd->vd_mdcb.mdcb_head = (struct dcb *)vd->vd_dcbphys;
        vd->vd_mdcb.mdcb_status = 0;
@@ -1393,8 +1468,10 @@ vdmaptype(vi, lp)
                lp->d_ntracks = p->ntrack;
                lp->d_ncylinders = p->ncyl;
                lp->d_secsize = p->secsize;
                lp->d_ntracks = p->ntrack;
                lp->d_ncylinders = p->ncyl;
                lp->d_secsize = p->secsize;
+               DELAY(100000);
                if (!vdreset_drive(vi))
                        return (0);
                if (!vdreset_drive(vi))
                        return (0);
+               DELAY(100000);
                vd->vd_dcb.opcode = VDOP_RD;
                vd->vd_dcb.intflg = DCBINT_NONE;
                vd->vd_dcb.nxtdcb = (struct dcb *)0;    /* end of chain */
                vd->vd_dcb.opcode = VDOP_RD;
                vd->vd_dcb.intflg = DCBINT_NONE;
                vd->vd_dcb.nxtdcb = (struct dcb *)0;    /* end of chain */
@@ -1424,7 +1501,6 @@ vdmaptype(vi, lp)
        }
        lp->d_npartitions = 8;
        lp->d_secpercyl = lp->d_nsectors * lp->d_ntracks;
        }
        lp->d_npartitions = 8;
        lp->d_secpercyl = lp->d_nsectors * lp->d_ntracks;
-       lp->d_rpm = 3600;
        bcopy(p->name, lp->d_typename, 4);
        return (1);
 }
        bcopy(p->name, lp->d_typename, 4);
        return (1);
 }