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 * 837097Sbostic * Redistribution and use in source and binary forms are permitted 937097Sbostic * provided that the above copyright notice and this paragraph are 1037097Sbostic * duplicated in all such forms and that any documentation, 1137097Sbostic * advertising materials, and other materials related to such 1237097Sbostic * distribution and use acknowledge that the software was developed 1337097Sbostic * by the University of California, Berkeley. The name of the 1437097Sbostic * University may not be used to endorse or promote products derived 1537097Sbostic * from this software without specific prior written permission. 1637097Sbostic * THIS SOFTWARE IS PROVIDED ``AS IS'' AND WITHOUT ANY EXPRESS OR 1737097Sbostic * IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED 1837565Sbostic * WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. 1937097Sbostic * 20*38743Sbostic * @(#)hd.c 7.7 (Berkeley) 08/23/89 2133165Sbostic */ 2233165Sbostic 2337097Sbostic #include "hd.h" 2433165Sbostic 2537097Sbostic #if NHD > 0 2637097Sbostic #include "param.h" 2737097Sbostic #include "buf.h" 2837097Sbostic #include "conf.h" 2937097Sbostic #include "dir.h" 3037097Sbostic #include "dkstat.h" 3137097Sbostic #include "disklabel.h" 3237097Sbostic #include "file.h" 3337097Sbostic #include "systm.h" 3437097Sbostic #include "vmmac.h" 3537097Sbostic #include "time.h" 3637097Sbostic #include "proc.h" 3737097Sbostic #include "uio.h" 3837097Sbostic #include "syslog.h" 3937097Sbostic #include "kernel.h" 4037097Sbostic #include "ioctl.h" 4137097Sbostic #include "stat.h" 4237097Sbostic #include "errno.h" 4337097Sbostic 4437097Sbostic #include "../tahoe/cpu.h" 4537097Sbostic #include "../tahoe/mtpr.h" 4637097Sbostic 4737097Sbostic #include "../tahoevba/vbavar.h" 4837097Sbostic #include "../tahoevba/hdreg.h" 4937097Sbostic 5037097Sbostic #define b_cylin b_resid 5137097Sbostic 5237097Sbostic #define hdunit(dev) (minor(dev)>>3) 5337097Sbostic #define hdpart(dev) (minor(dev)&0x07) 5437097Sbostic #define hdminor(unit, part) (((unit)<<3)|(part)) 5537097Sbostic 5637097Sbostic struct vba_ctlr *hdcminfo[NHDC]; 5737097Sbostic struct vba_device *hddinfo[NHD]; 5837097Sbostic int hdcprobe(), hdslave(), hdattach(), hddgo(), hdstrategy(); 59*38743Sbostic long hdstd[] = { 0 }; 6037097Sbostic struct vba_driver hdcdriver = 61*38743Sbostic { hdcprobe, hdslave, hdattach, hddgo, hdstd, "hd", hddinfo, "hdc", hdcminfo }; 6237097Sbostic 6333165Sbostic /* 6437097Sbostic * Per-controller state. 6533165Sbostic */ 6637097Sbostic struct hdcsoftc { 6737097Sbostic u_short hdc_flags; 6837097Sbostic #define HDC_INIT 0x01 /* controller initialized */ 6937097Sbostic #define HDC_STARTED 0x02 /* start command issued */ 7037097Sbostic #define HDC_LOCKED 0x04 /* locked for direct controller access */ 7137097Sbostic #define HDC_WAIT 0x08 /* someone needs direct controller access */ 7237097Sbostic u_short hdc_wticks; /* timeout */ 7337097Sbostic struct master_mcb *hdc_mcbp; /* address of controller mcb */ 7437097Sbostic struct registers *hdc_reg; /* base address of i/o regs */ 7537097Sbostic struct vb_buf hdc_rbuf; /* vba resources */ 7637097Sbostic struct master_mcb hdc_mcb; /* controller mcb */ 7737097Sbostic } hdcsoftc[NHDC]; 7833165Sbostic 7937097Sbostic #define HDCMAXTIME 20 /* max time for operation, sec. */ 8037097Sbostic #define HDCINTERRUPT 0xf0 /* interrupt vector */ 8133165Sbostic 8233165Sbostic /* 8337097Sbostic * Per-drive state; probably everything should be "hd_", not "dk_", 8437097Sbostic * but it's not worth it, and dk is a better mnemonic for disk anyway. 8533165Sbostic */ 8637097Sbostic struct dksoftc { 8737097Sbostic #ifdef COMPAT_42 8837097Sbostic u_short dk_def_cyl; /* definition track cylinder address */ 8937097Sbostic #endif 9037097Sbostic int dk_state; /* open fsm */ 9137097Sbostic u_short dk_bshift; /* shift for * (DEV_BSIZE / sectorsize) XXX */ 9237097Sbostic int dk_wlabel; /* if label sector is writeable */ 9337097Sbostic u_long dk_copenpart; /* character units open on this drive */ 9437097Sbostic u_long dk_bopenpart; /* block units open on this drive */ 9537097Sbostic u_long dk_openpart; /* all units open on this drive */ 9637097Sbostic int dk_unit; /* unit# */ 9737097Sbostic int dk_ctlr; /* controller# */ 9837097Sbostic int dk_format; /* if format program is using disk */ 9937097Sbostic struct buf dk_utab; /* i/o queue header */ 10037097Sbostic struct disklabel dk_label; /* disklabel for this disk */ 10137097Sbostic struct mcb dk_mcb; /* disk mcb */ 10237097Sbostic } dksoftc[NHD]; 10333165Sbostic 10433165Sbostic /* 10537097Sbostic * Drive states. Used during steps of open/initialization. 10637097Sbostic * States < OPEN (> 0) are transient, during an open operation. 10737097Sbostic * OPENRAW is used for unlabeled disks, to allow format operations. 10833165Sbostic */ 10937097Sbostic #define CLOSED 0 /* disk is closed */ 11037097Sbostic #define WANTOPEN 1 /* open requested, not started */ 11137097Sbostic #define WANTOPENRAW 2 /* open requested, no label */ 11237097Sbostic #define RDLABEL 3 /* reading pack label */ 11337097Sbostic #define OPEN 4 /* intialized and ready */ 11437097Sbostic #define OPENRAW 5 /* open, no label */ 11533165Sbostic 11637097Sbostic int hdcwstart, hdcwatch(); 11733165Sbostic 11837097Sbostic /* see if the controller is really there, if so, init it. */ 11937097Sbostic /* ARGSUSED */ 12037097Sbostic hdcprobe(reg, vm) 12137097Sbostic caddr_t reg; 12237097Sbostic /* register */ struct vba_ctlr *vm; 12333165Sbostic { 12437097Sbostic register int br, cvec; /* must be r12, r11 */ 12537097Sbostic register struct hdcsoftc *hdc; 12637097Sbostic static struct module_id id; 12737097Sbostic struct pte *dummypte; 12837097Sbostic caddr_t putl; 12933165Sbostic 13037097Sbostic /* initialize the hdc controller structure. */ 13137097Sbostic hdc = &hdcsoftc[vm->um_ctlr]; 13237097Sbostic if (!vbmemalloc(1, reg, &dummypte, &putl)) { 13337097Sbostic printf("hdc%d: vbmemalloc failed.\n", vm->um_ctlr); 13437097Sbostic return(0); 13533165Sbostic } 13637097Sbostic hdc->hdc_reg = (struct registers *)putl; 13733165Sbostic 13833165Sbostic /* 13937097Sbostic * try and ping the MID register; side effect of wbadaddr is to read 14037097Sbostic * the module id; the controller is bad if it's not an hdc, the hdc's 14137097Sbostic * writeable control store is not loaded, or the hdc failed the 14237097Sbostic * functional integrity test; 14333165Sbostic */ 14437097Sbostic if (wbadaddr(&hdc->hdc_reg->module_id, 4, 14537097Sbostic vtoph((struct process *)NULL, &id))) { 14637097Sbostic printf("hdc%d: can't access module register.\n", vm->um_ctlr); 14737097Sbostic return(0); 14837097Sbostic } 14937097Sbostic DELAY(10000); 15037097Sbostic mtpr(PADC, 0); 15137097Sbostic if (id.module_id != (u_char)HDC_MID) { 15237097Sbostic printf("hdc%d: bad module id; id = %x.\n", 15337097Sbostic vm->um_ctlr, id.module_id); 15437097Sbostic return(0); 15537097Sbostic } 15637097Sbostic if (id.code_rev == (u_char)0xff) { 15737097Sbostic printf("hdc%d: micro-code not loaded.\n", vm->um_ctlr); 15837097Sbostic return(0); 15937097Sbostic } 16037097Sbostic if (id.fit != (u_char)0xff) { 16137097Sbostic printf("hdc%d: FIT test failed.\n", vm->um_ctlr); 16237097Sbostic return(0); 16337097Sbostic } 16433165Sbostic 16537097Sbostic /* reset that pup; flag as inited */ 16637097Sbostic hdc->hdc_reg->soft_reset = 0; 16737097Sbostic DELAY(1000000); 16837097Sbostic hdc->hdc_flags |= HDC_INIT; 16933165Sbostic 17037097Sbostic /* allocate page tables and i/o buffer. */ 17137097Sbostic if (!vbainit(&hdc->hdc_rbuf, MAXPHYS, VB_32BIT|VB_SCATTER)) { 17237097Sbostic printf("hdc%d: vbainit failed\n", vm->um_ctlr); 17337097Sbostic return (0); 17437097Sbostic } 17533165Sbostic 17637097Sbostic /* set pointer to master control block */ 17737097Sbostic hdc->hdc_mcbp = 17837097Sbostic (struct master_mcb *)vtoph((struct proc *)NULL, &hdc->hdc_mcb); 17937097Sbostic 18037097Sbostic br = 0x17, cvec = HDCINTERRUPT + vm->um_ctlr; /* XXX */ 18137097Sbostic return(sizeof(struct registers)); 18233165Sbostic } 18333165Sbostic 18437097Sbostic /* ARGSUSED */ 18537097Sbostic hdslave(vi, vdaddr) 18637097Sbostic struct vba_device *vi; 18737097Sbostic struct vddevice *vdaddr; 18833165Sbostic { 18937097Sbostic register struct mcb *mcb; 19037097Sbostic register struct disklabel *lp; 19137097Sbostic register struct dksoftc *dk; 19237097Sbostic static struct status status; 19333165Sbostic 19437097Sbostic dk = &dksoftc[vi->ui_unit]; 19537097Sbostic dk->dk_unit = vi->ui_unit; 19637097Sbostic dk->dk_ctlr = vi->ui_ctlr; 19733165Sbostic 19837097Sbostic mcb = &dk->dk_mcb; 19937097Sbostic mcb->command = HCMD_STATUS; 20037097Sbostic mcb->chain[0].wcount = sizeof(struct status) / sizeof(long); 20137097Sbostic mcb->chain[0].memadr = (u_long)vtoph((struct process *)0, &status); 20237097Sbostic if (hdimcb(dk)) { 20337097Sbostic printf(" (no status)\n"); 20437097Sbostic return(0); 20533165Sbostic } 20633165Sbostic 20733165Sbostic /* 20837097Sbostic * Report the drive down if anything in the drive status looks bad. 20937097Sbostic * If the drive is offline and it is not on cylinder, then the drive 21037097Sbostic * is not there. If there is a fault condition, the hdc will try to 21137097Sbostic * clear it when we read the disklabel information. 21233165Sbostic */ 21337097Sbostic if (!(status.drs&DRS_ONLINE)) { 21437097Sbostic if (status.drs&DRS_ON_CYLINDER) 21537097Sbostic printf(" (not online)\n"); 21637097Sbostic return(0); 21733165Sbostic } 21837097Sbostic if (status.drs&DRS_FAULT) 21937097Sbostic printf(" (clearing fault)"); 22033165Sbostic 22137097Sbostic lp = &dk->dk_label; 22237097Sbostic #ifdef RAW_SIZE 22337097Sbostic lp->d_secsize = status.bytes_per_sec; 22437097Sbostic #else 22537097Sbostic lp->d_secsize = 512; 22637097Sbostic #endif 22737097Sbostic lp->d_nsectors = status.max_sector + 1; 22837097Sbostic lp->d_ntracks = status.max_head + 1; 22937097Sbostic lp->d_ncylinders = status.max_cyl + 1; 23037097Sbostic lp->d_secpercyl = lp->d_ntracks * lp->d_nsectors; 23137097Sbostic lp->d_npartitions = 1; 23237097Sbostic lp->d_partitions[0].p_offset = 0; 23337097Sbostic lp->d_partitions[0].p_size = LABELSECTOR + 1; 23437097Sbostic lp->d_rpm = status.rpm; 23537097Sbostic lp->d_typename[0] = 'h'; 23637097Sbostic lp->d_typename[1] = 'd'; 23737097Sbostic lp->d_typename[2] = '\0'; 23837097Sbostic #ifdef COMPAT_42 23937097Sbostic dk->dk_def_cyl = status.def_cyl; 24037097Sbostic #endif 24137097Sbostic return(1); 24233165Sbostic } 24333165Sbostic 24437097Sbostic hdattach(vi) 24537097Sbostic register struct vba_device *vi; 24633165Sbostic { 24737097Sbostic register struct dksoftc *dk; 24837097Sbostic register struct disklabel *lp; 24937097Sbostic register int unit; 25033165Sbostic 25137097Sbostic unit = vi->ui_unit; 25237097Sbostic if (hdinit(hdminor(unit, 0), 0)) { 25337097Sbostic printf(": unknown drive type"); 25437097Sbostic return; 25533165Sbostic } 25637097Sbostic dk = &dksoftc[unit]; 25737097Sbostic lp = &dk->dk_label; 25837097Sbostic hd_setsecsize(dk, lp); 25937097Sbostic if (dk->dk_state == OPEN) 26037097Sbostic printf(": %s <secsize %d, ntrak %d, ncyl %d, nsec %d>", 26137097Sbostic lp->d_typename, lp->d_secsize, lp->d_ntracks, 26237097Sbostic lp->d_ncylinders, lp->d_nsectors); 26333165Sbostic 26437097Sbostic /* 26537097Sbostic * (60 / rpm) / (sectors per track * (bytes per sector / 2)) 26637097Sbostic */ 26737097Sbostic if (vi->ui_dk >= 0) 26838169Smckusick dk_wpms[vi->ui_dk] = 26938169Smckusick (lp->d_rpm * lp->d_nsectors * lp->d_secsize) / 120; 27037097Sbostic #ifdef notyet 27137097Sbostic addswap(makedev(HDMAJOR, hdminor(unit, 0)), lp); 27237097Sbostic #endif 27337097Sbostic } 27433165Sbostic 27537097Sbostic hdopen(dev, flags, fmt) 27637097Sbostic dev_t dev; 27737097Sbostic int flags, fmt; 27833165Sbostic { 27937097Sbostic register struct disklabel *lp; 28037097Sbostic register struct dksoftc *dk; 28137097Sbostic register struct partition *pp; 28237097Sbostic register int unit; 28337097Sbostic struct vba_device *vi; 28437097Sbostic int s, error, part = hdpart(dev), mask = 1 << part; 28537097Sbostic daddr_t start, end; 28633165Sbostic 28737097Sbostic unit = hdunit(dev); 28837097Sbostic if (unit >= NHD || (vi = hddinfo[unit]) == 0 || vi->ui_alive == 0) 28937097Sbostic return(ENXIO); 29037097Sbostic dk = &dksoftc[unit]; 29137097Sbostic lp = &dk->dk_label; 29237097Sbostic s = spl7(); 29337097Sbostic while (dk->dk_state != OPEN && dk->dk_state != OPENRAW && 29437097Sbostic dk->dk_state != CLOSED) 29537097Sbostic sleep((caddr_t)dk, PZERO+1); 29637097Sbostic splx(s); 29737097Sbostic if (dk->dk_state != OPEN && dk->dk_state != OPENRAW) 29837097Sbostic if (error = hdinit(dev, flags)) 29937097Sbostic return(error); 30033165Sbostic 30137097Sbostic if (hdcwstart == 0) { 30237097Sbostic timeout(hdcwatch, (caddr_t)0, hz); 30337097Sbostic hdcwstart++; 30437097Sbostic } 30533165Sbostic /* 30637097Sbostic * Warn if a partion is opened that overlaps another partition 30737097Sbostic * which is open unless one is the "raw" partition (whole disk). 30833165Sbostic */ 30937097Sbostic #define RAWPART 8 /* 'x' partition */ /* XXX */ 31037097Sbostic if ((dk->dk_openpart & mask) == 0 && part != RAWPART) { 31137097Sbostic pp = &lp->d_partitions[part]; 31237097Sbostic start = pp->p_offset; 31337097Sbostic end = pp->p_offset + pp->p_size; 31437097Sbostic for (pp = lp->d_partitions; 31537097Sbostic pp < &lp->d_partitions[lp->d_npartitions]; pp++) { 31637097Sbostic if (pp->p_offset + pp->p_size <= start || 31737097Sbostic pp->p_offset >= end) 31837097Sbostic continue; 31937097Sbostic if (pp - lp->d_partitions == RAWPART) 32037097Sbostic continue; 32137097Sbostic if (dk->dk_openpart & (1 << (pp - lp->d_partitions))) 32237097Sbostic log(LOG_WARNING, 32337097Sbostic "hd%d%c: overlaps open partition (%c)\n", 32437097Sbostic unit, part + 'a', 32537097Sbostic pp - lp->d_partitions + 'a'); 32637097Sbostic } 32737097Sbostic } 32837097Sbostic if (part >= lp->d_npartitions) 32937097Sbostic return(ENXIO); 33037097Sbostic dk->dk_openpart |= mask; 33137097Sbostic switch (fmt) { 33237097Sbostic case S_IFCHR: 33337097Sbostic dk->dk_copenpart |= mask; 33433165Sbostic break; 33537097Sbostic case S_IFBLK: 33637097Sbostic dk->dk_bopenpart |= mask; 33737097Sbostic break; 33833165Sbostic } 33937097Sbostic return(0); 34033165Sbostic } 34133165Sbostic 34237097Sbostic /* ARGSUSED */ 34337097Sbostic hdclose(dev, flags, fmt) 34437097Sbostic dev_t dev; 34537097Sbostic int flags, fmt; 34633165Sbostic { 34737097Sbostic register struct dksoftc *dk; 34837097Sbostic int mask; 34933165Sbostic 35037097Sbostic dk = &dksoftc[hdunit(dev)]; 35137097Sbostic mask = 1 << hdpart(dev); 35237097Sbostic switch (fmt) { 35337097Sbostic case S_IFCHR: 35437097Sbostic dk->dk_copenpart &= ~mask; 35537097Sbostic break; 35637097Sbostic case S_IFBLK: 35737097Sbostic dk->dk_bopenpart &= ~mask; 35837097Sbostic break; 35933165Sbostic } 36037097Sbostic if (((dk->dk_copenpart | dk->dk_bopenpart) & mask) == 0) 36137097Sbostic dk->dk_openpart &= ~mask; 36233165Sbostic /* 36337097Sbostic * Should wait for i/o to complete on this partition 36437097Sbostic * even if others are open, but wait for work on blkflush(). 36533165Sbostic */ 36637097Sbostic if (dk->dk_openpart == 0) { 36737097Sbostic int s = spl7(); 36837097Sbostic while (dk->dk_utab.b_actf) 36937097Sbostic sleep((caddr_t)dk, PZERO-1); 37037097Sbostic splx(s); 37137097Sbostic dk->dk_state = CLOSED; 37237097Sbostic dk->dk_wlabel = 0; 37333165Sbostic } 37437097Sbostic return(0); 37537097Sbostic } 37633165Sbostic 37737097Sbostic hdinit(dev, flags) 37837097Sbostic dev_t dev; 37937097Sbostic int flags; 38037097Sbostic { 38137097Sbostic register struct dksoftc *dk; 38237097Sbostic register struct disklabel *lp; 38337097Sbostic struct vba_device *vi; 38437097Sbostic int error, unit; 38537097Sbostic char *msg, *readdisklabel(); 38637097Sbostic extern int cold; 38733165Sbostic 38837097Sbostic vi = hddinfo[unit = hdunit(dev)]; 38937097Sbostic dk = &dksoftc[unit]; 39037097Sbostic dk->dk_unit = vi->ui_slave; 39137097Sbostic dk->dk_ctlr = vi->ui_ctlr; 39233165Sbostic 39337097Sbostic if (flags & O_NDELAY) { 39437097Sbostic dk->dk_state = OPENRAW; 39537097Sbostic return(0); 39637097Sbostic } 39733165Sbostic 39837097Sbostic error = 0; 39937097Sbostic lp = &dk->dk_label; 40037097Sbostic dk->dk_state = RDLABEL; 40137097Sbostic if (msg = readdisklabel(dev, hdstrategy, lp)) { 40237097Sbostic if (cold) { 40337097Sbostic printf(": %s\n", msg); 40437097Sbostic dk->dk_state = CLOSED; 40537097Sbostic } else { 40637097Sbostic log(LOG_ERR, "hd%d: %s\n", unit, msg); 40737097Sbostic dk->dk_state = OPENRAW; 40833165Sbostic } 40937097Sbostic #ifdef COMPAT_42 41037097Sbostic hdclock(vi->ui_ctlr); 41137097Sbostic if (!(error = hdreadgeometry(dk))) 41237097Sbostic dk->dk_state = OPEN; 41337097Sbostic hdcunlock(vi->ui_ctlr); 41437097Sbostic #endif 41537097Sbostic } else 41637097Sbostic dk->dk_state = OPEN; 41737097Sbostic wakeup((caddr_t)dk); 41837097Sbostic return(error); 41937097Sbostic } 42033165Sbostic 42137097Sbostic hd_setsecsize(dk, lp) 42237097Sbostic register struct dksoftc *dk; 42337097Sbostic struct disklabel *lp; 42437097Sbostic { 42537097Sbostic register int mul; 42637097Sbostic 42733165Sbostic /* 42837097Sbostic * Calculate scaling shift for mapping 42937097Sbostic * DEV_BSIZE blocks to drive sectors. 43033165Sbostic */ 43137097Sbostic mul = DEV_BSIZE / lp->d_secsize; 43237097Sbostic dk->dk_bshift = 0; 43337097Sbostic while ((mul >>= 1) > 0) 43437097Sbostic dk->dk_bshift++; 43537097Sbostic } 43633165Sbostic 43737097Sbostic /* ARGSUSED */ 43837097Sbostic hddgo(vm) 43937097Sbostic struct vba_device *vm; 44037097Sbostic {} 44133165Sbostic 44237097Sbostic extern int name_ext; 44337097Sbostic hdstrategy(bp) 44437097Sbostic register struct buf *bp; 44537097Sbostic { 44637097Sbostic register struct vba_device *vi; 44737097Sbostic register struct disklabel *lp; 44837097Sbostic register struct dksoftc *dk; 44937097Sbostic struct buf *dp; 45037097Sbostic register int unit; 45137097Sbostic daddr_t sn, sz, maxsz; 45237097Sbostic int part, s; 45333165Sbostic 45437097Sbostic vi = hddinfo[unit = hdunit(bp->b_dev)]; 45537097Sbostic if (unit >= NHD || vi == 0 || vi->ui_alive == 0) { 45637097Sbostic bp->b_error = ENXIO; 45737097Sbostic goto bad; 45837097Sbostic } 45937097Sbostic dk = &dksoftc[unit]; 46037097Sbostic if (dk->dk_state < OPEN) 46137097Sbostic goto q; 46237097Sbostic if (dk->dk_state != OPEN && (bp->b_flags & B_READ) == 0) { 46337097Sbostic bp->b_error = EROFS; 46437097Sbostic goto bad; 46537097Sbostic } 46637097Sbostic part = hdpart(bp->b_dev); 46737097Sbostic if ((dk->dk_openpart & (1 << part)) == 0) { 46837097Sbostic bp->b_error = ENODEV; 46937097Sbostic goto bad; 47037097Sbostic } 47137097Sbostic lp = &dk->dk_label; 47237097Sbostic sz = (bp->b_bcount + lp->d_secsize - 1) / lp->d_secsize; 47337097Sbostic maxsz = lp->d_partitions[part].p_size; 47437097Sbostic sn = bp->b_blkno << dk->dk_bshift; 47537097Sbostic if (sn + lp->d_partitions[part].p_offset <= LABELSECTOR && 47637097Sbostic #if LABELSECTOR != 0 47737097Sbostic sn + lp->d_partitions[part].p_offset + sz > LABELSECTOR && 47833165Sbostic #endif 47937097Sbostic (bp->b_flags & B_READ) == 0 && dk->dk_wlabel == 0) { 48037097Sbostic bp->b_error = EROFS; 48137097Sbostic goto bad; 48233165Sbostic } 48337097Sbostic if (sn < 0 || sn + sz > maxsz) { 48437097Sbostic if (sn == maxsz) { 48537097Sbostic bp->b_resid = bp->b_bcount; 48637097Sbostic goto done; 48737097Sbostic } 48837097Sbostic sz = maxsz - sn; 48937097Sbostic if (sz <= 0) { 49037097Sbostic bp->b_error = EINVAL; 49137097Sbostic goto bad; 49237097Sbostic } 49337097Sbostic bp->b_bcount = sz * lp->d_secsize; 49437097Sbostic } 49537097Sbostic bp->b_cylin = (sn + lp->d_partitions[part].p_offset) / lp->d_secpercyl; 49633165Sbostic 49737097Sbostic q: s = spl7(); 49837097Sbostic dp = &dk->dk_utab; 49937097Sbostic disksort(dp, bp); 50037097Sbostic if (!dp->b_active) { 50137097Sbostic (void)hdustart(vi); 50237097Sbostic if (!vi->ui_mi->um_tab.b_active) 50337097Sbostic hdcstart(vi->ui_mi); 50437097Sbostic } 50537097Sbostic splx(s); 50633165Sbostic return; 50737097Sbostic bad: 50837097Sbostic bp->b_flags |= B_ERROR; 50937097Sbostic done: 51037097Sbostic biodone(bp); 51133165Sbostic } 51233165Sbostic 51337097Sbostic hdustart(vi) 51437097Sbostic register struct vba_device *vi; 51533165Sbostic { 51637097Sbostic register struct buf *bp, *dp; 51737097Sbostic register struct vba_ctlr *vm; 51837097Sbostic register struct dksoftc *dk; 51933165Sbostic 52037097Sbostic dk = &dksoftc[vi->ui_unit]; 52137097Sbostic dp = &dk->dk_utab; 52233165Sbostic 52337097Sbostic /* if queue empty, nothing to do. impossible? */ 52437097Sbostic if (dp->b_actf == NULL) 52537097Sbostic return; 52633165Sbostic 52737097Sbostic /* place on controller transfer queue */ 52837097Sbostic vm = vi->ui_mi; 52937097Sbostic if (vm->um_tab.b_actf == NULL) 53037097Sbostic vm->um_tab.b_actf = dp; 53137097Sbostic else 53237097Sbostic vm->um_tab.b_actl->b_forw = dp; 53337097Sbostic vm->um_tab.b_actl = dp; 53437097Sbostic dp->b_forw = NULL; 53537097Sbostic dp->b_active++; 53637097Sbostic } 53733165Sbostic 53837097Sbostic hdcstart(vm) 53937097Sbostic register struct vba_ctlr *vm; 54037097Sbostic { 54137097Sbostic register struct buf *bp; 54237097Sbostic register struct dksoftc *dk; 54337097Sbostic register struct disklabel *lp; 54437097Sbostic register struct master_mcb *master; 54537097Sbostic register struct mcb *mcb; 54637097Sbostic struct vba_device *vi; 54737097Sbostic struct hdcsoftc *hdc; 54837097Sbostic struct buf *dp; 54937097Sbostic int sn; 55033165Sbostic 55137097Sbostic /* pull a request off the controller queue */ 55237097Sbostic for (;;) { 55337097Sbostic if ((dp = vm->um_tab.b_actf) == NULL) 55437097Sbostic return; 55537097Sbostic if (bp = dp->b_actf) 55637097Sbostic break; 55737097Sbostic vm->um_tab.b_actf = dp->b_forw; 55833165Sbostic } 55933165Sbostic 56037097Sbostic /* mark controller active */ 56137097Sbostic vm->um_tab.b_active++; 56233165Sbostic 56337097Sbostic vi = hddinfo[hdunit(bp->b_dev)]; 56437097Sbostic dk = &dksoftc[vi->ui_unit]; 56537097Sbostic lp = &dk->dk_label; 56637097Sbostic sn = bp->b_blkno << dk->dk_bshift; 56733165Sbostic 56837097Sbostic /* fill in mcb */ 56937097Sbostic mcb = &dk->dk_mcb; 57037097Sbostic mcb->forw_phaddr = 0; 57137097Sbostic /* mcb->priority = 0; */ 57237097Sbostic mcb->interrupt = 1; 57337097Sbostic mcb->command = (bp->b_flags & B_READ) ? HCMD_READ:HCMD_WRITE; 57437565Sbostic mcb->cyl = bp->b_cylin; 57537565Sbostic /* assumes partition starts on cylinder boundary */ 57637097Sbostic mcb->head = (sn / lp->d_nsectors) % lp->d_ntracks; 57737097Sbostic mcb->sector = sn % lp->d_nsectors; 57837097Sbostic mcb->drive = vi->ui_slave; 57937097Sbostic /* mcb->context = 0; /* what do we want on interrupt? */ 58033165Sbostic 58137097Sbostic hdc = &hdcsoftc[vm->um_ctlr]; 58238576Sbostic if (!hd_sgsetup(bp, &hdc->hdc_rbuf, mcb->chain)) { 58337097Sbostic mcb->chain[0].wcount = (bp->b_bcount+3) >> 2; 58437097Sbostic mcb->chain[0].memadr = 58537097Sbostic vbasetup(bp, &hdc->hdc_rbuf, (int)lp->d_secsize); 58633165Sbostic } 58733165Sbostic 58837097Sbostic if (vi->ui_dk >= 0) { 58937097Sbostic dk_busy |= 1<<vi->ui_dk; 59037097Sbostic dk_xfer[vi->ui_dk]++; 59137097Sbostic dk_wds[vi->ui_dk] += bp->b_bcount>>6; 59237097Sbostic } 59333165Sbostic 59437097Sbostic master = &hdc->hdc_mcb; 59537097Sbostic master->mcw = MCL_QUEUED; 59637097Sbostic master->interrupt = HDCINTERRUPT + vm->um_ctlr; 59737097Sbostic master->forw_phaddr = (u_long)vtoph((struct proc *)NULL, mcb); 59837097Sbostic hdc->hdc_reg->master_mcb = (u_long)hdc->hdc_mcbp; 59937097Sbostic } 60033165Sbostic 60137097Sbostic /* 60237097Sbostic * Wait for controller to finish current operation 60337097Sbostic * so that direct controller accesses can be done. 60437097Sbostic */ 60537097Sbostic hdclock(ctlr) 60637097Sbostic int ctlr; 60737097Sbostic { 60837097Sbostic register struct vba_ctlr *vm = hdcminfo[ctlr]; 60937097Sbostic register struct hdcsoftc *hdc; 61037097Sbostic int s; 61133165Sbostic 61237097Sbostic hdc = &hdcsoftc[ctlr]; 61337097Sbostic s = spl7(); 61437097Sbostic while (vm->um_tab.b_active || hdc->hdc_flags & HDC_LOCKED) { 61537097Sbostic hdc->hdc_flags |= HDC_WAIT; 61637097Sbostic sleep((caddr_t)hdc, PRIBIO); 61733165Sbostic } 61837097Sbostic hdc->hdc_flags |= HDC_LOCKED; 61937097Sbostic splx(s); 62037097Sbostic } 62133165Sbostic 62237097Sbostic /* 62337097Sbostic * Continue normal operations after pausing for 62437097Sbostic * munging the controller directly. 62537097Sbostic */ 62637097Sbostic hdcunlock(ctlr) 62737097Sbostic int ctlr; 62837097Sbostic { 62937097Sbostic register struct vba_ctlr *vm; 63037097Sbostic register struct hdcsoftc *hdc = &hdcsoftc[ctlr]; 63133165Sbostic 63237097Sbostic hdc->hdc_flags &= ~HDC_LOCKED; 63337097Sbostic if (hdc->hdc_flags & HDC_WAIT) { 63437097Sbostic hdc->hdc_flags &= ~HDC_WAIT; 63537097Sbostic wakeup((caddr_t)hdc); 63637097Sbostic } else { 63737097Sbostic vm = hdcminfo[ctlr]; 63837097Sbostic if (vm->um_tab.b_actf) 63937097Sbostic hdcstart(vm); 64033165Sbostic } 64137097Sbostic } 64233165Sbostic 64337097Sbostic hdintr(ctlr) 64437097Sbostic int ctlr; 64537097Sbostic { 64637097Sbostic register struct buf *bp, *dp; 64737097Sbostic register struct vba_ctlr *vm; 64837097Sbostic register struct vba_device *vi; 64937097Sbostic register struct hdcsoftc *hdc; 65037097Sbostic register struct mcb *mcb; 65137097Sbostic struct master_mcb *master; 65237097Sbostic register int status; 65337097Sbostic int timedout; 65437097Sbostic struct dksoftc *dk; 65533165Sbostic 65637097Sbostic hdc = &hdcsoftc[ctlr]; 65737097Sbostic master = &hdc->hdc_mcb; 65837097Sbostic uncache(&master->mcs); 65937097Sbostic uncache(&master->context); 66033165Sbostic 66137097Sbostic vm = hdcminfo[ctlr]; 66237097Sbostic if (!vm->um_tab.b_active || !(master->mcs&MCS_DONE)) { 66337097Sbostic printf("hd%d: stray interrupt\n", ctlr); 66437097Sbostic return; 66533165Sbostic } 66633165Sbostic 66737097Sbostic dp = vm->um_tab.b_actf; 66837097Sbostic bp = dp->b_actf; 66937097Sbostic vi = hddinfo[hdunit(bp->b_dev)]; 67037097Sbostic dk = &dksoftc[vi->ui_unit]; 67137097Sbostic if (vi->ui_dk >= 0) 67237097Sbostic dk_busy &= ~(1<<vi->ui_dk); 67337097Sbostic timedout = (hdc->hdc_wticks >= HDCMAXTIME); 67433165Sbostic 67537097Sbostic mcb = &dk->dk_mcb; 67633165Sbostic 67737097Sbostic if (master->mcs & (MCS_SOFTERROR | MCS_FATALERROR) || timedout) 67837097Sbostic hdcerror(ctlr, *(u_long *)master->xstatus); 67937565Sbostic else 68037097Sbostic hdc->hdc_wticks = 0; 68137565Sbostic if (vm->um_tab.b_active) { 68237565Sbostic vm->um_tab.b_active = 0; 68337565Sbostic vm->um_tab.b_actf = dp->b_forw; 68437565Sbostic dp->b_active = 0; 68537565Sbostic dp->b_errcnt = 0; 68637565Sbostic dp->b_actf = bp->av_forw; 68737565Sbostic bp->b_resid = 0; 68837565Sbostic vbadone(bp, &hdc->hdc_rbuf); 68937565Sbostic biodone(bp); 69037565Sbostic /* start up now, if more work to do */ 69137565Sbostic if (dp->b_actf) 69237565Sbostic hdustart(vi); 69337565Sbostic else if (dk->dk_openpart == 0) 69437565Sbostic wakeup((caddr_t)dk); 69533165Sbostic } 69637097Sbostic /* if there are devices ready to transfer, start the controller. */ 69737097Sbostic if (hdc->hdc_flags & HDC_WAIT) { 69837097Sbostic hdc->hdc_flags &= ~HDC_WAIT; 69937097Sbostic wakeup((caddr_t)hdc); 70037097Sbostic } else if (vm->um_tab.b_actf) 70137097Sbostic hdcstart(vm); 70237097Sbostic } 70333165Sbostic 70437565Sbostic hdioctl(dev, cmd, data, flag) 70537097Sbostic dev_t dev; 70637565Sbostic int cmd, flag; 70737097Sbostic caddr_t data; 70837097Sbostic { 70937565Sbostic register int unit; 71037565Sbostic register struct dksoftc *dk; 71137565Sbostic register struct disklabel *lp; 71237097Sbostic int error; 71333165Sbostic 71437565Sbostic unit = hdunit(dev); 71537565Sbostic dk = &dksoftc[unit]; 71637565Sbostic lp = &dk->dk_label; 71737565Sbostic error = 0; 71837565Sbostic switch (cmd) { 71937565Sbostic case DIOCGDINFO: 72037565Sbostic *(struct disklabel *)data = *lp; 72137565Sbostic break; 72237565Sbostic case DIOCGPART: 72337565Sbostic ((struct partinfo *)data)->disklab = lp; 72437565Sbostic ((struct partinfo *)data)->part = 72537565Sbostic &lp->d_partitions[hdpart(dev)]; 72637565Sbostic break; 72737565Sbostic case DIOCSDINFO: 72837565Sbostic if ((flag & FWRITE) == 0) 72937565Sbostic error = EBADF; 73037565Sbostic else 73137565Sbostic error = setdisklabel(lp, (struct disklabel *)data, 73237565Sbostic (dk->dk_state == OPENRAW) ? 0 : dk->dk_openpart); 73337565Sbostic if (error == 0 && dk->dk_state == OPENRAW) 73437565Sbostic dk->dk_state = OPEN; 73537565Sbostic break; 73637565Sbostic case DIOCWLABEL: 73737565Sbostic if ((flag & FWRITE) == 0) 73837565Sbostic error = EBADF; 73937565Sbostic else 74037565Sbostic dk->dk_wlabel = *(int *)data; 74137565Sbostic break; 74237565Sbostic case DIOCWDINFO: 74337565Sbostic if ((flag & FWRITE) == 0) 74437565Sbostic error = EBADF; 74537565Sbostic else if ((error = setdisklabel(lp, (struct disklabel *)data, 74637565Sbostic (dk->dk_state == OPENRAW) ? 0 : dk->dk_openpart)) == 0) { 74737565Sbostic int wlab; 74833165Sbostic 74937565Sbostic if (error == 0 && dk->dk_state == OPENRAW) 75037565Sbostic dk->dk_state = OPEN; 75137565Sbostic /* simulate opening partition 0 so write succeeds */ 75237565Sbostic dk->dk_openpart |= (1 << 0); /* XXX */ 75337565Sbostic wlab = dk->dk_wlabel; 75437565Sbostic dk->dk_wlabel = 1; 75537565Sbostic error = writedisklabel(dev, hdstrategy, lp); 75637565Sbostic dk->dk_openpart = dk->dk_copenpart | dk->dk_bopenpart; 75737565Sbostic dk->dk_wlabel = wlab; 75837565Sbostic } 75937565Sbostic break; 76037097Sbostic default: 76137097Sbostic error = ENOTTY; 76233165Sbostic break; 76333165Sbostic } 76437565Sbostic return (error); 76537097Sbostic } 76633165Sbostic 76737097Sbostic /* 76837097Sbostic * Watch for lost interrupts. 76937097Sbostic */ 77037097Sbostic hdcwatch() 77137097Sbostic { 77237097Sbostic register struct hdcsoftc *hdc; 77337097Sbostic register struct vba_ctlr **vmp; 77437097Sbostic register int ctlr; 77537097Sbostic int s; 77633165Sbostic 77737097Sbostic timeout(hdcwatch, (caddr_t)0, hz); 77837097Sbostic for (vmp = hdcminfo, hdc = hdcsoftc, ctlr = 0; ctlr < NHDC; 77937097Sbostic ++ctlr, ++vmp, ++hdc) { 78037097Sbostic if (*vmp == 0 || (*vmp)->um_alive == 0) 78137097Sbostic continue; 78237097Sbostic s = spl7(); 78337097Sbostic if ((*vmp)->um_tab.b_active && 78437097Sbostic hdc->hdc_wticks++ >= HDCMAXTIME) { 78537097Sbostic printf("hd%d: lost interrupt\n", ctlr); 78637097Sbostic hdintr(ctlr); 78733165Sbostic } 78837097Sbostic splx(s); 78933165Sbostic } 79033165Sbostic } 79133165Sbostic 79237097Sbostic hddump(dev) 79337097Sbostic dev_t dev; 79433165Sbostic { 79537097Sbostic return(ENXIO); 79633165Sbostic } 79733165Sbostic 79837097Sbostic hdsize(dev) 79937097Sbostic dev_t dev; 80033165Sbostic { 80137097Sbostic register int unit = hdunit(dev); 80237097Sbostic register struct dksoftc *dk; 80337097Sbostic struct vba_device *vi; 80437097Sbostic struct disklabel *lp; 80533165Sbostic 80637097Sbostic if (unit >= NHD || (vi = hddinfo[unit]) == 0 || vi->ui_alive == 0 || 80737097Sbostic (dk = &dksoftc[unit])->dk_state != OPEN) 80837097Sbostic return (-1); 80937097Sbostic lp = &dk->dk_label; 81037097Sbostic return ((int)lp->d_partitions[hdpart(dev)].p_size >> dk->dk_bshift); 81133165Sbostic } 81233165Sbostic 81337097Sbostic hdimcb(dk) 81437097Sbostic register struct dksoftc *dk; 81533165Sbostic { 81637097Sbostic register struct master_mcb *master; 81737097Sbostic register struct mcb *mcb; 81837097Sbostic register struct hdcsoftc *hdc; 81937097Sbostic int timeout; 82033165Sbostic 82137097Sbostic /* fill in mcb */ 82237097Sbostic mcb = &dk->dk_mcb; 82337097Sbostic mcb->interrupt = 0; 82437097Sbostic mcb->forw_phaddr = 0; 82537097Sbostic mcb->drive = dk->dk_unit; 82633165Sbostic 82737097Sbostic hdc = &hdcsoftc[dk->dk_ctlr]; 82837097Sbostic master = &hdc->hdc_mcb; 82933165Sbostic 83037097Sbostic /* fill in master mcb */ 83137097Sbostic master->mcw = MCL_IMMEDIATE; 83237097Sbostic master->forw_phaddr = (u_long)vtoph((struct proc *)NULL, mcb); 83337097Sbostic master->mcs = 0; 83433165Sbostic 83537097Sbostic /* kick controller and wait */ 83637097Sbostic hdc->hdc_reg->master_mcb = (u_long)hdc->hdc_mcbp; 83737097Sbostic for (timeout = 15000; timeout; --timeout) { 83837097Sbostic DELAY(1000); 83937097Sbostic mtpr(PADC, 0); 84037097Sbostic if (master->mcs&MCS_FATALERROR) { 84137097Sbostic printf("hdc%d: fatal error\n", dk->dk_ctlr); 84237097Sbostic hdcerror(dk->dk_ctlr, *(u_long *)master->xstatus); 84337097Sbostic return(1); 84437097Sbostic } 84537097Sbostic if (master->mcs&MCS_DONE) 84637097Sbostic return(0); 84733165Sbostic } 84837097Sbostic printf("hdc%d: timed out\n", dk->dk_ctlr); 84937097Sbostic return(1); 85033165Sbostic } 85133165Sbostic 85237097Sbostic hdcerror(ctlr, code) 85337097Sbostic int ctlr; 85437097Sbostic u_long code; 85533165Sbostic { 85637565Sbostic printf("hd%d: error %lx\n", ctlr, code); 85733165Sbostic } 85833165Sbostic 85937097Sbostic #ifdef COMPAT_42 86037097Sbostic hdreadgeometry(dk) 86137097Sbostic struct dksoftc *dk; 86233165Sbostic { 86337097Sbostic static geometry_sector geometry; 86437097Sbostic register struct mcb *mcb; 86537097Sbostic register struct disklabel *lp; 86637097Sbostic geometry_block *geo; 86737097Sbostic int cnt; 86833165Sbostic 86933165Sbostic /* 87037097Sbostic * Read the geometry block (at head = 0 sector = 0 of the drive 87137097Sbostic * definition cylinder), validate it (must have the correct version 87237097Sbostic * number, header, and checksum). 87333165Sbostic */ 87437097Sbostic mcb = &dk->dk_mcb; 87537097Sbostic mcb->command = HCMD_READ; 87637097Sbostic mcb->cyl = dk->dk_def_cyl; 87737097Sbostic mcb->head = 0; 87837097Sbostic mcb->sector = 0; 87937097Sbostic mcb->chain[0].wcount = sizeof(geometry_sector) / sizeof(long); 88037097Sbostic mcb->chain[0].memadr = (u_long)vtoph((struct process *)0, &geometry); 88137097Sbostic /* mcb->chain[0].memadr = (long)&geometry; */ 88237097Sbostic if (hdimcb(dk)) { 88337097Sbostic printf("hd%d: can't read default geometry.\n", dk->dk_unit); 88437097Sbostic return(1); 88533165Sbostic } 88637097Sbostic geo = &geometry.geometry_block; 88737097Sbostic if (geo->version > 64000 || geo->version < 0) { 88837097Sbostic printf("hd%d: bad default geometry version#.\n", dk->dk_unit); 88937097Sbostic return(1); 89033165Sbostic } 89137097Sbostic if (bcmp(&geo->id[0], GB_ID, GB_ID_LEN)) { 89237097Sbostic printf("hd%d: bad default geometry header.\n", dk->dk_unit); 89337097Sbostic return(1); 89433165Sbostic } 89537097Sbostic GB_CHECKSUM(geo, cnt); 89637097Sbostic if (geometry.checksum != cnt) { 89737097Sbostic printf("hd%d: bad default geometry checksum.\n", dk->dk_unit); 89837097Sbostic return(1); 89933165Sbostic } 90037097Sbostic lp = &dk->dk_label; 90137565Sbostic 90237097Sbostic /* 1K block in Harris geometry; convert to sectors for disklabels */ 90337097Sbostic for (cnt = 0; cnt < GB_MAXPART; cnt++) { 90437097Sbostic lp->d_partitions[cnt].p_offset = 90537097Sbostic geo->partition[cnt].start * (1024 / lp->d_secsize); 90637097Sbostic lp->d_partitions[cnt].p_size = 90737097Sbostic geo->partition[cnt].length * (1024 / lp->d_secsize); 90833165Sbostic } 90937097Sbostic lp->d_npartitions = GB_MAXPART; 91037097Sbostic return(0); 91133165Sbostic } 91237097Sbostic #endif /* COMPAT_42 */ 91337097Sbostic #endif /* NHD */ 914