BSD 4_4 release
[unix-history] / usr / src / sys / tahoe / vba / hd.c
index 8b628d1..30afaa9 100644 (file)
@@ -5,47 +5,62 @@
  * This code is derived from software contributed to Berkeley by
  * Harris Corp.
  *
  * This code is derived from software contributed to Berkeley by
  * Harris Corp.
  *
- * 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.
+ * Redistribution and use in source and binary forms, with or without
+ * modification, are permitted provided that the following conditions
+ * are met:
+ * 1. Redistributions of source code must retain the above copyright
+ *    notice, this list of conditions and the following disclaimer.
+ * 2. Redistributions in binary form must reproduce the above copyright
+ *    notice, this list of conditions and the following disclaimer in the
+ *    documentation and/or other materials provided with the distribution.
+ * 3. All advertising materials mentioning features or use of this software
+ *    must display the following acknowledgement:
+ *     This product includes software developed by the University of
+ *     California, Berkeley and its contributors.
+ * 4. Neither the name of the University nor the names of its contributors
+ *    may be used to endorse or promote products derived from this software
+ *    without specific prior written permission.
  *
  *
- *     @(#)hd.c        7.3 (Berkeley) %G%
+ * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
+ * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
+ * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
+ * ARE DISCLAIMED.  IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
+ * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
+ * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
+ * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
+ * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+ * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
+ * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
+ * SUCH DAMAGE.
+ *
+ *     @(#)hd.c        7.12 (Berkeley) 12/16/90
  */
 
 #include "hd.h"
 
 #if NHD > 0
  */
 
 #include "hd.h"
 
 #if NHD > 0
-#include "param.h"
-#include "buf.h"
-#include "conf.h"
-#include "dir.h"
-#include "dkstat.h"
-#include "disklabel.h"
-#include "file.h"
-#include "systm.h"
-#include "vmmac.h"
-#include "time.h"
-#include "proc.h"
-#include "uio.h"
-#include "syslog.h"
-#include "kernel.h"
-#include "ioctl.h"
-#include "stat.h"
-#include "errno.h"
-
-#include "../tahoe/cpu.h"
-#include "../tahoe/mtpr.h"
-
-#include "../tahoevba/vbavar.h"
-#include "../tahoevba/hdreg.h"
+#include "sys/param.h"
+#include "sys/buf.h"
+#include "sys/conf.h"
+#include "sys/dkstat.h"
+#include "sys/disklabel.h"
+#include "sys/file.h"
+#include "sys/systm.h"
+#include "sys/vmmac.h"
+#include "sys/time.h"
+#include "sys/proc.h"
+#include "sys/uio.h"
+#include "sys/syslog.h"
+#include "sys/kernel.h"
+#include "sys/ioctl.h"
+#include "sys/stat.h"
+#include "sys/errno.h"
+
+#include "../include/cpu.h"
+#include "../include/mtpr.h"
+
+#include "../vba/vbavar.h"
+#include "../vba/hdreg.h"
 
 #define        b_cylin b_resid
 
 
 #define        b_cylin b_resid
 
@@ -56,8 +71,9 @@
 struct vba_ctlr *hdcminfo[NHDC];
 struct vba_device *hddinfo[NHD];
 int hdcprobe(), hdslave(), hdattach(), hddgo(), hdstrategy();
 struct vba_ctlr *hdcminfo[NHDC];
 struct vba_device *hddinfo[NHD];
 int hdcprobe(), hdslave(), hdattach(), hddgo(), hdstrategy();
+long hdstd[] = { 0 };
 struct vba_driver hdcdriver =
 struct vba_driver hdcdriver =
-    { hdcprobe, hdslave, hdattach, hddgo, 0L, "hd", hddinfo, "hdc", hdcminfo };
+    { hdcprobe, hdslave, hdattach, hddgo, hdstd, "hd", hddinfo, "hdc", hdcminfo };
 
 /*
  * Per-controller state.
 
 /*
  * Per-controller state.
@@ -141,10 +157,8 @@ hdcprobe(reg, vm)
         * functional integrity test;
         */
        if (wbadaddr(&hdc->hdc_reg->module_id, 4,
         * functional integrity test;
         */
        if (wbadaddr(&hdc->hdc_reg->module_id, 4,
-           vtoph((struct process *)NULL, &id))) {
-               printf("hdc%d: can't access module register.\n", vm->um_ctlr);
+           vtoph((struct process *)NULL, &id)))
                return(0);
                return(0);
-       }
        DELAY(10000);
        mtpr(PADC, 0);
        if (id.module_id != (u_char)HDC_MID) {
        DELAY(10000);
        mtpr(PADC, 0);
        if (id.module_id != (u_char)HDC_MID) {
@@ -216,7 +230,6 @@ hdslave(vi, vdaddr)
        }
        if (status.drs&DRS_FAULT)
                printf(" (clearing fault)");
        }
        if (status.drs&DRS_FAULT)
                printf(" (clearing fault)");
-       printf("\n");
 
        lp = &dk->dk_label;
 #ifdef RAW_SIZE
 
        lp = &dk->dk_label;
 #ifdef RAW_SIZE
@@ -265,8 +278,8 @@ hdattach(vi)
         * (60 / rpm) / (sectors per track * (bytes per sector / 2))
         */
        if (vi->ui_dk >= 0)
         * (60 / rpm) / (sectors per track * (bytes per sector / 2))
         */
        if (vi->ui_dk >= 0)
-               dk_mspw[vi->ui_dk] = 120.0 /
-                   (lp->d_rpm * lp->d_nsectors * lp->d_secsize);
+               dk_wpms[vi->ui_dk] =
+                   (lp->d_rpm * lp->d_nsectors * lp->d_secsize) / 120;
 #ifdef notyet
        addswap(makedev(HDMAJOR, hdminor(unit, 0)), lp);
 #endif
 #ifdef notyet
        addswap(makedev(HDMAJOR, hdminor(unit, 0)), lp);
 #endif
@@ -292,7 +305,11 @@ hdopen(dev, flags, fmt)
        s = spl7();
        while (dk->dk_state != OPEN && dk->dk_state != OPENRAW &&
            dk->dk_state != CLOSED)
        s = spl7();
        while (dk->dk_state != OPEN && dk->dk_state != OPENRAW &&
            dk->dk_state != CLOSED)
-               sleep((caddr_t)dk, PZERO+1);
+               if (error = tsleep((caddr_t)dk, (PZERO+1) | PCATCH,
+                   devopn, 0)) {
+                       splx(s);
+                       return (error);
+               }
        splx(s);
        if (dk->dk_state != OPEN && dk->dk_state != OPENRAW)
                if (error = hdinit(dev, flags))
        splx(s);
        if (dk->dk_state != OPEN && dk->dk_state != OPENRAW)
                if (error = hdinit(dev, flags))
@@ -571,14 +588,15 @@ hdcstart(vm)
        /* mcb->priority = 0; */
        mcb->interrupt = 1;
        mcb->command = (bp->b_flags & B_READ) ? HCMD_READ:HCMD_WRITE;
        /* mcb->priority = 0; */
        mcb->interrupt = 1;
        mcb->command = (bp->b_flags & B_READ) ? HCMD_READ:HCMD_WRITE;
-       mcb->cyl = sn / lp->d_secpercyl;
+       mcb->cyl = bp->b_cylin;
+/* assumes partition starts on cylinder boundary */
        mcb->head = (sn / lp->d_nsectors) % lp->d_ntracks;
        mcb->sector = sn % lp->d_nsectors;
        mcb->drive = vi->ui_slave;
        /* mcb->context = 0;            /* what do we want on interrupt? */
 
        hdc = &hdcsoftc[vm->um_ctlr];
        mcb->head = (sn / lp->d_nsectors) % lp->d_ntracks;
        mcb->sector = sn % lp->d_nsectors;
        mcb->drive = vi->ui_slave;
        /* mcb->context = 0;            /* what do we want on interrupt? */
 
        hdc = &hdcsoftc[vm->um_ctlr];
-       if (!hd_sgsetup(bp, hdc->hdc_rbuf, mcb->chain)) {
+       if (!hd_sgsetup(bp, &hdc->hdc_rbuf, mcb->chain)) {
                mcb->chain[0].wcount = (bp->b_bcount+3) >> 2;
                mcb->chain[0].memadr =
                    vbasetup(bp, &hdc->hdc_rbuf, (int)lp->d_secsize);
                mcb->chain[0].wcount = (bp->b_bcount+3) >> 2;
                mcb->chain[0].memadr =
                    vbasetup(bp, &hdc->hdc_rbuf, (int)lp->d_secsize);
@@ -675,23 +693,22 @@ hdintr(ctlr)
 
        if (master->mcs & (MCS_SOFTERROR | MCS_FATALERROR) || timedout)
                hdcerror(ctlr, *(u_long *)master->xstatus);
 
        if (master->mcs & (MCS_SOFTERROR | MCS_FATALERROR) || timedout)
                hdcerror(ctlr, *(u_long *)master->xstatus);
-       else {
+       else 
                hdc->hdc_wticks = 0;
                hdc->hdc_wticks = 0;
-               if (vm->um_tab.b_active) {
-                       vm->um_tab.b_active = 0;
-                       vm->um_tab.b_actf = dp->b_forw;
-                       dp->b_active = 0;
-                       dp->b_errcnt = 0;
-                       dp->b_actf = bp->av_forw;
-                       bp->b_resid = 0;
-                       vbadone(bp, &hdc->hdc_rbuf);
-                       biodone(bp);
-                       /* start up now, if more work to do */
-                       if (dp->b_actf)
-                               hdustart(vi);
-                       else if (dk->dk_openpart == 0)
-                               wakeup((caddr_t)dk);
-               }
+       if (vm->um_tab.b_active) {
+               vm->um_tab.b_active = 0;
+               vm->um_tab.b_actf = dp->b_forw;
+               dp->b_active = 0;
+               dp->b_errcnt = 0;
+               dp->b_actf = bp->av_forw;
+               bp->b_resid = 0;
+               vbadone(bp, &hdc->hdc_rbuf);
+               biodone(bp);
+               /* start up now, if more work to do */
+               if (dp->b_actf)
+                       hdustart(vi);
+               else if (dk->dk_openpart == 0)
+                       wakeup((caddr_t)dk);
        }
        /* if there are devices ready to transfer, start the controller. */
        if (hdc->hdc_flags & HDC_WAIT) {
        }
        /* if there are devices ready to transfer, start the controller. */
        if (hdc->hdc_flags & HDC_WAIT) {
@@ -701,20 +718,67 @@ hdintr(ctlr)
                hdcstart(vm);
 }
 
                hdcstart(vm);
 }
 
-hdioctl(dev, command, data, flag)
+hdioctl(dev, cmd, data, flag)
        dev_t dev;
        dev_t dev;
-       int command, flag;
+       int cmd, flag;
        caddr_t data;
 {
        caddr_t data;
 {
+       register int unit;
+       register struct dksoftc *dk;
+       register struct disklabel *lp;
        int error;
 
        int error;
 
-       switch (command) {
-
+       unit = hdunit(dev);
+       dk = &dksoftc[unit];
+       lp = &dk->dk_label;
+       error = 0;
+       switch (cmd) {
+       case DIOCGDINFO:
+               *(struct disklabel *)data = *lp;
+               break;
+       case DIOCGPART:
+               ((struct partinfo *)data)->disklab = lp;
+               ((struct partinfo *)data)->part =
+                   &lp->d_partitions[hdpart(dev)];
+               break;
+       case DIOCSDINFO:
+               if ((flag & FWRITE) == 0)
+                       error = EBADF;
+               else
+                       error = setdisklabel(lp, (struct disklabel *)data,
+                           (dk->dk_state == OPENRAW) ? 0 : dk->dk_openpart);
+               if (error == 0 && dk->dk_state == OPENRAW)
+                       dk->dk_state = OPEN;
+               break;
+       case DIOCWLABEL:
+               if ((flag & FWRITE) == 0)
+                       error = EBADF;
+               else
+                       dk->dk_wlabel = *(int *)data;
+               break;
+       case DIOCWDINFO:
+               if ((flag & FWRITE) == 0)
+                       error = EBADF;
+               else if ((error = setdisklabel(lp, (struct disklabel *)data,
+                   (dk->dk_state == OPENRAW) ? 0 : dk->dk_openpart)) == 0) {
+                       int wlab;
+
+                       if (error == 0 && dk->dk_state == OPENRAW)
+                               dk->dk_state = OPEN;
+                       /* simulate opening partition 0 so write succeeds */
+                       dk->dk_openpart |= (1 << 0);            /* XXX */
+                       wlab = dk->dk_wlabel;
+                       dk->dk_wlabel = 1;
+                       error = writedisklabel(dev, hdstrategy, lp);
+                       dk->dk_openpart = dk->dk_copenpart | dk->dk_bopenpart;
+                       dk->dk_wlabel = wlab;
+               }
+               break;
        default:
                error = ENOTTY;
                break;
        }
        default:
                error = ENOTTY;
                break;
        }
-       return(error);
+       return (error);
 }
 
 /*
 }
 
 /*
@@ -806,70 +870,7 @@ hdcerror(ctlr, code)
        int ctlr;
        u_long code;
 {
        int ctlr;
        u_long code;
 {
-       printf("hd%d: ", ctlr);
-       switch(code) {
-#define        P(op, msg)      case op: printf("%s\n", msg); return;
-       P(0x0100, "Invalid command code")
-       P(0x0221, "Total longword count too large")
-       P(0x0222, "Total longword count incorrect")
-       P(0x0223, "Longword count of zero not permitted")
-       P(0x0231, "Too many data chained items")
-       P(0x0232, "Data chain not permitted for this command")
-       P(0x0341, "Maximum logical cylinder address exceeded")
-       P(0x0342, "Maximum logical head address exceeded")
-       P(0x0343, "Maximum logical sectoraddress exceeded")
-       P(0x0351, "Maximum physical cylinder address exceeded")
-       P(0x0352, "Maximum physical head address exceeded")
-       P(0x0353, "Maximum physical sectoraddress exceeded")
-       P(0x0621, "Control store PROM revision incorrect")
-       P(0x0642, "Power fail detected")
-       P(0x0721, "Sector count test failed")
-       P(0x0731, "First access test failed")
-       P(0x0811, "Drive not online")
-       P(0x0812, "Drive not ready")
-       P(0x0813, "Drive seek error")
-       P(0x0814, "Drive faulted")
-       P(0x0815, "Drive reserved")
-       P(0x0816, "Drive write protected")
-       P(0x0841, "Timeout waiting for drive to go on-cylinder")
-       P(0x0851, "Timeout waiting for a specific sector address")
-       P(0x0921, "Correctable ECC error")
-       P(0x0A11, "Attempt to spill-off of physical boundary")
-       P(0x0A21, "Attempt to spill-off of logical boundary")
-       P(0x0A41, "Unknown DDC status (PSREAD)")
-       P(0x0A42, "Unknown DDC status (PSWRITE)")
-       P(0x0A51, "Track relocation limit exceeded")
-       P(0x0C00, "HFASM")
-       P(0x0C01, "data field error")
-       P(0x0C02, "sector not found")
-       P(0x0C03, "sector overrun")
-       P(0x0C04, "no data sync")
-       P(0x0C05, "FIFO data lost")
-       P(0x0C06, "correction failed")
-       P(0x0C07, "late interlock")
-       P(0x0D21, "Output data buffer parity error")
-       P(0x0D31, "Input data transfer FIFO indicates overflow")
-       P(0x0D32, "Input data buffer FIFO indicates overflow")
-       P(0x0D41, "Longword count != 0 indicates underflow")
-       P(0x0D42, "Output data buffer FIFO indicates underflow")
-       P(0x0E01, "FT timeout -- DDC interrupt")
-       P(0x0E02, "RDDB timeout -- IDTFINRDY -- and DDC interrupt")
-       P(0x0E03, "RDDB timeout -- DDC interrupt")
-       P(0x0E04, "RDDB timeout -- writing ZERO's to IDTF")
-       P(0x0E05, "RDDB timeout -- IDTFINRDY -- and IDBFEMPTY+")
-       P(0x0E06, "WRDB timeout -- ODTFOUTRDT -- and DDC interrupt")
-       P(0x0E07, "WRDB timeout -- ODTFOUTRDT -- and DDC interrupt")
-       P(0x0E08, "WRDB timeout -- DDC interrupt")
-       P(0x0E09, "WRDB timeout -- ODBFFULL+ and DDC interrupt")
-       P(0x0E0A, "VLT timeout -- DDC interrupt")
-       P(0x0E0B, "WRBA timeout -- ODTFOUTRDY-")
-       P(0x0F00, "Error log full")
-       default:
-               if (code >= 0x0B00 && code <= 0x0BFF)
-                       printf("Unknown DDC status type 0x%x.", code&0xff);
-               else
-                       printf("Unknown error %lx\n", code);
-       }
+       printf("hd%d: error %lx\n", ctlr, code);
 }
 
 #ifdef COMPAT_42
 }
 
 #ifdef COMPAT_42
@@ -914,6 +915,7 @@ hdreadgeometry(dk)
                return(1);
        }
        lp = &dk->dk_label;
                return(1);
        }
        lp = &dk->dk_label;
+
        /* 1K block in Harris geometry; convert to sectors for disklabels */
        for (cnt = 0; cnt < GB_MAXPART; cnt++) {
                lp->d_partitions[cnt].p_offset =
        /* 1K block in Harris geometry; convert to sectors for disklabels */
        for (cnt = 0; cnt < GB_MAXPART; cnt++) {
                lp->d_partitions[cnt].p_offset =