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*38744Sbostic * @(#)hd.c 7.8 (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(); 5938743Sbostic long hdstd[] = { 0 }; 6037097Sbostic struct vba_driver hdcdriver = 6138743Sbostic { 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, 145*38744Sbostic vtoph((struct process *)NULL, &id))) 14637097Sbostic return(0); 14737097Sbostic DELAY(10000); 14837097Sbostic mtpr(PADC, 0); 14937097Sbostic if (id.module_id != (u_char)HDC_MID) { 15037097Sbostic printf("hdc%d: bad module id; id = %x.\n", 15137097Sbostic vm->um_ctlr, id.module_id); 15237097Sbostic return(0); 15337097Sbostic } 15437097Sbostic if (id.code_rev == (u_char)0xff) { 15537097Sbostic printf("hdc%d: micro-code not loaded.\n", vm->um_ctlr); 15637097Sbostic return(0); 15737097Sbostic } 15837097Sbostic if (id.fit != (u_char)0xff) { 15937097Sbostic printf("hdc%d: FIT test failed.\n", vm->um_ctlr); 16037097Sbostic return(0); 16137097Sbostic } 16233165Sbostic 16337097Sbostic /* reset that pup; flag as inited */ 16437097Sbostic hdc->hdc_reg->soft_reset = 0; 16537097Sbostic DELAY(1000000); 16637097Sbostic hdc->hdc_flags |= HDC_INIT; 16733165Sbostic 16837097Sbostic /* allocate page tables and i/o buffer. */ 16937097Sbostic if (!vbainit(&hdc->hdc_rbuf, MAXPHYS, VB_32BIT|VB_SCATTER)) { 17037097Sbostic printf("hdc%d: vbainit failed\n", vm->um_ctlr); 17137097Sbostic return (0); 17237097Sbostic } 17333165Sbostic 17437097Sbostic /* set pointer to master control block */ 17537097Sbostic hdc->hdc_mcbp = 17637097Sbostic (struct master_mcb *)vtoph((struct proc *)NULL, &hdc->hdc_mcb); 17737097Sbostic 17837097Sbostic br = 0x17, cvec = HDCINTERRUPT + vm->um_ctlr; /* XXX */ 17937097Sbostic return(sizeof(struct registers)); 18033165Sbostic } 18133165Sbostic 18237097Sbostic /* ARGSUSED */ 18337097Sbostic hdslave(vi, vdaddr) 18437097Sbostic struct vba_device *vi; 18537097Sbostic struct vddevice *vdaddr; 18633165Sbostic { 18737097Sbostic register struct mcb *mcb; 18837097Sbostic register struct disklabel *lp; 18937097Sbostic register struct dksoftc *dk; 19037097Sbostic static struct status status; 19133165Sbostic 19237097Sbostic dk = &dksoftc[vi->ui_unit]; 19337097Sbostic dk->dk_unit = vi->ui_unit; 19437097Sbostic dk->dk_ctlr = vi->ui_ctlr; 19533165Sbostic 19637097Sbostic mcb = &dk->dk_mcb; 19737097Sbostic mcb->command = HCMD_STATUS; 19837097Sbostic mcb->chain[0].wcount = sizeof(struct status) / sizeof(long); 19937097Sbostic mcb->chain[0].memadr = (u_long)vtoph((struct process *)0, &status); 20037097Sbostic if (hdimcb(dk)) { 20137097Sbostic printf(" (no status)\n"); 20237097Sbostic return(0); 20333165Sbostic } 20433165Sbostic 20533165Sbostic /* 20637097Sbostic * Report the drive down if anything in the drive status looks bad. 20737097Sbostic * If the drive is offline and it is not on cylinder, then the drive 20837097Sbostic * is not there. If there is a fault condition, the hdc will try to 20937097Sbostic * clear it when we read the disklabel information. 21033165Sbostic */ 21137097Sbostic if (!(status.drs&DRS_ONLINE)) { 21237097Sbostic if (status.drs&DRS_ON_CYLINDER) 21337097Sbostic printf(" (not online)\n"); 21437097Sbostic return(0); 21533165Sbostic } 21637097Sbostic if (status.drs&DRS_FAULT) 21737097Sbostic printf(" (clearing fault)"); 21833165Sbostic 21937097Sbostic lp = &dk->dk_label; 22037097Sbostic #ifdef RAW_SIZE 22137097Sbostic lp->d_secsize = status.bytes_per_sec; 22237097Sbostic #else 22337097Sbostic lp->d_secsize = 512; 22437097Sbostic #endif 22537097Sbostic lp->d_nsectors = status.max_sector + 1; 22637097Sbostic lp->d_ntracks = status.max_head + 1; 22737097Sbostic lp->d_ncylinders = status.max_cyl + 1; 22837097Sbostic lp->d_secpercyl = lp->d_ntracks * lp->d_nsectors; 22937097Sbostic lp->d_npartitions = 1; 23037097Sbostic lp->d_partitions[0].p_offset = 0; 23137097Sbostic lp->d_partitions[0].p_size = LABELSECTOR + 1; 23237097Sbostic lp->d_rpm = status.rpm; 23337097Sbostic lp->d_typename[0] = 'h'; 23437097Sbostic lp->d_typename[1] = 'd'; 23537097Sbostic lp->d_typename[2] = '\0'; 23637097Sbostic #ifdef COMPAT_42 23737097Sbostic dk->dk_def_cyl = status.def_cyl; 23837097Sbostic #endif 23937097Sbostic return(1); 24033165Sbostic } 24133165Sbostic 24237097Sbostic hdattach(vi) 24337097Sbostic register struct vba_device *vi; 24433165Sbostic { 24537097Sbostic register struct dksoftc *dk; 24637097Sbostic register struct disklabel *lp; 24737097Sbostic register int unit; 24833165Sbostic 24937097Sbostic unit = vi->ui_unit; 25037097Sbostic if (hdinit(hdminor(unit, 0), 0)) { 25137097Sbostic printf(": unknown drive type"); 25237097Sbostic return; 25333165Sbostic } 25437097Sbostic dk = &dksoftc[unit]; 25537097Sbostic lp = &dk->dk_label; 25637097Sbostic hd_setsecsize(dk, lp); 25737097Sbostic if (dk->dk_state == OPEN) 25837097Sbostic printf(": %s <secsize %d, ntrak %d, ncyl %d, nsec %d>", 25937097Sbostic lp->d_typename, lp->d_secsize, lp->d_ntracks, 26037097Sbostic lp->d_ncylinders, lp->d_nsectors); 26133165Sbostic 26237097Sbostic /* 26337097Sbostic * (60 / rpm) / (sectors per track * (bytes per sector / 2)) 26437097Sbostic */ 26537097Sbostic if (vi->ui_dk >= 0) 26638169Smckusick dk_wpms[vi->ui_dk] = 26738169Smckusick (lp->d_rpm * lp->d_nsectors * lp->d_secsize) / 120; 26837097Sbostic #ifdef notyet 26937097Sbostic addswap(makedev(HDMAJOR, hdminor(unit, 0)), lp); 27037097Sbostic #endif 27137097Sbostic } 27233165Sbostic 27337097Sbostic hdopen(dev, flags, fmt) 27437097Sbostic dev_t dev; 27537097Sbostic int flags, fmt; 27633165Sbostic { 27737097Sbostic register struct disklabel *lp; 27837097Sbostic register struct dksoftc *dk; 27937097Sbostic register struct partition *pp; 28037097Sbostic register int unit; 28137097Sbostic struct vba_device *vi; 28237097Sbostic int s, error, part = hdpart(dev), mask = 1 << part; 28337097Sbostic daddr_t start, end; 28433165Sbostic 28537097Sbostic unit = hdunit(dev); 28637097Sbostic if (unit >= NHD || (vi = hddinfo[unit]) == 0 || vi->ui_alive == 0) 28737097Sbostic return(ENXIO); 28837097Sbostic dk = &dksoftc[unit]; 28937097Sbostic lp = &dk->dk_label; 29037097Sbostic s = spl7(); 29137097Sbostic while (dk->dk_state != OPEN && dk->dk_state != OPENRAW && 29237097Sbostic dk->dk_state != CLOSED) 29337097Sbostic sleep((caddr_t)dk, PZERO+1); 29437097Sbostic splx(s); 29537097Sbostic if (dk->dk_state != OPEN && dk->dk_state != OPENRAW) 29637097Sbostic if (error = hdinit(dev, flags)) 29737097Sbostic return(error); 29833165Sbostic 29937097Sbostic if (hdcwstart == 0) { 30037097Sbostic timeout(hdcwatch, (caddr_t)0, hz); 30137097Sbostic hdcwstart++; 30237097Sbostic } 30333165Sbostic /* 30437097Sbostic * Warn if a partion is opened that overlaps another partition 30537097Sbostic * which is open unless one is the "raw" partition (whole disk). 30633165Sbostic */ 30737097Sbostic #define RAWPART 8 /* 'x' partition */ /* XXX */ 30837097Sbostic if ((dk->dk_openpart & mask) == 0 && part != RAWPART) { 30937097Sbostic pp = &lp->d_partitions[part]; 31037097Sbostic start = pp->p_offset; 31137097Sbostic end = pp->p_offset + pp->p_size; 31237097Sbostic for (pp = lp->d_partitions; 31337097Sbostic pp < &lp->d_partitions[lp->d_npartitions]; pp++) { 31437097Sbostic if (pp->p_offset + pp->p_size <= start || 31537097Sbostic pp->p_offset >= end) 31637097Sbostic continue; 31737097Sbostic if (pp - lp->d_partitions == RAWPART) 31837097Sbostic continue; 31937097Sbostic if (dk->dk_openpart & (1 << (pp - lp->d_partitions))) 32037097Sbostic log(LOG_WARNING, 32137097Sbostic "hd%d%c: overlaps open partition (%c)\n", 32237097Sbostic unit, part + 'a', 32337097Sbostic pp - lp->d_partitions + 'a'); 32437097Sbostic } 32537097Sbostic } 32637097Sbostic if (part >= lp->d_npartitions) 32737097Sbostic return(ENXIO); 32837097Sbostic dk->dk_openpart |= mask; 32937097Sbostic switch (fmt) { 33037097Sbostic case S_IFCHR: 33137097Sbostic dk->dk_copenpart |= mask; 33233165Sbostic break; 33337097Sbostic case S_IFBLK: 33437097Sbostic dk->dk_bopenpart |= mask; 33537097Sbostic break; 33633165Sbostic } 33737097Sbostic return(0); 33833165Sbostic } 33933165Sbostic 34037097Sbostic /* ARGSUSED */ 34137097Sbostic hdclose(dev, flags, fmt) 34237097Sbostic dev_t dev; 34337097Sbostic int flags, fmt; 34433165Sbostic { 34537097Sbostic register struct dksoftc *dk; 34637097Sbostic int mask; 34733165Sbostic 34837097Sbostic dk = &dksoftc[hdunit(dev)]; 34937097Sbostic mask = 1 << hdpart(dev); 35037097Sbostic switch (fmt) { 35137097Sbostic case S_IFCHR: 35237097Sbostic dk->dk_copenpart &= ~mask; 35337097Sbostic break; 35437097Sbostic case S_IFBLK: 35537097Sbostic dk->dk_bopenpart &= ~mask; 35637097Sbostic break; 35733165Sbostic } 35837097Sbostic if (((dk->dk_copenpart | dk->dk_bopenpart) & mask) == 0) 35937097Sbostic dk->dk_openpart &= ~mask; 36033165Sbostic /* 36137097Sbostic * Should wait for i/o to complete on this partition 36237097Sbostic * even if others are open, but wait for work on blkflush(). 36333165Sbostic */ 36437097Sbostic if (dk->dk_openpart == 0) { 36537097Sbostic int s = spl7(); 36637097Sbostic while (dk->dk_utab.b_actf) 36737097Sbostic sleep((caddr_t)dk, PZERO-1); 36837097Sbostic splx(s); 36937097Sbostic dk->dk_state = CLOSED; 37037097Sbostic dk->dk_wlabel = 0; 37133165Sbostic } 37237097Sbostic return(0); 37337097Sbostic } 37433165Sbostic 37537097Sbostic hdinit(dev, flags) 37637097Sbostic dev_t dev; 37737097Sbostic int flags; 37837097Sbostic { 37937097Sbostic register struct dksoftc *dk; 38037097Sbostic register struct disklabel *lp; 38137097Sbostic struct vba_device *vi; 38237097Sbostic int error, unit; 38337097Sbostic char *msg, *readdisklabel(); 38437097Sbostic extern int cold; 38533165Sbostic 38637097Sbostic vi = hddinfo[unit = hdunit(dev)]; 38737097Sbostic dk = &dksoftc[unit]; 38837097Sbostic dk->dk_unit = vi->ui_slave; 38937097Sbostic dk->dk_ctlr = vi->ui_ctlr; 39033165Sbostic 39137097Sbostic if (flags & O_NDELAY) { 39237097Sbostic dk->dk_state = OPENRAW; 39337097Sbostic return(0); 39437097Sbostic } 39533165Sbostic 39637097Sbostic error = 0; 39737097Sbostic lp = &dk->dk_label; 39837097Sbostic dk->dk_state = RDLABEL; 39937097Sbostic if (msg = readdisklabel(dev, hdstrategy, lp)) { 40037097Sbostic if (cold) { 40137097Sbostic printf(": %s\n", msg); 40237097Sbostic dk->dk_state = CLOSED; 40337097Sbostic } else { 40437097Sbostic log(LOG_ERR, "hd%d: %s\n", unit, msg); 40537097Sbostic dk->dk_state = OPENRAW; 40633165Sbostic } 40737097Sbostic #ifdef COMPAT_42 40837097Sbostic hdclock(vi->ui_ctlr); 40937097Sbostic if (!(error = hdreadgeometry(dk))) 41037097Sbostic dk->dk_state = OPEN; 41137097Sbostic hdcunlock(vi->ui_ctlr); 41237097Sbostic #endif 41337097Sbostic } else 41437097Sbostic dk->dk_state = OPEN; 41537097Sbostic wakeup((caddr_t)dk); 41637097Sbostic return(error); 41737097Sbostic } 41833165Sbostic 41937097Sbostic hd_setsecsize(dk, lp) 42037097Sbostic register struct dksoftc *dk; 42137097Sbostic struct disklabel *lp; 42237097Sbostic { 42337097Sbostic register int mul; 42437097Sbostic 42533165Sbostic /* 42637097Sbostic * Calculate scaling shift for mapping 42737097Sbostic * DEV_BSIZE blocks to drive sectors. 42833165Sbostic */ 42937097Sbostic mul = DEV_BSIZE / lp->d_secsize; 43037097Sbostic dk->dk_bshift = 0; 43137097Sbostic while ((mul >>= 1) > 0) 43237097Sbostic dk->dk_bshift++; 43337097Sbostic } 43433165Sbostic 43537097Sbostic /* ARGSUSED */ 43637097Sbostic hddgo(vm) 43737097Sbostic struct vba_device *vm; 43837097Sbostic {} 43933165Sbostic 44037097Sbostic extern int name_ext; 44137097Sbostic hdstrategy(bp) 44237097Sbostic register struct buf *bp; 44337097Sbostic { 44437097Sbostic register struct vba_device *vi; 44537097Sbostic register struct disklabel *lp; 44637097Sbostic register struct dksoftc *dk; 44737097Sbostic struct buf *dp; 44837097Sbostic register int unit; 44937097Sbostic daddr_t sn, sz, maxsz; 45037097Sbostic int part, s; 45133165Sbostic 45237097Sbostic vi = hddinfo[unit = hdunit(bp->b_dev)]; 45337097Sbostic if (unit >= NHD || vi == 0 || vi->ui_alive == 0) { 45437097Sbostic bp->b_error = ENXIO; 45537097Sbostic goto bad; 45637097Sbostic } 45737097Sbostic dk = &dksoftc[unit]; 45837097Sbostic if (dk->dk_state < OPEN) 45937097Sbostic goto q; 46037097Sbostic if (dk->dk_state != OPEN && (bp->b_flags & B_READ) == 0) { 46137097Sbostic bp->b_error = EROFS; 46237097Sbostic goto bad; 46337097Sbostic } 46437097Sbostic part = hdpart(bp->b_dev); 46537097Sbostic if ((dk->dk_openpart & (1 << part)) == 0) { 46637097Sbostic bp->b_error = ENODEV; 46737097Sbostic goto bad; 46837097Sbostic } 46937097Sbostic lp = &dk->dk_label; 47037097Sbostic sz = (bp->b_bcount + lp->d_secsize - 1) / lp->d_secsize; 47137097Sbostic maxsz = lp->d_partitions[part].p_size; 47237097Sbostic sn = bp->b_blkno << dk->dk_bshift; 47337097Sbostic if (sn + lp->d_partitions[part].p_offset <= LABELSECTOR && 47437097Sbostic #if LABELSECTOR != 0 47537097Sbostic sn + lp->d_partitions[part].p_offset + sz > LABELSECTOR && 47633165Sbostic #endif 47737097Sbostic (bp->b_flags & B_READ) == 0 && dk->dk_wlabel == 0) { 47837097Sbostic bp->b_error = EROFS; 47937097Sbostic goto bad; 48033165Sbostic } 48137097Sbostic if (sn < 0 || sn + sz > maxsz) { 48237097Sbostic if (sn == maxsz) { 48337097Sbostic bp->b_resid = bp->b_bcount; 48437097Sbostic goto done; 48537097Sbostic } 48637097Sbostic sz = maxsz - sn; 48737097Sbostic if (sz <= 0) { 48837097Sbostic bp->b_error = EINVAL; 48937097Sbostic goto bad; 49037097Sbostic } 49137097Sbostic bp->b_bcount = sz * lp->d_secsize; 49237097Sbostic } 49337097Sbostic bp->b_cylin = (sn + lp->d_partitions[part].p_offset) / lp->d_secpercyl; 49433165Sbostic 49537097Sbostic q: s = spl7(); 49637097Sbostic dp = &dk->dk_utab; 49737097Sbostic disksort(dp, bp); 49837097Sbostic if (!dp->b_active) { 49937097Sbostic (void)hdustart(vi); 50037097Sbostic if (!vi->ui_mi->um_tab.b_active) 50137097Sbostic hdcstart(vi->ui_mi); 50237097Sbostic } 50337097Sbostic splx(s); 50433165Sbostic return; 50537097Sbostic bad: 50637097Sbostic bp->b_flags |= B_ERROR; 50737097Sbostic done: 50837097Sbostic biodone(bp); 50933165Sbostic } 51033165Sbostic 51137097Sbostic hdustart(vi) 51237097Sbostic register struct vba_device *vi; 51333165Sbostic { 51437097Sbostic register struct buf *bp, *dp; 51537097Sbostic register struct vba_ctlr *vm; 51637097Sbostic register struct dksoftc *dk; 51733165Sbostic 51837097Sbostic dk = &dksoftc[vi->ui_unit]; 51937097Sbostic dp = &dk->dk_utab; 52033165Sbostic 52137097Sbostic /* if queue empty, nothing to do. impossible? */ 52237097Sbostic if (dp->b_actf == NULL) 52337097Sbostic return; 52433165Sbostic 52537097Sbostic /* place on controller transfer queue */ 52637097Sbostic vm = vi->ui_mi; 52737097Sbostic if (vm->um_tab.b_actf == NULL) 52837097Sbostic vm->um_tab.b_actf = dp; 52937097Sbostic else 53037097Sbostic vm->um_tab.b_actl->b_forw = dp; 53137097Sbostic vm->um_tab.b_actl = dp; 53237097Sbostic dp->b_forw = NULL; 53337097Sbostic dp->b_active++; 53437097Sbostic } 53533165Sbostic 53637097Sbostic hdcstart(vm) 53737097Sbostic register struct vba_ctlr *vm; 53837097Sbostic { 53937097Sbostic register struct buf *bp; 54037097Sbostic register struct dksoftc *dk; 54137097Sbostic register struct disklabel *lp; 54237097Sbostic register struct master_mcb *master; 54337097Sbostic register struct mcb *mcb; 54437097Sbostic struct vba_device *vi; 54537097Sbostic struct hdcsoftc *hdc; 54637097Sbostic struct buf *dp; 54737097Sbostic int sn; 54833165Sbostic 54937097Sbostic /* pull a request off the controller queue */ 55037097Sbostic for (;;) { 55137097Sbostic if ((dp = vm->um_tab.b_actf) == NULL) 55237097Sbostic return; 55337097Sbostic if (bp = dp->b_actf) 55437097Sbostic break; 55537097Sbostic vm->um_tab.b_actf = dp->b_forw; 55633165Sbostic } 55733165Sbostic 55837097Sbostic /* mark controller active */ 55937097Sbostic vm->um_tab.b_active++; 56033165Sbostic 56137097Sbostic vi = hddinfo[hdunit(bp->b_dev)]; 56237097Sbostic dk = &dksoftc[vi->ui_unit]; 56337097Sbostic lp = &dk->dk_label; 56437097Sbostic sn = bp->b_blkno << dk->dk_bshift; 56533165Sbostic 56637097Sbostic /* fill in mcb */ 56737097Sbostic mcb = &dk->dk_mcb; 56837097Sbostic mcb->forw_phaddr = 0; 56937097Sbostic /* mcb->priority = 0; */ 57037097Sbostic mcb->interrupt = 1; 57137097Sbostic mcb->command = (bp->b_flags & B_READ) ? HCMD_READ:HCMD_WRITE; 57237565Sbostic mcb->cyl = bp->b_cylin; 57337565Sbostic /* assumes partition starts on cylinder boundary */ 57437097Sbostic mcb->head = (sn / lp->d_nsectors) % lp->d_ntracks; 57537097Sbostic mcb->sector = sn % lp->d_nsectors; 57637097Sbostic mcb->drive = vi->ui_slave; 57737097Sbostic /* mcb->context = 0; /* what do we want on interrupt? */ 57833165Sbostic 57937097Sbostic hdc = &hdcsoftc[vm->um_ctlr]; 58038576Sbostic if (!hd_sgsetup(bp, &hdc->hdc_rbuf, mcb->chain)) { 58137097Sbostic mcb->chain[0].wcount = (bp->b_bcount+3) >> 2; 58237097Sbostic mcb->chain[0].memadr = 58337097Sbostic vbasetup(bp, &hdc->hdc_rbuf, (int)lp->d_secsize); 58433165Sbostic } 58533165Sbostic 58637097Sbostic if (vi->ui_dk >= 0) { 58737097Sbostic dk_busy |= 1<<vi->ui_dk; 58837097Sbostic dk_xfer[vi->ui_dk]++; 58937097Sbostic dk_wds[vi->ui_dk] += bp->b_bcount>>6; 59037097Sbostic } 59133165Sbostic 59237097Sbostic master = &hdc->hdc_mcb; 59337097Sbostic master->mcw = MCL_QUEUED; 59437097Sbostic master->interrupt = HDCINTERRUPT + vm->um_ctlr; 59537097Sbostic master->forw_phaddr = (u_long)vtoph((struct proc *)NULL, mcb); 59637097Sbostic hdc->hdc_reg->master_mcb = (u_long)hdc->hdc_mcbp; 59737097Sbostic } 59833165Sbostic 59937097Sbostic /* 60037097Sbostic * Wait for controller to finish current operation 60137097Sbostic * so that direct controller accesses can be done. 60237097Sbostic */ 60337097Sbostic hdclock(ctlr) 60437097Sbostic int ctlr; 60537097Sbostic { 60637097Sbostic register struct vba_ctlr *vm = hdcminfo[ctlr]; 60737097Sbostic register struct hdcsoftc *hdc; 60837097Sbostic int s; 60933165Sbostic 61037097Sbostic hdc = &hdcsoftc[ctlr]; 61137097Sbostic s = spl7(); 61237097Sbostic while (vm->um_tab.b_active || hdc->hdc_flags & HDC_LOCKED) { 61337097Sbostic hdc->hdc_flags |= HDC_WAIT; 61437097Sbostic sleep((caddr_t)hdc, PRIBIO); 61533165Sbostic } 61637097Sbostic hdc->hdc_flags |= HDC_LOCKED; 61737097Sbostic splx(s); 61837097Sbostic } 61933165Sbostic 62037097Sbostic /* 62137097Sbostic * Continue normal operations after pausing for 62237097Sbostic * munging the controller directly. 62337097Sbostic */ 62437097Sbostic hdcunlock(ctlr) 62537097Sbostic int ctlr; 62637097Sbostic { 62737097Sbostic register struct vba_ctlr *vm; 62837097Sbostic register struct hdcsoftc *hdc = &hdcsoftc[ctlr]; 62933165Sbostic 63037097Sbostic hdc->hdc_flags &= ~HDC_LOCKED; 63137097Sbostic if (hdc->hdc_flags & HDC_WAIT) { 63237097Sbostic hdc->hdc_flags &= ~HDC_WAIT; 63337097Sbostic wakeup((caddr_t)hdc); 63437097Sbostic } else { 63537097Sbostic vm = hdcminfo[ctlr]; 63637097Sbostic if (vm->um_tab.b_actf) 63737097Sbostic hdcstart(vm); 63833165Sbostic } 63937097Sbostic } 64033165Sbostic 64137097Sbostic hdintr(ctlr) 64237097Sbostic int ctlr; 64337097Sbostic { 64437097Sbostic register struct buf *bp, *dp; 64537097Sbostic register struct vba_ctlr *vm; 64637097Sbostic register struct vba_device *vi; 64737097Sbostic register struct hdcsoftc *hdc; 64837097Sbostic register struct mcb *mcb; 64937097Sbostic struct master_mcb *master; 65037097Sbostic register int status; 65137097Sbostic int timedout; 65237097Sbostic struct dksoftc *dk; 65333165Sbostic 65437097Sbostic hdc = &hdcsoftc[ctlr]; 65537097Sbostic master = &hdc->hdc_mcb; 65637097Sbostic uncache(&master->mcs); 65737097Sbostic uncache(&master->context); 65833165Sbostic 65937097Sbostic vm = hdcminfo[ctlr]; 66037097Sbostic if (!vm->um_tab.b_active || !(master->mcs&MCS_DONE)) { 66137097Sbostic printf("hd%d: stray interrupt\n", ctlr); 66237097Sbostic return; 66333165Sbostic } 66433165Sbostic 66537097Sbostic dp = vm->um_tab.b_actf; 66637097Sbostic bp = dp->b_actf; 66737097Sbostic vi = hddinfo[hdunit(bp->b_dev)]; 66837097Sbostic dk = &dksoftc[vi->ui_unit]; 66937097Sbostic if (vi->ui_dk >= 0) 67037097Sbostic dk_busy &= ~(1<<vi->ui_dk); 67137097Sbostic timedout = (hdc->hdc_wticks >= HDCMAXTIME); 67233165Sbostic 67337097Sbostic mcb = &dk->dk_mcb; 67433165Sbostic 67537097Sbostic if (master->mcs & (MCS_SOFTERROR | MCS_FATALERROR) || timedout) 67637097Sbostic hdcerror(ctlr, *(u_long *)master->xstatus); 67737565Sbostic else 67837097Sbostic hdc->hdc_wticks = 0; 67937565Sbostic if (vm->um_tab.b_active) { 68037565Sbostic vm->um_tab.b_active = 0; 68137565Sbostic vm->um_tab.b_actf = dp->b_forw; 68237565Sbostic dp->b_active = 0; 68337565Sbostic dp->b_errcnt = 0; 68437565Sbostic dp->b_actf = bp->av_forw; 68537565Sbostic bp->b_resid = 0; 68637565Sbostic vbadone(bp, &hdc->hdc_rbuf); 68737565Sbostic biodone(bp); 68837565Sbostic /* start up now, if more work to do */ 68937565Sbostic if (dp->b_actf) 69037565Sbostic hdustart(vi); 69137565Sbostic else if (dk->dk_openpart == 0) 69237565Sbostic wakeup((caddr_t)dk); 69333165Sbostic } 69437097Sbostic /* if there are devices ready to transfer, start the controller. */ 69537097Sbostic if (hdc->hdc_flags & HDC_WAIT) { 69637097Sbostic hdc->hdc_flags &= ~HDC_WAIT; 69737097Sbostic wakeup((caddr_t)hdc); 69837097Sbostic } else if (vm->um_tab.b_actf) 69937097Sbostic hdcstart(vm); 70037097Sbostic } 70133165Sbostic 70237565Sbostic hdioctl(dev, cmd, data, flag) 70337097Sbostic dev_t dev; 70437565Sbostic int cmd, flag; 70537097Sbostic caddr_t data; 70637097Sbostic { 70737565Sbostic register int unit; 70837565Sbostic register struct dksoftc *dk; 70937565Sbostic register struct disklabel *lp; 71037097Sbostic int error; 71133165Sbostic 71237565Sbostic unit = hdunit(dev); 71337565Sbostic dk = &dksoftc[unit]; 71437565Sbostic lp = &dk->dk_label; 71537565Sbostic error = 0; 71637565Sbostic switch (cmd) { 71737565Sbostic case DIOCGDINFO: 71837565Sbostic *(struct disklabel *)data = *lp; 71937565Sbostic break; 72037565Sbostic case DIOCGPART: 72137565Sbostic ((struct partinfo *)data)->disklab = lp; 72237565Sbostic ((struct partinfo *)data)->part = 72337565Sbostic &lp->d_partitions[hdpart(dev)]; 72437565Sbostic break; 72537565Sbostic case DIOCSDINFO: 72637565Sbostic if ((flag & FWRITE) == 0) 72737565Sbostic error = EBADF; 72837565Sbostic else 72937565Sbostic error = setdisklabel(lp, (struct disklabel *)data, 73037565Sbostic (dk->dk_state == OPENRAW) ? 0 : dk->dk_openpart); 73137565Sbostic if (error == 0 && dk->dk_state == OPENRAW) 73237565Sbostic dk->dk_state = OPEN; 73337565Sbostic break; 73437565Sbostic case DIOCWLABEL: 73537565Sbostic if ((flag & FWRITE) == 0) 73637565Sbostic error = EBADF; 73737565Sbostic else 73837565Sbostic dk->dk_wlabel = *(int *)data; 73937565Sbostic break; 74037565Sbostic case DIOCWDINFO: 74137565Sbostic if ((flag & FWRITE) == 0) 74237565Sbostic error = EBADF; 74337565Sbostic else if ((error = setdisklabel(lp, (struct disklabel *)data, 74437565Sbostic (dk->dk_state == OPENRAW) ? 0 : dk->dk_openpart)) == 0) { 74537565Sbostic int wlab; 74633165Sbostic 74737565Sbostic if (error == 0 && dk->dk_state == OPENRAW) 74837565Sbostic dk->dk_state = OPEN; 74937565Sbostic /* simulate opening partition 0 so write succeeds */ 75037565Sbostic dk->dk_openpart |= (1 << 0); /* XXX */ 75137565Sbostic wlab = dk->dk_wlabel; 75237565Sbostic dk->dk_wlabel = 1; 75337565Sbostic error = writedisklabel(dev, hdstrategy, lp); 75437565Sbostic dk->dk_openpart = dk->dk_copenpart | dk->dk_bopenpart; 75537565Sbostic dk->dk_wlabel = wlab; 75637565Sbostic } 75737565Sbostic break; 75837097Sbostic default: 75937097Sbostic error = ENOTTY; 76033165Sbostic break; 76133165Sbostic } 76237565Sbostic return (error); 76337097Sbostic } 76433165Sbostic 76537097Sbostic /* 76637097Sbostic * Watch for lost interrupts. 76737097Sbostic */ 76837097Sbostic hdcwatch() 76937097Sbostic { 77037097Sbostic register struct hdcsoftc *hdc; 77137097Sbostic register struct vba_ctlr **vmp; 77237097Sbostic register int ctlr; 77337097Sbostic int s; 77433165Sbostic 77537097Sbostic timeout(hdcwatch, (caddr_t)0, hz); 77637097Sbostic for (vmp = hdcminfo, hdc = hdcsoftc, ctlr = 0; ctlr < NHDC; 77737097Sbostic ++ctlr, ++vmp, ++hdc) { 77837097Sbostic if (*vmp == 0 || (*vmp)->um_alive == 0) 77937097Sbostic continue; 78037097Sbostic s = spl7(); 78137097Sbostic if ((*vmp)->um_tab.b_active && 78237097Sbostic hdc->hdc_wticks++ >= HDCMAXTIME) { 78337097Sbostic printf("hd%d: lost interrupt\n", ctlr); 78437097Sbostic hdintr(ctlr); 78533165Sbostic } 78637097Sbostic splx(s); 78733165Sbostic } 78833165Sbostic } 78933165Sbostic 79037097Sbostic hddump(dev) 79137097Sbostic dev_t dev; 79233165Sbostic { 79337097Sbostic return(ENXIO); 79433165Sbostic } 79533165Sbostic 79637097Sbostic hdsize(dev) 79737097Sbostic dev_t dev; 79833165Sbostic { 79937097Sbostic register int unit = hdunit(dev); 80037097Sbostic register struct dksoftc *dk; 80137097Sbostic struct vba_device *vi; 80237097Sbostic struct disklabel *lp; 80333165Sbostic 80437097Sbostic if (unit >= NHD || (vi = hddinfo[unit]) == 0 || vi->ui_alive == 0 || 80537097Sbostic (dk = &dksoftc[unit])->dk_state != OPEN) 80637097Sbostic return (-1); 80737097Sbostic lp = &dk->dk_label; 80837097Sbostic return ((int)lp->d_partitions[hdpart(dev)].p_size >> dk->dk_bshift); 80933165Sbostic } 81033165Sbostic 81137097Sbostic hdimcb(dk) 81237097Sbostic register struct dksoftc *dk; 81333165Sbostic { 81437097Sbostic register struct master_mcb *master; 81537097Sbostic register struct mcb *mcb; 81637097Sbostic register struct hdcsoftc *hdc; 81737097Sbostic int timeout; 81833165Sbostic 81937097Sbostic /* fill in mcb */ 82037097Sbostic mcb = &dk->dk_mcb; 82137097Sbostic mcb->interrupt = 0; 82237097Sbostic mcb->forw_phaddr = 0; 82337097Sbostic mcb->drive = dk->dk_unit; 82433165Sbostic 82537097Sbostic hdc = &hdcsoftc[dk->dk_ctlr]; 82637097Sbostic master = &hdc->hdc_mcb; 82733165Sbostic 82837097Sbostic /* fill in master mcb */ 82937097Sbostic master->mcw = MCL_IMMEDIATE; 83037097Sbostic master->forw_phaddr = (u_long)vtoph((struct proc *)NULL, mcb); 83137097Sbostic master->mcs = 0; 83233165Sbostic 83337097Sbostic /* kick controller and wait */ 83437097Sbostic hdc->hdc_reg->master_mcb = (u_long)hdc->hdc_mcbp; 83537097Sbostic for (timeout = 15000; timeout; --timeout) { 83637097Sbostic DELAY(1000); 83737097Sbostic mtpr(PADC, 0); 83837097Sbostic if (master->mcs&MCS_FATALERROR) { 83937097Sbostic printf("hdc%d: fatal error\n", dk->dk_ctlr); 84037097Sbostic hdcerror(dk->dk_ctlr, *(u_long *)master->xstatus); 84137097Sbostic return(1); 84237097Sbostic } 84337097Sbostic if (master->mcs&MCS_DONE) 84437097Sbostic return(0); 84533165Sbostic } 84637097Sbostic printf("hdc%d: timed out\n", dk->dk_ctlr); 84737097Sbostic return(1); 84833165Sbostic } 84933165Sbostic 85037097Sbostic hdcerror(ctlr, code) 85137097Sbostic int ctlr; 85237097Sbostic u_long code; 85333165Sbostic { 85437565Sbostic printf("hd%d: error %lx\n", ctlr, code); 85533165Sbostic } 85633165Sbostic 85737097Sbostic #ifdef COMPAT_42 85837097Sbostic hdreadgeometry(dk) 85937097Sbostic struct dksoftc *dk; 86033165Sbostic { 86137097Sbostic static geometry_sector geometry; 86237097Sbostic register struct mcb *mcb; 86337097Sbostic register struct disklabel *lp; 86437097Sbostic geometry_block *geo; 86537097Sbostic int cnt; 86633165Sbostic 86733165Sbostic /* 86837097Sbostic * Read the geometry block (at head = 0 sector = 0 of the drive 86937097Sbostic * definition cylinder), validate it (must have the correct version 87037097Sbostic * number, header, and checksum). 87133165Sbostic */ 87237097Sbostic mcb = &dk->dk_mcb; 87337097Sbostic mcb->command = HCMD_READ; 87437097Sbostic mcb->cyl = dk->dk_def_cyl; 87537097Sbostic mcb->head = 0; 87637097Sbostic mcb->sector = 0; 87737097Sbostic mcb->chain[0].wcount = sizeof(geometry_sector) / sizeof(long); 87837097Sbostic mcb->chain[0].memadr = (u_long)vtoph((struct process *)0, &geometry); 87937097Sbostic /* mcb->chain[0].memadr = (long)&geometry; */ 88037097Sbostic if (hdimcb(dk)) { 88137097Sbostic printf("hd%d: can't read default geometry.\n", dk->dk_unit); 88237097Sbostic return(1); 88333165Sbostic } 88437097Sbostic geo = &geometry.geometry_block; 88537097Sbostic if (geo->version > 64000 || geo->version < 0) { 88637097Sbostic printf("hd%d: bad default geometry version#.\n", dk->dk_unit); 88737097Sbostic return(1); 88833165Sbostic } 88937097Sbostic if (bcmp(&geo->id[0], GB_ID, GB_ID_LEN)) { 89037097Sbostic printf("hd%d: bad default geometry header.\n", dk->dk_unit); 89137097Sbostic return(1); 89233165Sbostic } 89337097Sbostic GB_CHECKSUM(geo, cnt); 89437097Sbostic if (geometry.checksum != cnt) { 89537097Sbostic printf("hd%d: bad default geometry checksum.\n", dk->dk_unit); 89637097Sbostic return(1); 89733165Sbostic } 89837097Sbostic lp = &dk->dk_label; 89937565Sbostic 90037097Sbostic /* 1K block in Harris geometry; convert to sectors for disklabels */ 90137097Sbostic for (cnt = 0; cnt < GB_MAXPART; cnt++) { 90237097Sbostic lp->d_partitions[cnt].p_offset = 90337097Sbostic geo->partition[cnt].start * (1024 / lp->d_secsize); 90437097Sbostic lp->d_partitions[cnt].p_size = 90537097Sbostic geo->partition[cnt].length * (1024 / lp->d_secsize); 90633165Sbostic } 90737097Sbostic lp->d_npartitions = GB_MAXPART; 90837097Sbostic return(0); 90933165Sbostic } 91037097Sbostic #endif /* COMPAT_42 */ 91137097Sbostic #endif /* NHD */ 912