xref: /csrg-svn/sys/tahoe/vba/cy.c (revision 37638)
134487Skarels /*
234487Skarels  * Copyright (c) 1988 Regents of the University of California.
334487Skarels  * All rights reserved.
434487Skarels  *
534487Skarels  * This code is derived from software contributed to Berkeley by
634487Skarels  * Computer Consoles Inc.
734487Skarels  *
834487Skarels  * Redistribution and use in source and binary forms are permitted
934866Sbostic  * provided that the above copyright notice and this paragraph are
1034866Sbostic  * duplicated in all such forms and that any documentation,
1134866Sbostic  * advertising materials, and other materials related to such
1234866Sbostic  * distribution and use acknowledge that the software was developed
1334866Sbostic  * by the University of California, Berkeley.  The name of the
1434866Sbostic  * University may not be used to endorse or promote products derived
1534866Sbostic  * from this software without specific prior written permission.
1634866Sbostic  * THIS SOFTWARE IS PROVIDED ``AS IS'' AND WITHOUT ANY EXPRESS OR
1734866Sbostic  * IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED
1834866Sbostic  * WARRANTIES OF MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE.
1934487Skarels  *
20*37638Smckusick  *	@(#)cy.c	7.3 (Berkeley) 05/04/89
2134487Skarels  */
2224000Ssam 
2325979Ssam #include "yc.h"
2425675Ssam #if NCY > 0
2524000Ssam /*
2625675Ssam  * Cipher Tapemaster driver.
2724000Ssam  */
2830371Skarels #define CYDEBUG
2930371Skarels #ifdef	CYDEBUG
3025675Ssam int	cydebug = 0;
3130371Skarels #define	dlog(params)	if (cydebug) log params
3230371Skarels #else
3330371Skarels #define dlog(params)	/* */
3430371Skarels #endif
3524000Ssam 
3625675Ssam #include "param.h"
3725675Ssam #include "systm.h"
3825675Ssam #include "vm.h"
3925675Ssam #include "buf.h"
4025675Ssam #include "file.h"
4125675Ssam #include "dir.h"
4225675Ssam #include "user.h"
4325675Ssam #include "proc.h"
4425675Ssam #include "signal.h"
4525675Ssam #include "uio.h"
4625675Ssam #include "ioctl.h"
4725675Ssam #include "mtio.h"
4825675Ssam #include "errno.h"
4925675Ssam #include "cmap.h"
5025979Ssam #include "kernel.h"
5125979Ssam #include "syslog.h"
5230294Ssam #include "tty.h"
5324000Ssam 
5429952Skarels #include "../tahoe/cpu.h"
5529952Skarels #include "../tahoe/mtpr.h"
5629952Skarels #include "../tahoe/pte.h"
5729952Skarels 
5825675Ssam #include "../tahoevba/vbavar.h"
5925979Ssam #define	CYERROR
6025675Ssam #include "../tahoevba/cyreg.h"
6124000Ssam 
6225979Ssam /*
6325979Ssam  * There is a ccybuf per tape controller.
6425979Ssam  * It is used as the token to pass to the internal routines
6525979Ssam  * to execute tape ioctls, and also acts as a lock on the slaves
6625979Ssam  * on the controller, since there is only one per controller.
6725979Ssam  * In particular, when the tape is rewinding on close we release
6825979Ssam  * the user process but any further attempts to use the tape drive
6925979Ssam  * before the rewind completes will hang waiting for ccybuf.
7025979Ssam  */
7125979Ssam struct	buf ccybuf[NCY];
7224000Ssam 
7325979Ssam int	cyprobe(), cyslave(), cyattach();
7425979Ssam struct	buf ycutab[NYC];
7525979Ssam short	yctocy[NYC];
7625675Ssam struct	vba_ctlr *cyminfo[NCY];
7725979Ssam struct	vba_device *ycdinfo[NYC];
7825857Ssam long	cystd[] = { 0 };
7925857Ssam struct	vba_driver cydriver =
8025979Ssam    { cyprobe, cyslave, cyattach, 0, cystd, "yc", ycdinfo, "cy", cyminfo };
8124000Ssam 
8225979Ssam /* bits in minor device */
8325979Ssam #define	YCUNIT(dev)	(minor(dev)&03)
8425979Ssam #define	CYUNIT(dev)	(yctocy[YCUNIT(dev)])
8525979Ssam #define	T_NOREWIND	0x04
8630371Skarels #define	T_1600BPI	0x00		/* pseudo */
8730371Skarels #define	T_3200BPI	0x08		/* unused */
8825979Ssam 
8925979Ssam #define	INF	1000000L		/* close to infinity */
9025979Ssam 
9124000Ssam /*
9225979Ssam  * Software state and shared command areas per controller.
9325979Ssam  *
9430719Skarels  * The i/o intermediate buffer must be allocated in startup()
9530719Skarels  * so its address will fit in 20-bits (YECH!!!!!!!!!!!!!!).
9624000Ssam  */
9725979Ssam struct cy_softc {
9825979Ssam 	int	cy_bs;		/* controller's buffer size */
9925979Ssam 	struct	cyscp *cy_scp;	/* system configuration block address */
10025979Ssam 	struct	cyccb cy_ccb;	/* channel control block */
10125979Ssam 	struct	cyscb cy_scb;	/* system configuration block */
10225979Ssam 	struct	cytpb cy_tpb;	/* tape parameter block */
10325979Ssam 	struct	cytpb cy_nop;	/* nop parameter block for cyintr */
10430719Skarels 	struct	vb_buf cy_rbuf;	/* vba resources */
10525979Ssam } cy_softc[NCY];
10624000Ssam 
10725979Ssam /*
10825979Ssam  * Software state per tape transport.
10925979Ssam  */
11025979Ssam struct	yc_softc {
11125979Ssam 	char	yc_openf;	/* lock against multiple opens */
11225979Ssam 	char	yc_lastiow;	/* last operation was a write */
11325979Ssam 	short	yc_tact;	/* timeout is active */
11425979Ssam 	long	yc_timo;	/* time until timeout expires */
11525979Ssam 	u_short	yc_control;	/* copy of last tpcb.tpcontrol */
11625979Ssam 	u_short	yc_status;	/* copy of last tpcb.tpstatus */
11725979Ssam 	u_short	yc_resid;	/* copy of last bc */
11825979Ssam 	u_short	yc_dens;	/* prototype control word with density info */
11925979Ssam 	struct	tty *yc_ttyp;	/* user's tty for errors */
12025979Ssam 	daddr_t	yc_blkno;	/* block number, for block device tape */
12125979Ssam 	daddr_t	yc_nxrec;	/* position of end of tape, if known */
12230371Skarels 	int	yc_blksize;	/* current tape blocksize estimate */
12330371Skarels 	int	yc_blks;	/* number of I/O operations since open */
12430371Skarels 	int	yc_softerrs;	/* number of soft I/O errors since open */
12525979Ssam } yc_softc[NYC];
12624000Ssam 
12724000Ssam /*
12825979Ssam  * States for vm->um_tab.b_active, the per controller state flag.
12925979Ssam  * This is used to sequence control in the driver.
13024000Ssam  */
13125979Ssam #define	SSEEK	1		/* seeking */
13225979Ssam #define	SIO	2		/* doing seq i/o */
13325979Ssam #define	SCOM	3		/* sending control command */
13425979Ssam #define	SREW	4		/* sending a rewind */
13525979Ssam #define	SERASE	5		/* erase inter-record gap */
13625979Ssam #define	SERASED	6		/* erased inter-record gap */
13724000Ssam 
13825979Ssam /* there's no way to figure these out dynamically? -- yech */
13925979Ssam struct	cyscp *cyscp[] =
14025979Ssam     { (struct cyscp *)0xc0000c06, (struct cyscp *)0xc0000c16 };
14125979Ssam #define	NCYSCP	(sizeof (cyscp) / sizeof (cyscp[0]))
14225979Ssam 
14325857Ssam cyprobe(reg, vm)
14425857Ssam 	caddr_t reg;
14525857Ssam 	struct vba_ctlr *vm;
14625675Ssam {
14725857Ssam 	register br, cvec;			/* must be r12, r11 */
14830371Skarels 	register struct cy_softc *cy;
14930371Skarels 	int ctlr = vm->um_ctlr;
15025675Ssam 
15130294Ssam #ifdef lint
15230294Ssam 	br = 0; cvec = br; br = cvec;
15330294Ssam 	cyintr(0);
15430294Ssam #endif
15525857Ssam 	if (badcyaddr(reg+1))
15625675Ssam 		return (0);
15730371Skarels 	if (ctlr > NCYSCP || cyscp[ctlr] == 0)		/* XXX */
15830371Skarels 		return (0);
15930371Skarels 	cy = &cy_softc[ctlr];
16030371Skarels 	cy->cy_scp = cyscp[ctlr];			/* XXX */
16125979Ssam 	/*
16225979Ssam 	 * Tapemaster controller must have interrupt handler
16325979Ssam 	 * disable interrupt, so we'll just kludge things
16425979Ssam 	 * (stupid multibus non-vectored interrupt crud).
16525979Ssam 	 */
16630371Skarels 	if (cyinit(ctlr, reg)) {
16730371Skarels 		uncache(&cy->cy_tpb.tpcount);
16830371Skarels 		cy->cy_bs = htoms(cy->cy_tpb.tpcount);
16930371Skarels 		/*
17030371Skarels 		 * Setup nop parameter block for clearing interrupts.
17130371Skarels 		 */
17230371Skarels 		cy->cy_nop.tpcmd = CY_NOP;
17330371Skarels 		cy->cy_nop.tpcontrol = 0;
17430371Skarels 		/*
17530371Skarels 		 * Allocate page tables.
17630371Skarels 		 */
17730719Skarels 		if (cybuf == 0) {
17830719Skarels 			printf("no cy buffer!!!\n");
17930719Skarels 			return (0);
18030719Skarels 		}
18130719Skarels 		cy->cy_rbuf.vb_rawbuf = cybuf + ctlr * CYMAXIO;
18231737Skarels 		if (vbainit(&cy->cy_rbuf, CYMAXIO, VB_20BIT) == 0) {
18331737Skarels 			printf("cy%d: vbainit failed\n", ctlr);
18431737Skarels 			return (0);
18531737Skarels 		}
18630371Skarels 
18730371Skarels 		br = 0x13, cvec = 0x80;			/* XXX */
18830371Skarels 		return (sizeof (struct cyccb));
18930371Skarels 	} else
19030371Skarels 		return (0);
19125675Ssam }
19225675Ssam 
19324000Ssam /*
19425857Ssam  * Check to see if a drive is attached to a controller.
19525857Ssam  * Since we can only tell that a drive is there if a tape is loaded and
19625857Ssam  * the drive is placed online, we always indicate the slave is present.
19724000Ssam  */
19825857Ssam cyslave(vi, addr)
19925857Ssam 	struct vba_device *vi;
20025857Ssam 	caddr_t addr;
20124000Ssam {
20225857Ssam 
20325857Ssam #ifdef lint
20425857Ssam 	vi = vi; addr = addr;
20525857Ssam #endif
20625857Ssam 	return (1);
20725857Ssam }
20825857Ssam 
20925857Ssam cyattach(vi)
21025857Ssam 	struct vba_device *vi;
21125857Ssam {
21225979Ssam 	register struct cy_softc *cy;
21325979Ssam 	int ctlr = vi->ui_mi->um_ctlr;
21425857Ssam 
21525979Ssam 	yctocy[vi->ui_unit] = ctlr;
21625979Ssam 	cy = &cy_softc[ctlr];
21730371Skarels 	if (vi->ui_slave == 0 && cy->cy_bs)
21830371Skarels 		printf("; %dkb buffer", cy->cy_bs/1024);
21925857Ssam }
22025857Ssam 
22125857Ssam /*
22225857Ssam  * Initialize the controller after a controller reset or
22325857Ssam  * during autoconfigure.  All of the system control blocks
22425857Ssam  * are initialized and the controller is asked to configure
22525857Ssam  * itself for later use.
22625857Ssam  */
22730371Skarels cyinit(ctlr, addr)
22825979Ssam 	int ctlr;
22930371Skarels 	register caddr_t addr;
23025857Ssam {
23125979Ssam 	register struct cy_softc *cy = &cy_softc[ctlr];
23225675Ssam 	register int *pte;
23324000Ssam 
23424000Ssam 	/*
23525675Ssam 	 * Initialize the system configuration pointer.
23624000Ssam 	 */
23725675Ssam 	/* make kernel writable */
23830719Skarels 	pte = (int *)&Sysmap[btop((int)cy->cy_scp &~ KERNBASE)];
23925675Ssam 	*pte &= ~PG_PROT; *pte |= PG_KW;
24025979Ssam 	mtpr(TBIS, cy->cy_scp);
24125675Ssam 	/* load the correct values in the scp */
24225979Ssam 	cy->cy_scp->csp_buswidth = CSP_16BITS;
24325979Ssam 	cyldmba(cy->cy_scp->csp_scb, (caddr_t)&cy->cy_scb);
24425675Ssam 	/* put it back to read-only */
24525675Ssam 	*pte &= ~PG_PROT; *pte |= PG_KR;
24625979Ssam 	mtpr(TBIS, cy->cy_scp);
24725675Ssam 
24824000Ssam 	/*
24925675Ssam 	 * Init system configuration block.
25024000Ssam 	 */
25130371Skarels 	cy->cy_scb.csb_fixed = CSB_FIXED;
25225675Ssam 	/* set pointer to the channel control block */
25325979Ssam 	cyldmba(cy->cy_scb.csb_ccb, (caddr_t)&cy->cy_ccb);
25425675Ssam 
25524000Ssam 	/*
25625675Ssam 	 * Initialize the chanel control block.
25724000Ssam 	 */
25825979Ssam 	cy->cy_ccb.cbcw = CBCW_CLRINT;
25925979Ssam 	cy->cy_ccb.cbgate = GATE_OPEN;
26025675Ssam 	/* set pointer to the tape parameter block */
26125979Ssam 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
26225675Ssam 
26324000Ssam 	/*
26425979Ssam 	 * Issue a nop cmd and get the internal buffer size for buffered i/o.
26524000Ssam 	 */
26625979Ssam 	cy->cy_tpb.tpcmd = CY_NOP;
26725979Ssam 	cy->cy_tpb.tpcontrol = CYCW_16BITS;
26825979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
26925979Ssam 	CY_GO(addr);
27025979Ssam 	if (cywait(&cy->cy_ccb) || (cy->cy_tpb.tpstatus&CYS_ERR)) {
27125979Ssam 		uncache(&cy->cy_tpb.tpstatus);
27225979Ssam 		printf("cy%d: timeout or err during init, status=%b\n", ctlr,
27325979Ssam 		    cy->cy_tpb.tpstatus, CYS_BITS);
27425675Ssam 		return (0);
27525675Ssam 	}
27625979Ssam 	cy->cy_tpb.tpcmd = CY_CONFIG;
27725979Ssam 	cy->cy_tpb.tpcontrol = CYCW_16BITS;
27825979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
27925979Ssam 	CY_GO(addr);
28025979Ssam 	if (cywait(&cy->cy_ccb) || (cy->cy_tpb.tpstatus&CYS_ERR)) {
28125979Ssam 		uncache(&cy->cy_tpb.tpstatus);
28225979Ssam 		printf("cy%d: configuration failure, status=%b\n", ctlr,
28325979Ssam 		    cy->cy_tpb.tpstatus, CYS_BITS);
28425675Ssam 		return (0);
28525675Ssam 	}
28625675Ssam 	return (1);
28724000Ssam }
28824000Ssam 
28925979Ssam int	cytimer();
29025979Ssam /*
29125979Ssam  * Open the device.  Tapes are unique open
29225979Ssam  * devices, so we refuse if it is already open.
29325979Ssam  * We also check that a tape is available, and
29425979Ssam  * don't block waiting here; if you want to wait
29525979Ssam  * for a tape you should timeout in user code.
29625979Ssam  */
29725675Ssam cyopen(dev, flag)
29825979Ssam 	dev_t dev;
29925675Ssam 	register int flag;
30025675Ssam {
30125979Ssam 	register int ycunit;
30225979Ssam 	register struct vba_device *vi;
30325979Ssam 	register struct yc_softc *yc;
30425675Ssam 
30525979Ssam 	ycunit = YCUNIT(dev);
30625979Ssam 	if (ycunit >= NYC || (vi = ycdinfo[ycunit]) == 0 || vi->ui_alive == 0)
30725675Ssam 		return (ENXIO);
30825979Ssam 	if ((yc = &yc_softc[ycunit])->yc_openf)
30925979Ssam 		return (EBUSY);
31030371Skarels 	yc->yc_openf = 1;
31125979Ssam #define	PACKUNIT(vi) \
31225979Ssam     (((vi->ui_slave&1)<<11)|((vi->ui_slave&2)<<9)|((vi->ui_slave&4)>>2))
31325979Ssam 	/* no way to select density */
31425979Ssam 	yc->yc_dens = PACKUNIT(vi)|CYCW_IE|CYCW_16BITS;
31530371Skarels 	if (yc->yc_tact == 0) {
31630371Skarels 		yc->yc_timo = INF;
31730371Skarels 		yc->yc_tact = 1;
31830371Skarels 		timeout(cytimer, (caddr_t)dev, 5*hz);
31930371Skarels 	}
32025979Ssam 	cycommand(dev, CY_SENSE, 1);
32125979Ssam 	if ((yc->yc_status&CYS_OL) == 0) {	/* not on-line */
32234285Skarels 		uprintf("cy%d: not online\n", ycunit);
32330439Skarels 		yc->yc_openf = 0;
32430872Skarels 		return (EIO);
32525675Ssam 	}
32625979Ssam 	if ((flag&FWRITE) && (yc->yc_status&CYS_WP)) {
32734285Skarels 		uprintf("cy%d: no write ring\n", ycunit);
32830439Skarels 		yc->yc_openf = 0;
32930872Skarels 		return (EIO);
33025675Ssam 	}
33125979Ssam 	yc->yc_blkno = (daddr_t)0;
33225979Ssam 	yc->yc_nxrec = INF;
33325979Ssam 	yc->yc_lastiow = 0;
33430869Skarels 	yc->yc_blksize = CYMAXIO;		/* guess > 0 */
33530371Skarels 	yc->yc_blks = 0;
33630371Skarels 	yc->yc_softerrs = 0;
33725979Ssam 	yc->yc_ttyp = u.u_ttyp;
33825675Ssam 	return (0);
33925675Ssam }
34025675Ssam 
34125979Ssam /*
34225979Ssam  * Close tape device.
34325979Ssam  *
34425979Ssam  * If tape was open for writing or last operation was a write,
34525979Ssam  * then write two EOF's and backspace over the last one.
34625979Ssam  * Unless this is a non-rewinding special file, rewind the tape.
34725979Ssam  * Make the tape available to others.
34825979Ssam  */
34925675Ssam cyclose(dev, flag)
35025979Ssam 	dev_t dev;
35130371Skarels 	int flag;
35225675Ssam {
35330371Skarels 	struct yc_softc *yc = &yc_softc[YCUNIT(dev)];
35425675Ssam 
35525979Ssam 	if (flag == FWRITE || (flag&FWRITE) && yc->yc_lastiow) {
35634285Skarels 		cycommand(dev, CY_WEOF, 1);	/* can't use count with WEOF */
35734285Skarels 		cycommand(dev, CY_WEOF, 1);
35825979Ssam 		cycommand(dev, CY_SREV, 1);
35925675Ssam 	}
36025979Ssam 	if ((minor(dev)&T_NOREWIND) == 0)
36125979Ssam 		/*
36225979Ssam 		 * 0 count means don't hang waiting for rewind complete
36325979Ssam 		 * rather ccybuf stays busy until the operation completes
36425979Ssam 		 * preventing further opens from completing by preventing
36525979Ssam 		 * a CY_SENSE from completing.
36625979Ssam 		 */
36725979Ssam 		cycommand(dev, CY_REW, 0);
36830371Skarels 	if (yc->yc_blks > 10 && yc->yc_softerrs > yc->yc_blks / 10)
36930371Skarels 		log(LOG_INFO, "yc%d: %d soft errors in %d blocks\n",
37030371Skarels 		    YCUNIT(dev), yc->yc_softerrs, yc->yc_blks);
37130371Skarels 	dlog((LOG_INFO, "%d soft errors in %d blocks\n",
37230371Skarels 	    yc->yc_softerrs, yc->yc_blks));
37325979Ssam 	yc->yc_openf = 0;
37430719Skarels 	return (0);
37525675Ssam }
37625675Ssam 
37724000Ssam /*
37825979Ssam  * Execute a command on the tape drive a specified number of times.
37924000Ssam  */
38025979Ssam cycommand(dev, com, count)
38125979Ssam 	dev_t dev;
38225979Ssam 	int com, count;
38324000Ssam {
38425979Ssam 	register struct buf *bp;
38525675Ssam 	int s;
38625675Ssam 
38725979Ssam 	bp = &ccybuf[CYUNIT(dev)];
38825675Ssam 	s = spl3();
38930371Skarels 	dlog((LOG_INFO, "cycommand(%o, %x, %d), b_flags %x\n",
39030371Skarels 	    dev, com, count, bp->b_flags));
39125979Ssam 	while (bp->b_flags&B_BUSY) {
39225979Ssam 		/*
39325979Ssam 		 * This special check is because B_BUSY never
39425979Ssam 		 * gets cleared in the non-waiting rewind case.
39525979Ssam 		 */
39625979Ssam 		if (bp->b_repcnt == 0 && (bp->b_flags&B_DONE))
39725979Ssam 			break;
39825979Ssam 		bp->b_flags |= B_WANTED;
39925979Ssam 		sleep((caddr_t)bp, PRIBIO);
40025675Ssam 	}
40125979Ssam 	bp->b_flags = B_BUSY|B_READ;
40225675Ssam 	splx(s);
40325979Ssam 	bp->b_dev = dev;
40425979Ssam 	bp->b_repcnt = count;
40525979Ssam 	bp->b_command = com;
40625979Ssam 	bp->b_blkno = 0;
40725979Ssam 	cystrategy(bp);
40825979Ssam 	/*
40925979Ssam 	 * In case of rewind from close; don't wait.
41025979Ssam 	 * This is the only case where count can be 0.
41125979Ssam 	 */
41225979Ssam 	if (count == 0)
41325979Ssam 		return;
41430371Skarels 	biowait(bp);
41525979Ssam 	if (bp->b_flags&B_WANTED)
41625979Ssam 		wakeup((caddr_t)bp);
41725979Ssam 	bp->b_flags &= B_ERROR;
41824000Ssam }
41924000Ssam 
42025675Ssam cystrategy(bp)
42125675Ssam 	register struct buf *bp;
42225675Ssam {
42325979Ssam 	int ycunit = YCUNIT(bp->b_dev);
42425979Ssam 	register struct vba_ctlr *vm;
42525979Ssam 	register struct buf *dp;
42625675Ssam 	int s;
42725675Ssam 
42825979Ssam 	/*
42925979Ssam 	 * Put transfer at end of unit queue.
43025979Ssam 	 */
43130371Skarels 	dlog((LOG_INFO, "cystrategy(%o, %x)\n", bp->b_dev, bp->b_command));
43225979Ssam 	dp = &ycutab[ycunit];
43325675Ssam 	bp->av_forw = NULL;
43425979Ssam 	vm = ycdinfo[ycunit]->ui_mi;
43525979Ssam 	/* BEGIN GROT */
43634507Skarels 	if (bp->b_flags & B_RAW) {
43730869Skarels 		if (bp->b_bcount >= CYMAXIO) {
43825979Ssam 			uprintf("cy%d: i/o size too large\n", vm->um_ctlr);
43930869Skarels 			bp->b_error = EINVAL;
44025979Ssam 			bp->b_resid = bp->b_bcount;
44125979Ssam 			bp->b_flags |= B_ERROR;
44230371Skarels 			biodone(bp);
44325675Ssam 			return;
44425675Ssam 		}
44524000Ssam 	}
44625979Ssam 	/* END GROT */
44725675Ssam 	s = spl3();
44825979Ssam 	if (dp->b_actf == NULL) {
44925979Ssam 		dp->b_actf = bp;
45025979Ssam 		/*
45125979Ssam 		 * Transport not already active...
45225979Ssam 		 * put at end of controller queue.
45325979Ssam 		 */
45425979Ssam 		 dp->b_forw = NULL;
45525979Ssam 		 if (vm->um_tab.b_actf == NULL)
45625979Ssam 			vm->um_tab.b_actf = dp;
45725979Ssam 		else
45825979Ssam 			vm->um_tab.b_actl->b_forw = dp;
45925979Ssam 	} else
46025979Ssam 		dp->b_actl->av_forw = bp;
46125979Ssam 	dp->b_actl = bp;
46225979Ssam 	/*
46325979Ssam 	 * If the controller is not busy, get it going.
46425979Ssam 	 */
46525979Ssam 	if (vm->um_tab.b_active == 0)
46625979Ssam 		cystart(vm);
46724000Ssam 	splx(s);
46824000Ssam }
46924000Ssam 
47024000Ssam /*
47125979Ssam  * Start activity on a cy controller.
47224000Ssam  */
47325979Ssam cystart(vm)
47425979Ssam 	register struct vba_ctlr *vm;
47524000Ssam {
47625979Ssam 	register struct buf *bp, *dp;
47725979Ssam 	register struct yc_softc *yc;
47825979Ssam 	register struct cy_softc *cy;
47925979Ssam 	int ycunit;
48025979Ssam 	daddr_t blkno;
48124000Ssam 
48230371Skarels 	dlog((LOG_INFO, "cystart()\n"));
48325979Ssam 	/*
48425979Ssam 	 * Look for an idle transport on the controller.
48525979Ssam 	 */
48625979Ssam loop:
48725979Ssam 	if ((dp = vm->um_tab.b_actf) == NULL)
48825675Ssam 		return;
48925979Ssam 	if ((bp = dp->b_actf) == NULL) {
49025979Ssam 		vm->um_tab.b_actf = dp->b_forw;
49125979Ssam 		goto loop;
49225675Ssam 	}
49325979Ssam 	ycunit = YCUNIT(bp->b_dev);
49425979Ssam 	yc = &yc_softc[ycunit];
49525979Ssam 	cy = &cy_softc[CYUNIT(bp->b_dev)];
49625979Ssam 	/*
49725979Ssam 	 * Default is that last command was NOT a write command;
49825979Ssam 	 * if we do a write command we will notice this in cyintr().
49925979Ssam 	 */
50025979Ssam 	yc->yc_lastiow = 0;
50125979Ssam 	if (yc->yc_openf < 0 ||
50225979Ssam 	    (bp->b_command != CY_SENSE && (cy->cy_tpb.tpstatus&CYS_OL) == 0)) {
50325979Ssam 		/*
50425979Ssam 		 * Have had a hard error on a non-raw tape
50525979Ssam 		 * or the tape unit is now unavailable (e.g.
50625979Ssam 		 * taken off line).
50725979Ssam 		 */
50830371Skarels 		dlog((LOG_INFO, "openf %d command %x status %b\n",
50930371Skarels 		   yc->yc_openf, bp->b_command, cy->cy_tpb.tpstatus, CYS_BITS));
51025979Ssam 		bp->b_flags |= B_ERROR;
51125979Ssam 		goto next;
51225675Ssam 	}
51325979Ssam 	if (bp == &ccybuf[CYUNIT(bp->b_dev)]) {
51425979Ssam 		/*
51525979Ssam 		 * Execute control operation with the specified count.
51625979Ssam 		 *
51725979Ssam 		 * Set next state; give 5 minutes to complete
51825979Ssam 		 * rewind or file mark search, or 10 seconds per
51925979Ssam 		 * iteration (minimum 60 seconds and max 5 minutes)
52025979Ssam 		 * to complete other ops.
52125979Ssam 		 */
52225979Ssam 		if (bp->b_command == CY_REW) {
52325979Ssam 			vm->um_tab.b_active = SREW;
52425979Ssam 			yc->yc_timo = 5*60;
52530869Skarels 		} else if (bp->b_command == CY_FSF ||
52630869Skarels 		    bp->b_command == CY_BSF) {
52730869Skarels 			vm->um_tab.b_active = SCOM;
52830869Skarels 			yc->yc_timo = 5*60;
52925979Ssam 		} else {
53025979Ssam 			vm->um_tab.b_active = SCOM;
53125979Ssam 			yc->yc_timo = imin(imax(10*(int)bp->b_repcnt,60),5*60);
53225979Ssam 		}
53325979Ssam 		cy->cy_tpb.tprec = htoms(bp->b_repcnt);
53430719Skarels 		dlog((LOG_INFO, "bpcmd "));
53525979Ssam 		goto dobpcmd;
53624000Ssam 	}
53725979Ssam 	/*
53834507Skarels 	 * For raw I/O, save the current block
53934507Skarels 	 * number in case we have to retry.
54025979Ssam 	 */
54134507Skarels 	if (bp->b_flags & B_RAW) {
54234507Skarels 		if (vm->um_tab.b_errcnt == 0) {
54334507Skarels 			yc->yc_blkno = bp->b_blkno;
54434507Skarels 			yc->yc_nxrec = yc->yc_blkno + 1;
54534507Skarels 		}
54634507Skarels 	} else {
54725979Ssam 		/*
54834507Skarels 		 * Handle boundary cases for operation
54934507Skarels 		 * on non-raw tapes.
55025979Ssam 		 */
55134507Skarels 		if (bp->b_blkno > yc->yc_nxrec) {
55234507Skarels 			/*
55334507Skarels 			 * Can't read past known end-of-file.
55434507Skarels 			 */
55534507Skarels 			bp->b_flags |= B_ERROR;
55634507Skarels 			bp->b_error = ENXIO;
55734507Skarels 			goto next;
55834507Skarels 		}
55934507Skarels 		if (bp->b_blkno == yc->yc_nxrec && bp->b_flags&B_READ) {
56034507Skarels 			/*
56134507Skarels 			 * Reading at end of file returns 0 bytes.
56234507Skarels 			 */
56334507Skarels 			bp->b_resid = bp->b_bcount;
56434507Skarels 			clrbuf(bp);
56534507Skarels 			goto next;
56634507Skarels 		}
56734507Skarels 		if ((bp->b_flags&B_READ) == 0)
56834507Skarels 			/*
56934507Skarels 			 * Writing sets EOF.
57034507Skarels 			 */
57134507Skarels 			yc->yc_nxrec = bp->b_blkno + 1;
57224000Ssam 	}
57330719Skarels 	if ((blkno = yc->yc_blkno) == bp->b_blkno) {
57425979Ssam 		caddr_t addr;
57525979Ssam 		int cmd;
57625675Ssam 
57725979Ssam 		/*
57825979Ssam 		 * Choose the appropriate i/o command based on the
57930371Skarels 		 * transfer size, the estimated block size,
58030371Skarels 		 * and the controller's internal buffer size.
58130869Skarels 		 * If the request length is longer than the tape
58230869Skarels 		 * block length, a buffered read will fail,
58330869Skarels 		 * thus, we request at most the size that we expect.
58430869Skarels 		 * We then check for larger records when the read completes.
58525979Ssam 		 * If we're retrying a read on a raw device because
58625979Ssam 		 * the original try was a buffer request which failed
58725979Ssam 		 * due to a record length error, then we force the use
58825979Ssam 		 * of the raw controller read (YECH!!!!).
58925979Ssam 		 */
59025979Ssam 		if (bp->b_flags&B_READ) {
59130869Skarels 			if (yc->yc_blksize <= cy->cy_bs &&
59230869Skarels 			    vm->um_tab.b_errcnt == 0)
59330869Skarels 				cmd = CY_BRCOM;
59430869Skarels 			else
59525979Ssam 				cmd = CY_RCOM;
59625979Ssam 		} else {
59725979Ssam 			/*
59825979Ssam 			 * On write error retries erase the
59925979Ssam 			 * inter-record gap before rewriting.
60025979Ssam 			 */
60125979Ssam 			if (vm->um_tab.b_errcnt &&
60225979Ssam 			    vm->um_tab.b_active != SERASED) {
60325979Ssam 				vm->um_tab.b_active = SERASE;
60425979Ssam 				bp->b_command = CY_ERASE;
60525979Ssam 				yc->yc_timo = 60;
60625979Ssam 				goto dobpcmd;
60725675Ssam 			}
60825979Ssam 			cmd = (bp->b_bcount > cy->cy_bs) ? CY_WCOM : CY_BWCOM;
60925675Ssam 		}
61025979Ssam 		vm->um_tab.b_active = SIO;
61130719Skarels 		addr = (caddr_t)vbasetup(bp, &cy->cy_rbuf, 1);
61225979Ssam 		cy->cy_tpb.tpcmd = cmd;
61325979Ssam 		cy->cy_tpb.tpcontrol = yc->yc_dens;
61425979Ssam 		if (cmd == CY_RCOM || cmd == CY_WCOM)
61525979Ssam 			cy->cy_tpb.tpcontrol |= CYCW_LOCK;
61625979Ssam 		cy->cy_tpb.tpstatus = 0;
61725979Ssam 		cy->cy_tpb.tpcount = 0;
61825979Ssam 		cyldmba(cy->cy_tpb.tpdata, (caddr_t)addr);
61925979Ssam 		cy->cy_tpb.tprec = 0;
62030869Skarels 		if (cmd == CY_BRCOM)
62134487Skarels 			cy->cy_tpb.tpsize = htoms(imin(yc->yc_blksize,
62234487Skarels 			    (int)bp->b_bcount));
62330371Skarels 		else
62430371Skarels 			cy->cy_tpb.tpsize = htoms(bp->b_bcount);
62525979Ssam 		cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
62625979Ssam 		do
62725979Ssam 			uncache(&cy->cy_ccb.cbgate);
62825979Ssam 		while (cy->cy_ccb.cbgate == GATE_CLOSED);
62925979Ssam 		cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
63025979Ssam 		cy->cy_ccb.cbcw = CBCW_IE;
63125979Ssam 		cy->cy_ccb.cbgate = GATE_CLOSED;
63230371Skarels 		dlog((LOG_INFO, "CY_GO(%x) cmd %x control %x size %d\n",
63325979Ssam 		    vm->um_addr, cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol,
63430371Skarels 		    htoms(cy->cy_tpb.tpsize)));
63525979Ssam 		CY_GO(vm->um_addr);
63625979Ssam 		return;
63724000Ssam 	}
63825979Ssam 	/*
63925979Ssam 	 * Tape positioned incorrectly; set to seek forwards
64025979Ssam 	 * or backwards to the correct spot.  This happens
64125979Ssam 	 * for raw tapes only on error retries.
64225979Ssam 	 */
64325979Ssam 	vm->um_tab.b_active = SSEEK;
64430719Skarels 	if (blkno < bp->b_blkno) {
64525979Ssam 		bp->b_command = CY_SFORW;
64630719Skarels 		cy->cy_tpb.tprec = htoms(bp->b_blkno - blkno);
64725979Ssam 	} else {
64825979Ssam 		bp->b_command = CY_SREV;
64930719Skarels 		cy->cy_tpb.tprec = htoms(blkno - bp->b_blkno);
65024000Ssam 	}
65134487Skarels 	yc->yc_timo = imin(imax((int)(10 * htoms(cy->cy_tpb.tprec)), 60), 5*60);
65225979Ssam dobpcmd:
65325979Ssam 	/*
65425979Ssam 	 * Do the command in bp.  Reverse direction commands
65525979Ssam 	 * are indicated by having CYCW_REV or'd into their
65625979Ssam 	 * value.  For these we must set the appropriate bit
65725979Ssam 	 * in the control field.
65825979Ssam 	 */
65925979Ssam 	if (bp->b_command&CYCW_REV) {
66025979Ssam 		cy->cy_tpb.tpcmd = bp->b_command &~ CYCW_REV;
66125979Ssam 		cy->cy_tpb.tpcontrol = yc->yc_dens | CYCW_REV;
66230719Skarels dlog((LOG_INFO, "cmd %x control %x\n", cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol));
66325979Ssam 	} else {
66425979Ssam 		cy->cy_tpb.tpcmd = bp->b_command;
66525979Ssam 		cy->cy_tpb.tpcontrol = yc->yc_dens;
66630719Skarels dlog((LOG_INFO, "cmd %x control %x\n", cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol));
66724000Ssam 	}
66825979Ssam 	cy->cy_tpb.tpstatus = 0;
66925979Ssam 	cy->cy_tpb.tpcount = 0;
67025979Ssam 	cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
67125979Ssam 	do
67225979Ssam 		uncache(&cy->cy_ccb.cbgate);
67325979Ssam 	while (cy->cy_ccb.cbgate == GATE_CLOSED);
67425979Ssam 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
67525979Ssam 	cy->cy_ccb.cbcw = CBCW_IE;
67625979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
67730371Skarels 	dlog((LOG_INFO, "CY_GO(%x) cmd %x control %x rec %d\n",
67825979Ssam 	    vm->um_addr, cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol,
67930371Skarels 	    htoms(cy->cy_tpb.tprec)));
68025979Ssam 	CY_GO(vm->um_addr);
68125979Ssam 	return;
68225979Ssam next:
68325979Ssam 	/*
68425979Ssam 	 * Done with this operation due to error or the
68530719Skarels 	 * fact that it doesn't do anything.
68630719Skarels 	 * Dequeue the transfer and continue
68725979Ssam 	 * processing this slave.
68825979Ssam 	 */
68925979Ssam 	vm->um_tab.b_errcnt = 0;
69025979Ssam 	dp->b_actf = bp->av_forw;
69130371Skarels 	biodone(bp);
69225979Ssam 	goto loop;
69325675Ssam }
69425675Ssam 
69525675Ssam /*
69625979Ssam  * Cy interrupt routine.
69725675Ssam  */
69830719Skarels cyintr(cyunit)
69930719Skarels 	int cyunit;
70025675Ssam {
70125979Ssam 	struct buf *dp;
70224000Ssam 	register struct buf *bp;
70330719Skarels 	register struct vba_ctlr *vm = cyminfo[cyunit];
70425979Ssam 	register struct cy_softc *cy;
70525979Ssam 	register struct yc_softc *yc;
70630719Skarels 	int err;
70725979Ssam 	register state;
70824000Ssam 
70930719Skarels 	dlog((LOG_INFO, "cyintr(%d)\n", cyunit));
71025979Ssam 	/*
71125979Ssam 	 * First, turn off the interrupt from the controller
71225979Ssam 	 * (device uses Multibus non-vectored interrupts...yech).
71325979Ssam 	 */
71425979Ssam 	cy = &cy_softc[vm->um_ctlr];
71525979Ssam 	cy->cy_ccb.cbcw = CBCW_CLRINT;
71630294Ssam 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_nop);
71725979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
71825979Ssam 	CY_GO(vm->um_addr);
71925979Ssam 	if ((dp = vm->um_tab.b_actf) == NULL) {
72030371Skarels 		dlog((LOG_ERR, "cy%d: stray interrupt", vm->um_ctlr));
72124000Ssam 		return;
72224000Ssam 	}
72325979Ssam 	bp = dp->b_actf;
72425979Ssam 	cy = &cy_softc[cyunit];
72525979Ssam 	cyuncachetpb(cy);
72630294Ssam 	yc = &yc_softc[YCUNIT(bp->b_dev)];
72725979Ssam 	/*
72825984Ssam 	 * If last command was a rewind and tape is
72925984Ssam 	 * still moving, wait for the operation to complete.
73025979Ssam 	 */
73125979Ssam 	if (vm->um_tab.b_active == SREW) {
73225979Ssam 		vm->um_tab.b_active = SCOM;
73325979Ssam 		if ((cy->cy_tpb.tpstatus&CYS_RDY) == 0) {
73425979Ssam 			yc->yc_timo = 5*60;	/* 5 minutes */
73525979Ssam 			return;
73624000Ssam 		}
73724000Ssam 	}
73825979Ssam 	/*
73925979Ssam 	 * An operation completed...record status.
74025979Ssam 	 */
74125979Ssam 	yc->yc_timo = INF;
74225979Ssam 	yc->yc_control = cy->cy_tpb.tpcontrol;
74325979Ssam 	yc->yc_status = cy->cy_tpb.tpstatus;
74425979Ssam 	yc->yc_resid = bp->b_bcount - htoms(cy->cy_tpb.tpcount);
74530371Skarels 	dlog((LOG_INFO, "cmd %x control %b status %b resid %d\n",
74625979Ssam 	    cy->cy_tpb.tpcmd, yc->yc_control, CYCW_BITS,
74730371Skarels 	    yc->yc_status, CYS_BITS, yc->yc_resid));
74825979Ssam 	if ((bp->b_flags&B_READ) == 0)
74925979Ssam 		yc->yc_lastiow = 1;
75025979Ssam 	state = vm->um_tab.b_active;
75125979Ssam 	vm->um_tab.b_active = 0;
75225979Ssam 	/*
75325979Ssam 	 * Check for errors.
75425979Ssam 	 */
75525979Ssam 	if (cy->cy_tpb.tpstatus&CYS_ERR) {
75625979Ssam 		err = cy->cy_tpb.tpstatus&CYS_ERR;
75730371Skarels 		dlog((LOG_INFO, "error %d\n", err));
75825979Ssam 		/*
75925979Ssam 		 * If we hit the end of tape file, update our position.
76025979Ssam 		 */
76125979Ssam 		if (err == CYER_FM) {
76225979Ssam 			yc->yc_status |= CYS_FM;
76325979Ssam 			state = SCOM;		/* force completion */
76425979Ssam 			cyseteof(bp);		/* set blkno and nxrec */
76525979Ssam 			goto opdone;
76625979Ssam 		}
76725979Ssam 		/*
76825979Ssam 		 * Fix up errors which occur due to backspacing over
76925979Ssam 		 * the beginning of the tape.
77025979Ssam 		 */
77125979Ssam 		if (err == CYER_BOT && cy->cy_tpb.tpcontrol&CYCW_REV) {
77225979Ssam 			yc->yc_status |= CYS_BOT;
77325979Ssam 			goto ignoreerr;
77425979Ssam 		}
77525979Ssam 		/*
77625979Ssam 		 * If we were reading raw tape and the only error was that the
77725979Ssam 		 * record was too long, then we don't consider this an error.
77825979Ssam 		 */
77934507Skarels 		if ((bp->b_flags & (B_READ|B_RAW)) == (B_READ|B_RAW) &&
78025979Ssam 		    err == CYER_STROBE) {
78125979Ssam 			/*
78230371Skarels 			 * Retry reads with the command changed to
78330371Skarels 			 * a raw read if necessary.  Setting b_errcnt
78425979Ssam 			 * here causes cystart (above) to force a CY_RCOM.
78525979Ssam 			 */
78630869Skarels 			if (cy->cy_tpb.tpcmd == CY_BRCOM &&
78730719Skarels 			    vm->um_tab.b_errcnt++ == 0) {
78830371Skarels 				yc->yc_blkno++;
78930371Skarels 				goto opcont;
79030371Skarels 			} else
79125979Ssam 				goto ignoreerr;
79225979Ssam 		}
79325979Ssam 		/*
79425979Ssam 		 * If error is not hard, and this was an i/o operation
79525979Ssam 		 * retry up to 8 times.
79625979Ssam 		 */
79734285Skarels 		if (state == SIO && (CYMASK(err) &
79834285Skarels 		    ((bp->b_flags&B_READ) ? CYER_RSOFT : CYER_WSOFT))) {
79925979Ssam 			if (++vm->um_tab.b_errcnt < 7) {
80025979Ssam 				yc->yc_blkno++;
80125979Ssam 				goto opcont;
80225979Ssam 			}
80325979Ssam 		} else
80425979Ssam 			/*
80525979Ssam 			 * Hard or non-i/o errors on non-raw tape
80625979Ssam 			 * cause it to close.
80725979Ssam 			 */
80834507Skarels 			if ((bp->b_flags&B_RAW) == 0 &&
80934507Skarels 			    yc->yc_openf > 0)
81025979Ssam 				yc->yc_openf = -1;
81125979Ssam 		/*
81225979Ssam 		 * Couldn't recover from error.
81325979Ssam 		 */
81425979Ssam 		tprintf(yc->yc_ttyp,
81530371Skarels 		    "yc%d: hard error bn%d status=%b, %s\n", YCUNIT(bp->b_dev),
81630371Skarels 		    bp->b_blkno, yc->yc_status, CYS_BITS,
81730371Skarels 		    (err < NCYERROR) ? cyerror[err] : "");
81825979Ssam 		bp->b_flags |= B_ERROR;
81925979Ssam 		goto opdone;
82030869Skarels 	} else if (cy->cy_tpb.tpcmd == CY_BRCOM) {
82130869Skarels 		int reclen = htoms(cy->cy_tpb.tprec);
82230869Skarels 
82330869Skarels 		/*
82430869Skarels 		 * If we did a buffered read, check whether the read
82530869Skarels 		 * was long enough.  If we asked the controller for less
82630869Skarels 		 * than the user asked for because the previous record
82730869Skarels 		 * was shorter, update our notion of record size
82830869Skarels 		 * and retry.  If the record is longer than the buffer,
82930869Skarels 		 * bump the errcnt so the retry will use direct read.
83030869Skarels 		 */
83130869Skarels 		if (reclen > yc->yc_blksize && bp->b_bcount > yc->yc_blksize) {
83230869Skarels 			yc->yc_blksize = reclen;
83330869Skarels 			if (reclen > cy->cy_bs)
83430869Skarels 				vm->um_tab.b_errcnt++;
83530869Skarels 			yc->yc_blkno++;
83630869Skarels 			goto opcont;
83730869Skarels 		}
83824000Ssam 	}
83925979Ssam 	/*
84025979Ssam 	 * Advance tape control FSM.
84125979Ssam 	 */
84225979Ssam ignoreerr:
84325979Ssam 	/*
84425979Ssam 	 * If we hit a tape mark update our position.
84525979Ssam 	 */
84625979Ssam 	if (yc->yc_status&CYS_FM && bp->b_flags&B_READ) {
84725979Ssam 		cyseteof(bp);
84825979Ssam 		goto opdone;
84925675Ssam 	}
85025979Ssam 	switch (state) {
85124000Ssam 
85225979Ssam 	case SIO:
85325979Ssam 		/*
85425979Ssam 		 * Read/write increments tape block number.
85525979Ssam 		 */
85625979Ssam 		yc->yc_blkno++;
85730371Skarels 		yc->yc_blks++;
85830371Skarels 		if (vm->um_tab.b_errcnt || yc->yc_status & CYS_CR)
85930371Skarels 			yc->yc_softerrs++;
86030371Skarels 		yc->yc_blksize = htoms(cy->cy_tpb.tpcount);
86130371Skarels 		dlog((LOG_ERR, "blocksize %d", yc->yc_blksize));
86225979Ssam 		goto opdone;
86324000Ssam 
86425979Ssam 	case SCOM:
86525979Ssam 		/*
86625979Ssam 		 * For forward/backward space record update current position.
86725979Ssam 		 */
86830294Ssam 		if (bp == &ccybuf[CYUNIT(bp->b_dev)])
86930294Ssam 			switch ((int)bp->b_command) {
87024000Ssam 
87130294Ssam 			case CY_SFORW:
87230294Ssam 				yc->yc_blkno -= bp->b_repcnt;
87330294Ssam 				break;
87424000Ssam 
87530294Ssam 			case CY_SREV:
87630294Ssam 				yc->yc_blkno += bp->b_repcnt;
87730294Ssam 				break;
87830294Ssam 			}
87925979Ssam 		goto opdone;
88025979Ssam 
88125979Ssam 	case SSEEK:
88230719Skarels 		yc->yc_blkno = bp->b_blkno;
88325979Ssam 		goto opcont;
88424000Ssam 
88525979Ssam 	case SERASE:
88625979Ssam 		/*
88725979Ssam 		 * Completed erase of the inter-record gap due to a
88825979Ssam 		 * write error; now retry the write operation.
88925979Ssam 		 */
89025979Ssam 		vm->um_tab.b_active = SERASED;
89125979Ssam 		goto opcont;
89224000Ssam 	}
89325675Ssam 
89425979Ssam opdone:
89525979Ssam 	/*
89625979Ssam 	 * Reset error count and remove from device queue.
89725979Ssam 	 */
89825979Ssam 	vm->um_tab.b_errcnt = 0;
89925979Ssam 	dp->b_actf = bp->av_forw;
90025979Ssam 	/*
90125979Ssam 	 * Save resid and release resources.
90225979Ssam 	 */
90325979Ssam 	bp->b_resid = bp->b_bcount - htoms(cy->cy_tpb.tpcount);
90430719Skarels 	if (bp != &ccybuf[cyunit])
90530719Skarels 		vbadone(bp, &cy->cy_rbuf);
90630371Skarels 	biodone(bp);
90725979Ssam 	/*
90825979Ssam 	 * Circulate slave to end of controller
90925979Ssam 	 * queue to give other slaves a chance.
91025979Ssam 	 */
91125979Ssam 	vm->um_tab.b_actf = dp->b_forw;
91225979Ssam 	if (dp->b_actf) {
91325979Ssam 		dp->b_forw = NULL;
91425979Ssam 		if (vm->um_tab.b_actf == NULL)
91525979Ssam 			vm->um_tab.b_actf = dp;
91625979Ssam 		else
91725979Ssam 			vm->um_tab.b_actl->b_forw = dp;
91824000Ssam 	}
91925979Ssam 	if (vm->um_tab.b_actf == 0)
92024000Ssam 		return;
92125979Ssam opcont:
92225979Ssam 	cystart(vm);
92324000Ssam }
92424000Ssam 
92525979Ssam cytimer(dev)
92625979Ssam 	int dev;
92724000Ssam {
92825979Ssam 	register struct yc_softc *yc = &yc_softc[YCUNIT(dev)];
92925979Ssam 	int s;
93024000Ssam 
93130371Skarels 	if (yc->yc_openf == 0 && yc->yc_timo == INF) {
93230371Skarels 		yc->yc_tact = 0;
93330371Skarels 		return;
93430371Skarels 	}
93525979Ssam 	if (yc->yc_timo != INF && (yc->yc_timo -= 5) < 0) {
93625979Ssam 		printf("yc%d: lost interrupt\n", YCUNIT(dev));
93725979Ssam 		yc->yc_timo = INF;
93825979Ssam 		s = spl3();
93925979Ssam 		cyintr(CYUNIT(dev));
94025979Ssam 		splx(s);
94124000Ssam 	}
94225979Ssam 	timeout(cytimer, (caddr_t)dev, 5*hz);
94324000Ssam }
94424000Ssam 
94525979Ssam cyseteof(bp)
94625979Ssam 	register struct buf *bp;
94724000Ssam {
94825979Ssam 	register int cyunit = CYUNIT(bp->b_dev);
94925979Ssam 	register struct cy_softc *cy = &cy_softc[cyunit];
95025979Ssam 	register struct yc_softc *yc = &yc_softc[YCUNIT(bp->b_dev)];
95124000Ssam 
95225979Ssam 	if (bp == &ccybuf[cyunit]) {
95330719Skarels 		if (yc->yc_blkno > bp->b_blkno) {
95425979Ssam 			/* reversing */
95530719Skarels 			yc->yc_nxrec = bp->b_blkno - htoms(cy->cy_tpb.tpcount);
95625979Ssam 			yc->yc_blkno = yc->yc_nxrec;
95725979Ssam 		} else {
95830719Skarels 			yc->yc_blkno = bp->b_blkno + htoms(cy->cy_tpb.tpcount);
95925979Ssam 			yc->yc_nxrec = yc->yc_blkno - 1;
96024000Ssam 		}
96125675Ssam 		return;
96225675Ssam 	}
96325979Ssam 	/* eof on read */
96430719Skarels 	yc->yc_nxrec = bp->b_blkno;
96524000Ssam }
96624000Ssam 
96725675Ssam /*ARGSUSED*/
96825675Ssam cyioctl(dev, cmd, data, flag)
96925979Ssam 	caddr_t data;
97025675Ssam 	dev_t dev;
97125675Ssam {
97225979Ssam 	int ycunit = YCUNIT(dev);
97325979Ssam 	register struct yc_softc *yc = &yc_softc[ycunit];
97425979Ssam 	register struct buf *bp = &ccybuf[CYUNIT(dev)];
97525979Ssam 	register callcount;
97625979Ssam 	int fcount, op;
97725979Ssam 	struct mtop *mtop;
97825979Ssam 	struct mtget *mtget;
97925979Ssam 	/* we depend of the values and order of the MT codes here */
98025979Ssam 	static cyops[] =
98130371Skarels 	{CY_WEOF,CY_FSF,CY_BSF,CY_SFORW,CY_SREV,CY_REW,CY_OFFL,CY_SENSE};
98225675Ssam 
98325675Ssam 	switch (cmd) {
98425675Ssam 
98525979Ssam 	case MTIOCTOP:	/* tape operation */
98625979Ssam 		mtop = (struct mtop *)data;
98725979Ssam 		switch (op = mtop->mt_op) {
98825675Ssam 
98925979Ssam 		case MTWEOF:
99030371Skarels 			callcount = mtop->mt_count;
99130371Skarels 			fcount = 1;
99230371Skarels 			break;
99330371Skarels 
99425979Ssam 		case MTFSR: case MTBSR:
99530371Skarels 			callcount = 1;
99630371Skarels 			fcount = mtop->mt_count;
99730371Skarels 			break;
99830371Skarels 
99925979Ssam 		case MTFSF: case MTBSF:
100025979Ssam 			callcount = mtop->mt_count;
100125979Ssam 			fcount = 1;
100225979Ssam 			break;
100325675Ssam 
100425979Ssam 		case MTREW: case MTOFFL: case MTNOP:
100525979Ssam 			callcount = 1;
100625979Ssam 			fcount = 1;
100725979Ssam 			break;
100825675Ssam 
100925979Ssam 		default:
101025979Ssam 			return (ENXIO);
101125979Ssam 		}
101225979Ssam 		if (callcount <= 0 || fcount <= 0)
101325979Ssam 			return (EINVAL);
101425979Ssam 		while (--callcount >= 0) {
101530371Skarels #ifdef notdef
101625979Ssam 			/*
101725979Ssam 			 * Gagh, this controller is the pits...
101825979Ssam 			 */
101925979Ssam 			if (op == MTFSF || op == MTBSF) {
102025979Ssam 				do
102125979Ssam 					cycommand(dev, cyops[op], 1);
102225979Ssam 				while ((bp->b_flags&B_ERROR) == 0 &&
102325979Ssam 				 (yc->yc_status&(CYS_EOT|CYS_BOT|CYS_FM)) == 0);
102425979Ssam 			} else
102530371Skarels #endif
102625979Ssam 				cycommand(dev, cyops[op], fcount);
102730371Skarels 			dlog((LOG_INFO,
102830371Skarels 			    "cyioctl: status %x, b_flags %x, resid %d\n",
102930371Skarels 			    yc->yc_status, bp->b_flags, bp->b_resid));
103025979Ssam 			if ((bp->b_flags&B_ERROR) ||
103125979Ssam 			    (yc->yc_status&(CYS_BOT|CYS_EOT)))
103225979Ssam 				break;
103325979Ssam 		}
103425979Ssam 		bp->b_resid = callcount + 1;
1035*37638Smckusick 		/*
1036*37638Smckusick 		 * Pick up the device's error number and pass it
1037*37638Smckusick 		 * to the user; if there is an error but the number
1038*37638Smckusick 		 * is 0 set a generalized code.
1039*37638Smckusick 		 */
1040*37638Smckusick 		if ((bp->b_flags & B_ERROR) == 0)
1041*37638Smckusick 			return (0);
1042*37638Smckusick 		if (bp->b_error)
1043*37638Smckusick 			return (bp->b_error);
1044*37638Smckusick 		return (EIO);
104525979Ssam 
104625979Ssam 	case MTIOCGET:
104725979Ssam 		cycommand(dev, CY_SENSE, 1);
104825979Ssam 		mtget = (struct mtget *)data;
104925979Ssam 		mtget->mt_dsreg = yc->yc_status;
105025979Ssam 		mtget->mt_erreg = yc->yc_control;
105125979Ssam 		mtget->mt_resid = yc->yc_resid;
105225979Ssam 		mtget->mt_type = MT_ISCY;
105325675Ssam 		break;
105425675Ssam 
105525675Ssam 	default:
105625675Ssam 		return (ENXIO);
105725675Ssam 	}
105825675Ssam 	return (0);
105925675Ssam }
106025675Ssam 
106125675Ssam /*
106225675Ssam  * Poll until the controller is ready.
106325675Ssam  */
106425675Ssam cywait(cp)
106525979Ssam 	register struct cyccb *cp;
106624000Ssam {
106725675Ssam 	register int i = 5000;
106824000Ssam 
106925979Ssam 	uncache(&cp->cbgate);
107025979Ssam 	while (i-- > 0 && cp->cbgate == GATE_CLOSED) {
107124000Ssam 		DELAY(1000);
107225979Ssam 		uncache(&cp->cbgate);
107324000Ssam 	}
107425675Ssam 	return (i <= 0);
107524000Ssam }
107624000Ssam 
107725675Ssam /*
107830371Skarels  * Load a 20 bit pointer into a Tapemaster pointer.
107925675Ssam  */
108030371Skarels cyldmba(reg, value)
108134487Skarels 	register u_char *reg;
108225979Ssam 	caddr_t value;
108324000Ssam {
108425979Ssam 	register int v = (int)value;
108525675Ssam 
108625979Ssam 	*reg++ = v;
108725979Ssam 	*reg++ = v >> 8;
108825979Ssam 	*reg++ = 0;
108925979Ssam 	*reg = (v&0xf0000) >> 12;
109024000Ssam }
109124000Ssam 
109225675Ssam /*
109325675Ssam  * Unconditionally reset all controllers to their initial state.
109425675Ssam  */
109525675Ssam cyreset(vba)
109625675Ssam 	int vba;
109724000Ssam {
109825675Ssam 	register caddr_t addr;
109925675Ssam 	register int ctlr;
110024000Ssam 
110125675Ssam 	for (ctlr = 0; ctlr < NCY; ctlr++)
110225675Ssam 		if (cyminfo[ctlr] && cyminfo[ctlr]->um_vbanum == vba) {
110325675Ssam 			addr = cyminfo[ctlr]->um_addr;
110425675Ssam 			CY_RESET(addr);
110530371Skarels 			if (!cyinit(ctlr, addr)) {
110625675Ssam 				printf("cy%d: reset failed\n", ctlr);
110725675Ssam 				cyminfo[ctlr] = NULL;
110825675Ssam 			}
110925675Ssam 		}
111024000Ssam }
111125979Ssam 
111225979Ssam cyuncachetpb(cy)
111325979Ssam 	struct cy_softc *cy;
111425979Ssam {
111525979Ssam 	register long *lp = (long *)&cy->cy_tpb;
111625979Ssam 	register int i;
111725979Ssam 
111825979Ssam 	for (i = 0; i < howmany(sizeof (struct cytpb), sizeof (long)); i++)
111925979Ssam 		uncache(lp++);
112025979Ssam }
112125979Ssam 
112225979Ssam /*
112325979Ssam  * Dump routine.
112425979Ssam  */
112530869Skarels #define	DUMPREC	(32*1024)
112625979Ssam cydump(dev)
112725979Ssam 	dev_t dev;
112825979Ssam {
112925979Ssam 	register struct cy_softc *cy;
113025979Ssam 	register int bs, num, start;
113125979Ssam 	register caddr_t addr;
113230294Ssam 	int unit = CYUNIT(dev), error;
113325979Ssam 
113425979Ssam 	if (unit >= NCY || cyminfo[unit] == 0 ||
113525979Ssam 	    (cy = &cy_softc[unit])->cy_bs == 0 || YCUNIT(dev) >= NYC)
113625979Ssam 		return (ENXIO);
113725979Ssam 	if (cywait(&cy->cy_ccb))
113825979Ssam 		return (EFAULT);
113925979Ssam #define	phys(a)	((caddr_t)((int)(a)&~0xc0000000))
114030294Ssam 	addr = phys(cyminfo[unit]->um_addr);
114125979Ssam 	num = maxfree, start = NBPG*2;
114225979Ssam 	while (num > 0) {
114330869Skarels 		bs = num > btoc(DUMPREC) ? btoc(DUMPREC) : num;
114425979Ssam 		error = cydwrite(cy, start, bs, addr);
114525979Ssam 		if (error)
114625979Ssam 			return (error);
114725979Ssam 		start += bs, num -= bs;
114825979Ssam 	}
114925979Ssam 	cyweof(cy, addr);
115025979Ssam 	cyweof(cy, addr);
115125979Ssam 	uncache(&cy->cy_tpb);
115225979Ssam 	if (cy->cy_tpb.tpstatus&CYS_ERR)
115325979Ssam 		return (EIO);
115425979Ssam 	cyrewind(cy, addr);
115525979Ssam 	return (0);
115625979Ssam }
115725979Ssam 
115825979Ssam cydwrite(cy, pf, npf, addr)
115925979Ssam 	register struct cy_softc *cy;
116025979Ssam 	int pf, npf;
116125979Ssam 	caddr_t addr;
116225979Ssam {
116325979Ssam 
116425979Ssam 	cy->cy_tpb.tpcmd = CY_WCOM;
116525979Ssam 	cy->cy_tpb.tpcontrol = CYCW_LOCK|CYCW_25IPS|CYCW_16BITS;
116625979Ssam 	cy->cy_tpb.tpstatus = 0;
116725979Ssam 	cy->cy_tpb.tpsize = htoms(npf*NBPG);
116825979Ssam 	cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
116925979Ssam 	cyldmba(cy->cy_tpb.tpdata, (caddr_t)(pf*NBPG));
117025979Ssam 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
117125979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
117225979Ssam 	CY_GO(addr);
117325979Ssam 	if (cywait(&cy->cy_ccb))
117425979Ssam 		return (EFAULT);
117525979Ssam 	uncache(&cy->cy_tpb);
117625979Ssam 	if (cy->cy_tpb.tpstatus&CYS_ERR)
117725979Ssam 		return (EIO);
117825979Ssam 	return (0);
117925979Ssam }
118025979Ssam 
118125979Ssam cyweof(cy, addr)
118225979Ssam 	register struct cy_softc *cy;
118325979Ssam 	caddr_t addr;
118425979Ssam {
118525979Ssam 
118625979Ssam 	cy->cy_tpb.tpcmd = CY_WEOF;
118725979Ssam 	cy->cy_tpb.tpcount = htoms(1);
118825979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
118925979Ssam 	CY_GO(addr);
119025979Ssam 	(void) cywait(&cy->cy_ccb);
119125979Ssam }
119225979Ssam 
119325979Ssam cyrewind(cy, addr)
119425979Ssam 	register struct cy_softc *cy;
119525979Ssam 	caddr_t addr;
119625979Ssam {
119725979Ssam 
119825979Ssam 	cy->cy_tpb.tpcmd = CY_REW;
119925979Ssam 	cy->cy_tpb.tpcount = htoms(1);
120025979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
120125979Ssam 	CY_GO(addr);
120225979Ssam 	(void) cywait(&cy->cy_ccb);
120325979Ssam }
120424000Ssam #endif
1205