xref: /csrg-svn/sys/tahoe/vba/cy.c (revision 30872)
1*30872Skarels /*	cy.c	1.13	87/04/09	*/
224000Ssam 
325979Ssam #include "yc.h"
425675Ssam #if NCY > 0
524000Ssam /*
625675Ssam  * Cipher Tapemaster driver.
724000Ssam  */
830371Skarels #define CYDEBUG
930371Skarels #ifdef	CYDEBUG
1025675Ssam int	cydebug = 0;
1130371Skarels #define	dlog(params)	if (cydebug) log params
1230371Skarels #else
1330371Skarels #define dlog(params)	/* */
1430371Skarels #endif
1524000Ssam 
1625675Ssam #include "param.h"
1725675Ssam #include "systm.h"
1825675Ssam #include "vm.h"
1925675Ssam #include "buf.h"
2025675Ssam #include "file.h"
2125675Ssam #include "dir.h"
2225675Ssam #include "user.h"
2325675Ssam #include "proc.h"
2425675Ssam #include "signal.h"
2525675Ssam #include "uio.h"
2625675Ssam #include "ioctl.h"
2725675Ssam #include "mtio.h"
2825675Ssam #include "errno.h"
2925675Ssam #include "cmap.h"
3025979Ssam #include "kernel.h"
3125979Ssam #include "syslog.h"
3230294Ssam #include "tty.h"
3324000Ssam 
3429952Skarels #include "../tahoe/cpu.h"
3529952Skarels #include "../tahoe/mtpr.h"
3629952Skarels #include "../tahoe/pte.h"
3729952Skarels 
3825675Ssam #include "../tahoevba/vbavar.h"
3925979Ssam #define	CYERROR
4025675Ssam #include "../tahoevba/cyreg.h"
4124000Ssam 
4225979Ssam /*
4325979Ssam  * There is a ccybuf per tape controller.
4425979Ssam  * It is used as the token to pass to the internal routines
4525979Ssam  * to execute tape ioctls, and also acts as a lock on the slaves
4625979Ssam  * on the controller, since there is only one per controller.
4725979Ssam  * In particular, when the tape is rewinding on close we release
4825979Ssam  * the user process but any further attempts to use the tape drive
4925979Ssam  * before the rewind completes will hang waiting for ccybuf.
5025979Ssam  */
5125979Ssam struct	buf ccybuf[NCY];
5224000Ssam 
5325979Ssam /*
5425979Ssam  * Raw tape operations use rcybuf.  The driver notices when
5525979Ssam  * rcybuf is being used and allows the user program to contine
5625979Ssam  * after errors and read records not of the standard length.
5725979Ssam  */
5825979Ssam struct	buf rcybuf[NCY];
5924000Ssam 
6025979Ssam int	cyprobe(), cyslave(), cyattach();
6125979Ssam struct	buf ycutab[NYC];
6225979Ssam short	yctocy[NYC];
6325675Ssam struct	vba_ctlr *cyminfo[NCY];
6425979Ssam struct	vba_device *ycdinfo[NYC];
6525857Ssam long	cystd[] = { 0 };
6625857Ssam struct	vba_driver cydriver =
6725979Ssam    { cyprobe, cyslave, cyattach, 0, cystd, "yc", ycdinfo, "cy", cyminfo };
6824000Ssam 
6925979Ssam /* bits in minor device */
7025979Ssam #define	YCUNIT(dev)	(minor(dev)&03)
7125979Ssam #define	CYUNIT(dev)	(yctocy[YCUNIT(dev)])
7225979Ssam #define	T_NOREWIND	0x04
7330371Skarels #define	T_1600BPI	0x00		/* pseudo */
7430371Skarels #define	T_3200BPI	0x08		/* unused */
7525979Ssam 
7625979Ssam #define	INF	1000000L		/* close to infinity */
7725979Ssam 
7824000Ssam /*
7925979Ssam  * Software state and shared command areas per controller.
8025979Ssam  *
8130719Skarels  * The i/o intermediate buffer must be allocated in startup()
8230719Skarels  * so its address will fit in 20-bits (YECH!!!!!!!!!!!!!!).
8324000Ssam  */
8425979Ssam struct cy_softc {
8525979Ssam 	int	cy_bs;		/* controller's buffer size */
8625979Ssam 	struct	cyscp *cy_scp;	/* system configuration block address */
8725979Ssam 	struct	cyccb cy_ccb;	/* channel control block */
8825979Ssam 	struct	cyscb cy_scb;	/* system configuration block */
8925979Ssam 	struct	cytpb cy_tpb;	/* tape parameter block */
9025979Ssam 	struct	cytpb cy_nop;	/* nop parameter block for cyintr */
9130719Skarels 	struct	vb_buf cy_rbuf;	/* vba resources */
9225979Ssam } cy_softc[NCY];
9324000Ssam 
9425979Ssam /*
9525979Ssam  * Software state per tape transport.
9625979Ssam  */
9725979Ssam struct	yc_softc {
9825979Ssam 	char	yc_openf;	/* lock against multiple opens */
9925979Ssam 	char	yc_lastiow;	/* last operation was a write */
10025979Ssam 	short	yc_tact;	/* timeout is active */
10125979Ssam 	long	yc_timo;	/* time until timeout expires */
10225979Ssam 	u_short	yc_control;	/* copy of last tpcb.tpcontrol */
10325979Ssam 	u_short	yc_status;	/* copy of last tpcb.tpstatus */
10425979Ssam 	u_short	yc_resid;	/* copy of last bc */
10525979Ssam 	u_short	yc_dens;	/* prototype control word with density info */
10625979Ssam 	struct	tty *yc_ttyp;	/* user's tty for errors */
10725979Ssam 	daddr_t	yc_blkno;	/* block number, for block device tape */
10825979Ssam 	daddr_t	yc_nxrec;	/* position of end of tape, if known */
10930371Skarels 	int	yc_blksize;	/* current tape blocksize estimate */
11030371Skarels 	int	yc_blks;	/* number of I/O operations since open */
11130371Skarels 	int	yc_softerrs;	/* number of soft I/O errors since open */
11225979Ssam } yc_softc[NYC];
11324000Ssam 
11424000Ssam /*
11525979Ssam  * States for vm->um_tab.b_active, the per controller state flag.
11625979Ssam  * This is used to sequence control in the driver.
11724000Ssam  */
11825979Ssam #define	SSEEK	1		/* seeking */
11925979Ssam #define	SIO	2		/* doing seq i/o */
12025979Ssam #define	SCOM	3		/* sending control command */
12125979Ssam #define	SREW	4		/* sending a rewind */
12225979Ssam #define	SERASE	5		/* erase inter-record gap */
12325979Ssam #define	SERASED	6		/* erased inter-record gap */
12424000Ssam 
12525979Ssam /* there's no way to figure these out dynamically? -- yech */
12625979Ssam struct	cyscp *cyscp[] =
12725979Ssam     { (struct cyscp *)0xc0000c06, (struct cyscp *)0xc0000c16 };
12825979Ssam #define	NCYSCP	(sizeof (cyscp) / sizeof (cyscp[0]))
12925979Ssam 
13025857Ssam cyprobe(reg, vm)
13125857Ssam 	caddr_t reg;
13225857Ssam 	struct vba_ctlr *vm;
13325675Ssam {
13425857Ssam 	register br, cvec;			/* must be r12, r11 */
13530371Skarels 	register struct cy_softc *cy;
13630371Skarels 	int ctlr = vm->um_ctlr;
13725675Ssam 
13830294Ssam #ifdef lint
13930294Ssam 	br = 0; cvec = br; br = cvec;
14030294Ssam 	cyintr(0);
14130294Ssam #endif
14225857Ssam 	if (badcyaddr(reg+1))
14325675Ssam 		return (0);
14430371Skarels 	if (ctlr > NCYSCP || cyscp[ctlr] == 0)		/* XXX */
14530371Skarels 		return (0);
14630371Skarels 	cy = &cy_softc[ctlr];
14730371Skarels 	cy->cy_scp = cyscp[ctlr];			/* XXX */
14825979Ssam 	/*
14925979Ssam 	 * Tapemaster controller must have interrupt handler
15025979Ssam 	 * disable interrupt, so we'll just kludge things
15125979Ssam 	 * (stupid multibus non-vectored interrupt crud).
15225979Ssam 	 */
15330371Skarels 	if (cyinit(ctlr, reg)) {
15430371Skarels 		uncache(&cy->cy_tpb.tpcount);
15530371Skarels 		cy->cy_bs = htoms(cy->cy_tpb.tpcount);
15630371Skarels 		/*
15730371Skarels 		 * Setup nop parameter block for clearing interrupts.
15830371Skarels 		 */
15930371Skarels 		cy->cy_nop.tpcmd = CY_NOP;
16030371Skarels 		cy->cy_nop.tpcontrol = 0;
16130371Skarels 		/*
16230371Skarels 		 * Allocate page tables.
16330371Skarels 		 */
16430719Skarels 		if (cybuf == 0) {
16530719Skarels 			printf("no cy buffer!!!\n");
16630719Skarels 			return (0);
16730719Skarels 		}
16830719Skarels 		cy->cy_rbuf.vb_rawbuf = cybuf + ctlr * CYMAXIO;
16930719Skarels 		vbainit(&cy->cy_rbuf, CYMAXIO, VB_20BIT);
17030371Skarels 
17130371Skarels 		br = 0x13, cvec = 0x80;			/* XXX */
17230371Skarels 		return (sizeof (struct cyccb));
17330371Skarels 	} else
17430371Skarels 		return (0);
17525675Ssam }
17625675Ssam 
17724000Ssam /*
17825857Ssam  * Check to see if a drive is attached to a controller.
17925857Ssam  * Since we can only tell that a drive is there if a tape is loaded and
18025857Ssam  * the drive is placed online, we always indicate the slave is present.
18124000Ssam  */
18225857Ssam cyslave(vi, addr)
18325857Ssam 	struct vba_device *vi;
18425857Ssam 	caddr_t addr;
18524000Ssam {
18625857Ssam 
18725857Ssam #ifdef lint
18825857Ssam 	vi = vi; addr = addr;
18925857Ssam #endif
19025857Ssam 	return (1);
19125857Ssam }
19225857Ssam 
19325857Ssam cyattach(vi)
19425857Ssam 	struct vba_device *vi;
19525857Ssam {
19625979Ssam 	register struct cy_softc *cy;
19725979Ssam 	int ctlr = vi->ui_mi->um_ctlr;
19825857Ssam 
19925979Ssam 	yctocy[vi->ui_unit] = ctlr;
20025979Ssam 	cy = &cy_softc[ctlr];
20130371Skarels 	if (vi->ui_slave == 0 && cy->cy_bs)
20230371Skarels 		printf("; %dkb buffer", cy->cy_bs/1024);
20325857Ssam }
20425857Ssam 
20525857Ssam /*
20625857Ssam  * Initialize the controller after a controller reset or
20725857Ssam  * during autoconfigure.  All of the system control blocks
20825857Ssam  * are initialized and the controller is asked to configure
20925857Ssam  * itself for later use.
21025857Ssam  */
21130371Skarels cyinit(ctlr, addr)
21225979Ssam 	int ctlr;
21330371Skarels 	register caddr_t addr;
21425857Ssam {
21525979Ssam 	register struct cy_softc *cy = &cy_softc[ctlr];
21625675Ssam 	register int *pte;
21724000Ssam 
21824000Ssam 	/*
21925675Ssam 	 * Initialize the system configuration pointer.
22024000Ssam 	 */
22125675Ssam 	/* make kernel writable */
22230719Skarels 	pte = (int *)&Sysmap[btop((int)cy->cy_scp &~ KERNBASE)];
22325675Ssam 	*pte &= ~PG_PROT; *pte |= PG_KW;
22425979Ssam 	mtpr(TBIS, cy->cy_scp);
22525675Ssam 	/* load the correct values in the scp */
22625979Ssam 	cy->cy_scp->csp_buswidth = CSP_16BITS;
22725979Ssam 	cyldmba(cy->cy_scp->csp_scb, (caddr_t)&cy->cy_scb);
22825675Ssam 	/* put it back to read-only */
22925675Ssam 	*pte &= ~PG_PROT; *pte |= PG_KR;
23025979Ssam 	mtpr(TBIS, cy->cy_scp);
23125675Ssam 
23224000Ssam 	/*
23325675Ssam 	 * Init system configuration block.
23424000Ssam 	 */
23530371Skarels 	cy->cy_scb.csb_fixed = CSB_FIXED;
23625675Ssam 	/* set pointer to the channel control block */
23725979Ssam 	cyldmba(cy->cy_scb.csb_ccb, (caddr_t)&cy->cy_ccb);
23825675Ssam 
23924000Ssam 	/*
24025675Ssam 	 * Initialize the chanel control block.
24124000Ssam 	 */
24225979Ssam 	cy->cy_ccb.cbcw = CBCW_CLRINT;
24325979Ssam 	cy->cy_ccb.cbgate = GATE_OPEN;
24425675Ssam 	/* set pointer to the tape parameter block */
24525979Ssam 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
24625675Ssam 
24724000Ssam 	/*
24825979Ssam 	 * Issue a nop cmd and get the internal buffer size for buffered i/o.
24924000Ssam 	 */
25025979Ssam 	cy->cy_tpb.tpcmd = CY_NOP;
25125979Ssam 	cy->cy_tpb.tpcontrol = CYCW_16BITS;
25225979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
25325979Ssam 	CY_GO(addr);
25425979Ssam 	if (cywait(&cy->cy_ccb) || (cy->cy_tpb.tpstatus&CYS_ERR)) {
25525979Ssam 		uncache(&cy->cy_tpb.tpstatus);
25625979Ssam 		printf("cy%d: timeout or err during init, status=%b\n", ctlr,
25725979Ssam 		    cy->cy_tpb.tpstatus, CYS_BITS);
25825675Ssam 		return (0);
25925675Ssam 	}
26025979Ssam 	cy->cy_tpb.tpcmd = CY_CONFIG;
26125979Ssam 	cy->cy_tpb.tpcontrol = CYCW_16BITS;
26225979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
26325979Ssam 	CY_GO(addr);
26425979Ssam 	if (cywait(&cy->cy_ccb) || (cy->cy_tpb.tpstatus&CYS_ERR)) {
26525979Ssam 		uncache(&cy->cy_tpb.tpstatus);
26625979Ssam 		printf("cy%d: configuration failure, status=%b\n", ctlr,
26725979Ssam 		    cy->cy_tpb.tpstatus, CYS_BITS);
26825675Ssam 		return (0);
26925675Ssam 	}
27025675Ssam 	return (1);
27124000Ssam }
27224000Ssam 
27325979Ssam int	cytimer();
27425979Ssam /*
27525979Ssam  * Open the device.  Tapes are unique open
27625979Ssam  * devices, so we refuse if it is already open.
27725979Ssam  * We also check that a tape is available, and
27825979Ssam  * don't block waiting here; if you want to wait
27925979Ssam  * for a tape you should timeout in user code.
28025979Ssam  */
28125675Ssam cyopen(dev, flag)
28225979Ssam 	dev_t dev;
28325675Ssam 	register int flag;
28425675Ssam {
28525979Ssam 	register int ycunit;
28625979Ssam 	register struct vba_device *vi;
28725979Ssam 	register struct yc_softc *yc;
28825979Ssam 	int s;
28925675Ssam 
29025979Ssam 	ycunit = YCUNIT(dev);
29125979Ssam 	if (ycunit >= NYC || (vi = ycdinfo[ycunit]) == 0 || vi->ui_alive == 0)
29225675Ssam 		return (ENXIO);
29325979Ssam 	if ((yc = &yc_softc[ycunit])->yc_openf)
29425979Ssam 		return (EBUSY);
29530371Skarels 	yc->yc_openf = 1;
29625979Ssam #define	PACKUNIT(vi) \
29725979Ssam     (((vi->ui_slave&1)<<11)|((vi->ui_slave&2)<<9)|((vi->ui_slave&4)>>2))
29825979Ssam 	/* no way to select density */
29925979Ssam 	yc->yc_dens = PACKUNIT(vi)|CYCW_IE|CYCW_16BITS;
30030371Skarels 	if (yc->yc_tact == 0) {
30130371Skarels 		yc->yc_timo = INF;
30230371Skarels 		yc->yc_tact = 1;
30330371Skarels 		timeout(cytimer, (caddr_t)dev, 5*hz);
30430371Skarels 	}
30525979Ssam 	cycommand(dev, CY_SENSE, 1);
30625979Ssam 	if ((yc->yc_status&CYS_OL) == 0) {	/* not on-line */
30725979Ssam 		uprintf("yc%d: not online\n", ycunit);
30830439Skarels 		yc->yc_openf = 0;
309*30872Skarels 		return (EIO);
31025675Ssam 	}
31125979Ssam 	if ((flag&FWRITE) && (yc->yc_status&CYS_WP)) {
31225979Ssam 		uprintf("yc%d: no write ring\n", ycunit);
31330439Skarels 		yc->yc_openf = 0;
314*30872Skarels 		return (EIO);
31525675Ssam 	}
31625979Ssam 	yc->yc_blkno = (daddr_t)0;
31725979Ssam 	yc->yc_nxrec = INF;
31825979Ssam 	yc->yc_lastiow = 0;
31930869Skarels 	yc->yc_blksize = CYMAXIO;		/* guess > 0 */
32030371Skarels 	yc->yc_blks = 0;
32130371Skarels 	yc->yc_softerrs = 0;
32225979Ssam 	yc->yc_ttyp = u.u_ttyp;
32325675Ssam 	return (0);
32425675Ssam }
32525675Ssam 
32625979Ssam /*
32725979Ssam  * Close tape device.
32825979Ssam  *
32925979Ssam  * If tape was open for writing or last operation was a write,
33025979Ssam  * then write two EOF's and backspace over the last one.
33125979Ssam  * Unless this is a non-rewinding special file, rewind the tape.
33225979Ssam  * Make the tape available to others.
33325979Ssam  */
33425675Ssam cyclose(dev, flag)
33525979Ssam 	dev_t dev;
33630371Skarels 	int flag;
33725675Ssam {
33830371Skarels 	struct yc_softc *yc = &yc_softc[YCUNIT(dev)];
33925675Ssam 
34025979Ssam 	if (flag == FWRITE || (flag&FWRITE) && yc->yc_lastiow) {
34125979Ssam 		cycommand(dev, CY_WEOF, 2);
34225979Ssam 		cycommand(dev, CY_SREV, 1);
34325675Ssam 	}
34425979Ssam 	if ((minor(dev)&T_NOREWIND) == 0)
34525979Ssam 		/*
34625979Ssam 		 * 0 count means don't hang waiting for rewind complete
34725979Ssam 		 * rather ccybuf stays busy until the operation completes
34825979Ssam 		 * preventing further opens from completing by preventing
34925979Ssam 		 * a CY_SENSE from completing.
35025979Ssam 		 */
35125979Ssam 		cycommand(dev, CY_REW, 0);
35230371Skarels 	if (yc->yc_blks > 10 && yc->yc_softerrs > yc->yc_blks / 10)
35330371Skarels 		log(LOG_INFO, "yc%d: %d soft errors in %d blocks\n",
35430371Skarels 		    YCUNIT(dev), yc->yc_softerrs, yc->yc_blks);
35530371Skarels 	dlog((LOG_INFO, "%d soft errors in %d blocks\n",
35630371Skarels 	    yc->yc_softerrs, yc->yc_blks));
35725979Ssam 	yc->yc_openf = 0;
35830719Skarels 	return (0);
35925675Ssam }
36025675Ssam 
36124000Ssam /*
36225979Ssam  * Execute a command on the tape drive a specified number of times.
36324000Ssam  */
36425979Ssam cycommand(dev, com, count)
36525979Ssam 	dev_t dev;
36625979Ssam 	int com, count;
36724000Ssam {
36825979Ssam 	register struct buf *bp;
36925675Ssam 	int s;
37025675Ssam 
37125979Ssam 	bp = &ccybuf[CYUNIT(dev)];
37225675Ssam 	s = spl3();
37330371Skarels 	dlog((LOG_INFO, "cycommand(%o, %x, %d), b_flags %x\n",
37430371Skarels 	    dev, com, count, bp->b_flags));
37525979Ssam 	while (bp->b_flags&B_BUSY) {
37625979Ssam 		/*
37725979Ssam 		 * This special check is because B_BUSY never
37825979Ssam 		 * gets cleared in the non-waiting rewind case.
37925979Ssam 		 */
38025979Ssam 		if (bp->b_repcnt == 0 && (bp->b_flags&B_DONE))
38125979Ssam 			break;
38225979Ssam 		bp->b_flags |= B_WANTED;
38325979Ssam 		sleep((caddr_t)bp, PRIBIO);
38425675Ssam 	}
38525979Ssam 	bp->b_flags = B_BUSY|B_READ;
38625675Ssam 	splx(s);
38725979Ssam 	bp->b_dev = dev;
38825979Ssam 	bp->b_repcnt = count;
38925979Ssam 	bp->b_command = com;
39025979Ssam 	bp->b_blkno = 0;
39125979Ssam 	cystrategy(bp);
39225979Ssam 	/*
39325979Ssam 	 * In case of rewind from close; don't wait.
39425979Ssam 	 * This is the only case where count can be 0.
39525979Ssam 	 */
39625979Ssam 	if (count == 0)
39725979Ssam 		return;
39830371Skarels 	biowait(bp);
39925979Ssam 	if (bp->b_flags&B_WANTED)
40025979Ssam 		wakeup((caddr_t)bp);
40125979Ssam 	bp->b_flags &= B_ERROR;
40224000Ssam }
40324000Ssam 
40425675Ssam cystrategy(bp)
40525675Ssam 	register struct buf *bp;
40625675Ssam {
40725979Ssam 	int ycunit = YCUNIT(bp->b_dev);
40825979Ssam 	register struct vba_ctlr *vm;
40925979Ssam 	register struct buf *dp;
41025675Ssam 	int s;
41125675Ssam 
41225979Ssam 	/*
41325979Ssam 	 * Put transfer at end of unit queue.
41425979Ssam 	 */
41530371Skarels 	dlog((LOG_INFO, "cystrategy(%o, %x)\n", bp->b_dev, bp->b_command));
41625979Ssam 	dp = &ycutab[ycunit];
41725675Ssam 	bp->av_forw = NULL;
41825979Ssam 	vm = ycdinfo[ycunit]->ui_mi;
41925979Ssam 	/* BEGIN GROT */
42025979Ssam 	if (bp == &rcybuf[CYUNIT(bp->b_dev)]) {
42130869Skarels 		if (bp->b_bcount >= CYMAXIO) {
42225979Ssam 			uprintf("cy%d: i/o size too large\n", vm->um_ctlr);
42330869Skarels 			bp->b_error = EINVAL;
42425979Ssam 			bp->b_resid = bp->b_bcount;
42525979Ssam 			bp->b_flags |= B_ERROR;
42630371Skarels 			biodone(bp);
42725675Ssam 			return;
42825675Ssam 		}
42924000Ssam 	}
43025979Ssam 	/* END GROT */
43125675Ssam 	s = spl3();
43225979Ssam 	if (dp->b_actf == NULL) {
43325979Ssam 		dp->b_actf = bp;
43425979Ssam 		/*
43525979Ssam 		 * Transport not already active...
43625979Ssam 		 * put at end of controller queue.
43725979Ssam 		 */
43825979Ssam 		 dp->b_forw = NULL;
43925979Ssam 		 if (vm->um_tab.b_actf == NULL)
44025979Ssam 			vm->um_tab.b_actf = dp;
44125979Ssam 		else
44225979Ssam 			vm->um_tab.b_actl->b_forw = dp;
44325979Ssam 	} else
44425979Ssam 		dp->b_actl->av_forw = bp;
44525979Ssam 	dp->b_actl = bp;
44625979Ssam 	/*
44725979Ssam 	 * If the controller is not busy, get it going.
44825979Ssam 	 */
44925979Ssam 	if (vm->um_tab.b_active == 0)
45025979Ssam 		cystart(vm);
45124000Ssam 	splx(s);
45224000Ssam }
45324000Ssam 
45424000Ssam /*
45525979Ssam  * Start activity on a cy controller.
45624000Ssam  */
45725979Ssam cystart(vm)
45825979Ssam 	register struct vba_ctlr *vm;
45924000Ssam {
46025979Ssam 	register struct buf *bp, *dp;
46125979Ssam 	register struct yc_softc *yc;
46225979Ssam 	register struct cy_softc *cy;
46325979Ssam 	int ycunit;
46425979Ssam 	daddr_t blkno;
46524000Ssam 
46630371Skarels 	dlog((LOG_INFO, "cystart()\n"));
46725979Ssam 	/*
46825979Ssam 	 * Look for an idle transport on the controller.
46925979Ssam 	 */
47025979Ssam loop:
47125979Ssam 	if ((dp = vm->um_tab.b_actf) == NULL)
47225675Ssam 		return;
47325979Ssam 	if ((bp = dp->b_actf) == NULL) {
47425979Ssam 		vm->um_tab.b_actf = dp->b_forw;
47525979Ssam 		goto loop;
47625675Ssam 	}
47725979Ssam 	ycunit = YCUNIT(bp->b_dev);
47825979Ssam 	yc = &yc_softc[ycunit];
47925979Ssam 	cy = &cy_softc[CYUNIT(bp->b_dev)];
48025979Ssam 	/*
48125979Ssam 	 * Default is that last command was NOT a write command;
48225979Ssam 	 * if we do a write command we will notice this in cyintr().
48325979Ssam 	 */
48425979Ssam 	yc->yc_lastiow = 0;
48525979Ssam 	if (yc->yc_openf < 0 ||
48625979Ssam 	    (bp->b_command != CY_SENSE && (cy->cy_tpb.tpstatus&CYS_OL) == 0)) {
48725979Ssam 		/*
48825979Ssam 		 * Have had a hard error on a non-raw tape
48925979Ssam 		 * or the tape unit is now unavailable (e.g.
49025979Ssam 		 * taken off line).
49125979Ssam 		 */
49230371Skarels 		dlog((LOG_INFO, "openf %d command %x status %b\n",
49330371Skarels 		   yc->yc_openf, bp->b_command, cy->cy_tpb.tpstatus, CYS_BITS));
49425979Ssam 		bp->b_flags |= B_ERROR;
49525979Ssam 		goto next;
49625675Ssam 	}
49725979Ssam 	if (bp == &ccybuf[CYUNIT(bp->b_dev)]) {
49825979Ssam 		/*
49925979Ssam 		 * Execute control operation with the specified count.
50025979Ssam 		 *
50125979Ssam 		 * Set next state; give 5 minutes to complete
50225979Ssam 		 * rewind or file mark search, or 10 seconds per
50325979Ssam 		 * iteration (minimum 60 seconds and max 5 minutes)
50425979Ssam 		 * to complete other ops.
50525979Ssam 		 */
50625979Ssam 		if (bp->b_command == CY_REW) {
50725979Ssam 			vm->um_tab.b_active = SREW;
50825979Ssam 			yc->yc_timo = 5*60;
50930869Skarels 		} else if (bp->b_command == CY_FSF ||
51030869Skarels 		    bp->b_command == CY_BSF) {
51130869Skarels 			vm->um_tab.b_active = SCOM;
51230869Skarels 			yc->yc_timo = 5*60;
51325979Ssam 		} else {
51425979Ssam 			vm->um_tab.b_active = SCOM;
51525979Ssam 			yc->yc_timo = imin(imax(10*(int)bp->b_repcnt,60),5*60);
51625979Ssam 		}
51725979Ssam 		cy->cy_tpb.tprec = htoms(bp->b_repcnt);
51830719Skarels 		dlog((LOG_INFO, "bpcmd "));
51925979Ssam 		goto dobpcmd;
52024000Ssam 	}
52125979Ssam 	/*
52225979Ssam 	 * The following checks handle boundary cases for operation
52325979Ssam 	 * on no-raw tapes.  On raw tapes the initialization of
52425979Ssam 	 * yc->yc_nxrec by cyphys causes them to be skipped normally
52525979Ssam 	 * (except in the case of retries).
52625979Ssam 	 */
52730719Skarels 	if (bp->b_blkno > yc->yc_nxrec) {
52825979Ssam 		/*
52925979Ssam 		 * Can't read past known end-of-file.
53025979Ssam 		 */
53125979Ssam 		bp->b_flags |= B_ERROR;
53225979Ssam 		bp->b_error = ENXIO;
53325979Ssam 		goto next;
53424000Ssam 	}
53530719Skarels 	if (bp->b_blkno == yc->yc_nxrec && bp->b_flags&B_READ) {
53625979Ssam 		/*
53725979Ssam 		 * Reading at end of file returns 0 bytes.
53825979Ssam 		 */
53925979Ssam 		bp->b_resid = bp->b_bcount;
54025979Ssam 		clrbuf(bp);
54125979Ssam 		goto next;
54224000Ssam 	}
54325979Ssam 	if ((bp->b_flags&B_READ) == 0)
54425979Ssam 		/*
54525979Ssam 		 * Writing sets EOF.
54625979Ssam 		 */
54730719Skarels 		yc->yc_nxrec = bp->b_blkno + 1;
54830719Skarels 	if ((blkno = yc->yc_blkno) == bp->b_blkno) {
54925979Ssam 		caddr_t addr;
55025979Ssam 		int cmd;
55125675Ssam 
55225979Ssam 		/*
55325979Ssam 		 * Choose the appropriate i/o command based on the
55430371Skarels 		 * transfer size, the estimated block size,
55530371Skarels 		 * and the controller's internal buffer size.
55630869Skarels 		 * If the request length is longer than the tape
55730869Skarels 		 * block length, a buffered read will fail,
55830869Skarels 		 * thus, we request at most the size that we expect.
55930869Skarels 		 * We then check for larger records when the read completes.
56025979Ssam 		 * If we're retrying a read on a raw device because
56125979Ssam 		 * the original try was a buffer request which failed
56225979Ssam 		 * due to a record length error, then we force the use
56325979Ssam 		 * of the raw controller read (YECH!!!!).
56425979Ssam 		 */
56525979Ssam 		if (bp->b_flags&B_READ) {
56630869Skarels 			if (yc->yc_blksize <= cy->cy_bs &&
56730869Skarels 			    vm->um_tab.b_errcnt == 0)
56830869Skarels 				cmd = CY_BRCOM;
56930869Skarels 			else
57025979Ssam 				cmd = CY_RCOM;
57125979Ssam 		} else {
57225979Ssam 			/*
57325979Ssam 			 * On write error retries erase the
57425979Ssam 			 * inter-record gap before rewriting.
57525979Ssam 			 */
57625979Ssam 			if (vm->um_tab.b_errcnt &&
57725979Ssam 			    vm->um_tab.b_active != SERASED) {
57825979Ssam 				vm->um_tab.b_active = SERASE;
57925979Ssam 				bp->b_command = CY_ERASE;
58025979Ssam 				yc->yc_timo = 60;
58125979Ssam 				goto dobpcmd;
58225675Ssam 			}
58325979Ssam 			cmd = (bp->b_bcount > cy->cy_bs) ? CY_WCOM : CY_BWCOM;
58425675Ssam 		}
58525979Ssam 		vm->um_tab.b_active = SIO;
58630719Skarels 		addr = (caddr_t)vbasetup(bp, &cy->cy_rbuf, 1);
58725979Ssam 		cy->cy_tpb.tpcmd = cmd;
58825979Ssam 		cy->cy_tpb.tpcontrol = yc->yc_dens;
58925979Ssam 		if (cmd == CY_RCOM || cmd == CY_WCOM)
59025979Ssam 			cy->cy_tpb.tpcontrol |= CYCW_LOCK;
59125979Ssam 		cy->cy_tpb.tpstatus = 0;
59225979Ssam 		cy->cy_tpb.tpcount = 0;
59325979Ssam 		cyldmba(cy->cy_tpb.tpdata, (caddr_t)addr);
59425979Ssam 		cy->cy_tpb.tprec = 0;
59530869Skarels 		if (cmd == CY_BRCOM)
59630869Skarels 			cy->cy_tpb.tpsize = htoms(min(yc->yc_blksize,
59730869Skarels 			    bp->b_bcount));
59830371Skarels 		else
59930371Skarels 			cy->cy_tpb.tpsize = htoms(bp->b_bcount);
60025979Ssam 		cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
60125979Ssam 		do
60225979Ssam 			uncache(&cy->cy_ccb.cbgate);
60325979Ssam 		while (cy->cy_ccb.cbgate == GATE_CLOSED);
60425979Ssam 		cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
60525979Ssam 		cy->cy_ccb.cbcw = CBCW_IE;
60625979Ssam 		cy->cy_ccb.cbgate = GATE_CLOSED;
60730371Skarels 		dlog((LOG_INFO, "CY_GO(%x) cmd %x control %x size %d\n",
60825979Ssam 		    vm->um_addr, cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol,
60930371Skarels 		    htoms(cy->cy_tpb.tpsize)));
61025979Ssam 		CY_GO(vm->um_addr);
61125979Ssam 		return;
61224000Ssam 	}
61325979Ssam 	/*
61425979Ssam 	 * Tape positioned incorrectly; set to seek forwards
61525979Ssam 	 * or backwards to the correct spot.  This happens
61625979Ssam 	 * for raw tapes only on error retries.
61725979Ssam 	 */
61825979Ssam 	vm->um_tab.b_active = SSEEK;
61930719Skarels 	if (blkno < bp->b_blkno) {
62025979Ssam 		bp->b_command = CY_SFORW;
62130719Skarels 		cy->cy_tpb.tprec = htoms(bp->b_blkno - blkno);
62225979Ssam 	} else {
62325979Ssam 		bp->b_command = CY_SREV;
62430719Skarels 		cy->cy_tpb.tprec = htoms(blkno - bp->b_blkno);
62524000Ssam 	}
62625979Ssam 	yc->yc_timo = imin(imax(10 * htoms(cy->cy_tpb.tprec), 60), 5*60);
62725979Ssam dobpcmd:
62825979Ssam 	/*
62925979Ssam 	 * Do the command in bp.  Reverse direction commands
63025979Ssam 	 * are indicated by having CYCW_REV or'd into their
63125979Ssam 	 * value.  For these we must set the appropriate bit
63225979Ssam 	 * in the control field.
63325979Ssam 	 */
63425979Ssam 	if (bp->b_command&CYCW_REV) {
63525979Ssam 		cy->cy_tpb.tpcmd = bp->b_command &~ CYCW_REV;
63625979Ssam 		cy->cy_tpb.tpcontrol = yc->yc_dens | CYCW_REV;
63730719Skarels dlog((LOG_INFO, "cmd %x control %x\n", cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol));
63825979Ssam 	} else {
63925979Ssam 		cy->cy_tpb.tpcmd = bp->b_command;
64025979Ssam 		cy->cy_tpb.tpcontrol = yc->yc_dens;
64130719Skarels dlog((LOG_INFO, "cmd %x control %x\n", cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol));
64224000Ssam 	}
64325979Ssam 	cy->cy_tpb.tpstatus = 0;
64425979Ssam 	cy->cy_tpb.tpcount = 0;
64525979Ssam 	cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
64625979Ssam 	do
64725979Ssam 		uncache(&cy->cy_ccb.cbgate);
64825979Ssam 	while (cy->cy_ccb.cbgate == GATE_CLOSED);
64925979Ssam 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
65025979Ssam 	cy->cy_ccb.cbcw = CBCW_IE;
65125979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
65230371Skarels 	dlog((LOG_INFO, "CY_GO(%x) cmd %x control %x rec %d\n",
65325979Ssam 	    vm->um_addr, cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol,
65430371Skarels 	    htoms(cy->cy_tpb.tprec)));
65525979Ssam 	CY_GO(vm->um_addr);
65625979Ssam 	return;
65725979Ssam next:
65825979Ssam 	/*
65925979Ssam 	 * Done with this operation due to error or the
66030719Skarels 	 * fact that it doesn't do anything.
66130719Skarels 	 * Dequeue the transfer and continue
66225979Ssam 	 * processing this slave.
66325979Ssam 	 */
66425979Ssam 	vm->um_tab.b_errcnt = 0;
66525979Ssam 	dp->b_actf = bp->av_forw;
66630371Skarels 	biodone(bp);
66725979Ssam 	goto loop;
66825675Ssam }
66925675Ssam 
67025675Ssam /*
67125979Ssam  * Cy interrupt routine.
67225675Ssam  */
67330719Skarels cyintr(cyunit)
67430719Skarels 	int cyunit;
67525675Ssam {
67625979Ssam 	struct buf *dp;
67724000Ssam 	register struct buf *bp;
67830719Skarels 	register struct vba_ctlr *vm = cyminfo[cyunit];
67925979Ssam 	register struct cy_softc *cy;
68025979Ssam 	register struct yc_softc *yc;
68130719Skarels 	int err;
68225979Ssam 	register state;
68324000Ssam 
68430719Skarels 	dlog((LOG_INFO, "cyintr(%d)\n", cyunit));
68525979Ssam 	/*
68625979Ssam 	 * First, turn off the interrupt from the controller
68725979Ssam 	 * (device uses Multibus non-vectored interrupts...yech).
68825979Ssam 	 */
68925979Ssam 	cy = &cy_softc[vm->um_ctlr];
69025979Ssam 	cy->cy_ccb.cbcw = CBCW_CLRINT;
69130294Ssam 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_nop);
69225979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
69325979Ssam 	CY_GO(vm->um_addr);
69425979Ssam 	if ((dp = vm->um_tab.b_actf) == NULL) {
69530371Skarels 		dlog((LOG_ERR, "cy%d: stray interrupt", vm->um_ctlr));
69624000Ssam 		return;
69724000Ssam 	}
69825979Ssam 	bp = dp->b_actf;
69925979Ssam 	cy = &cy_softc[cyunit];
70025979Ssam 	cyuncachetpb(cy);
70130294Ssam 	yc = &yc_softc[YCUNIT(bp->b_dev)];
70225979Ssam 	/*
70325984Ssam 	 * If last command was a rewind and tape is
70425984Ssam 	 * still moving, wait for the operation to complete.
70525979Ssam 	 */
70625979Ssam 	if (vm->um_tab.b_active == SREW) {
70725979Ssam 		vm->um_tab.b_active = SCOM;
70825979Ssam 		if ((cy->cy_tpb.tpstatus&CYS_RDY) == 0) {
70925979Ssam 			yc->yc_timo = 5*60;	/* 5 minutes */
71025979Ssam 			return;
71124000Ssam 		}
71224000Ssam 	}
71325979Ssam 	/*
71425979Ssam 	 * An operation completed...record status.
71525979Ssam 	 */
71625979Ssam 	yc->yc_timo = INF;
71725979Ssam 	yc->yc_control = cy->cy_tpb.tpcontrol;
71825979Ssam 	yc->yc_status = cy->cy_tpb.tpstatus;
71925979Ssam 	yc->yc_resid = bp->b_bcount - htoms(cy->cy_tpb.tpcount);
72030371Skarels 	dlog((LOG_INFO, "cmd %x control %b status %b resid %d\n",
72125979Ssam 	    cy->cy_tpb.tpcmd, yc->yc_control, CYCW_BITS,
72230371Skarels 	    yc->yc_status, CYS_BITS, yc->yc_resid));
72325979Ssam 	if ((bp->b_flags&B_READ) == 0)
72425979Ssam 		yc->yc_lastiow = 1;
72525979Ssam 	state = vm->um_tab.b_active;
72625979Ssam 	vm->um_tab.b_active = 0;
72725979Ssam 	/*
72825979Ssam 	 * Check for errors.
72925979Ssam 	 */
73025979Ssam 	if (cy->cy_tpb.tpstatus&CYS_ERR) {
73125979Ssam 		err = cy->cy_tpb.tpstatus&CYS_ERR;
73230371Skarels 		dlog((LOG_INFO, "error %d\n", err));
73325979Ssam 		/*
73425979Ssam 		 * If we hit the end of tape file, update our position.
73525979Ssam 		 */
73625979Ssam 		if (err == CYER_FM) {
73725979Ssam 			yc->yc_status |= CYS_FM;
73825979Ssam 			state = SCOM;		/* force completion */
73925979Ssam 			cyseteof(bp);		/* set blkno and nxrec */
74025979Ssam 			goto opdone;
74125979Ssam 		}
74225979Ssam 		/*
74325979Ssam 		 * Fix up errors which occur due to backspacing over
74425979Ssam 		 * the beginning of the tape.
74525979Ssam 		 */
74625979Ssam 		if (err == CYER_BOT && cy->cy_tpb.tpcontrol&CYCW_REV) {
74725979Ssam 			yc->yc_status |= CYS_BOT;
74825979Ssam 			goto ignoreerr;
74925979Ssam 		}
75025979Ssam 		/*
75125979Ssam 		 * If we were reading raw tape and the only error was that the
75225979Ssam 		 * record was too long, then we don't consider this an error.
75325979Ssam 		 */
75425979Ssam 		if (bp == &rcybuf[cyunit] && (bp->b_flags&B_READ) &&
75525979Ssam 		    err == CYER_STROBE) {
75625979Ssam 			/*
75730371Skarels 			 * Retry reads with the command changed to
75830371Skarels 			 * a raw read if necessary.  Setting b_errcnt
75925979Ssam 			 * here causes cystart (above) to force a CY_RCOM.
76025979Ssam 			 */
76130869Skarels 			if (cy->cy_tpb.tpcmd == CY_BRCOM &&
76230719Skarels 			    vm->um_tab.b_errcnt++ == 0) {
76330371Skarels 				yc->yc_blkno++;
76430371Skarels 				goto opcont;
76530371Skarels 			} else
76625979Ssam 				goto ignoreerr;
76725979Ssam 		}
76825979Ssam 		/*
76925979Ssam 		 * If error is not hard, and this was an i/o operation
77025979Ssam 		 * retry up to 8 times.
77125979Ssam 		 */
77225984Ssam 		if (((1<<err)&CYER_SOFT) && state == SIO) {
77325979Ssam 			if (++vm->um_tab.b_errcnt < 7) {
77425979Ssam 				yc->yc_blkno++;
77525979Ssam 				goto opcont;
77625979Ssam 			}
77725979Ssam 		} else
77825979Ssam 			/*
77925979Ssam 			 * Hard or non-i/o errors on non-raw tape
78025979Ssam 			 * cause it to close.
78125979Ssam 			 */
78230371Skarels 			if (yc->yc_openf > 0 && bp != &rcybuf[cyunit])
78325979Ssam 				yc->yc_openf = -1;
78425979Ssam 		/*
78525979Ssam 		 * Couldn't recover from error.
78625979Ssam 		 */
78725979Ssam 		tprintf(yc->yc_ttyp,
78830371Skarels 		    "yc%d: hard error bn%d status=%b, %s\n", YCUNIT(bp->b_dev),
78930371Skarels 		    bp->b_blkno, yc->yc_status, CYS_BITS,
79030371Skarels 		    (err < NCYERROR) ? cyerror[err] : "");
79125979Ssam 		bp->b_flags |= B_ERROR;
79225979Ssam 		goto opdone;
79330869Skarels 	} else if (cy->cy_tpb.tpcmd == CY_BRCOM) {
79430869Skarels 		int reclen = htoms(cy->cy_tpb.tprec);
79530869Skarels 
79630869Skarels 		/*
79730869Skarels 		 * If we did a buffered read, check whether the read
79830869Skarels 		 * was long enough.  If we asked the controller for less
79930869Skarels 		 * than the user asked for because the previous record
80030869Skarels 		 * was shorter, update our notion of record size
80130869Skarels 		 * and retry.  If the record is longer than the buffer,
80230869Skarels 		 * bump the errcnt so the retry will use direct read.
80330869Skarels 		 */
80430869Skarels 		if (reclen > yc->yc_blksize && bp->b_bcount > yc->yc_blksize) {
80530869Skarels 			yc->yc_blksize = reclen;
80630869Skarels 			if (reclen > cy->cy_bs)
80730869Skarels 				vm->um_tab.b_errcnt++;
80830869Skarels 			yc->yc_blkno++;
80930869Skarels 			goto opcont;
81030869Skarels 		}
81124000Ssam 	}
81225979Ssam 	/*
81325979Ssam 	 * Advance tape control FSM.
81425979Ssam 	 */
81525979Ssam ignoreerr:
81625979Ssam 	/*
81725979Ssam 	 * If we hit a tape mark update our position.
81825979Ssam 	 */
81925979Ssam 	if (yc->yc_status&CYS_FM && bp->b_flags&B_READ) {
82025979Ssam 		cyseteof(bp);
82125979Ssam 		goto opdone;
82225675Ssam 	}
82325979Ssam 	switch (state) {
82424000Ssam 
82525979Ssam 	case SIO:
82625979Ssam 		/*
82725979Ssam 		 * Read/write increments tape block number.
82825979Ssam 		 */
82925979Ssam 		yc->yc_blkno++;
83030371Skarels 		yc->yc_blks++;
83130371Skarels 		if (vm->um_tab.b_errcnt || yc->yc_status & CYS_CR)
83230371Skarels 			yc->yc_softerrs++;
83330371Skarels 		yc->yc_blksize = htoms(cy->cy_tpb.tpcount);
83430371Skarels 		dlog((LOG_ERR, "blocksize %d", yc->yc_blksize));
83525979Ssam 		goto opdone;
83624000Ssam 
83725979Ssam 	case SCOM:
83825979Ssam 		/*
83925979Ssam 		 * For forward/backward space record update current position.
84025979Ssam 		 */
84130294Ssam 		if (bp == &ccybuf[CYUNIT(bp->b_dev)])
84230294Ssam 			switch ((int)bp->b_command) {
84324000Ssam 
84430294Ssam 			case CY_SFORW:
84530294Ssam 				yc->yc_blkno -= bp->b_repcnt;
84630294Ssam 				break;
84724000Ssam 
84830294Ssam 			case CY_SREV:
84930294Ssam 				yc->yc_blkno += bp->b_repcnt;
85030294Ssam 				break;
85130294Ssam 			}
85225979Ssam 		goto opdone;
85325979Ssam 
85425979Ssam 	case SSEEK:
85530719Skarels 		yc->yc_blkno = bp->b_blkno;
85625979Ssam 		goto opcont;
85724000Ssam 
85825979Ssam 	case SERASE:
85925979Ssam 		/*
86025979Ssam 		 * Completed erase of the inter-record gap due to a
86125979Ssam 		 * write error; now retry the write operation.
86225979Ssam 		 */
86325979Ssam 		vm->um_tab.b_active = SERASED;
86425979Ssam 		goto opcont;
86524000Ssam 	}
86625675Ssam 
86725979Ssam opdone:
86825979Ssam 	/*
86925979Ssam 	 * Reset error count and remove from device queue.
87025979Ssam 	 */
87125979Ssam 	vm->um_tab.b_errcnt = 0;
87225979Ssam 	dp->b_actf = bp->av_forw;
87325979Ssam 	/*
87425979Ssam 	 * Save resid and release resources.
87525979Ssam 	 */
87625979Ssam 	bp->b_resid = bp->b_bcount - htoms(cy->cy_tpb.tpcount);
87730719Skarels 	if (bp != &ccybuf[cyunit])
87830719Skarels 		vbadone(bp, &cy->cy_rbuf);
87930371Skarels 	biodone(bp);
88025979Ssam 	/*
88125979Ssam 	 * Circulate slave to end of controller
88225979Ssam 	 * queue to give other slaves a chance.
88325979Ssam 	 */
88425979Ssam 	vm->um_tab.b_actf = dp->b_forw;
88525979Ssam 	if (dp->b_actf) {
88625979Ssam 		dp->b_forw = NULL;
88725979Ssam 		if (vm->um_tab.b_actf == NULL)
88825979Ssam 			vm->um_tab.b_actf = dp;
88925979Ssam 		else
89025979Ssam 			vm->um_tab.b_actl->b_forw = dp;
89124000Ssam 	}
89225979Ssam 	if (vm->um_tab.b_actf == 0)
89324000Ssam 		return;
89425979Ssam opcont:
89525979Ssam 	cystart(vm);
89624000Ssam }
89724000Ssam 
89825979Ssam cytimer(dev)
89925979Ssam 	int dev;
90024000Ssam {
90125979Ssam 	register struct yc_softc *yc = &yc_softc[YCUNIT(dev)];
90225979Ssam 	int s;
90324000Ssam 
90430371Skarels 	if (yc->yc_openf == 0 && yc->yc_timo == INF) {
90530371Skarels 		yc->yc_tact = 0;
90630371Skarels 		return;
90730371Skarels 	}
90825979Ssam 	if (yc->yc_timo != INF && (yc->yc_timo -= 5) < 0) {
90925979Ssam 		printf("yc%d: lost interrupt\n", YCUNIT(dev));
91025979Ssam 		yc->yc_timo = INF;
91125979Ssam 		s = spl3();
91225979Ssam 		cyintr(CYUNIT(dev));
91325979Ssam 		splx(s);
91424000Ssam 	}
91525979Ssam 	timeout(cytimer, (caddr_t)dev, 5*hz);
91624000Ssam }
91724000Ssam 
91825979Ssam cyseteof(bp)
91925979Ssam 	register struct buf *bp;
92024000Ssam {
92125979Ssam 	register int cyunit = CYUNIT(bp->b_dev);
92225979Ssam 	register struct cy_softc *cy = &cy_softc[cyunit];
92325979Ssam 	register struct yc_softc *yc = &yc_softc[YCUNIT(bp->b_dev)];
92424000Ssam 
92525979Ssam 	if (bp == &ccybuf[cyunit]) {
92630719Skarels 		if (yc->yc_blkno > bp->b_blkno) {
92725979Ssam 			/* reversing */
92830719Skarels 			yc->yc_nxrec = bp->b_blkno - htoms(cy->cy_tpb.tpcount);
92925979Ssam 			yc->yc_blkno = yc->yc_nxrec;
93025979Ssam 		} else {
93130719Skarels 			yc->yc_blkno = bp->b_blkno + htoms(cy->cy_tpb.tpcount);
93225979Ssam 			yc->yc_nxrec = yc->yc_blkno - 1;
93324000Ssam 		}
93425675Ssam 		return;
93525675Ssam 	}
93625979Ssam 	/* eof on read */
93730719Skarels 	yc->yc_nxrec = bp->b_blkno;
93824000Ssam }
93924000Ssam 
94025979Ssam cyread(dev, uio)
94125979Ssam 	dev_t dev;
94225979Ssam 	struct uio *uio;
94325675Ssam {
94425979Ssam 	int errno;
94525675Ssam 
94625979Ssam 	errno = cyphys(dev, uio);
94725979Ssam 	if (errno)
94825979Ssam 		return (errno);
94925979Ssam 	return (physio(cystrategy, &rcybuf[CYUNIT(dev)], dev, B_READ, minphys, uio));
95025675Ssam }
95125675Ssam 
95225979Ssam cywrite(dev, uio)
95325979Ssam 	dev_t dev;
95425979Ssam 	struct uio *uio;
95524000Ssam {
95625979Ssam 	int errno;
95724000Ssam 
95825979Ssam 	errno = cyphys(dev, uio);
95925979Ssam 	if (errno)
96025979Ssam 		return (errno);
96125979Ssam 	return (physio(cystrategy, &rcybuf[CYUNIT(dev)], dev, B_WRITE, minphys, uio));
96224000Ssam }
96324000Ssam 
96424000Ssam /*
96525979Ssam  * Check that a raw device exits.
96625979Ssam  * If it does, set up the yc_blkno and yc_nxrec
96725979Ssam  * so that the tape will appear positioned correctly.
96825979Ssam  */
96925979Ssam cyphys(dev, uio)
97025675Ssam 	dev_t dev;
97125675Ssam 	struct uio *uio;
97225675Ssam {
97325979Ssam 	register int ycunit = YCUNIT(dev);
97425979Ssam 	register daddr_t a;
97525979Ssam 	register struct yc_softc *yc;
97625979Ssam 	register struct vba_device *vi;
97725675Ssam 
97825979Ssam 	if (ycunit >= NYC || (vi = ycdinfo[ycunit]) == 0 || vi->ui_alive == 0)
97925979Ssam 		return (ENXIO);
98025979Ssam 	yc = &yc_softc[ycunit];
98130719Skarels 	a = uio->uio_offset >> DEV_BSHIFT;
98225979Ssam 	yc->yc_blkno = a;
98325979Ssam 	yc->yc_nxrec = a + 1;
98425979Ssam 	return (0);
98525675Ssam }
98625675Ssam 
98725675Ssam /*ARGSUSED*/
98825675Ssam cyioctl(dev, cmd, data, flag)
98925979Ssam 	caddr_t data;
99025675Ssam 	dev_t dev;
99125675Ssam {
99225979Ssam 	int ycunit = YCUNIT(dev);
99325979Ssam 	register struct yc_softc *yc = &yc_softc[ycunit];
99425979Ssam 	register struct buf *bp = &ccybuf[CYUNIT(dev)];
99525979Ssam 	register callcount;
99625979Ssam 	int fcount, op;
99725979Ssam 	struct mtop *mtop;
99825979Ssam 	struct mtget *mtget;
99925979Ssam 	/* we depend of the values and order of the MT codes here */
100025979Ssam 	static cyops[] =
100130371Skarels 	{CY_WEOF,CY_FSF,CY_BSF,CY_SFORW,CY_SREV,CY_REW,CY_OFFL,CY_SENSE};
100225675Ssam 
100325675Ssam 	switch (cmd) {
100425675Ssam 
100525979Ssam 	case MTIOCTOP:	/* tape operation */
100625979Ssam 		mtop = (struct mtop *)data;
100725979Ssam 		switch (op = mtop->mt_op) {
100825675Ssam 
100925979Ssam 		case MTWEOF:
101030371Skarels 			callcount = mtop->mt_count;
101130371Skarels 			fcount = 1;
101230371Skarels 			break;
101330371Skarels 
101425979Ssam 		case MTFSR: case MTBSR:
101530371Skarels 			callcount = 1;
101630371Skarels 			fcount = mtop->mt_count;
101730371Skarels 			break;
101830371Skarels 
101925979Ssam 		case MTFSF: case MTBSF:
102025979Ssam 			callcount = mtop->mt_count;
102125979Ssam 			fcount = 1;
102225979Ssam 			break;
102325675Ssam 
102425979Ssam 		case MTREW: case MTOFFL: case MTNOP:
102525979Ssam 			callcount = 1;
102625979Ssam 			fcount = 1;
102725979Ssam 			break;
102825675Ssam 
102925979Ssam 		default:
103025979Ssam 			return (ENXIO);
103125979Ssam 		}
103225979Ssam 		if (callcount <= 0 || fcount <= 0)
103325979Ssam 			return (EINVAL);
103425979Ssam 		while (--callcount >= 0) {
103530371Skarels #ifdef notdef
103625979Ssam 			/*
103725979Ssam 			 * Gagh, this controller is the pits...
103825979Ssam 			 */
103925979Ssam 			if (op == MTFSF || op == MTBSF) {
104025979Ssam 				do
104125979Ssam 					cycommand(dev, cyops[op], 1);
104225979Ssam 				while ((bp->b_flags&B_ERROR) == 0 &&
104325979Ssam 				 (yc->yc_status&(CYS_EOT|CYS_BOT|CYS_FM)) == 0);
104425979Ssam 			} else
104530371Skarels #endif
104625979Ssam 				cycommand(dev, cyops[op], fcount);
104730371Skarels 			dlog((LOG_INFO,
104830371Skarels 			    "cyioctl: status %x, b_flags %x, resid %d\n",
104930371Skarels 			    yc->yc_status, bp->b_flags, bp->b_resid));
105025979Ssam 			if ((bp->b_flags&B_ERROR) ||
105125979Ssam 			    (yc->yc_status&(CYS_BOT|CYS_EOT)))
105225979Ssam 				break;
105325979Ssam 		}
105425979Ssam 		bp->b_resid = callcount + 1;
105525979Ssam 		return (geterror(bp));
105625979Ssam 
105725979Ssam 	case MTIOCGET:
105825979Ssam 		cycommand(dev, CY_SENSE, 1);
105925979Ssam 		mtget = (struct mtget *)data;
106025979Ssam 		mtget->mt_dsreg = yc->yc_status;
106125979Ssam 		mtget->mt_erreg = yc->yc_control;
106225979Ssam 		mtget->mt_resid = yc->yc_resid;
106325979Ssam 		mtget->mt_type = MT_ISCY;
106425675Ssam 		break;
106525675Ssam 
106625675Ssam 	default:
106725675Ssam 		return (ENXIO);
106825675Ssam 	}
106925675Ssam 	return (0);
107025675Ssam }
107125675Ssam 
107225675Ssam /*
107325675Ssam  * Poll until the controller is ready.
107425675Ssam  */
107525675Ssam cywait(cp)
107625979Ssam 	register struct cyccb *cp;
107724000Ssam {
107825675Ssam 	register int i = 5000;
107924000Ssam 
108025979Ssam 	uncache(&cp->cbgate);
108125979Ssam 	while (i-- > 0 && cp->cbgate == GATE_CLOSED) {
108224000Ssam 		DELAY(1000);
108325979Ssam 		uncache(&cp->cbgate);
108424000Ssam 	}
108525675Ssam 	return (i <= 0);
108624000Ssam }
108724000Ssam 
108825675Ssam /*
108930371Skarels  * Load a 20 bit pointer into a Tapemaster pointer.
109025675Ssam  */
109130371Skarels cyldmba(reg, value)
109230371Skarels 	register caddr_t reg;
109325979Ssam 	caddr_t value;
109424000Ssam {
109525979Ssam 	register int v = (int)value;
109625675Ssam 
109725979Ssam 	*reg++ = v;
109825979Ssam 	*reg++ = v >> 8;
109925979Ssam 	*reg++ = 0;
110025979Ssam 	*reg = (v&0xf0000) >> 12;
110124000Ssam }
110224000Ssam 
110325675Ssam /*
110425675Ssam  * Unconditionally reset all controllers to their initial state.
110525675Ssam  */
110625675Ssam cyreset(vba)
110725675Ssam 	int vba;
110824000Ssam {
110925675Ssam 	register caddr_t addr;
111025675Ssam 	register int ctlr;
111124000Ssam 
111225675Ssam 	for (ctlr = 0; ctlr < NCY; ctlr++)
111325675Ssam 		if (cyminfo[ctlr] && cyminfo[ctlr]->um_vbanum == vba) {
111425675Ssam 			addr = cyminfo[ctlr]->um_addr;
111525675Ssam 			CY_RESET(addr);
111630371Skarels 			if (!cyinit(ctlr, addr)) {
111725675Ssam 				printf("cy%d: reset failed\n", ctlr);
111825675Ssam 				cyminfo[ctlr] = NULL;
111925675Ssam 			}
112025675Ssam 		}
112124000Ssam }
112225979Ssam 
112325979Ssam cyuncachetpb(cy)
112425979Ssam 	struct cy_softc *cy;
112525979Ssam {
112625979Ssam 	register long *lp = (long *)&cy->cy_tpb;
112725979Ssam 	register int i;
112825979Ssam 
112925979Ssam 	for (i = 0; i < howmany(sizeof (struct cytpb), sizeof (long)); i++)
113025979Ssam 		uncache(lp++);
113125979Ssam }
113225979Ssam 
113325979Ssam /*
113425979Ssam  * Dump routine.
113525979Ssam  */
113630869Skarels #define	DUMPREC	(32*1024)
113725979Ssam cydump(dev)
113825979Ssam 	dev_t dev;
113925979Ssam {
114025979Ssam 	register struct cy_softc *cy;
114125979Ssam 	register int bs, num, start;
114225979Ssam 	register caddr_t addr;
114330294Ssam 	int unit = CYUNIT(dev), error;
114425979Ssam 
114525979Ssam 	if (unit >= NCY || cyminfo[unit] == 0 ||
114625979Ssam 	    (cy = &cy_softc[unit])->cy_bs == 0 || YCUNIT(dev) >= NYC)
114725979Ssam 		return (ENXIO);
114825979Ssam 	if (cywait(&cy->cy_ccb))
114925979Ssam 		return (EFAULT);
115025979Ssam #define	phys(a)	((caddr_t)((int)(a)&~0xc0000000))
115130294Ssam 	addr = phys(cyminfo[unit]->um_addr);
115225979Ssam 	num = maxfree, start = NBPG*2;
115325979Ssam 	while (num > 0) {
115430869Skarels 		bs = num > btoc(DUMPREC) ? btoc(DUMPREC) : num;
115525979Ssam 		error = cydwrite(cy, start, bs, addr);
115625979Ssam 		if (error)
115725979Ssam 			return (error);
115825979Ssam 		start += bs, num -= bs;
115925979Ssam 	}
116025979Ssam 	cyweof(cy, addr);
116125979Ssam 	cyweof(cy, addr);
116225979Ssam 	uncache(&cy->cy_tpb);
116325979Ssam 	if (cy->cy_tpb.tpstatus&CYS_ERR)
116425979Ssam 		return (EIO);
116525979Ssam 	cyrewind(cy, addr);
116625979Ssam 	return (0);
116725979Ssam }
116825979Ssam 
116925979Ssam cydwrite(cy, pf, npf, addr)
117025979Ssam 	register struct cy_softc *cy;
117125979Ssam 	int pf, npf;
117225979Ssam 	caddr_t addr;
117325979Ssam {
117425979Ssam 
117525979Ssam 	cy->cy_tpb.tpcmd = CY_WCOM;
117625979Ssam 	cy->cy_tpb.tpcontrol = CYCW_LOCK|CYCW_25IPS|CYCW_16BITS;
117725979Ssam 	cy->cy_tpb.tpstatus = 0;
117825979Ssam 	cy->cy_tpb.tpsize = htoms(npf*NBPG);
117925979Ssam 	cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
118025979Ssam 	cyldmba(cy->cy_tpb.tpdata, (caddr_t)(pf*NBPG));
118125979Ssam 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
118225979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
118325979Ssam 	CY_GO(addr);
118425979Ssam 	if (cywait(&cy->cy_ccb))
118525979Ssam 		return (EFAULT);
118625979Ssam 	uncache(&cy->cy_tpb);
118725979Ssam 	if (cy->cy_tpb.tpstatus&CYS_ERR)
118825979Ssam 		return (EIO);
118925979Ssam 	return (0);
119025979Ssam }
119125979Ssam 
119225979Ssam cyweof(cy, addr)
119325979Ssam 	register struct cy_softc *cy;
119425979Ssam 	caddr_t addr;
119525979Ssam {
119625979Ssam 
119725979Ssam 	cy->cy_tpb.tpcmd = CY_WEOF;
119825979Ssam 	cy->cy_tpb.tpcount = htoms(1);
119925979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
120025979Ssam 	CY_GO(addr);
120125979Ssam 	(void) cywait(&cy->cy_ccb);
120225979Ssam }
120325979Ssam 
120425979Ssam cyrewind(cy, addr)
120525979Ssam 	register struct cy_softc *cy;
120625979Ssam 	caddr_t addr;
120725979Ssam {
120825979Ssam 
120925979Ssam 	cy->cy_tpb.tpcmd = CY_REW;
121025979Ssam 	cy->cy_tpb.tpcount = htoms(1);
121125979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
121225979Ssam 	CY_GO(addr);
121325979Ssam 	(void) cywait(&cy->cy_ccb);
121425979Ssam }
121524000Ssam #endif
1216