133165Sbostic /* 237097Sbostic * Copyright (c) 1988 The Regents of the University of California. 337097Sbostic * All rights reserved. 433165Sbostic * 537097Sbostic * This code is derived from software contributed to Berkeley by 637097Sbostic * Harris Corp. 737097Sbostic * 8*44534Sbostic * %sccs.include.redist.c% 937097Sbostic * 10*44534Sbostic * @(#)hd.c 7.11 (Berkeley) 06/28/90 1133165Sbostic */ 1233165Sbostic 1337097Sbostic #include "hd.h" 1433165Sbostic 1537097Sbostic #if NHD > 0 1637097Sbostic #include "param.h" 1737097Sbostic #include "buf.h" 1837097Sbostic #include "conf.h" 1937097Sbostic #include "dkstat.h" 2037097Sbostic #include "disklabel.h" 2137097Sbostic #include "file.h" 2237097Sbostic #include "systm.h" 2337097Sbostic #include "vmmac.h" 2437097Sbostic #include "time.h" 2537097Sbostic #include "proc.h" 2637097Sbostic #include "uio.h" 2737097Sbostic #include "syslog.h" 2837097Sbostic #include "kernel.h" 2937097Sbostic #include "ioctl.h" 3037097Sbostic #include "stat.h" 3137097Sbostic #include "errno.h" 3237097Sbostic 3337097Sbostic #include "../tahoe/cpu.h" 3437097Sbostic #include "../tahoe/mtpr.h" 3537097Sbostic 3637097Sbostic #include "../tahoevba/vbavar.h" 3737097Sbostic #include "../tahoevba/hdreg.h" 3837097Sbostic 3937097Sbostic #define b_cylin b_resid 4037097Sbostic 4137097Sbostic #define hdunit(dev) (minor(dev)>>3) 4237097Sbostic #define hdpart(dev) (minor(dev)&0x07) 4337097Sbostic #define hdminor(unit, part) (((unit)<<3)|(part)) 4437097Sbostic 4537097Sbostic struct vba_ctlr *hdcminfo[NHDC]; 4637097Sbostic struct vba_device *hddinfo[NHD]; 4737097Sbostic int hdcprobe(), hdslave(), hdattach(), hddgo(), hdstrategy(); 4838743Sbostic long hdstd[] = { 0 }; 4937097Sbostic struct vba_driver hdcdriver = 5038743Sbostic { hdcprobe, hdslave, hdattach, hddgo, hdstd, "hd", hddinfo, "hdc", hdcminfo }; 5137097Sbostic 5233165Sbostic /* 5337097Sbostic * Per-controller state. 5433165Sbostic */ 5537097Sbostic struct hdcsoftc { 5637097Sbostic u_short hdc_flags; 5737097Sbostic #define HDC_INIT 0x01 /* controller initialized */ 5837097Sbostic #define HDC_STARTED 0x02 /* start command issued */ 5937097Sbostic #define HDC_LOCKED 0x04 /* locked for direct controller access */ 6037097Sbostic #define HDC_WAIT 0x08 /* someone needs direct controller access */ 6137097Sbostic u_short hdc_wticks; /* timeout */ 6237097Sbostic struct master_mcb *hdc_mcbp; /* address of controller mcb */ 6337097Sbostic struct registers *hdc_reg; /* base address of i/o regs */ 6437097Sbostic struct vb_buf hdc_rbuf; /* vba resources */ 6537097Sbostic struct master_mcb hdc_mcb; /* controller mcb */ 6637097Sbostic } hdcsoftc[NHDC]; 6733165Sbostic 6837097Sbostic #define HDCMAXTIME 20 /* max time for operation, sec. */ 6937097Sbostic #define HDCINTERRUPT 0xf0 /* interrupt vector */ 7033165Sbostic 7133165Sbostic /* 7237097Sbostic * Per-drive state; probably everything should be "hd_", not "dk_", 7337097Sbostic * but it's not worth it, and dk is a better mnemonic for disk anyway. 7433165Sbostic */ 7537097Sbostic struct dksoftc { 7637097Sbostic #ifdef COMPAT_42 7737097Sbostic u_short dk_def_cyl; /* definition track cylinder address */ 7837097Sbostic #endif 7937097Sbostic int dk_state; /* open fsm */ 8037097Sbostic u_short dk_bshift; /* shift for * (DEV_BSIZE / sectorsize) XXX */ 8137097Sbostic int dk_wlabel; /* if label sector is writeable */ 8237097Sbostic u_long dk_copenpart; /* character units open on this drive */ 8337097Sbostic u_long dk_bopenpart; /* block units open on this drive */ 8437097Sbostic u_long dk_openpart; /* all units open on this drive */ 8537097Sbostic int dk_unit; /* unit# */ 8637097Sbostic int dk_ctlr; /* controller# */ 8737097Sbostic int dk_format; /* if format program is using disk */ 8837097Sbostic struct buf dk_utab; /* i/o queue header */ 8937097Sbostic struct disklabel dk_label; /* disklabel for this disk */ 9037097Sbostic struct mcb dk_mcb; /* disk mcb */ 9137097Sbostic } dksoftc[NHD]; 9233165Sbostic 9333165Sbostic /* 9437097Sbostic * Drive states. Used during steps of open/initialization. 9537097Sbostic * States < OPEN (> 0) are transient, during an open operation. 9637097Sbostic * OPENRAW is used for unlabeled disks, to allow format operations. 9733165Sbostic */ 9837097Sbostic #define CLOSED 0 /* disk is closed */ 9937097Sbostic #define WANTOPEN 1 /* open requested, not started */ 10037097Sbostic #define WANTOPENRAW 2 /* open requested, no label */ 10137097Sbostic #define RDLABEL 3 /* reading pack label */ 10237097Sbostic #define OPEN 4 /* intialized and ready */ 10337097Sbostic #define OPENRAW 5 /* open, no label */ 10433165Sbostic 10537097Sbostic int hdcwstart, hdcwatch(); 10633165Sbostic 10737097Sbostic /* see if the controller is really there, if so, init it. */ 10837097Sbostic /* ARGSUSED */ 10937097Sbostic hdcprobe(reg, vm) 11037097Sbostic caddr_t reg; 11137097Sbostic /* register */ struct vba_ctlr *vm; 11233165Sbostic { 11337097Sbostic register int br, cvec; /* must be r12, r11 */ 11437097Sbostic register struct hdcsoftc *hdc; 11537097Sbostic static struct module_id id; 11637097Sbostic struct pte *dummypte; 11737097Sbostic caddr_t putl; 11833165Sbostic 11937097Sbostic /* initialize the hdc controller structure. */ 12037097Sbostic hdc = &hdcsoftc[vm->um_ctlr]; 12137097Sbostic if (!vbmemalloc(1, reg, &dummypte, &putl)) { 12237097Sbostic printf("hdc%d: vbmemalloc failed.\n", vm->um_ctlr); 12337097Sbostic return(0); 12433165Sbostic } 12537097Sbostic hdc->hdc_reg = (struct registers *)putl; 12633165Sbostic 12733165Sbostic /* 12837097Sbostic * try and ping the MID register; side effect of wbadaddr is to read 12937097Sbostic * the module id; the controller is bad if it's not an hdc, the hdc's 13037097Sbostic * writeable control store is not loaded, or the hdc failed the 13137097Sbostic * functional integrity test; 13233165Sbostic */ 13337097Sbostic if (wbadaddr(&hdc->hdc_reg->module_id, 4, 13438744Sbostic vtoph((struct process *)NULL, &id))) 13537097Sbostic return(0); 13637097Sbostic DELAY(10000); 13737097Sbostic mtpr(PADC, 0); 13837097Sbostic if (id.module_id != (u_char)HDC_MID) { 13937097Sbostic printf("hdc%d: bad module id; id = %x.\n", 14037097Sbostic vm->um_ctlr, id.module_id); 14137097Sbostic return(0); 14237097Sbostic } 14337097Sbostic if (id.code_rev == (u_char)0xff) { 14437097Sbostic printf("hdc%d: micro-code not loaded.\n", vm->um_ctlr); 14537097Sbostic return(0); 14637097Sbostic } 14737097Sbostic if (id.fit != (u_char)0xff) { 14837097Sbostic printf("hdc%d: FIT test failed.\n", vm->um_ctlr); 14937097Sbostic return(0); 15037097Sbostic } 15133165Sbostic 15237097Sbostic /* reset that pup; flag as inited */ 15337097Sbostic hdc->hdc_reg->soft_reset = 0; 15437097Sbostic DELAY(1000000); 15537097Sbostic hdc->hdc_flags |= HDC_INIT; 15633165Sbostic 15737097Sbostic /* allocate page tables and i/o buffer. */ 15837097Sbostic if (!vbainit(&hdc->hdc_rbuf, MAXPHYS, VB_32BIT|VB_SCATTER)) { 15937097Sbostic printf("hdc%d: vbainit failed\n", vm->um_ctlr); 16037097Sbostic return (0); 16137097Sbostic } 16233165Sbostic 16337097Sbostic /* set pointer to master control block */ 16437097Sbostic hdc->hdc_mcbp = 16537097Sbostic (struct master_mcb *)vtoph((struct proc *)NULL, &hdc->hdc_mcb); 16637097Sbostic 16737097Sbostic br = 0x17, cvec = HDCINTERRUPT + vm->um_ctlr; /* XXX */ 16837097Sbostic return(sizeof(struct registers)); 16933165Sbostic } 17033165Sbostic 17137097Sbostic /* ARGSUSED */ 17237097Sbostic hdslave(vi, vdaddr) 17337097Sbostic struct vba_device *vi; 17437097Sbostic struct vddevice *vdaddr; 17533165Sbostic { 17637097Sbostic register struct mcb *mcb; 17737097Sbostic register struct disklabel *lp; 17837097Sbostic register struct dksoftc *dk; 17937097Sbostic static struct status status; 18033165Sbostic 18137097Sbostic dk = &dksoftc[vi->ui_unit]; 18237097Sbostic dk->dk_unit = vi->ui_unit; 18337097Sbostic dk->dk_ctlr = vi->ui_ctlr; 18433165Sbostic 18537097Sbostic mcb = &dk->dk_mcb; 18637097Sbostic mcb->command = HCMD_STATUS; 18737097Sbostic mcb->chain[0].wcount = sizeof(struct status) / sizeof(long); 18837097Sbostic mcb->chain[0].memadr = (u_long)vtoph((struct process *)0, &status); 18937097Sbostic if (hdimcb(dk)) { 19037097Sbostic printf(" (no status)\n"); 19137097Sbostic return(0); 19233165Sbostic } 19333165Sbostic 19433165Sbostic /* 19537097Sbostic * Report the drive down if anything in the drive status looks bad. 19637097Sbostic * If the drive is offline and it is not on cylinder, then the drive 19737097Sbostic * is not there. If there is a fault condition, the hdc will try to 19837097Sbostic * clear it when we read the disklabel information. 19933165Sbostic */ 20037097Sbostic if (!(status.drs&DRS_ONLINE)) { 20137097Sbostic if (status.drs&DRS_ON_CYLINDER) 20237097Sbostic printf(" (not online)\n"); 20337097Sbostic return(0); 20433165Sbostic } 20537097Sbostic if (status.drs&DRS_FAULT) 20637097Sbostic printf(" (clearing fault)"); 20733165Sbostic 20837097Sbostic lp = &dk->dk_label; 20937097Sbostic #ifdef RAW_SIZE 21037097Sbostic lp->d_secsize = status.bytes_per_sec; 21137097Sbostic #else 21237097Sbostic lp->d_secsize = 512; 21337097Sbostic #endif 21437097Sbostic lp->d_nsectors = status.max_sector + 1; 21537097Sbostic lp->d_ntracks = status.max_head + 1; 21637097Sbostic lp->d_ncylinders = status.max_cyl + 1; 21737097Sbostic lp->d_secpercyl = lp->d_ntracks * lp->d_nsectors; 21837097Sbostic lp->d_npartitions = 1; 21937097Sbostic lp->d_partitions[0].p_offset = 0; 22037097Sbostic lp->d_partitions[0].p_size = LABELSECTOR + 1; 22137097Sbostic lp->d_rpm = status.rpm; 22237097Sbostic lp->d_typename[0] = 'h'; 22337097Sbostic lp->d_typename[1] = 'd'; 22437097Sbostic lp->d_typename[2] = '\0'; 22537097Sbostic #ifdef COMPAT_42 22637097Sbostic dk->dk_def_cyl = status.def_cyl; 22737097Sbostic #endif 22837097Sbostic return(1); 22933165Sbostic } 23033165Sbostic 23137097Sbostic hdattach(vi) 23237097Sbostic register struct vba_device *vi; 23333165Sbostic { 23437097Sbostic register struct dksoftc *dk; 23537097Sbostic register struct disklabel *lp; 23637097Sbostic register int unit; 23733165Sbostic 23837097Sbostic unit = vi->ui_unit; 23937097Sbostic if (hdinit(hdminor(unit, 0), 0)) { 24037097Sbostic printf(": unknown drive type"); 24137097Sbostic return; 24233165Sbostic } 24337097Sbostic dk = &dksoftc[unit]; 24437097Sbostic lp = &dk->dk_label; 24537097Sbostic hd_setsecsize(dk, lp); 24637097Sbostic if (dk->dk_state == OPEN) 24737097Sbostic printf(": %s <secsize %d, ntrak %d, ncyl %d, nsec %d>", 24837097Sbostic lp->d_typename, lp->d_secsize, lp->d_ntracks, 24937097Sbostic lp->d_ncylinders, lp->d_nsectors); 25033165Sbostic 25137097Sbostic /* 25237097Sbostic * (60 / rpm) / (sectors per track * (bytes per sector / 2)) 25337097Sbostic */ 25437097Sbostic if (vi->ui_dk >= 0) 25538169Smckusick dk_wpms[vi->ui_dk] = 25638169Smckusick (lp->d_rpm * lp->d_nsectors * lp->d_secsize) / 120; 25737097Sbostic #ifdef notyet 25837097Sbostic addswap(makedev(HDMAJOR, hdminor(unit, 0)), lp); 25937097Sbostic #endif 26037097Sbostic } 26133165Sbostic 26237097Sbostic hdopen(dev, flags, fmt) 26337097Sbostic dev_t dev; 26437097Sbostic int flags, fmt; 26533165Sbostic { 26637097Sbostic register struct disklabel *lp; 26737097Sbostic register struct dksoftc *dk; 26837097Sbostic register struct partition *pp; 26937097Sbostic register int unit; 27037097Sbostic struct vba_device *vi; 27137097Sbostic int s, error, part = hdpart(dev), mask = 1 << part; 27237097Sbostic daddr_t start, end; 27333165Sbostic 27437097Sbostic unit = hdunit(dev); 27537097Sbostic if (unit >= NHD || (vi = hddinfo[unit]) == 0 || vi->ui_alive == 0) 27637097Sbostic return(ENXIO); 27737097Sbostic dk = &dksoftc[unit]; 27837097Sbostic lp = &dk->dk_label; 27937097Sbostic s = spl7(); 28037097Sbostic while (dk->dk_state != OPEN && dk->dk_state != OPENRAW && 28137097Sbostic dk->dk_state != CLOSED) 28240734Skarels if (error = tsleep((caddr_t)dk, (PZERO+1) | PCATCH, 28340734Skarels devopn, 0)) { 28440734Skarels splx(s); 28540734Skarels return (error); 28640734Skarels } 28737097Sbostic splx(s); 28837097Sbostic if (dk->dk_state != OPEN && dk->dk_state != OPENRAW) 28937097Sbostic if (error = hdinit(dev, flags)) 29037097Sbostic return(error); 29133165Sbostic 29237097Sbostic if (hdcwstart == 0) { 29337097Sbostic timeout(hdcwatch, (caddr_t)0, hz); 29437097Sbostic hdcwstart++; 29537097Sbostic } 29633165Sbostic /* 29737097Sbostic * Warn if a partion is opened that overlaps another partition 29837097Sbostic * which is open unless one is the "raw" partition (whole disk). 29933165Sbostic */ 30037097Sbostic #define RAWPART 8 /* 'x' partition */ /* XXX */ 30137097Sbostic if ((dk->dk_openpart & mask) == 0 && part != RAWPART) { 30237097Sbostic pp = &lp->d_partitions[part]; 30337097Sbostic start = pp->p_offset; 30437097Sbostic end = pp->p_offset + pp->p_size; 30537097Sbostic for (pp = lp->d_partitions; 30637097Sbostic pp < &lp->d_partitions[lp->d_npartitions]; pp++) { 30737097Sbostic if (pp->p_offset + pp->p_size <= start || 30837097Sbostic pp->p_offset >= end) 30937097Sbostic continue; 31037097Sbostic if (pp - lp->d_partitions == RAWPART) 31137097Sbostic continue; 31237097Sbostic if (dk->dk_openpart & (1 << (pp - lp->d_partitions))) 31337097Sbostic log(LOG_WARNING, 31437097Sbostic "hd%d%c: overlaps open partition (%c)\n", 31537097Sbostic unit, part + 'a', 31637097Sbostic pp - lp->d_partitions + 'a'); 31737097Sbostic } 31837097Sbostic } 31937097Sbostic if (part >= lp->d_npartitions) 32037097Sbostic return(ENXIO); 32137097Sbostic dk->dk_openpart |= mask; 32237097Sbostic switch (fmt) { 32337097Sbostic case S_IFCHR: 32437097Sbostic dk->dk_copenpart |= mask; 32533165Sbostic break; 32637097Sbostic case S_IFBLK: 32737097Sbostic dk->dk_bopenpart |= mask; 32837097Sbostic break; 32933165Sbostic } 33037097Sbostic return(0); 33133165Sbostic } 33233165Sbostic 33337097Sbostic /* ARGSUSED */ 33437097Sbostic hdclose(dev, flags, fmt) 33537097Sbostic dev_t dev; 33637097Sbostic int flags, fmt; 33733165Sbostic { 33837097Sbostic register struct dksoftc *dk; 33937097Sbostic int mask; 34033165Sbostic 34137097Sbostic dk = &dksoftc[hdunit(dev)]; 34237097Sbostic mask = 1 << hdpart(dev); 34337097Sbostic switch (fmt) { 34437097Sbostic case S_IFCHR: 34537097Sbostic dk->dk_copenpart &= ~mask; 34637097Sbostic break; 34737097Sbostic case S_IFBLK: 34837097Sbostic dk->dk_bopenpart &= ~mask; 34937097Sbostic break; 35033165Sbostic } 35137097Sbostic if (((dk->dk_copenpart | dk->dk_bopenpart) & mask) == 0) 35237097Sbostic dk->dk_openpart &= ~mask; 35333165Sbostic /* 35437097Sbostic * Should wait for i/o to complete on this partition 35537097Sbostic * even if others are open, but wait for work on blkflush(). 35633165Sbostic */ 35737097Sbostic if (dk->dk_openpart == 0) { 35837097Sbostic int s = spl7(); 35937097Sbostic while (dk->dk_utab.b_actf) 36037097Sbostic sleep((caddr_t)dk, PZERO-1); 36137097Sbostic splx(s); 36237097Sbostic dk->dk_state = CLOSED; 36337097Sbostic dk->dk_wlabel = 0; 36433165Sbostic } 36537097Sbostic return(0); 36637097Sbostic } 36733165Sbostic 36837097Sbostic hdinit(dev, flags) 36937097Sbostic dev_t dev; 37037097Sbostic int flags; 37137097Sbostic { 37237097Sbostic register struct dksoftc *dk; 37337097Sbostic register struct disklabel *lp; 37437097Sbostic struct vba_device *vi; 37537097Sbostic int error, unit; 37637097Sbostic char *msg, *readdisklabel(); 37737097Sbostic extern int cold; 37833165Sbostic 37937097Sbostic vi = hddinfo[unit = hdunit(dev)]; 38037097Sbostic dk = &dksoftc[unit]; 38137097Sbostic dk->dk_unit = vi->ui_slave; 38237097Sbostic dk->dk_ctlr = vi->ui_ctlr; 38333165Sbostic 38437097Sbostic if (flags & O_NDELAY) { 38537097Sbostic dk->dk_state = OPENRAW; 38637097Sbostic return(0); 38737097Sbostic } 38833165Sbostic 38937097Sbostic error = 0; 39037097Sbostic lp = &dk->dk_label; 39137097Sbostic dk->dk_state = RDLABEL; 39237097Sbostic if (msg = readdisklabel(dev, hdstrategy, lp)) { 39337097Sbostic if (cold) { 39437097Sbostic printf(": %s\n", msg); 39537097Sbostic dk->dk_state = CLOSED; 39637097Sbostic } else { 39737097Sbostic log(LOG_ERR, "hd%d: %s\n", unit, msg); 39837097Sbostic dk->dk_state = OPENRAW; 39933165Sbostic } 40037097Sbostic #ifdef COMPAT_42 40137097Sbostic hdclock(vi->ui_ctlr); 40237097Sbostic if (!(error = hdreadgeometry(dk))) 40337097Sbostic dk->dk_state = OPEN; 40437097Sbostic hdcunlock(vi->ui_ctlr); 40537097Sbostic #endif 40637097Sbostic } else 40737097Sbostic dk->dk_state = OPEN; 40837097Sbostic wakeup((caddr_t)dk); 40937097Sbostic return(error); 41037097Sbostic } 41133165Sbostic 41237097Sbostic hd_setsecsize(dk, lp) 41337097Sbostic register struct dksoftc *dk; 41437097Sbostic struct disklabel *lp; 41537097Sbostic { 41637097Sbostic register int mul; 41737097Sbostic 41833165Sbostic /* 41937097Sbostic * Calculate scaling shift for mapping 42037097Sbostic * DEV_BSIZE blocks to drive sectors. 42133165Sbostic */ 42237097Sbostic mul = DEV_BSIZE / lp->d_secsize; 42337097Sbostic dk->dk_bshift = 0; 42437097Sbostic while ((mul >>= 1) > 0) 42537097Sbostic dk->dk_bshift++; 42637097Sbostic } 42733165Sbostic 42837097Sbostic /* ARGSUSED */ 42937097Sbostic hddgo(vm) 43037097Sbostic struct vba_device *vm; 43137097Sbostic {} 43233165Sbostic 43337097Sbostic extern int name_ext; 43437097Sbostic hdstrategy(bp) 43537097Sbostic register struct buf *bp; 43637097Sbostic { 43737097Sbostic register struct vba_device *vi; 43837097Sbostic register struct disklabel *lp; 43937097Sbostic register struct dksoftc *dk; 44037097Sbostic struct buf *dp; 44137097Sbostic register int unit; 44237097Sbostic daddr_t sn, sz, maxsz; 44337097Sbostic int part, s; 44433165Sbostic 44537097Sbostic vi = hddinfo[unit = hdunit(bp->b_dev)]; 44637097Sbostic if (unit >= NHD || vi == 0 || vi->ui_alive == 0) { 44737097Sbostic bp->b_error = ENXIO; 44837097Sbostic goto bad; 44937097Sbostic } 45037097Sbostic dk = &dksoftc[unit]; 45137097Sbostic if (dk->dk_state < OPEN) 45237097Sbostic goto q; 45337097Sbostic if (dk->dk_state != OPEN && (bp->b_flags & B_READ) == 0) { 45437097Sbostic bp->b_error = EROFS; 45537097Sbostic goto bad; 45637097Sbostic } 45737097Sbostic part = hdpart(bp->b_dev); 45837097Sbostic if ((dk->dk_openpart & (1 << part)) == 0) { 45937097Sbostic bp->b_error = ENODEV; 46037097Sbostic goto bad; 46137097Sbostic } 46237097Sbostic lp = &dk->dk_label; 46337097Sbostic sz = (bp->b_bcount + lp->d_secsize - 1) / lp->d_secsize; 46437097Sbostic maxsz = lp->d_partitions[part].p_size; 46537097Sbostic sn = bp->b_blkno << dk->dk_bshift; 46637097Sbostic if (sn + lp->d_partitions[part].p_offset <= LABELSECTOR && 46737097Sbostic #if LABELSECTOR != 0 46837097Sbostic sn + lp->d_partitions[part].p_offset + sz > LABELSECTOR && 46933165Sbostic #endif 47037097Sbostic (bp->b_flags & B_READ) == 0 && dk->dk_wlabel == 0) { 47137097Sbostic bp->b_error = EROFS; 47237097Sbostic goto bad; 47333165Sbostic } 47437097Sbostic if (sn < 0 || sn + sz > maxsz) { 47537097Sbostic if (sn == maxsz) { 47637097Sbostic bp->b_resid = bp->b_bcount; 47737097Sbostic goto done; 47837097Sbostic } 47937097Sbostic sz = maxsz - sn; 48037097Sbostic if (sz <= 0) { 48137097Sbostic bp->b_error = EINVAL; 48237097Sbostic goto bad; 48337097Sbostic } 48437097Sbostic bp->b_bcount = sz * lp->d_secsize; 48537097Sbostic } 48637097Sbostic bp->b_cylin = (sn + lp->d_partitions[part].p_offset) / lp->d_secpercyl; 48733165Sbostic 48837097Sbostic q: s = spl7(); 48937097Sbostic dp = &dk->dk_utab; 49037097Sbostic disksort(dp, bp); 49137097Sbostic if (!dp->b_active) { 49237097Sbostic (void)hdustart(vi); 49337097Sbostic if (!vi->ui_mi->um_tab.b_active) 49437097Sbostic hdcstart(vi->ui_mi); 49537097Sbostic } 49637097Sbostic splx(s); 49733165Sbostic return; 49837097Sbostic bad: 49937097Sbostic bp->b_flags |= B_ERROR; 50037097Sbostic done: 50137097Sbostic biodone(bp); 50233165Sbostic } 50333165Sbostic 50437097Sbostic hdustart(vi) 50537097Sbostic register struct vba_device *vi; 50633165Sbostic { 50737097Sbostic register struct buf *bp, *dp; 50837097Sbostic register struct vba_ctlr *vm; 50937097Sbostic register struct dksoftc *dk; 51033165Sbostic 51137097Sbostic dk = &dksoftc[vi->ui_unit]; 51237097Sbostic dp = &dk->dk_utab; 51333165Sbostic 51437097Sbostic /* if queue empty, nothing to do. impossible? */ 51537097Sbostic if (dp->b_actf == NULL) 51637097Sbostic return; 51733165Sbostic 51837097Sbostic /* place on controller transfer queue */ 51937097Sbostic vm = vi->ui_mi; 52037097Sbostic if (vm->um_tab.b_actf == NULL) 52137097Sbostic vm->um_tab.b_actf = dp; 52237097Sbostic else 52337097Sbostic vm->um_tab.b_actl->b_forw = dp; 52437097Sbostic vm->um_tab.b_actl = dp; 52537097Sbostic dp->b_forw = NULL; 52637097Sbostic dp->b_active++; 52737097Sbostic } 52833165Sbostic 52937097Sbostic hdcstart(vm) 53037097Sbostic register struct vba_ctlr *vm; 53137097Sbostic { 53237097Sbostic register struct buf *bp; 53337097Sbostic register struct dksoftc *dk; 53437097Sbostic register struct disklabel *lp; 53537097Sbostic register struct master_mcb *master; 53637097Sbostic register struct mcb *mcb; 53737097Sbostic struct vba_device *vi; 53837097Sbostic struct hdcsoftc *hdc; 53937097Sbostic struct buf *dp; 54037097Sbostic int sn; 54133165Sbostic 54237097Sbostic /* pull a request off the controller queue */ 54337097Sbostic for (;;) { 54437097Sbostic if ((dp = vm->um_tab.b_actf) == NULL) 54537097Sbostic return; 54637097Sbostic if (bp = dp->b_actf) 54737097Sbostic break; 54837097Sbostic vm->um_tab.b_actf = dp->b_forw; 54933165Sbostic } 55033165Sbostic 55137097Sbostic /* mark controller active */ 55237097Sbostic vm->um_tab.b_active++; 55333165Sbostic 55437097Sbostic vi = hddinfo[hdunit(bp->b_dev)]; 55537097Sbostic dk = &dksoftc[vi->ui_unit]; 55637097Sbostic lp = &dk->dk_label; 55737097Sbostic sn = bp->b_blkno << dk->dk_bshift; 55833165Sbostic 55937097Sbostic /* fill in mcb */ 56037097Sbostic mcb = &dk->dk_mcb; 56137097Sbostic mcb->forw_phaddr = 0; 56237097Sbostic /* mcb->priority = 0; */ 56337097Sbostic mcb->interrupt = 1; 56437097Sbostic mcb->command = (bp->b_flags & B_READ) ? HCMD_READ:HCMD_WRITE; 56537565Sbostic mcb->cyl = bp->b_cylin; 56637565Sbostic /* assumes partition starts on cylinder boundary */ 56737097Sbostic mcb->head = (sn / lp->d_nsectors) % lp->d_ntracks; 56837097Sbostic mcb->sector = sn % lp->d_nsectors; 56937097Sbostic mcb->drive = vi->ui_slave; 57037097Sbostic /* mcb->context = 0; /* what do we want on interrupt? */ 57133165Sbostic 57237097Sbostic hdc = &hdcsoftc[vm->um_ctlr]; 57338576Sbostic if (!hd_sgsetup(bp, &hdc->hdc_rbuf, mcb->chain)) { 57437097Sbostic mcb->chain[0].wcount = (bp->b_bcount+3) >> 2; 57537097Sbostic mcb->chain[0].memadr = 57637097Sbostic vbasetup(bp, &hdc->hdc_rbuf, (int)lp->d_secsize); 57733165Sbostic } 57833165Sbostic 57937097Sbostic if (vi->ui_dk >= 0) { 58037097Sbostic dk_busy |= 1<<vi->ui_dk; 58137097Sbostic dk_xfer[vi->ui_dk]++; 58237097Sbostic dk_wds[vi->ui_dk] += bp->b_bcount>>6; 58337097Sbostic } 58433165Sbostic 58537097Sbostic master = &hdc->hdc_mcb; 58637097Sbostic master->mcw = MCL_QUEUED; 58737097Sbostic master->interrupt = HDCINTERRUPT + vm->um_ctlr; 58837097Sbostic master->forw_phaddr = (u_long)vtoph((struct proc *)NULL, mcb); 58937097Sbostic hdc->hdc_reg->master_mcb = (u_long)hdc->hdc_mcbp; 59037097Sbostic } 59133165Sbostic 59237097Sbostic /* 59337097Sbostic * Wait for controller to finish current operation 59437097Sbostic * so that direct controller accesses can be done. 59537097Sbostic */ 59637097Sbostic hdclock(ctlr) 59737097Sbostic int ctlr; 59837097Sbostic { 59937097Sbostic register struct vba_ctlr *vm = hdcminfo[ctlr]; 60037097Sbostic register struct hdcsoftc *hdc; 60137097Sbostic int s; 60233165Sbostic 60337097Sbostic hdc = &hdcsoftc[ctlr]; 60437097Sbostic s = spl7(); 60537097Sbostic while (vm->um_tab.b_active || hdc->hdc_flags & HDC_LOCKED) { 60637097Sbostic hdc->hdc_flags |= HDC_WAIT; 60737097Sbostic sleep((caddr_t)hdc, PRIBIO); 60833165Sbostic } 60937097Sbostic hdc->hdc_flags |= HDC_LOCKED; 61037097Sbostic splx(s); 61137097Sbostic } 61233165Sbostic 61337097Sbostic /* 61437097Sbostic * Continue normal operations after pausing for 61537097Sbostic * munging the controller directly. 61637097Sbostic */ 61737097Sbostic hdcunlock(ctlr) 61837097Sbostic int ctlr; 61937097Sbostic { 62037097Sbostic register struct vba_ctlr *vm; 62137097Sbostic register struct hdcsoftc *hdc = &hdcsoftc[ctlr]; 62233165Sbostic 62337097Sbostic hdc->hdc_flags &= ~HDC_LOCKED; 62437097Sbostic if (hdc->hdc_flags & HDC_WAIT) { 62537097Sbostic hdc->hdc_flags &= ~HDC_WAIT; 62637097Sbostic wakeup((caddr_t)hdc); 62737097Sbostic } else { 62837097Sbostic vm = hdcminfo[ctlr]; 62937097Sbostic if (vm->um_tab.b_actf) 63037097Sbostic hdcstart(vm); 63133165Sbostic } 63237097Sbostic } 63333165Sbostic 63437097Sbostic hdintr(ctlr) 63537097Sbostic int ctlr; 63637097Sbostic { 63737097Sbostic register struct buf *bp, *dp; 63837097Sbostic register struct vba_ctlr *vm; 63937097Sbostic register struct vba_device *vi; 64037097Sbostic register struct hdcsoftc *hdc; 64137097Sbostic register struct mcb *mcb; 64237097Sbostic struct master_mcb *master; 64337097Sbostic register int status; 64437097Sbostic int timedout; 64537097Sbostic struct dksoftc *dk; 64633165Sbostic 64737097Sbostic hdc = &hdcsoftc[ctlr]; 64837097Sbostic master = &hdc->hdc_mcb; 64937097Sbostic uncache(&master->mcs); 65037097Sbostic uncache(&master->context); 65133165Sbostic 65237097Sbostic vm = hdcminfo[ctlr]; 65337097Sbostic if (!vm->um_tab.b_active || !(master->mcs&MCS_DONE)) { 65437097Sbostic printf("hd%d: stray interrupt\n", ctlr); 65537097Sbostic return; 65633165Sbostic } 65733165Sbostic 65837097Sbostic dp = vm->um_tab.b_actf; 65937097Sbostic bp = dp->b_actf; 66037097Sbostic vi = hddinfo[hdunit(bp->b_dev)]; 66137097Sbostic dk = &dksoftc[vi->ui_unit]; 66237097Sbostic if (vi->ui_dk >= 0) 66337097Sbostic dk_busy &= ~(1<<vi->ui_dk); 66437097Sbostic timedout = (hdc->hdc_wticks >= HDCMAXTIME); 66533165Sbostic 66637097Sbostic mcb = &dk->dk_mcb; 66733165Sbostic 66837097Sbostic if (master->mcs & (MCS_SOFTERROR | MCS_FATALERROR) || timedout) 66937097Sbostic hdcerror(ctlr, *(u_long *)master->xstatus); 67037565Sbostic else 67137097Sbostic hdc->hdc_wticks = 0; 67237565Sbostic if (vm->um_tab.b_active) { 67337565Sbostic vm->um_tab.b_active = 0; 67437565Sbostic vm->um_tab.b_actf = dp->b_forw; 67537565Sbostic dp->b_active = 0; 67637565Sbostic dp->b_errcnt = 0; 67737565Sbostic dp->b_actf = bp->av_forw; 67837565Sbostic bp->b_resid = 0; 67937565Sbostic vbadone(bp, &hdc->hdc_rbuf); 68037565Sbostic biodone(bp); 68137565Sbostic /* start up now, if more work to do */ 68237565Sbostic if (dp->b_actf) 68337565Sbostic hdustart(vi); 68437565Sbostic else if (dk->dk_openpart == 0) 68537565Sbostic wakeup((caddr_t)dk); 68633165Sbostic } 68737097Sbostic /* if there are devices ready to transfer, start the controller. */ 68837097Sbostic if (hdc->hdc_flags & HDC_WAIT) { 68937097Sbostic hdc->hdc_flags &= ~HDC_WAIT; 69037097Sbostic wakeup((caddr_t)hdc); 69137097Sbostic } else if (vm->um_tab.b_actf) 69237097Sbostic hdcstart(vm); 69337097Sbostic } 69433165Sbostic 69537565Sbostic hdioctl(dev, cmd, data, flag) 69637097Sbostic dev_t dev; 69737565Sbostic int cmd, flag; 69837097Sbostic caddr_t data; 69937097Sbostic { 70037565Sbostic register int unit; 70137565Sbostic register struct dksoftc *dk; 70237565Sbostic register struct disklabel *lp; 70337097Sbostic int error; 70433165Sbostic 70537565Sbostic unit = hdunit(dev); 70637565Sbostic dk = &dksoftc[unit]; 70737565Sbostic lp = &dk->dk_label; 70837565Sbostic error = 0; 70937565Sbostic switch (cmd) { 71037565Sbostic case DIOCGDINFO: 71137565Sbostic *(struct disklabel *)data = *lp; 71237565Sbostic break; 71337565Sbostic case DIOCGPART: 71437565Sbostic ((struct partinfo *)data)->disklab = lp; 71537565Sbostic ((struct partinfo *)data)->part = 71637565Sbostic &lp->d_partitions[hdpart(dev)]; 71737565Sbostic break; 71837565Sbostic case DIOCSDINFO: 71937565Sbostic if ((flag & FWRITE) == 0) 72037565Sbostic error = EBADF; 72137565Sbostic else 72237565Sbostic error = setdisklabel(lp, (struct disklabel *)data, 72337565Sbostic (dk->dk_state == OPENRAW) ? 0 : dk->dk_openpart); 72437565Sbostic if (error == 0 && dk->dk_state == OPENRAW) 72537565Sbostic dk->dk_state = OPEN; 72637565Sbostic break; 72737565Sbostic case DIOCWLABEL: 72837565Sbostic if ((flag & FWRITE) == 0) 72937565Sbostic error = EBADF; 73037565Sbostic else 73137565Sbostic dk->dk_wlabel = *(int *)data; 73237565Sbostic break; 73337565Sbostic case DIOCWDINFO: 73437565Sbostic if ((flag & FWRITE) == 0) 73537565Sbostic error = EBADF; 73637565Sbostic else if ((error = setdisklabel(lp, (struct disklabel *)data, 73737565Sbostic (dk->dk_state == OPENRAW) ? 0 : dk->dk_openpart)) == 0) { 73837565Sbostic int wlab; 73933165Sbostic 74037565Sbostic if (error == 0 && dk->dk_state == OPENRAW) 74137565Sbostic dk->dk_state = OPEN; 74237565Sbostic /* simulate opening partition 0 so write succeeds */ 74337565Sbostic dk->dk_openpart |= (1 << 0); /* XXX */ 74437565Sbostic wlab = dk->dk_wlabel; 74537565Sbostic dk->dk_wlabel = 1; 74637565Sbostic error = writedisklabel(dev, hdstrategy, lp); 74737565Sbostic dk->dk_openpart = dk->dk_copenpart | dk->dk_bopenpart; 74837565Sbostic dk->dk_wlabel = wlab; 74937565Sbostic } 75037565Sbostic break; 75137097Sbostic default: 75237097Sbostic error = ENOTTY; 75333165Sbostic break; 75433165Sbostic } 75537565Sbostic return (error); 75637097Sbostic } 75733165Sbostic 75837097Sbostic /* 75937097Sbostic * Watch for lost interrupts. 76037097Sbostic */ 76137097Sbostic hdcwatch() 76237097Sbostic { 76337097Sbostic register struct hdcsoftc *hdc; 76437097Sbostic register struct vba_ctlr **vmp; 76537097Sbostic register int ctlr; 76637097Sbostic int s; 76733165Sbostic 76837097Sbostic timeout(hdcwatch, (caddr_t)0, hz); 76937097Sbostic for (vmp = hdcminfo, hdc = hdcsoftc, ctlr = 0; ctlr < NHDC; 77037097Sbostic ++ctlr, ++vmp, ++hdc) { 77137097Sbostic if (*vmp == 0 || (*vmp)->um_alive == 0) 77237097Sbostic continue; 77337097Sbostic s = spl7(); 77437097Sbostic if ((*vmp)->um_tab.b_active && 77537097Sbostic hdc->hdc_wticks++ >= HDCMAXTIME) { 77637097Sbostic printf("hd%d: lost interrupt\n", ctlr); 77737097Sbostic hdintr(ctlr); 77833165Sbostic } 77937097Sbostic splx(s); 78033165Sbostic } 78133165Sbostic } 78233165Sbostic 78337097Sbostic hddump(dev) 78437097Sbostic dev_t dev; 78533165Sbostic { 78637097Sbostic return(ENXIO); 78733165Sbostic } 78833165Sbostic 78937097Sbostic hdsize(dev) 79037097Sbostic dev_t dev; 79133165Sbostic { 79237097Sbostic register int unit = hdunit(dev); 79337097Sbostic register struct dksoftc *dk; 79437097Sbostic struct vba_device *vi; 79537097Sbostic struct disklabel *lp; 79633165Sbostic 79737097Sbostic if (unit >= NHD || (vi = hddinfo[unit]) == 0 || vi->ui_alive == 0 || 79837097Sbostic (dk = &dksoftc[unit])->dk_state != OPEN) 79937097Sbostic return (-1); 80037097Sbostic lp = &dk->dk_label; 80137097Sbostic return ((int)lp->d_partitions[hdpart(dev)].p_size >> dk->dk_bshift); 80233165Sbostic } 80333165Sbostic 80437097Sbostic hdimcb(dk) 80537097Sbostic register struct dksoftc *dk; 80633165Sbostic { 80737097Sbostic register struct master_mcb *master; 80837097Sbostic register struct mcb *mcb; 80937097Sbostic register struct hdcsoftc *hdc; 81037097Sbostic int timeout; 81133165Sbostic 81237097Sbostic /* fill in mcb */ 81337097Sbostic mcb = &dk->dk_mcb; 81437097Sbostic mcb->interrupt = 0; 81537097Sbostic mcb->forw_phaddr = 0; 81637097Sbostic mcb->drive = dk->dk_unit; 81733165Sbostic 81837097Sbostic hdc = &hdcsoftc[dk->dk_ctlr]; 81937097Sbostic master = &hdc->hdc_mcb; 82033165Sbostic 82137097Sbostic /* fill in master mcb */ 82237097Sbostic master->mcw = MCL_IMMEDIATE; 82337097Sbostic master->forw_phaddr = (u_long)vtoph((struct proc *)NULL, mcb); 82437097Sbostic master->mcs = 0; 82533165Sbostic 82637097Sbostic /* kick controller and wait */ 82737097Sbostic hdc->hdc_reg->master_mcb = (u_long)hdc->hdc_mcbp; 82837097Sbostic for (timeout = 15000; timeout; --timeout) { 82937097Sbostic DELAY(1000); 83037097Sbostic mtpr(PADC, 0); 83137097Sbostic if (master->mcs&MCS_FATALERROR) { 83237097Sbostic printf("hdc%d: fatal error\n", dk->dk_ctlr); 83337097Sbostic hdcerror(dk->dk_ctlr, *(u_long *)master->xstatus); 83437097Sbostic return(1); 83537097Sbostic } 83637097Sbostic if (master->mcs&MCS_DONE) 83737097Sbostic return(0); 83833165Sbostic } 83937097Sbostic printf("hdc%d: timed out\n", dk->dk_ctlr); 84037097Sbostic return(1); 84133165Sbostic } 84233165Sbostic 84337097Sbostic hdcerror(ctlr, code) 84437097Sbostic int ctlr; 84537097Sbostic u_long code; 84633165Sbostic { 84737565Sbostic printf("hd%d: error %lx\n", ctlr, code); 84833165Sbostic } 84933165Sbostic 85037097Sbostic #ifdef COMPAT_42 85137097Sbostic hdreadgeometry(dk) 85237097Sbostic struct dksoftc *dk; 85333165Sbostic { 85437097Sbostic static geometry_sector geometry; 85537097Sbostic register struct mcb *mcb; 85637097Sbostic register struct disklabel *lp; 85737097Sbostic geometry_block *geo; 85837097Sbostic int cnt; 85933165Sbostic 86033165Sbostic /* 86137097Sbostic * Read the geometry block (at head = 0 sector = 0 of the drive 86237097Sbostic * definition cylinder), validate it (must have the correct version 86337097Sbostic * number, header, and checksum). 86433165Sbostic */ 86537097Sbostic mcb = &dk->dk_mcb; 86637097Sbostic mcb->command = HCMD_READ; 86737097Sbostic mcb->cyl = dk->dk_def_cyl; 86837097Sbostic mcb->head = 0; 86937097Sbostic mcb->sector = 0; 87037097Sbostic mcb->chain[0].wcount = sizeof(geometry_sector) / sizeof(long); 87137097Sbostic mcb->chain[0].memadr = (u_long)vtoph((struct process *)0, &geometry); 87237097Sbostic /* mcb->chain[0].memadr = (long)&geometry; */ 87337097Sbostic if (hdimcb(dk)) { 87437097Sbostic printf("hd%d: can't read default geometry.\n", dk->dk_unit); 87537097Sbostic return(1); 87633165Sbostic } 87737097Sbostic geo = &geometry.geometry_block; 87837097Sbostic if (geo->version > 64000 || geo->version < 0) { 87937097Sbostic printf("hd%d: bad default geometry version#.\n", dk->dk_unit); 88037097Sbostic return(1); 88133165Sbostic } 88237097Sbostic if (bcmp(&geo->id[0], GB_ID, GB_ID_LEN)) { 88337097Sbostic printf("hd%d: bad default geometry header.\n", dk->dk_unit); 88437097Sbostic return(1); 88533165Sbostic } 88637097Sbostic GB_CHECKSUM(geo, cnt); 88737097Sbostic if (geometry.checksum != cnt) { 88837097Sbostic printf("hd%d: bad default geometry checksum.\n", dk->dk_unit); 88937097Sbostic return(1); 89033165Sbostic } 89137097Sbostic lp = &dk->dk_label; 89237565Sbostic 89337097Sbostic /* 1K block in Harris geometry; convert to sectors for disklabels */ 89437097Sbostic for (cnt = 0; cnt < GB_MAXPART; cnt++) { 89537097Sbostic lp->d_partitions[cnt].p_offset = 89637097Sbostic geo->partition[cnt].start * (1024 / lp->d_secsize); 89737097Sbostic lp->d_partitions[cnt].p_size = 89837097Sbostic geo->partition[cnt].length * (1024 / lp->d_secsize); 89933165Sbostic } 90037097Sbostic lp->d_npartitions = GB_MAXPART; 90137097Sbostic return(0); 90233165Sbostic } 90337097Sbostic #endif /* COMPAT_42 */ 90437097Sbostic #endif /* NHD */ 905