home *** CD-ROM | disk | FTP | other *** search
/ InfoMagic Source Code 1993 July / THE_SOURCE_CODE_CD_ROM.iso / bsd_srcs / sys / tahoe / vba / hd.c < prev    next >
Encoding:
C/C++ Source or Header  |  1991-05-08  |  22.9 KB  |  931 lines

  1. /*
  2.  * Copyright (c) 1988 The Regents of the University of California.
  3.  * All rights reserved.
  4.  *
  5.  * This code is derived from software contributed to Berkeley by
  6.  * Harris Corp.
  7.  *
  8.  * Redistribution and use in source and binary forms, with or without
  9.  * modification, are permitted provided that the following conditions
  10.  * are met:
  11.  * 1. Redistributions of source code must retain the above copyright
  12.  *    notice, this list of conditions and the following disclaimer.
  13.  * 2. Redistributions in binary form must reproduce the above copyright
  14.  *    notice, this list of conditions and the following disclaimer in the
  15.  *    documentation and/or other materials provided with the distribution.
  16.  * 3. All advertising materials mentioning features or use of this software
  17.  *    must display the following acknowledgement:
  18.  *    This product includes software developed by the University of
  19.  *    California, Berkeley and its contributors.
  20.  * 4. Neither the name of the University nor the names of its contributors
  21.  *    may be used to endorse or promote products derived from this software
  22.  *    without specific prior written permission.
  23.  *
  24.  * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
  25.  * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
  26.  * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
  27.  * ARE DISCLAIMED.  IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
  28.  * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
  29.  * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
  30.  * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
  31.  * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
  32.  * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
  33.  * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
  34.  * SUCH DAMAGE.
  35.  *
  36.  *    @(#)hd.c    7.12 (Berkeley) 12/16/90
  37.  */
  38.  
  39. #include "hd.h"
  40.  
  41. #if NHD > 0
  42. #include "sys/param.h"
  43. #include "sys/buf.h"
  44. #include "sys/conf.h"
  45. #include "sys/dkstat.h"
  46. #include "sys/disklabel.h"
  47. #include "sys/file.h"
  48. #include "sys/systm.h"
  49. #include "sys/vmmac.h"
  50. #include "sys/time.h"
  51. #include "sys/proc.h"
  52. #include "sys/uio.h"
  53. #include "sys/syslog.h"
  54. #include "sys/kernel.h"
  55. #include "sys/ioctl.h"
  56. #include "sys/stat.h"
  57. #include "sys/errno.h"
  58.  
  59. #include "../include/cpu.h"
  60. #include "../include/mtpr.h"
  61.  
  62. #include "../vba/vbavar.h"
  63. #include "../vba/hdreg.h"
  64.  
  65. #define    b_cylin    b_resid
  66.  
  67. #define    hdunit(dev)        (minor(dev)>>3)
  68. #define    hdpart(dev)        (minor(dev)&0x07)
  69. #define    hdminor(unit, part)    (((unit)<<3)|(part))
  70.  
  71. struct vba_ctlr *hdcminfo[NHDC];
  72. struct vba_device *hddinfo[NHD];
  73. int hdcprobe(), hdslave(), hdattach(), hddgo(), hdstrategy();
  74. long hdstd[] = { 0 };
  75. struct vba_driver hdcdriver =
  76.     { hdcprobe, hdslave, hdattach, hddgo, hdstd, "hd", hddinfo, "hdc", hdcminfo };
  77.  
  78. /*
  79.  * Per-controller state.
  80.  */
  81. struct hdcsoftc {
  82.     u_short    hdc_flags;
  83. #define    HDC_INIT    0x01    /* controller initialized */
  84. #define    HDC_STARTED    0x02    /* start command issued */
  85. #define    HDC_LOCKED    0x04    /* locked for direct controller access */
  86. #define    HDC_WAIT    0x08    /* someone needs direct controller access */
  87.     u_short    hdc_wticks;        /* timeout */
  88.     struct master_mcb *hdc_mcbp;    /* address of controller mcb */
  89.     struct registers *hdc_reg;    /* base address of i/o regs */
  90.     struct vb_buf hdc_rbuf;        /* vba resources */
  91.     struct master_mcb hdc_mcb;    /* controller mcb */
  92. } hdcsoftc[NHDC];
  93.  
  94. #define    HDCMAXTIME    20        /* max time for operation, sec. */
  95. #define    HDCINTERRUPT    0xf0        /* interrupt vector */
  96.  
  97. /*
  98.  * Per-drive state; probably everything should be "hd_", not "dk_",
  99.  * but it's not worth it, and dk is a better mnemonic for disk anyway.
  100.  */
  101. struct dksoftc {
  102. #ifdef COMPAT_42
  103.     u_short    dk_def_cyl;    /* definition track cylinder address */
  104. #endif
  105.     int    dk_state;    /* open fsm */
  106.     u_short    dk_bshift;    /* shift for * (DEV_BSIZE / sectorsize) XXX */
  107.     int    dk_wlabel;    /* if label sector is writeable */
  108.     u_long    dk_copenpart;    /* character units open on this drive */
  109.     u_long    dk_bopenpart;    /* block units open on this drive */
  110.     u_long    dk_openpart;    /* all units open on this drive */
  111.     int    dk_unit;    /* unit# */
  112.     int    dk_ctlr;    /* controller# */
  113.     int    dk_format;    /* if format program is using disk */
  114.     struct buf dk_utab;        /* i/o queue header */
  115.     struct disklabel dk_label;    /* disklabel for this disk */
  116.     struct mcb dk_mcb;        /* disk mcb */
  117. } dksoftc[NHD];
  118.  
  119. /*
  120.  * Drive states.  Used during steps of open/initialization.
  121.  * States < OPEN (> 0) are transient, during an open operation.
  122.  * OPENRAW is used for unlabeled disks, to allow format operations.
  123.  */
  124. #define    CLOSED        0        /* disk is closed */
  125. #define    WANTOPEN    1        /* open requested, not started */
  126. #define    WANTOPENRAW    2        /* open requested, no label */
  127. #define    RDLABEL        3        /* reading pack label */
  128. #define    OPEN        4        /* intialized and ready */
  129. #define    OPENRAW        5        /* open, no label */
  130.  
  131. int hdcwstart, hdcwatch();
  132.  
  133. /* see if the controller is really there, if so, init it. */
  134. /* ARGSUSED */
  135. hdcprobe(reg, vm)
  136.     caddr_t reg;
  137.     /* register */ struct vba_ctlr *vm;
  138. {
  139.     register int br, cvec;        /* must be r12, r11 */
  140.     register struct hdcsoftc *hdc;
  141.     static struct module_id id;
  142.     struct pte *dummypte;
  143.     caddr_t putl;
  144.  
  145.     /* initialize the hdc controller structure. */
  146.     hdc = &hdcsoftc[vm->um_ctlr];
  147.     if (!vbmemalloc(1, reg, &dummypte, &putl)) {
  148.         printf("hdc%d: vbmemalloc failed.\n", vm->um_ctlr);
  149.         return(0);
  150.     }
  151.     hdc->hdc_reg = (struct registers *)putl;
  152.  
  153.     /*
  154.      * try and ping the MID register; side effect of wbadaddr is to read
  155.      * the module id; the controller is bad if it's not an hdc, the hdc's
  156.      * writeable control store is not loaded, or the hdc failed the
  157.      * functional integrity test;
  158.      */
  159.     if (wbadaddr(&hdc->hdc_reg->module_id, 4,
  160.         vtoph((struct process *)NULL, &id)))
  161.         return(0);
  162.     DELAY(10000);
  163.     mtpr(PADC, 0);
  164.     if (id.module_id != (u_char)HDC_MID) {
  165.         printf("hdc%d: bad module id; id = %x.\n",
  166.             vm->um_ctlr, id.module_id);
  167.         return(0);
  168.     }
  169.     if (id.code_rev == (u_char)0xff) {
  170.         printf("hdc%d: micro-code not loaded.\n", vm->um_ctlr);
  171.         return(0);
  172.     }
  173.     if (id.fit != (u_char)0xff) {
  174.         printf("hdc%d: FIT test failed.\n", vm->um_ctlr);
  175.         return(0);
  176.     }
  177.  
  178.     /* reset that pup; flag as inited */
  179.     hdc->hdc_reg->soft_reset = 0;
  180.     DELAY(1000000);
  181.     hdc->hdc_flags |= HDC_INIT;
  182.  
  183.     /* allocate page tables and i/o buffer. */
  184.     if (!vbainit(&hdc->hdc_rbuf, MAXPHYS, VB_32BIT|VB_SCATTER)) {
  185.         printf("hdc%d: vbainit failed\n", vm->um_ctlr);
  186.         return (0);
  187.     }
  188.  
  189.     /* set pointer to master control block */
  190.     hdc->hdc_mcbp =
  191.         (struct master_mcb *)vtoph((struct proc *)NULL, &hdc->hdc_mcb);
  192.  
  193.     br = 0x17, cvec = HDCINTERRUPT + vm->um_ctlr;        /* XXX */
  194.     return(sizeof(struct registers));
  195. }
  196.  
  197. /* ARGSUSED */
  198. hdslave(vi, vdaddr)
  199.     struct vba_device *vi;
  200.     struct vddevice *vdaddr;
  201. {
  202.     register struct mcb *mcb;
  203.     register struct disklabel *lp;
  204.     register struct dksoftc *dk;
  205.     static struct status status;
  206.  
  207.     dk = &dksoftc[vi->ui_unit];
  208.     dk->dk_unit = vi->ui_unit;
  209.     dk->dk_ctlr = vi->ui_ctlr;
  210.  
  211.     mcb = &dk->dk_mcb;
  212.     mcb->command = HCMD_STATUS;
  213.     mcb->chain[0].wcount = sizeof(struct status) / sizeof(long);
  214.     mcb->chain[0].memadr  = (u_long)vtoph((struct process *)0, &status);
  215.     if (hdimcb(dk)) {
  216.         printf(" (no status)\n");
  217.         return(0);
  218.     }
  219.  
  220.     /*
  221.      * Report the drive down if anything in the drive status looks bad.
  222.      * If the drive is offline and it is not on cylinder, then the drive
  223.      * is not there.  If there is a fault condition, the hdc will try to
  224.      * clear it when we read the disklabel information.
  225.      */
  226.     if (!(status.drs&DRS_ONLINE)) {
  227.         if (status.drs&DRS_ON_CYLINDER)
  228.             printf(" (not online)\n");
  229.         return(0);
  230.     }
  231.     if (status.drs&DRS_FAULT)
  232.         printf(" (clearing fault)");
  233.  
  234.     lp = &dk->dk_label;
  235. #ifdef RAW_SIZE
  236.     lp->d_secsize = status.bytes_per_sec;
  237. #else
  238.     lp->d_secsize = 512;
  239. #endif
  240.     lp->d_nsectors = status.max_sector + 1;
  241.     lp->d_ntracks = status.max_head + 1;
  242.     lp->d_ncylinders = status.max_cyl + 1;
  243.     lp->d_secpercyl = lp->d_ntracks * lp->d_nsectors;
  244.     lp->d_npartitions = 1;
  245.     lp->d_partitions[0].p_offset = 0;
  246.     lp->d_partitions[0].p_size = LABELSECTOR + 1;
  247.     lp->d_rpm = status.rpm;
  248.     lp->d_typename[0] = 'h';
  249.     lp->d_typename[1] = 'd';
  250.     lp->d_typename[2] = '\0';
  251. #ifdef COMPAT_42
  252.     dk->dk_def_cyl = status.def_cyl;
  253. #endif
  254.     return(1);
  255. }
  256.  
  257. hdattach(vi)
  258.     register struct vba_device *vi;
  259. {
  260.     register struct dksoftc *dk;
  261.     register struct disklabel *lp;
  262.     register int unit;
  263.  
  264.     unit = vi->ui_unit;
  265.     if (hdinit(hdminor(unit, 0), 0)) {
  266.         printf(": unknown drive type");
  267.         return;
  268.     }
  269.     dk = &dksoftc[unit];
  270.     lp = &dk->dk_label;
  271.     hd_setsecsize(dk, lp);
  272.     if (dk->dk_state == OPEN)
  273.         printf(": %s <secsize %d, ntrak %d, ncyl %d, nsec %d>",
  274.             lp->d_typename, lp->d_secsize, lp->d_ntracks,
  275.             lp->d_ncylinders, lp->d_nsectors);
  276.  
  277.     /*
  278.      * (60 / rpm) / (sectors per track * (bytes per sector / 2))
  279.      */
  280.     if (vi->ui_dk >= 0)
  281.         dk_wpms[vi->ui_dk] =
  282.             (lp->d_rpm * lp->d_nsectors * lp->d_secsize) / 120;
  283. #ifdef notyet
  284.     addswap(makedev(HDMAJOR, hdminor(unit, 0)), lp);
  285. #endif
  286. }
  287.  
  288. hdopen(dev, flags, fmt)
  289.     dev_t dev;
  290.     int flags, fmt;
  291. {
  292.     register struct disklabel *lp;
  293.     register struct dksoftc *dk;
  294.     register struct partition *pp;
  295.     register int unit;
  296.     struct vba_device *vi;
  297.     int s, error, part = hdpart(dev), mask = 1 << part;
  298.     daddr_t start, end;
  299.  
  300.     unit = hdunit(dev);
  301.     if (unit >= NHD || (vi = hddinfo[unit]) == 0 || vi->ui_alive == 0)
  302.         return(ENXIO);
  303.     dk = &dksoftc[unit];
  304.     lp = &dk->dk_label;
  305.     s = spl7();
  306.     while (dk->dk_state != OPEN && dk->dk_state != OPENRAW &&
  307.         dk->dk_state != CLOSED)
  308.         if (error = tsleep((caddr_t)dk, (PZERO+1) | PCATCH,
  309.             devopn, 0)) {
  310.             splx(s);
  311.             return (error);
  312.         }
  313.     splx(s);
  314.     if (dk->dk_state != OPEN && dk->dk_state != OPENRAW)
  315.         if (error = hdinit(dev, flags))
  316.             return(error);
  317.  
  318.     if (hdcwstart == 0) {
  319.         timeout(hdcwatch, (caddr_t)0, hz);
  320.         hdcwstart++;
  321.     }
  322.     /*
  323.      * Warn if a partion is opened that overlaps another partition
  324.      * which is open unless one is the "raw" partition (whole disk).
  325.      */
  326. #define    RAWPART        8        /* 'x' partition */    /* XXX */
  327.     if ((dk->dk_openpart & mask) == 0 && part != RAWPART) {
  328.         pp = &lp->d_partitions[part];
  329.         start = pp->p_offset;
  330.         end = pp->p_offset + pp->p_size;
  331.         for (pp = lp->d_partitions;
  332.              pp < &lp->d_partitions[lp->d_npartitions]; pp++) {
  333.             if (pp->p_offset + pp->p_size <= start ||
  334.                 pp->p_offset >= end)
  335.                 continue;
  336.             if (pp - lp->d_partitions == RAWPART)
  337.                 continue;
  338.             if (dk->dk_openpart & (1 << (pp - lp->d_partitions)))
  339.                 log(LOG_WARNING,
  340.                     "hd%d%c: overlaps open partition (%c)\n",
  341.                     unit, part + 'a',
  342.                     pp - lp->d_partitions + 'a');
  343.         }
  344.     }
  345.     if (part >= lp->d_npartitions)
  346.         return(ENXIO);
  347.     dk->dk_openpart |= mask;
  348.     switch (fmt) {
  349.     case S_IFCHR:
  350.         dk->dk_copenpart |= mask;
  351.         break;
  352.     case S_IFBLK:
  353.         dk->dk_bopenpart |= mask;
  354.         break;
  355.     }
  356.     return(0);
  357. }
  358.  
  359. /* ARGSUSED */
  360. hdclose(dev, flags, fmt)
  361.     dev_t dev;
  362.     int flags, fmt;
  363. {
  364.     register struct dksoftc *dk;
  365.     int mask;
  366.  
  367.     dk = &dksoftc[hdunit(dev)];
  368.     mask = 1 << hdpart(dev);
  369.     switch (fmt) {
  370.     case S_IFCHR:
  371.         dk->dk_copenpart &= ~mask;
  372.         break;
  373.     case S_IFBLK:
  374.         dk->dk_bopenpart &= ~mask;
  375.         break;
  376.     }
  377.     if (((dk->dk_copenpart | dk->dk_bopenpart) & mask) == 0)
  378.         dk->dk_openpart &= ~mask;
  379.     /*
  380.      * Should wait for i/o to complete on this partition
  381.      * even if others are open, but wait for work on blkflush().
  382.      */
  383.     if (dk->dk_openpart == 0) {
  384.         int s = spl7();
  385.         while (dk->dk_utab.b_actf)
  386.             sleep((caddr_t)dk, PZERO-1);
  387.         splx(s);
  388.         dk->dk_state = CLOSED;
  389.         dk->dk_wlabel = 0;
  390.     }
  391.     return(0);
  392. }
  393.  
  394. hdinit(dev, flags)
  395.     dev_t dev;
  396.     int flags;
  397. {
  398.     register struct dksoftc *dk;
  399.     register struct disklabel *lp;
  400.     struct vba_device *vi;
  401.     int error, unit;
  402.     char *msg, *readdisklabel();
  403.     extern int cold;
  404.  
  405.     vi = hddinfo[unit = hdunit(dev)];
  406.     dk = &dksoftc[unit];
  407.     dk->dk_unit = vi->ui_slave;
  408.     dk->dk_ctlr = vi->ui_ctlr;
  409.  
  410.     if (flags & O_NDELAY) {
  411.         dk->dk_state = OPENRAW;
  412.         return(0);
  413.     }
  414.  
  415.     error = 0;
  416.     lp = &dk->dk_label;
  417.     dk->dk_state = RDLABEL;
  418.     if (msg = readdisklabel(dev, hdstrategy, lp)) {
  419.         if (cold) {
  420.             printf(": %s\n", msg);
  421.             dk->dk_state = CLOSED;
  422.         } else {
  423.             log(LOG_ERR, "hd%d: %s\n", unit, msg);
  424.             dk->dk_state = OPENRAW;
  425.         }
  426. #ifdef COMPAT_42
  427.         hdclock(vi->ui_ctlr);
  428.         if (!(error = hdreadgeometry(dk)))
  429.             dk->dk_state = OPEN;
  430.         hdcunlock(vi->ui_ctlr);
  431. #endif
  432.     } else
  433.         dk->dk_state = OPEN;
  434.     wakeup((caddr_t)dk);
  435.     return(error);
  436. }
  437.  
  438. hd_setsecsize(dk, lp)
  439.     register struct dksoftc *dk;
  440.     struct disklabel *lp;
  441. {
  442.     register int mul;
  443.  
  444.     /*
  445.      * Calculate scaling shift for mapping
  446.      * DEV_BSIZE blocks to drive sectors.
  447.      */
  448.     mul = DEV_BSIZE / lp->d_secsize;
  449.     dk->dk_bshift = 0;
  450.     while ((mul >>= 1) > 0)
  451.         dk->dk_bshift++;
  452. }
  453.  
  454. /* ARGSUSED */
  455. hddgo(vm)
  456.     struct vba_device *vm;
  457. {}
  458.  
  459. extern int name_ext;
  460. hdstrategy(bp)
  461.     register struct buf *bp;
  462. {
  463.     register struct vba_device *vi;
  464.     register struct disklabel *lp;
  465.     register struct dksoftc *dk;
  466.     struct buf *dp;
  467.     register int unit;
  468.     daddr_t sn, sz, maxsz;
  469.     int part, s;
  470.  
  471.     vi = hddinfo[unit = hdunit(bp->b_dev)];
  472.     if (unit >= NHD || vi == 0 || vi->ui_alive == 0) {
  473.         bp->b_error = ENXIO;
  474.         goto bad;
  475.     }
  476.     dk = &dksoftc[unit];
  477.     if (dk->dk_state < OPEN)
  478.         goto q;
  479.     if (dk->dk_state != OPEN && (bp->b_flags & B_READ) == 0) {
  480.         bp->b_error = EROFS;
  481.         goto bad;
  482.     }
  483.     part = hdpart(bp->b_dev);
  484.     if ((dk->dk_openpart & (1 << part)) == 0) {
  485.         bp->b_error = ENODEV;
  486.         goto bad;
  487.     }
  488.     lp = &dk->dk_label;
  489.     sz = (bp->b_bcount + lp->d_secsize - 1) / lp->d_secsize;
  490.     maxsz = lp->d_partitions[part].p_size;
  491.     sn = bp->b_blkno << dk->dk_bshift;
  492.     if (sn + lp->d_partitions[part].p_offset <= LABELSECTOR &&
  493. #if LABELSECTOR != 0
  494.         sn + lp->d_partitions[part].p_offset + sz > LABELSECTOR &&
  495. #endif
  496.         (bp->b_flags & B_READ) == 0 && dk->dk_wlabel == 0) {
  497.         bp->b_error = EROFS;
  498.         goto bad;
  499.     }
  500.     if (sn < 0 || sn + sz > maxsz) {
  501.         if (sn == maxsz) {
  502.             bp->b_resid = bp->b_bcount;
  503.             goto done;
  504.         }
  505.         sz = maxsz - sn;
  506.         if (sz <= 0) {
  507.             bp->b_error = EINVAL;
  508.             goto bad;
  509.         }
  510.         bp->b_bcount = sz * lp->d_secsize;
  511.     }
  512.     bp->b_cylin = (sn + lp->d_partitions[part].p_offset) / lp->d_secpercyl;
  513.  
  514. q:    s = spl7();
  515.     dp = &dk->dk_utab;
  516.     disksort(dp, bp);
  517.     if (!dp->b_active) {
  518.         (void)hdustart(vi);
  519.         if (!vi->ui_mi->um_tab.b_active)
  520.             hdcstart(vi->ui_mi);
  521.     }
  522.     splx(s);
  523.     return;
  524. bad:
  525.     bp->b_flags |= B_ERROR;
  526. done:
  527.     biodone(bp);
  528. }
  529.  
  530. hdustart(vi)
  531.     register struct vba_device *vi;
  532. {
  533.     register struct buf *bp, *dp;
  534.     register struct vba_ctlr *vm;
  535.     register struct dksoftc *dk;
  536.  
  537.     dk = &dksoftc[vi->ui_unit];
  538.     dp = &dk->dk_utab;
  539.  
  540.     /* if queue empty, nothing to do.  impossible? */
  541.     if (dp->b_actf == NULL)
  542.         return;
  543.  
  544.     /* place on controller transfer queue */
  545.     vm = vi->ui_mi;
  546.     if (vm->um_tab.b_actf == NULL)
  547.         vm->um_tab.b_actf = dp;
  548.     else
  549.         vm->um_tab.b_actl->b_forw = dp;
  550.     vm->um_tab.b_actl = dp;
  551.     dp->b_forw = NULL;
  552.     dp->b_active++;
  553. }
  554.  
  555. hdcstart(vm)
  556.     register struct vba_ctlr *vm;
  557. {
  558.     register struct buf *bp;
  559.     register struct dksoftc *dk;
  560.     register struct disklabel *lp;
  561.     register struct master_mcb *master;
  562.     register struct mcb *mcb;
  563.     struct vba_device *vi;
  564.     struct hdcsoftc *hdc;
  565.     struct buf *dp;
  566.     int sn;
  567.  
  568.     /* pull a request off the controller queue */
  569.     for (;;) {
  570.         if ((dp = vm->um_tab.b_actf) == NULL)
  571.             return;
  572.         if (bp = dp->b_actf)
  573.             break;
  574.         vm->um_tab.b_actf = dp->b_forw;
  575.     }
  576.  
  577.     /* mark controller active */
  578.     vm->um_tab.b_active++;
  579.  
  580.     vi = hddinfo[hdunit(bp->b_dev)];
  581.     dk = &dksoftc[vi->ui_unit];
  582.     lp = &dk->dk_label;
  583.     sn = bp->b_blkno << dk->dk_bshift;
  584.  
  585.     /* fill in mcb */
  586.     mcb = &dk->dk_mcb;
  587.     mcb->forw_phaddr = 0;
  588.     /* mcb->priority = 0; */
  589.     mcb->interrupt = 1;
  590.     mcb->command = (bp->b_flags & B_READ) ? HCMD_READ:HCMD_WRITE;
  591.     mcb->cyl = bp->b_cylin;
  592. /* assumes partition starts on cylinder boundary */
  593.     mcb->head = (sn / lp->d_nsectors) % lp->d_ntracks;
  594.     mcb->sector = sn % lp->d_nsectors;
  595.     mcb->drive = vi->ui_slave;
  596.     /* mcb->context = 0;        /* what do we want on interrupt? */
  597.  
  598.     hdc = &hdcsoftc[vm->um_ctlr];
  599.     if (!hd_sgsetup(bp, &hdc->hdc_rbuf, mcb->chain)) {
  600.         mcb->chain[0].wcount = (bp->b_bcount+3) >> 2;
  601.         mcb->chain[0].memadr =
  602.             vbasetup(bp, &hdc->hdc_rbuf, (int)lp->d_secsize);
  603.     }
  604.  
  605.     if (vi->ui_dk >= 0) {
  606.         dk_busy |= 1<<vi->ui_dk;
  607.         dk_xfer[vi->ui_dk]++;
  608.         dk_wds[vi->ui_dk] += bp->b_bcount>>6;
  609.     }
  610.  
  611.     master = &hdc->hdc_mcb;
  612.     master->mcw = MCL_QUEUED;
  613.     master->interrupt = HDCINTERRUPT + vm->um_ctlr;
  614.     master->forw_phaddr = (u_long)vtoph((struct proc *)NULL, mcb);
  615.     hdc->hdc_reg->master_mcb = (u_long)hdc->hdc_mcbp;
  616. }
  617.  
  618. /*
  619.  * Wait for controller to finish current operation
  620.  * so that direct controller accesses can be done.
  621.  */
  622. hdclock(ctlr)
  623.     int ctlr;
  624. {
  625.     register struct vba_ctlr *vm = hdcminfo[ctlr];
  626.     register struct hdcsoftc *hdc;
  627.     int s;
  628.  
  629.     hdc = &hdcsoftc[ctlr];
  630.     s = spl7();
  631.     while (vm->um_tab.b_active || hdc->hdc_flags & HDC_LOCKED) {
  632.         hdc->hdc_flags |= HDC_WAIT;
  633.         sleep((caddr_t)hdc, PRIBIO);
  634.     }
  635.     hdc->hdc_flags |= HDC_LOCKED;
  636.     splx(s);
  637. }
  638.  
  639. /*
  640.  * Continue normal operations after pausing for 
  641.  * munging the controller directly.
  642.  */
  643. hdcunlock(ctlr)
  644.     int ctlr;
  645. {
  646.     register struct vba_ctlr *vm;
  647.     register struct hdcsoftc *hdc = &hdcsoftc[ctlr];
  648.  
  649.     hdc->hdc_flags &= ~HDC_LOCKED;
  650.     if (hdc->hdc_flags & HDC_WAIT) {
  651.         hdc->hdc_flags &= ~HDC_WAIT;
  652.         wakeup((caddr_t)hdc);
  653.     } else {
  654.         vm = hdcminfo[ctlr];
  655.         if (vm->um_tab.b_actf)
  656.             hdcstart(vm);
  657.     }
  658. }
  659.  
  660. hdintr(ctlr)
  661.     int ctlr;
  662. {
  663.     register struct buf *bp, *dp;
  664.     register struct vba_ctlr *vm;
  665.     register struct vba_device *vi;
  666.     register struct hdcsoftc *hdc;
  667.     register struct mcb *mcb;
  668.     struct master_mcb *master;
  669.     register int status;
  670.     int timedout;
  671.     struct dksoftc *dk;
  672.  
  673.     hdc = &hdcsoftc[ctlr];
  674.     master = &hdc->hdc_mcb;
  675.     uncache(&master->mcs);
  676.     uncache(&master->context);
  677.  
  678.     vm = hdcminfo[ctlr];
  679.     if (!vm->um_tab.b_active || !(master->mcs&MCS_DONE)) {
  680.         printf("hd%d: stray interrupt\n", ctlr);
  681.         return;
  682.     }
  683.  
  684.     dp = vm->um_tab.b_actf;
  685.     bp = dp->b_actf;
  686.     vi = hddinfo[hdunit(bp->b_dev)];
  687.     dk = &dksoftc[vi->ui_unit];
  688.     if (vi->ui_dk >= 0)
  689.         dk_busy &= ~(1<<vi->ui_dk);
  690.     timedout = (hdc->hdc_wticks >= HDCMAXTIME);
  691.  
  692.     mcb = &dk->dk_mcb;
  693.  
  694.     if (master->mcs & (MCS_SOFTERROR | MCS_FATALERROR) || timedout)
  695.         hdcerror(ctlr, *(u_long *)master->xstatus);
  696.     else 
  697.         hdc->hdc_wticks = 0;
  698.     if (vm->um_tab.b_active) {
  699.         vm->um_tab.b_active = 0;
  700.         vm->um_tab.b_actf = dp->b_forw;
  701.         dp->b_active = 0;
  702.         dp->b_errcnt = 0;
  703.         dp->b_actf = bp->av_forw;
  704.         bp->b_resid = 0;
  705.         vbadone(bp, &hdc->hdc_rbuf);
  706.         biodone(bp);
  707.         /* start up now, if more work to do */
  708.         if (dp->b_actf)
  709.             hdustart(vi);
  710.         else if (dk->dk_openpart == 0)
  711.             wakeup((caddr_t)dk);
  712.     }
  713.     /* if there are devices ready to transfer, start the controller. */
  714.     if (hdc->hdc_flags & HDC_WAIT) {
  715.         hdc->hdc_flags &= ~HDC_WAIT;
  716.         wakeup((caddr_t)hdc);
  717.     } else if (vm->um_tab.b_actf)
  718.         hdcstart(vm);
  719. }
  720.  
  721. hdioctl(dev, cmd, data, flag)
  722.     dev_t dev;
  723.     int cmd, flag;
  724.     caddr_t data;
  725. {
  726.     register int unit;
  727.     register struct dksoftc *dk;
  728.     register struct disklabel *lp;
  729.     int error;
  730.  
  731.     unit = hdunit(dev);
  732.     dk = &dksoftc[unit];
  733.     lp = &dk->dk_label;
  734.     error = 0;
  735.     switch (cmd) {
  736.     case DIOCGDINFO:
  737.         *(struct disklabel *)data = *lp;
  738.         break;
  739.     case DIOCGPART:
  740.         ((struct partinfo *)data)->disklab = lp;
  741.         ((struct partinfo *)data)->part =
  742.             &lp->d_partitions[hdpart(dev)];
  743.         break;
  744.     case DIOCSDINFO:
  745.         if ((flag & FWRITE) == 0)
  746.             error = EBADF;
  747.         else
  748.             error = setdisklabel(lp, (struct disklabel *)data,
  749.                 (dk->dk_state == OPENRAW) ? 0 : dk->dk_openpart);
  750.         if (error == 0 && dk->dk_state == OPENRAW)
  751.             dk->dk_state = OPEN;
  752.         break;
  753.     case DIOCWLABEL:
  754.         if ((flag & FWRITE) == 0)
  755.             error = EBADF;
  756.         else
  757.             dk->dk_wlabel = *(int *)data;
  758.         break;
  759.     case DIOCWDINFO:
  760.         if ((flag & FWRITE) == 0)
  761.             error = EBADF;
  762.         else if ((error = setdisklabel(lp, (struct disklabel *)data,
  763.             (dk->dk_state == OPENRAW) ? 0 : dk->dk_openpart)) == 0) {
  764.             int wlab;
  765.  
  766.             if (error == 0 && dk->dk_state == OPENRAW)
  767.                 dk->dk_state = OPEN;
  768.             /* simulate opening partition 0 so write succeeds */
  769.             dk->dk_openpart |= (1 << 0);        /* XXX */
  770.             wlab = dk->dk_wlabel;
  771.             dk->dk_wlabel = 1;
  772.             error = writedisklabel(dev, hdstrategy, lp);
  773.             dk->dk_openpart = dk->dk_copenpart | dk->dk_bopenpart;
  774.             dk->dk_wlabel = wlab;
  775.         }
  776.         break;
  777.     default:
  778.         error = ENOTTY;
  779.         break;
  780.     }
  781.     return (error);
  782. }
  783.  
  784. /*
  785.  * Watch for lost interrupts.
  786.  */
  787. hdcwatch()
  788. {
  789.     register struct hdcsoftc *hdc;
  790.     register struct vba_ctlr **vmp;
  791.     register int ctlr;
  792.     int s;
  793.  
  794.     timeout(hdcwatch, (caddr_t)0, hz);
  795.     for (vmp = hdcminfo, hdc = hdcsoftc, ctlr = 0; ctlr < NHDC;
  796.         ++ctlr, ++vmp, ++hdc) {
  797.         if (*vmp == 0 || (*vmp)->um_alive == 0)
  798.             continue;
  799.         s = spl7();
  800.         if ((*vmp)->um_tab.b_active &&
  801.             hdc->hdc_wticks++ >= HDCMAXTIME) {
  802.             printf("hd%d: lost interrupt\n", ctlr);
  803.             hdintr(ctlr);
  804.         }
  805.         splx(s);
  806.     }
  807. }
  808.  
  809. hddump(dev)
  810.     dev_t dev;
  811. {
  812.     return(ENXIO);
  813. }
  814.  
  815. hdsize(dev)
  816.     dev_t dev;
  817. {
  818.     register int unit = hdunit(dev);
  819.     register struct dksoftc *dk;
  820.     struct vba_device *vi;
  821.     struct disklabel *lp;
  822.  
  823.     if (unit >= NHD || (vi = hddinfo[unit]) == 0 || vi->ui_alive == 0 ||
  824.         (dk = &dksoftc[unit])->dk_state != OPEN)
  825.         return (-1);
  826.     lp = &dk->dk_label;
  827.     return ((int)lp->d_partitions[hdpart(dev)].p_size >> dk->dk_bshift);
  828. }
  829.  
  830. hdimcb(dk)
  831.     register struct dksoftc *dk;
  832. {
  833.     register struct master_mcb *master;
  834.     register struct mcb *mcb;
  835.     register struct hdcsoftc *hdc;
  836.     int timeout;
  837.  
  838.     /* fill in mcb */
  839.     mcb = &dk->dk_mcb;
  840.     mcb->interrupt = 0;
  841.     mcb->forw_phaddr = 0;
  842.     mcb->drive = dk->dk_unit;
  843.  
  844.     hdc = &hdcsoftc[dk->dk_ctlr];
  845.     master = &hdc->hdc_mcb;
  846.  
  847.     /* fill in master mcb */
  848.     master->mcw = MCL_IMMEDIATE;
  849.     master->forw_phaddr = (u_long)vtoph((struct proc *)NULL, mcb);
  850.     master->mcs = 0;
  851.  
  852.     /* kick controller and wait */
  853.     hdc->hdc_reg->master_mcb = (u_long)hdc->hdc_mcbp;
  854.     for (timeout = 15000; timeout; --timeout) {
  855.         DELAY(1000);
  856.         mtpr(PADC, 0);
  857.         if (master->mcs&MCS_FATALERROR) {
  858.             printf("hdc%d: fatal error\n", dk->dk_ctlr);
  859.             hdcerror(dk->dk_ctlr, *(u_long *)master->xstatus);
  860.             return(1);
  861.         }
  862.         if (master->mcs&MCS_DONE)
  863.             return(0);
  864.     }
  865.     printf("hdc%d: timed out\n", dk->dk_ctlr);
  866.     return(1);
  867. }
  868.  
  869. hdcerror(ctlr, code)
  870.     int ctlr;
  871.     u_long code;
  872. {
  873.     printf("hd%d: error %lx\n", ctlr, code);
  874. }
  875.  
  876. #ifdef COMPAT_42
  877. hdreadgeometry(dk)
  878.     struct dksoftc *dk;
  879. {
  880.     static geometry_sector geometry;
  881.     register struct mcb *mcb;
  882.     register struct disklabel *lp;
  883.     geometry_block *geo;
  884.     int cnt;
  885.  
  886.     /*
  887.      * Read the geometry block (at head = 0 sector = 0 of the drive
  888.      * definition cylinder), validate it (must have the correct version
  889.      * number, header, and checksum).
  890.      */
  891.     mcb = &dk->dk_mcb;
  892.     mcb->command = HCMD_READ;
  893.     mcb->cyl = dk->dk_def_cyl;
  894.     mcb->head = 0;
  895.     mcb->sector = 0;
  896.     mcb->chain[0].wcount = sizeof(geometry_sector) / sizeof(long);
  897.     mcb->chain[0].memadr  = (u_long)vtoph((struct process *)0, &geometry);
  898.     /* mcb->chain[0].memadr = (long)&geometry; */
  899.     if (hdimcb(dk)) {
  900.          printf("hd%d: can't read default geometry.\n", dk->dk_unit);
  901.         return(1);
  902.     }
  903.     geo = &geometry.geometry_block;
  904.      if (geo->version > 64000  ||  geo->version < 0) {
  905.          printf("hd%d: bad default geometry version#.\n", dk->dk_unit);
  906.         return(1);
  907.     }
  908.      if (bcmp(&geo->id[0], GB_ID, GB_ID_LEN)) {
  909.          printf("hd%d: bad default geometry header.\n", dk->dk_unit);
  910.         return(1);
  911.     }
  912.     GB_CHECKSUM(geo, cnt);
  913.     if (geometry.checksum != cnt) {
  914.         printf("hd%d: bad default geometry checksum.\n", dk->dk_unit);
  915.         return(1);
  916.     }
  917.     lp = &dk->dk_label;
  918.  
  919.     /* 1K block in Harris geometry; convert to sectors for disklabels */
  920.     for (cnt = 0; cnt < GB_MAXPART; cnt++) {
  921.         lp->d_partitions[cnt].p_offset =
  922.             geo->partition[cnt].start * (1024 / lp->d_secsize);
  923.         lp->d_partitions[cnt].p_size =
  924.             geo->partition[cnt].length * (1024 / lp->d_secsize);
  925.     }
  926.     lp->d_npartitions = GB_MAXPART;
  927.     return(0);
  928. }
  929. #endif /* COMPAT_42 */
  930. #endif /* NHD */
  931.