add appropriate copyright notice
[unix-history] / usr / src / sys / tahoe / vba / vd.c
index 6d6ede3..6de9137 100644 (file)
@@ -2,14 +2,22 @@
  * 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
  * 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.
+ * 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.
  *
  *
- *     @(#)vd.c        7.1 (Berkeley) %G%
+ *     @(#)vd.c        7.6 (Berkeley) %G%
  */
 
 #include "dk.h"
  */
 
 #include "dk.h"
@@ -227,6 +235,9 @@ 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_npartitions = 1;
+       lp->d_partitions[0].p_offset = 0;
+       lp->d_partitions[0].p_size = LABELSECTOR + 1;
 
        /*
         * Initialize invariant portion of
 
        /*
         * Initialize invariant portion of
@@ -848,9 +859,10 @@ vdharderr(what, vd, bp, dcb)
 
        if (vd->vd_wticks < VDMAXTIME)
                status &= ~DONTCARE;
 
        if (vd->vd_wticks < VDMAXTIME)
                status &= ~DONTCARE;
-       blkdone = ((((dcb->err_cyl & 0xfff) * lp->d_ntracks + dcb->err_trk)
-           * lp->d_nsectors + dcb->err_sec) >> dksoftc[unit].dk_bshift)
-           - lp->d_partitions[vdpart(bp->b_dev)].p_offset - bp->b_blkno;
+       blkdone = ((((dcb->err_cyl & 0xfff) * lp->d_ntracks + dcb->err_trk) *
+           lp->d_nsectors + dcb->err_sec -
+           lp->d_partitions[vdpart(bp->b_dev)].p_offset) >>
+           dksoftc[unit].dk_bshift) - bp->b_blkno;
        diskerr(bp, "dk", what, LOG_PRINTF, blkdone, lp);
        printf(", status %b", status, VDERRBITS);
        if (vd->vd_type == VDTYPE_SMDE)
        diskerr(bp, "dk", what, LOG_PRINTF, blkdone, lp);
        printf(", status %b", status, VDERRBITS);
        if (vd->vd_type == VDTYPE_SMDE)
@@ -866,9 +878,10 @@ vdsofterr(bp, dcb)
        int status = dcb->operrsta;
        int blkdone;
 
        int status = dcb->operrsta;
        int blkdone;
 
-       blkdone = ((((dcb->err_cyl & 0xfff) * lp->d_ntracks + dcb->err_trk)
-           * lp->d_nsectors + dcb->err_sec) >> dksoftc[unit].dk_bshift)
-           - lp->d_partitions[vdpart(bp->b_dev)].p_offset - bp->b_blkno;
+       blkdone = ((((dcb->err_cyl & 0xfff) * lp->d_ntracks + dcb->err_trk) *
+           lp->d_nsectors + dcb->err_sec -
+           lp->d_partitions[vdpart(bp->b_dev)].p_offset) >>
+           dksoftc[unit].dk_bshift) - bp->b_blkno;
 
        if (status != (DCBS_CCD|DCBS_SOFT|DCBS_ERR|DCBS_DONE)) {
                diskerr(bp, "dk", "soft error", LOG_WARNING, blkdone, lp);
 
        if (status != (DCBS_CCD|DCBS_SOFT|DCBS_ERR|DCBS_DONE)) {
                diskerr(bp, "dk", "soft error", LOG_WARNING, blkdone, lp);
@@ -889,7 +902,7 @@ vdioctl(dev, cmd, data, flag)
        register int unit = vdunit(dev);
        register struct disklabel *lp = &dklabel[unit];
        register struct dksoftc *dk = &dksoftc[unit];
        register int unit = vdunit(dev);
        register struct disklabel *lp = &dklabel[unit];
        register struct dksoftc *dk = &dksoftc[unit];
-       int error = 0, wlab, vdformat();
+       int error = 0, vdformat();
 
        switch (cmd) {
 
 
        switch (cmd) {
 
@@ -922,19 +935,21 @@ vdioctl(dev, cmd, data, flag)
                break;
 
        case DIOCWDINFO:
                break;
 
        case DIOCWDINFO:
-               /* simulate opening partition 0 so write succeeds */
-               dk->dk_openpart |= (1 << 0);            /* XXX */
-               wlab = dk->dk_wlabel;
-               dk->dk_wlabel = 1;
                if ((flag & FWRITE) == 0)
                        error = EBADF;
                else if ((error = setdisklabel(lp, (struct disklabel *)data,
                    (dk->dk_state == OPENRAW) ? 0 : dk->dk_openpart)) == 0) {
                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;
+
                        dk->dk_state = OPEN;
                        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, vdstrategy, lp);
                        error = writedisklabel(dev, vdstrategy, lp);
+                       dk->dk_openpart = dk->dk_copenpart | dk->dk_bopenpart;
+                       dk->dk_wlabel = wlab;
                }
                }
-               dk->dk_openpart = dk->dk_copenpart | dk->dk_bopenpart;
-               dk->dk_wlabel = wlab;
                break;
 
        case DIOCWFORMAT:
                break;
 
        case DIOCWFORMAT:
@@ -1278,6 +1293,16 @@ struct   vdst {
        { 66, 23, 850, 512, "NEC 800",
                {0,      1290300},      /* a cyl   0 - 849 */
        },
        { 66, 23, 850, 512, "NEC 800",
                {0,      1290300},      /* a cyl   0 - 849 */
        },
+       { 64, 20, 842, 512, "2361a",
+               {0,      61440},        /* a cyl   0 - 47 */
+               {61440,  67840},        /* b cyl  48 - 100 */
+               {129280, 942080},       /* c cyl 101 - 836 */
+               {0,      1071360},      /* d cyl   0 - 836 */
+               {449280, 311040},       /* e cyl 351 - 593 */
+               {760320, 311040},       /* f cyl 594 - 836 */
+               {449280, 622080},       /* g cyl 351 - 836 */
+               {129280, 320000}        /* h cyl 101 - 350 */
+       },
        { 48, 24, 711, 512, "xsd",
                {0,      61056},        /* a cyl   0 - 52 */
                {61056,  61056},        /* b cyl  53 - 105 */
        { 48, 24, 711, 512, "xsd",
                {0,      61056},        /* a cyl   0 - 52 */
                {61056,  61056},        /* b cyl  53 - 105 */