xref: /csrg-svn/sys/tahoe/vba/cy.c (revision 25984)
1*25984Ssam /*	cy.c	1.6	86/01/27	*/
224000Ssam 
325979Ssam #include "yc.h"
425675Ssam #if NCY > 0
524000Ssam /*
625675Ssam  * Cipher Tapemaster driver.
724000Ssam  */
825675Ssam int	cydebug = 0;
925979Ssam #define	dlog	if (cydebug) log
1024000Ssam 
1125675Ssam #include "../tahoe/mtpr.h"
1225675Ssam #include "../tahoe/pte.h"
1324000Ssam 
1425675Ssam #include "param.h"
1525675Ssam #include "systm.h"
1625675Ssam #include "vm.h"
1725675Ssam #include "buf.h"
1825675Ssam #include "file.h"
1925675Ssam #include "dir.h"
2025675Ssam #include "user.h"
2125675Ssam #include "proc.h"
2225675Ssam #include "signal.h"
2325675Ssam #include "uio.h"
2425675Ssam #include "ioctl.h"
2525675Ssam #include "mtio.h"
2625675Ssam #include "errno.h"
2725675Ssam #include "cmap.h"
2825979Ssam #include "kernel.h"
2925979Ssam #include "syslog.h"
3024000Ssam 
3125675Ssam #include "../tahoevba/vbavar.h"
3225979Ssam #define	CYERROR
3325675Ssam #include "../tahoevba/cyreg.h"
3424000Ssam 
3525979Ssam /*
3625979Ssam  * There is a ccybuf per tape controller.
3725979Ssam  * It is used as the token to pass to the internal routines
3825979Ssam  * to execute tape ioctls, and also acts as a lock on the slaves
3925979Ssam  * on the controller, since there is only one per controller.
4025979Ssam  * In particular, when the tape is rewinding on close we release
4125979Ssam  * the user process but any further attempts to use the tape drive
4225979Ssam  * before the rewind completes will hang waiting for ccybuf.
4325979Ssam  */
4425979Ssam struct	buf ccybuf[NCY];
4524000Ssam 
4625979Ssam /*
4725979Ssam  * Raw tape operations use rcybuf.  The driver notices when
4825979Ssam  * rcybuf is being used and allows the user program to contine
4925979Ssam  * after errors and read records not of the standard length.
5025979Ssam  */
5125979Ssam struct	buf rcybuf[NCY];
5224000Ssam 
5325979Ssam int	cyprobe(), cyslave(), cyattach();
5425979Ssam struct	buf ycutab[NYC];
5525979Ssam short	yctocy[NYC];
5625675Ssam struct	vba_ctlr *cyminfo[NCY];
5725979Ssam struct	vba_device *ycdinfo[NYC];
5825857Ssam long	cystd[] = { 0 };
5925857Ssam struct	vba_driver cydriver =
6025979Ssam    { cyprobe, cyslave, cyattach, 0, cystd, "yc", ycdinfo, "cy", cyminfo };
6124000Ssam 
6225979Ssam /* bits in minor device */
6325979Ssam #define	YCUNIT(dev)	(minor(dev)&03)
6425979Ssam #define	CYUNIT(dev)	(yctocy[YCUNIT(dev)])
6525979Ssam #define	T_NOREWIND	0x04
6625979Ssam #define	T_1600BPI	0x08
6725979Ssam #define	T_3200BPI	0x10
6825979Ssam 
6925979Ssam #define	INF	1000000L		/* close to infinity */
7025979Ssam #define	CYMAXIO	(32*NBPG)		/* max i/o size */
7125979Ssam 
7224000Ssam /*
7325979Ssam  * Software state and shared command areas per controller.
7425979Ssam  *
7525979Ssam  * The i/o buffer must be defined statically to insure
7625979Ssam  * it's address will fit in 20-bits (YECH!!!!!!!!!!!!!!)
7724000Ssam  */
7825979Ssam struct cy_softc {
7925979Ssam 	struct	pte *cy_map;	/* pte's for mapped buffer i/o */
8025979Ssam 	caddr_t	cy_utl;		/* mapped virtual address */
8125979Ssam 	int	cy_bs;		/* controller's buffer size */
8225979Ssam 	char	cy_buf[CYMAXIO];/* intermediate buffer */
8325979Ssam 	struct	cyscp *cy_scp;	/* system configuration block address */
8425979Ssam 	struct	cyccb cy_ccb;	/* channel control block */
8525979Ssam 	struct	cyscb cy_scb;	/* system configuration block */
8625979Ssam 	struct	cytpb cy_tpb;	/* tape parameter block */
8725979Ssam 	struct	cytpb cy_nop;	/* nop parameter block for cyintr */
8825979Ssam } cy_softc[NCY];
8924000Ssam 
9025979Ssam /*
9125979Ssam  * Software state per tape transport.
9225979Ssam  */
9325979Ssam struct	yc_softc {
9425979Ssam 	char	yc_openf;	/* lock against multiple opens */
9525979Ssam 	char	yc_lastiow;	/* last operation was a write */
9625979Ssam 	short	yc_tact;	/* timeout is active */
9725979Ssam 	long	yc_timo;	/* time until timeout expires */
9825979Ssam 	u_short	yc_control;	/* copy of last tpcb.tpcontrol */
9925979Ssam 	u_short	yc_status;	/* copy of last tpcb.tpstatus */
10025979Ssam 	u_short	yc_resid;	/* copy of last bc */
10125979Ssam 	u_short	yc_dens;	/* prototype control word with density info */
10225979Ssam 	struct	tty *yc_ttyp;	/* user's tty for errors */
10325979Ssam 	daddr_t	yc_blkno;	/* block number, for block device tape */
10425979Ssam 	daddr_t	yc_nxrec;	/* position of end of tape, if known */
10525979Ssam } yc_softc[NYC];
10624000Ssam 
10724000Ssam /*
10825979Ssam  * States for vm->um_tab.b_active, the per controller state flag.
10925979Ssam  * This is used to sequence control in the driver.
11024000Ssam  */
11125979Ssam #define	SSEEK	1		/* seeking */
11225979Ssam #define	SIO	2		/* doing seq i/o */
11325979Ssam #define	SCOM	3		/* sending control command */
11425979Ssam #define	SREW	4		/* sending a rewind */
11525979Ssam #define	SERASE	5		/* erase inter-record gap */
11625979Ssam #define	SERASED	6		/* erased inter-record gap */
11724000Ssam 
11825979Ssam /* there's no way to figure these out dynamically? -- yech */
11925979Ssam struct	cyscp *cyscp[] =
12025979Ssam     { (struct cyscp *)0xc0000c06, (struct cyscp *)0xc0000c16 };
12125979Ssam #define	NCYSCP	(sizeof (cyscp) / sizeof (cyscp[0]))
12225979Ssam 
12325857Ssam cyprobe(reg, vm)
12425857Ssam 	caddr_t reg;
12525857Ssam 	struct vba_ctlr *vm;
12625675Ssam {
12725857Ssam 	register br, cvec;			/* must be r12, r11 */
12825979Ssam 	struct cy_softc *cy;
12925675Ssam 
13025857Ssam 	if (badcyaddr(reg+1))
13125675Ssam 		return (0);
13225979Ssam 	if (vm->um_ctlr > NCYSCP || cyscp[vm->um_ctlr] == 0)	/* XXX */
13325979Ssam 		return (0);					/* XXX */
13425979Ssam 	cy_softc[vm->um_ctlr].cy_scp = cyscp[vm->um_ctlr];	/* XXX */
13525979Ssam 	/*
13625979Ssam 	 * Tapemaster controller must have interrupt handler
13725979Ssam 	 * disable interrupt, so we'll just kludge things
13825979Ssam 	 * (stupid multibus non-vectored interrupt crud).
13925979Ssam 	 */
14025979Ssam 	br = 0x13, cvec = 0x80;					/* XXX */
14125979Ssam 	return (sizeof (struct cyccb));
14225675Ssam }
14325675Ssam 
14424000Ssam /*
14525857Ssam  * Check to see if a drive is attached to a controller.
14625857Ssam  * Since we can only tell that a drive is there if a tape is loaded and
14725857Ssam  * the drive is placed online, we always indicate the slave is present.
14824000Ssam  */
14925857Ssam cyslave(vi, addr)
15025857Ssam 	struct vba_device *vi;
15125857Ssam 	caddr_t addr;
15224000Ssam {
15325857Ssam 
15425857Ssam #ifdef lint
15525857Ssam 	vi = vi; addr = addr;
15625857Ssam #endif
15725857Ssam 	return (1);
15825857Ssam }
15925857Ssam 
16025857Ssam cyattach(vi)
16125857Ssam 	struct vba_device *vi;
16225857Ssam {
16325979Ssam 	register struct cy_softc *cy;
16425979Ssam 	int ctlr = vi->ui_mi->um_ctlr;
16525857Ssam 
16625979Ssam 	yctocy[vi->ui_unit] = ctlr;
16725979Ssam 	cy = &cy_softc[ctlr];
16825979Ssam 	if (cy->cy_bs == 0 && cyinit(ctlr)) {
16925979Ssam 		uncache(&cy->cy_tpb.tpcount);
17025979Ssam 		cy->cy_bs = htoms(cy->cy_tpb.tpcount);
17125979Ssam 		printf("cy%d: %dkb buffer\n", ctlr, cy->cy_bs/1024);
17225979Ssam 		/*
17325979Ssam 		 * Setup nop parameter block for clearing interrupts.
17425979Ssam 		 */
17525979Ssam 		cy->cy_nop.tpcmd = CY_NOP;
17625979Ssam 		cy->cy_nop.tpcontrol = 0;
17725979Ssam 		/*
17825979Ssam 		 * Allocate page tables.
17925979Ssam 		 */
18025979Ssam 		vbmapalloc(btoc(CYMAXIO)+1, &cy->cy_map, &cy->cy_utl);
18125857Ssam 	}
18225857Ssam }
18325857Ssam 
18425857Ssam /*
18525857Ssam  * Initialize the controller after a controller reset or
18625857Ssam  * during autoconfigure.  All of the system control blocks
18725857Ssam  * are initialized and the controller is asked to configure
18825857Ssam  * itself for later use.
18925857Ssam  */
19025979Ssam cyinit(ctlr)
19125979Ssam 	int ctlr;
19225857Ssam {
19325979Ssam 	register struct cy_softc *cy = &cy_softc[ctlr];
19425979Ssam 	register caddr_t addr = cyminfo[ctlr]->um_addr;
19525675Ssam 	register int *pte;
19624000Ssam 
19724000Ssam 	/*
19825675Ssam 	 * Initialize the system configuration pointer.
19924000Ssam 	 */
20025675Ssam 	/* make kernel writable */
20125979Ssam 	pte = (int *)vtopte((struct proc *)0, btop(cy->cy_scp));
20225675Ssam 	*pte &= ~PG_PROT; *pte |= PG_KW;
20325979Ssam 	mtpr(TBIS, cy->cy_scp);
20425675Ssam 	/* load the correct values in the scp */
20525979Ssam 	cy->cy_scp->csp_buswidth = CSP_16BITS;
20625979Ssam 	cyldmba(cy->cy_scp->csp_scb, (caddr_t)&cy->cy_scb);
20725675Ssam 	/* put it back to read-only */
20825675Ssam 	*pte &= ~PG_PROT; *pte |= PG_KR;
20925979Ssam 	mtpr(TBIS, cy->cy_scp);
21025675Ssam 
21124000Ssam 	/*
21225675Ssam 	 * Init system configuration block.
21324000Ssam 	 */
21425979Ssam 	cy->cy_scb.csb_fixed = 0x3;
21525675Ssam 	/* set pointer to the channel control block */
21625979Ssam 	cyldmba(cy->cy_scb.csb_ccb, (caddr_t)&cy->cy_ccb);
21725675Ssam 
21824000Ssam 	/*
21925675Ssam 	 * Initialize the chanel control block.
22024000Ssam 	 */
22125979Ssam 	cy->cy_ccb.cbcw = CBCW_CLRINT;
22225979Ssam 	cy->cy_ccb.cbgate = GATE_OPEN;
22325675Ssam 	/* set pointer to the tape parameter block */
22425979Ssam 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
22525675Ssam 
22624000Ssam 	/*
22725979Ssam 	 * Issue a nop cmd and get the internal buffer size for buffered i/o.
22824000Ssam 	 */
22925979Ssam 	cy->cy_tpb.tpcmd = CY_NOP;
23025979Ssam 	cy->cy_tpb.tpcontrol = CYCW_16BITS;
23125979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
23225979Ssam 	CY_GO(addr);
23325979Ssam 	if (cywait(&cy->cy_ccb) || (cy->cy_tpb.tpstatus&CYS_ERR)) {
23425979Ssam 		uncache(&cy->cy_tpb.tpstatus);
23525979Ssam 		printf("cy%d: timeout or err during init, status=%b\n", ctlr,
23625979Ssam 		    cy->cy_tpb.tpstatus, CYS_BITS);
23725675Ssam 		return (0);
23825675Ssam 	}
23925979Ssam 	cy->cy_tpb.tpcmd = CY_CONFIG;
24025979Ssam 	cy->cy_tpb.tpcontrol = CYCW_16BITS;
24125979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
24225979Ssam 	CY_GO(addr);
24325979Ssam 	if (cywait(&cy->cy_ccb) || (cy->cy_tpb.tpstatus&CYS_ERR)) {
24425979Ssam 		uncache(&cy->cy_tpb.tpstatus);
24525979Ssam 		printf("cy%d: configuration failure, status=%b\n", ctlr,
24625979Ssam 		    cy->cy_tpb.tpstatus, CYS_BITS);
24725675Ssam 		return (0);
24825675Ssam 	}
24925675Ssam 	return (1);
25024000Ssam }
25124000Ssam 
25225979Ssam int	cytimer();
25325979Ssam /*
25425979Ssam  * Open the device.  Tapes are unique open
25525979Ssam  * devices, so we refuse if it is already open.
25625979Ssam  * We also check that a tape is available, and
25725979Ssam  * don't block waiting here; if you want to wait
25825979Ssam  * for a tape you should timeout in user code.
25925979Ssam  */
26025675Ssam cyopen(dev, flag)
26125979Ssam 	dev_t dev;
26225675Ssam 	register int flag;
26325675Ssam {
26425979Ssam 	register int ycunit;
26525979Ssam 	register struct vba_device *vi;
26625979Ssam 	register struct yc_softc *yc;
26725979Ssam 	int s;
26825675Ssam 
26925979Ssam 	ycunit = YCUNIT(dev);
27025979Ssam 	if (ycunit >= NYC || (vi = ycdinfo[ycunit]) == 0 || vi->ui_alive == 0)
27125675Ssam 		return (ENXIO);
27225979Ssam 	if ((yc = &yc_softc[ycunit])->yc_openf)
27325979Ssam 		return (EBUSY);
27425979Ssam #define	PACKUNIT(vi) \
27525979Ssam     (((vi->ui_slave&1)<<11)|((vi->ui_slave&2)<<9)|((vi->ui_slave&4)>>2))
27625979Ssam 	/* no way to select density */
27725979Ssam 	yc->yc_dens = PACKUNIT(vi)|CYCW_IE|CYCW_16BITS;
27825979Ssam 	cycommand(dev, CY_SENSE, 1);
27925979Ssam 	if ((yc->yc_status&CYS_OL) == 0) {	/* not on-line */
28025979Ssam 		uprintf("yc%d: not online\n", ycunit);
28125675Ssam 		return (ENXIO);
28225675Ssam 	}
28325979Ssam 	if ((flag&FWRITE) && (yc->yc_status&CYS_WP)) {
28425979Ssam 		uprintf("yc%d: no write ring\n", ycunit);
28525675Ssam 		return (ENXIO);
28625675Ssam 	}
28725979Ssam 	yc->yc_openf = 1;
28825979Ssam 	yc->yc_blkno = (daddr_t)0;
28925979Ssam 	yc->yc_nxrec = INF;
29025979Ssam 	yc->yc_lastiow = 0;
29125979Ssam 	yc->yc_ttyp = u.u_ttyp;
29225979Ssam 	s = splclock();
29325979Ssam 	if (yc->yc_tact == 0) {
29425979Ssam 		yc->yc_timo = INF;
29525979Ssam 		yc->yc_tact = 1;
29625979Ssam 		timeout(cytimer, (caddr_t)dev, 5*hz);
29725675Ssam 	}
29825979Ssam 	splx(s);
29925675Ssam 	return (0);
30025675Ssam }
30125675Ssam 
30225979Ssam /*
30325979Ssam  * Close tape device.
30425979Ssam  *
30525979Ssam  * If tape was open for writing or last operation was a write,
30625979Ssam  * then write two EOF's and backspace over the last one.
30725979Ssam  * Unless this is a non-rewinding special file, rewind the tape.
30825979Ssam  * Make the tape available to others.
30925979Ssam  */
31025675Ssam cyclose(dev, flag)
31125979Ssam 	dev_t dev;
31225979Ssam 	register int flag;
31325675Ssam {
31425979Ssam 	register struct yc_softc *yc = &yc_softc[YCUNIT(dev)];
31525675Ssam 
31625979Ssam 	if (flag == FWRITE || (flag&FWRITE) && yc->yc_lastiow) {
31725979Ssam 		cycommand(dev, CY_WEOF, 2);
31825979Ssam 		cycommand(dev, CY_SREV, 1);
31925675Ssam 	}
32025979Ssam 	if ((minor(dev)&T_NOREWIND) == 0)
32125979Ssam 		/*
32225979Ssam 		 * 0 count means don't hang waiting for rewind complete
32325979Ssam 		 * rather ccybuf stays busy until the operation completes
32425979Ssam 		 * preventing further opens from completing by preventing
32525979Ssam 		 * a CY_SENSE from completing.
32625979Ssam 		 */
32725979Ssam 		cycommand(dev, CY_REW, 0);
32825979Ssam 	yc->yc_openf = 0;
32925675Ssam }
33025675Ssam 
33124000Ssam /*
33225979Ssam  * Execute a command on the tape drive a specified number of times.
33324000Ssam  */
33425979Ssam cycommand(dev, com, count)
33525979Ssam 	dev_t dev;
33625979Ssam 	int com, count;
33724000Ssam {
33825675Ssam 	register int unit = CYUNIT(dev);
33925979Ssam 	register struct buf *bp;
34025675Ssam 	int s;
34125675Ssam 
34225979Ssam 	bp = &ccybuf[CYUNIT(dev)];
34325675Ssam 	s = spl3();
34425979Ssam 	dlog(LOG_INFO, "cycommand(%o, %x, %d), b_flags %x\n",
34525979Ssam 	    dev, com, count, bp->b_flags);
34625979Ssam 	while (bp->b_flags&B_BUSY) {
34725979Ssam 		/*
34825979Ssam 		 * This special check is because B_BUSY never
34925979Ssam 		 * gets cleared in the non-waiting rewind case.
35025979Ssam 		 */
35125979Ssam 		if (bp->b_repcnt == 0 && (bp->b_flags&B_DONE))
35225979Ssam 			break;
35325979Ssam 		bp->b_flags |= B_WANTED;
35425979Ssam 		sleep((caddr_t)bp, PRIBIO);
35525675Ssam 	}
35625979Ssam 	bp->b_flags = B_BUSY|B_READ;
35725675Ssam 	splx(s);
35825979Ssam 	bp->b_dev = dev;
35925979Ssam 	bp->b_repcnt = count;
36025979Ssam 	bp->b_command = com;
36125979Ssam 	bp->b_blkno = 0;
36225979Ssam 	cystrategy(bp);
36325979Ssam 	/*
36425979Ssam 	 * In case of rewind from close; don't wait.
36525979Ssam 	 * This is the only case where count can be 0.
36625979Ssam 	 */
36725979Ssam 	if (count == 0)
36825979Ssam 		return;
36925979Ssam 	iowait(bp);
37025979Ssam 	if (bp->b_flags&B_WANTED)
37125979Ssam 		wakeup((caddr_t)bp);
37225979Ssam 	bp->b_flags &= B_ERROR;
37324000Ssam }
37424000Ssam 
37525675Ssam cystrategy(bp)
37625675Ssam 	register struct buf *bp;
37725675Ssam {
37825979Ssam 	int ycunit = YCUNIT(bp->b_dev);
37925979Ssam 	register struct vba_ctlr *vm;
38025979Ssam 	register struct buf *dp;
38125675Ssam 	int s;
38225675Ssam 
38325979Ssam 	/*
38425979Ssam 	 * Put transfer at end of unit queue.
38525979Ssam 	 */
38625979Ssam 	dlog(LOG_INFO, "cystrategy(%o, %x)\n", bp->b_dev, bp->b_command);
38725979Ssam 	dp = &ycutab[ycunit];
38825675Ssam 	bp->av_forw = NULL;
38925979Ssam 	vm = ycdinfo[ycunit]->ui_mi;
39025979Ssam 	/* BEGIN GROT */
39125979Ssam 	if (bp == &rcybuf[CYUNIT(bp->b_dev)]) {
39225979Ssam 		if (bp->b_bcount > CYMAXIO) {
39325979Ssam 			uprintf("cy%d: i/o size too large\n", vm->um_ctlr);
39425979Ssam 			bp->b_error = EIO;
39525979Ssam 			bp->b_resid = bp->b_bcount;
39625979Ssam 			bp->b_flags |= B_ERROR;
39725675Ssam 			iodone(bp);
39825675Ssam 			return;
39925675Ssam 		}
40025979Ssam 		vbasetup(bp, CYMAXIO);
40124000Ssam 	}
40225979Ssam 	/* END GROT */
40325675Ssam 	s = spl3();
40425979Ssam 	if (dp->b_actf == NULL) {
40525979Ssam 		dp->b_actf = bp;
40625979Ssam 		/*
40725979Ssam 		 * Transport not already active...
40825979Ssam 		 * put at end of controller queue.
40925979Ssam 		 */
41025979Ssam 		 dp->b_forw = NULL;
41125979Ssam 		 if (vm->um_tab.b_actf == NULL)
41225979Ssam 			vm->um_tab.b_actf = dp;
41325979Ssam 		else
41425979Ssam 			vm->um_tab.b_actl->b_forw = dp;
41525979Ssam 	} else
41625979Ssam 		dp->b_actl->av_forw = bp;
41725979Ssam 	dp->b_actl = bp;
41825979Ssam 	/*
41925979Ssam 	 * If the controller is not busy, get it going.
42025979Ssam 	 */
42125979Ssam 	if (vm->um_tab.b_active == 0)
42225979Ssam 		cystart(vm);
42324000Ssam 	splx(s);
42424000Ssam }
42524000Ssam 
42624000Ssam /*
42725979Ssam  * Start activity on a cy controller.
42824000Ssam  */
42925979Ssam cystart(vm)
43025979Ssam 	register struct vba_ctlr *vm;
43124000Ssam {
43225979Ssam 	register struct buf *bp, *dp;
43325979Ssam 	register struct yc_softc *yc;
43425979Ssam 	register struct cy_softc *cy;
43525979Ssam 	register struct vba_device *vi;
43625979Ssam 	int ycunit;
43725979Ssam 	daddr_t blkno;
43824000Ssam 
43925979Ssam 	dlog(LOG_INFO, "cystart()\n");
44025979Ssam 	/*
44125979Ssam 	 * Look for an idle transport on the controller.
44225979Ssam 	 */
44325979Ssam loop:
44425979Ssam 	if ((dp = vm->um_tab.b_actf) == NULL)
44525675Ssam 		return;
44625979Ssam 	if ((bp = dp->b_actf) == NULL) {
44725979Ssam 		vm->um_tab.b_actf = dp->b_forw;
44825979Ssam 		goto loop;
44925675Ssam 	}
45025979Ssam 	ycunit = YCUNIT(bp->b_dev);
45125979Ssam 	yc = &yc_softc[ycunit];
45225979Ssam 	cy = &cy_softc[CYUNIT(bp->b_dev)];
45325979Ssam 	/*
45425979Ssam 	 * Default is that last command was NOT a write command;
45525979Ssam 	 * if we do a write command we will notice this in cyintr().
45625979Ssam 	 */
45725979Ssam 	yc->yc_lastiow = 0;
45825979Ssam 	if (yc->yc_openf < 0 ||
45925979Ssam 	    (bp->b_command != CY_SENSE && (cy->cy_tpb.tpstatus&CYS_OL) == 0)) {
46025979Ssam 		/*
46125979Ssam 		 * Have had a hard error on a non-raw tape
46225979Ssam 		 * or the tape unit is now unavailable (e.g.
46325979Ssam 		 * taken off line).
46425979Ssam 		 */
46525979Ssam 		dlog(LOG_INFO, "openf %d command %x status %b\n",
46625979Ssam 		    yc->yc_openf, bp->b_command, cy->cy_tpb.tpstatus, CYS_BITS);
46725979Ssam 		bp->b_flags |= B_ERROR;
46825979Ssam 		goto next;
46925675Ssam 	}
47025979Ssam 	if (bp == &ccybuf[CYUNIT(bp->b_dev)]) {
47125979Ssam 		/*
47225979Ssam 		 * Execute control operation with the specified count.
47325979Ssam 		 *
47425979Ssam 		 * Set next state; give 5 minutes to complete
47525979Ssam 		 * rewind or file mark search, or 10 seconds per
47625979Ssam 		 * iteration (minimum 60 seconds and max 5 minutes)
47725979Ssam 		 * to complete other ops.
47825979Ssam 		 */
47925979Ssam 		if (bp->b_command == CY_REW) {
48025979Ssam 			vm->um_tab.b_active = SREW;
48125979Ssam 			yc->yc_timo = 5*60;
48225979Ssam 		} else {
48325979Ssam 			vm->um_tab.b_active = SCOM;
48425979Ssam 			yc->yc_timo = imin(imax(10*(int)bp->b_repcnt,60),5*60);
48525979Ssam 		}
48625979Ssam 		cy->cy_tpb.tprec = htoms(bp->b_repcnt);
48725979Ssam 		goto dobpcmd;
48824000Ssam 	}
48925979Ssam 	/*
49025979Ssam 	 * The following checks handle boundary cases for operation
49125979Ssam 	 * on no-raw tapes.  On raw tapes the initialization of
49225979Ssam 	 * yc->yc_nxrec by cyphys causes them to be skipped normally
49325979Ssam 	 * (except in the case of retries).
49425979Ssam 	 */
49525979Ssam 	if (bdbtofsb(bp->b_blkno) > yc->yc_nxrec) {
49625979Ssam 		/*
49725979Ssam 		 * Can't read past known end-of-file.
49825979Ssam 		 */
49925979Ssam 		bp->b_flags |= B_ERROR;
50025979Ssam 		bp->b_error = ENXIO;
50125979Ssam 		goto next;
50224000Ssam 	}
50325979Ssam 	if (bdbtofsb(bp->b_blkno) == yc->yc_nxrec && bp->b_flags&B_READ) {
50425979Ssam 		/*
50525979Ssam 		 * Reading at end of file returns 0 bytes.
50625979Ssam 		 */
50725979Ssam 		bp->b_resid = bp->b_bcount;
50825979Ssam 		clrbuf(bp);
50925979Ssam 		goto next;
51024000Ssam 	}
51125979Ssam 	if ((bp->b_flags&B_READ) == 0)
51225979Ssam 		/*
51325979Ssam 		 * Writing sets EOF.
51425979Ssam 		 */
51525979Ssam 		yc->yc_nxrec = bdbtofsb(bp->b_blkno) + 1;
51625979Ssam 	if ((blkno = yc->yc_blkno) == bdbtofsb(bp->b_blkno)) {
51725979Ssam 		caddr_t addr;
51825979Ssam 		int cmd;
51925675Ssam 
52025979Ssam 		/*
52125979Ssam 		 * Choose the appropriate i/o command based on the
52225979Ssam 		 * transfer size and the controller's internal buffer.
52325979Ssam 		 * If we're retrying a read on a raw device because
52425979Ssam 		 * the original try was a buffer request which failed
52525979Ssam 		 * due to a record length error, then we force the use
52625979Ssam 		 * of the raw controller read (YECH!!!!).
52725979Ssam 		 */
52825979Ssam 		if (bp->b_flags&B_READ) {
52925979Ssam 			if (bp->b_bcount > cy->cy_bs || bp->b_errcnt)
53025979Ssam 				cmd = CY_RCOM;
53125979Ssam 			else
53225979Ssam 				cmd = CY_BRCOM;
53325979Ssam 		} else {
53425979Ssam 			/*
53525979Ssam 			 * On write error retries erase the
53625979Ssam 			 * inter-record gap before rewriting.
53725979Ssam 			 */
53825979Ssam 			if (vm->um_tab.b_errcnt &&
53925979Ssam 			    vm->um_tab.b_active != SERASED) {
54025979Ssam 				vm->um_tab.b_active = SERASE;
54125979Ssam 				bp->b_command = CY_ERASE;
54225979Ssam 				yc->yc_timo = 60;
54325979Ssam 				goto dobpcmd;
54425675Ssam 			}
54525979Ssam 			cmd = (bp->b_bcount > cy->cy_bs) ? CY_WCOM : CY_BWCOM;
54625675Ssam 		}
54725979Ssam 		vm->um_tab.b_active = SIO;
54825979Ssam 		addr = (caddr_t)vbastart(bp, cy->cy_buf,
54925979Ssam 		    (long *)cy->cy_map, cy->cy_utl);
55025979Ssam 		cy->cy_tpb.tpcmd = cmd;
55125979Ssam 		cy->cy_tpb.tpcontrol = yc->yc_dens;
55225979Ssam 		if (cmd == CY_RCOM || cmd == CY_WCOM)
55325979Ssam 			cy->cy_tpb.tpcontrol |= CYCW_LOCK;
55425979Ssam 		cy->cy_tpb.tpstatus = 0;
55525979Ssam 		cy->cy_tpb.tpcount = 0;
55625979Ssam 		cyldmba(cy->cy_tpb.tpdata, (caddr_t)addr);
55725979Ssam 		cy->cy_tpb.tprec = 0;
55825979Ssam 		cy->cy_tpb.tpsize = htoms(bp->b_bcount);
55925979Ssam 		cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
56025979Ssam 		do
56125979Ssam 			uncache(&cy->cy_ccb.cbgate);
56225979Ssam 		while (cy->cy_ccb.cbgate == GATE_CLOSED);
56325979Ssam 		cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
56425979Ssam 		cy->cy_ccb.cbcw = CBCW_IE;
56525979Ssam 		cy->cy_ccb.cbgate = GATE_CLOSED;
56625979Ssam 		dlog(LOG_INFO, "CY_GO(%x) cmd %x control %x size %d\n",
56725979Ssam 		    vm->um_addr, cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol,
56825979Ssam 		    htoms(cy->cy_tpb.tpsize));
56925979Ssam 		CY_GO(vm->um_addr);
57025979Ssam 		return;
57124000Ssam 	}
57225979Ssam 	/*
57325979Ssam 	 * Tape positioned incorrectly; set to seek forwards
57425979Ssam 	 * or backwards to the correct spot.  This happens
57525979Ssam 	 * for raw tapes only on error retries.
57625979Ssam 	 */
57725979Ssam 	vm->um_tab.b_active = SSEEK;
57825979Ssam 	if (blkno < bdbtofsb(bp->b_blkno)) {
57925979Ssam 		bp->b_command = CY_SFORW;
58025979Ssam 		cy->cy_tpb.tprec = htoms(bdbtofsb(bp->b_blkno) - blkno);
58125979Ssam 	} else {
58225979Ssam 		bp->b_command = CY_SREV;
58325979Ssam 		cy->cy_tpb.tprec = htoms(blkno - bdbtofsb(bp->b_blkno));
58424000Ssam 	}
58525979Ssam 	yc->yc_timo = imin(imax(10 * htoms(cy->cy_tpb.tprec), 60), 5*60);
58625979Ssam dobpcmd:
58725979Ssam 	/*
58825979Ssam 	 * Do the command in bp.  Reverse direction commands
58925979Ssam 	 * are indicated by having CYCW_REV or'd into their
59025979Ssam 	 * value.  For these we must set the appropriate bit
59125979Ssam 	 * in the control field.
59225979Ssam 	 */
59325979Ssam 	if (bp->b_command&CYCW_REV) {
59425979Ssam 		cy->cy_tpb.tpcmd = bp->b_command &~ CYCW_REV;
59525979Ssam 		cy->cy_tpb.tpcontrol = yc->yc_dens | CYCW_REV;
59625979Ssam 	} else {
59725979Ssam 		cy->cy_tpb.tpcmd = bp->b_command;
59825979Ssam 		cy->cy_tpb.tpcontrol = yc->yc_dens;
59924000Ssam 	}
60025979Ssam 	cy->cy_tpb.tpstatus = 0;
60125979Ssam 	cy->cy_tpb.tpcount = 0;
60225979Ssam 	cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
60325979Ssam 	do
60425979Ssam 		uncache(&cy->cy_ccb.cbgate);
60525979Ssam 	while (cy->cy_ccb.cbgate == GATE_CLOSED);
60625979Ssam 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
60725979Ssam 	cy->cy_ccb.cbcw = CBCW_IE;
60825979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
60925979Ssam 	dlog(LOG_INFO, "CY_GO(%x) cmd %x control %x rec %d\n",
61025979Ssam 	    vm->um_addr, cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol,
61125979Ssam 	    htoms(cy->cy_tpb.tprec));
61225979Ssam 	CY_GO(vm->um_addr);
61325979Ssam 	return;
61425979Ssam next:
61525979Ssam 	/*
61625979Ssam 	 * Done with this operation due to error or the
61725979Ssam 	 * fact that it doesn't do anything.  Release VERSAbus
61825979Ssam 	 * resource (if any), dequeue the transfer and continue
61925979Ssam 	 * processing this slave.
62025979Ssam 	 */
62125979Ssam 	if (bp == &rcybuf[CYUNIT(bp->b_dev)])
62225979Ssam 		vbadone(bp, cy->cy_buf, (long *)cy->cy_map, cy->cy_utl);
62325979Ssam 	vm->um_tab.b_errcnt = 0;
62425979Ssam 	dp->b_actf = bp->av_forw;
62525979Ssam 	iodone(bp);
62625979Ssam 	goto loop;
62725675Ssam }
62825675Ssam 
62925675Ssam /*
63025979Ssam  * Cy interrupt routine.
63125675Ssam  */
63225979Ssam cyintr(cipher)
63325979Ssam 	int cipher;
63425675Ssam {
63525979Ssam 	struct buf *dp;
63624000Ssam 	register struct buf *bp;
63725979Ssam 	register struct vba_ctlr *vm = cyminfo[cipher];
63825979Ssam 	register struct cy_softc *cy;
63925979Ssam 	register struct yc_softc *yc;
64025979Ssam 	int cyunit, err;
64125979Ssam 	register state;
64224000Ssam 
64325979Ssam 	dlog(LOG_INFO, "cyintr(%d)\n", cipher);
64425979Ssam 	/*
64525979Ssam 	 * First, turn off the interrupt from the controller
64625979Ssam 	 * (device uses Multibus non-vectored interrupts...yech).
64725979Ssam 	 */
64825979Ssam 	cy = &cy_softc[vm->um_ctlr];
64925979Ssam 	cy->cy_ccb.cbcw = CBCW_CLRINT;
65025979Ssam 	cyldmba(cy->cy_ccb.cbtpb, &cy->cy_nop);
65125979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
65225979Ssam 	CY_GO(vm->um_addr);
65325979Ssam 	if ((dp = vm->um_tab.b_actf) == NULL) {
65425979Ssam 		dlog(LOG_ERR, "cy%d: stray interrupt", vm->um_ctlr);
65524000Ssam 		return;
65624000Ssam 	}
65725979Ssam 	bp = dp->b_actf;
65825979Ssam 	cyunit = CYUNIT(bp->b_dev);
65925979Ssam 	cy = &cy_softc[cyunit];
66025979Ssam 	cyuncachetpb(cy);
66125979Ssam 	/*
662*25984Ssam 	 * If last command was a rewind and tape is
663*25984Ssam 	 * still moving, wait for the operation to complete.
66425979Ssam 	 */
66525979Ssam 	if (vm->um_tab.b_active == SREW) {
66625979Ssam 		vm->um_tab.b_active = SCOM;
66725979Ssam 		if ((cy->cy_tpb.tpstatus&CYS_RDY) == 0) {
66825979Ssam 			yc->yc_timo = 5*60;	/* 5 minutes */
66925979Ssam 			return;
67024000Ssam 		}
67124000Ssam 	}
67225979Ssam 	/*
67325979Ssam 	 * An operation completed...record status.
67425979Ssam 	 */
67525979Ssam 	yc = &yc_softc[YCUNIT(bp->b_dev)];
67625979Ssam 	yc->yc_timo = INF;
67725979Ssam 	yc->yc_control = cy->cy_tpb.tpcontrol;
67825979Ssam 	yc->yc_status = cy->cy_tpb.tpstatus;
67925979Ssam 	yc->yc_resid = bp->b_bcount - htoms(cy->cy_tpb.tpcount);
68025979Ssam 	dlog(LOG_INFO, "cmd %x control %b status %b resid %d\n",
68125979Ssam 	    cy->cy_tpb.tpcmd, yc->yc_control, CYCW_BITS,
68225979Ssam 	    yc->yc_status, CYS_BITS, yc->yc_resid);
68325979Ssam 	if ((bp->b_flags&B_READ) == 0)
68425979Ssam 		yc->yc_lastiow = 1;
68525979Ssam 	state = vm->um_tab.b_active;
68625979Ssam 	vm->um_tab.b_active = 0;
68725979Ssam 	/*
68825979Ssam 	 * Check for errors.
68925979Ssam 	 */
69025979Ssam 	if (cy->cy_tpb.tpstatus&CYS_ERR) {
69125979Ssam 		err = cy->cy_tpb.tpstatus&CYS_ERR;
69225979Ssam 		dlog(LOG_INFO, "error %d\n", err);
69325979Ssam 		/*
69425979Ssam 		 * If we hit the end of tape file, update our position.
69525979Ssam 		 */
69625979Ssam 		if (err == CYER_FM) {
69725979Ssam 			yc->yc_status |= CYS_FM;
69825979Ssam 			state = SCOM;		/* force completion */
69925979Ssam 			cyseteof(bp);		/* set blkno and nxrec */
70025979Ssam 			goto opdone;
70125979Ssam 		}
70225979Ssam 		/*
70325979Ssam 		 * Fix up errors which occur due to backspacing over
70425979Ssam 		 * the beginning of the tape.
70525979Ssam 		 */
70625979Ssam 		if (err == CYER_BOT && cy->cy_tpb.tpcontrol&CYCW_REV) {
70725979Ssam 			yc->yc_status |= CYS_BOT;
70825979Ssam 			goto ignoreerr;
70925979Ssam 		}
71025979Ssam 		/*
71125979Ssam 		 * If we were reading raw tape and the only error was that the
71225979Ssam 		 * record was too long, then we don't consider this an error.
71325979Ssam 		 */
71425979Ssam 		if (bp == &rcybuf[cyunit] && (bp->b_flags&B_READ) &&
71525979Ssam 		    err == CYER_STROBE) {
71625979Ssam 			/*
71725979Ssam 			 * Retry reads once with the command changed to
71825979Ssam 			 * a raw read (if possible).  Setting b_errcnt
71925979Ssam 			 * here causes cystart (above) to force a CY_RCOM.
72025979Ssam 			 */
72125979Ssam 			if (bp->b_errcnt++ != 0)
72225979Ssam 				goto ignoreerr;
72325979Ssam 			yc->yc_blkno++;
72425979Ssam 			goto opcont;
72525979Ssam 		}
72625979Ssam 		/*
72725979Ssam 		 * If error is not hard, and this was an i/o operation
72825979Ssam 		 * retry up to 8 times.
72925979Ssam 		 */
730*25984Ssam 		if (((1<<err)&CYER_SOFT) && state == SIO) {
73125979Ssam 			if (++vm->um_tab.b_errcnt < 7) {
73225979Ssam 				yc->yc_blkno++;
73325979Ssam 				goto opcont;
73425979Ssam 			}
73525979Ssam 		} else
73625979Ssam 			/*
73725979Ssam 			 * Hard or non-i/o errors on non-raw tape
73825979Ssam 			 * cause it to close.
73925979Ssam 			 */
74025979Ssam 			if (yc->yc_openf>0 && bp != &rcybuf[cyunit])
74125979Ssam 				yc->yc_openf = -1;
74225979Ssam 		/*
74325979Ssam 		 * Couldn't recover from error.
74425979Ssam 		 */
74525979Ssam 		tprintf(yc->yc_ttyp,
74625979Ssam 		    "yc%d: hard error bn%d status=%b", YCUNIT(bp->b_dev),
74725979Ssam 		    bp->b_blkno, yc->yc_status, CYS_BITS);
74825979Ssam 		if (err < NCYERROR)
74925979Ssam 			tprintf(yc->yc_ttyp, ", %s", cyerror[err]);
75025979Ssam 		tprintf(yc->yc_ttyp, "\n");
75125979Ssam 		bp->b_flags |= B_ERROR;
75225979Ssam 		goto opdone;
75324000Ssam 	}
75425979Ssam 	/*
75525979Ssam 	 * Advance tape control FSM.
75625979Ssam 	 */
75725979Ssam ignoreerr:
75825979Ssam 	/*
75925979Ssam 	 * If we hit a tape mark update our position.
76025979Ssam 	 */
76125979Ssam 	if (yc->yc_status&CYS_FM && bp->b_flags&B_READ) {
76225979Ssam 		cyseteof(bp);
76325979Ssam 		goto opdone;
76425675Ssam 	}
76525979Ssam 	switch (state) {
76624000Ssam 
76725979Ssam 	case SIO:
76825979Ssam 		/*
76925979Ssam 		 * Read/write increments tape block number.
77025979Ssam 		 */
77125979Ssam 		yc->yc_blkno++;
77225979Ssam 		goto opdone;
77324000Ssam 
77425979Ssam 	case SCOM:
77525979Ssam 		/*
77625979Ssam 		 * For forward/backward space record update current position.
77725979Ssam 		 */
77825979Ssam 		if (bp == &ccybuf[CYUNIT(bp->b_dev)]) switch (bp->b_command) {
77924000Ssam 
78025979Ssam 		case CY_SFORW:
78125979Ssam 			yc->yc_blkno -= bp->b_repcnt;
78225979Ssam 			break;
78324000Ssam 
78425979Ssam 		case CY_SREV:
78525979Ssam 			yc->yc_blkno += bp->b_repcnt;
78625979Ssam 			break;
78724000Ssam 		}
78825979Ssam 		goto opdone;
78925979Ssam 
79025979Ssam 	case SSEEK:
79125979Ssam 		yc->yc_blkno = bdbtofsb(bp->b_blkno);
79225979Ssam 		goto opcont;
79324000Ssam 
79425979Ssam 	case SERASE:
79525979Ssam 		/*
79625979Ssam 		 * Completed erase of the inter-record gap due to a
79725979Ssam 		 * write error; now retry the write operation.
79825979Ssam 		 */
79925979Ssam 		vm->um_tab.b_active = SERASED;
80025979Ssam 		goto opcont;
80124000Ssam 	}
80225675Ssam 
80325979Ssam opdone:
80425979Ssam 	/*
80525979Ssam 	 * Reset error count and remove from device queue.
80625979Ssam 	 */
80725979Ssam 	vm->um_tab.b_errcnt = 0;
80825979Ssam 	dp->b_actf = bp->av_forw;
80925979Ssam 	/*
81025979Ssam 	 * Save resid and release resources.
81125979Ssam 	 */
81225979Ssam 	bp->b_resid = bp->b_bcount - htoms(cy->cy_tpb.tpcount);
81325979Ssam 	if (bp == &rcybuf[CYUNIT(bp->b_dev)])
81425979Ssam 		vbadone(bp, cy->cy_buf, (long *)cy->cy_map, cy->cy_utl);
81525979Ssam 	iodone(bp);
81625979Ssam 	/*
81725979Ssam 	 * Circulate slave to end of controller
81825979Ssam 	 * queue to give other slaves a chance.
81925979Ssam 	 */
82025979Ssam 	vm->um_tab.b_actf = dp->b_forw;
82125979Ssam 	if (dp->b_actf) {
82225979Ssam 		dp->b_forw = NULL;
82325979Ssam 		if (vm->um_tab.b_actf == NULL)
82425979Ssam 			vm->um_tab.b_actf = dp;
82525979Ssam 		else
82625979Ssam 			vm->um_tab.b_actl->b_forw = dp;
82724000Ssam 	}
82825979Ssam 	if (vm->um_tab.b_actf == 0)
82924000Ssam 		return;
83025979Ssam opcont:
83125979Ssam 	cystart(vm);
83224000Ssam }
83324000Ssam 
83425979Ssam cytimer(dev)
83525979Ssam 	int dev;
83624000Ssam {
83725979Ssam 	register struct yc_softc *yc = &yc_softc[YCUNIT(dev)];
83825979Ssam 	int s;
83924000Ssam 
84025979Ssam 	if (yc->yc_timo != INF && (yc->yc_timo -= 5) < 0) {
84125979Ssam 		printf("yc%d: lost interrupt\n", YCUNIT(dev));
84225979Ssam 		yc->yc_timo = INF;
84325979Ssam 		s = spl3();
84425979Ssam 		cyintr(CYUNIT(dev));
84525979Ssam 		splx(s);
84624000Ssam 	}
84725979Ssam 	timeout(cytimer, (caddr_t)dev, 5*hz);
84824000Ssam }
84924000Ssam 
85025979Ssam cyseteof(bp)
85125979Ssam 	register struct buf *bp;
85224000Ssam {
85325979Ssam 	register int cyunit = CYUNIT(bp->b_dev);
85425979Ssam 	register struct cy_softc *cy = &cy_softc[cyunit];
85525979Ssam 	register struct yc_softc *yc = &yc_softc[YCUNIT(bp->b_dev)];
85624000Ssam 
85725979Ssam 	if (bp == &ccybuf[cyunit]) {
85825979Ssam 		if (yc->yc_blkno > bdbtofsb(bp->b_blkno)) {
85925979Ssam 			/* reversing */
86025979Ssam 			yc->yc_nxrec = bdbtofsb(bp->b_blkno) -
86125979Ssam 			    htoms(cy->cy_tpb.tpcount);
86225979Ssam 			yc->yc_blkno = yc->yc_nxrec;
86325979Ssam 		} else {
86425979Ssam 			yc->yc_blkno = bdbtofsb(bp->b_blkno) +
86525979Ssam 			    htoms(cy->cy_tpb.tpcount);
86625979Ssam 			yc->yc_nxrec = yc->yc_blkno - 1;
86724000Ssam 		}
86825675Ssam 		return;
86925675Ssam 	}
87025979Ssam 	/* eof on read */
87125979Ssam 	yc->yc_nxrec = bdbtofsb(bp->b_blkno);
87224000Ssam }
87324000Ssam 
87425979Ssam cyread(dev, uio)
87525979Ssam 	dev_t dev;
87625979Ssam 	struct uio *uio;
87725675Ssam {
87825979Ssam 	int errno;
87925675Ssam 
88025979Ssam 	errno = cyphys(dev, uio);
88125979Ssam 	if (errno)
88225979Ssam 		return (errno);
88325979Ssam 	return (physio(cystrategy, &rcybuf[CYUNIT(dev)], dev, B_READ, minphys, uio));
88425675Ssam }
88525675Ssam 
88625979Ssam cywrite(dev, uio)
88725979Ssam 	dev_t dev;
88825979Ssam 	struct uio *uio;
88924000Ssam {
89025979Ssam 	int errno;
89124000Ssam 
89225979Ssam 	errno = cyphys(dev, uio);
89325979Ssam 	if (errno)
89425979Ssam 		return (errno);
89525979Ssam 	return (physio(cystrategy, &rcybuf[CYUNIT(dev)], dev, B_WRITE, minphys, uio));
89624000Ssam }
89724000Ssam 
89824000Ssam /*
89925979Ssam  * Check that a raw device exits.
90025979Ssam  * If it does, set up the yc_blkno and yc_nxrec
90125979Ssam  * so that the tape will appear positioned correctly.
90225979Ssam  */
90325979Ssam cyphys(dev, uio)
90425675Ssam 	dev_t dev;
90525675Ssam 	struct uio *uio;
90625675Ssam {
90725979Ssam 	register int ycunit = YCUNIT(dev);
90825979Ssam 	register daddr_t a;
90925979Ssam 	register struct yc_softc *yc;
91025979Ssam 	register struct vba_device *vi;
91125675Ssam 
91225979Ssam 	if (ycunit >= NYC || (vi = ycdinfo[ycunit]) == 0 || vi->ui_alive == 0)
91325979Ssam 		return (ENXIO);
91425979Ssam 	yc = &yc_softc[ycunit];
91525979Ssam 	a = bdbtofsb(uio->uio_offset >> DEV_BSHIFT);
91625979Ssam 	yc->yc_blkno = a;
91725979Ssam 	yc->yc_nxrec = a + 1;
91825979Ssam 	return (0);
91925675Ssam }
92025675Ssam 
92125675Ssam /*ARGSUSED*/
92225675Ssam cyioctl(dev, cmd, data, flag)
92325979Ssam 	caddr_t data;
92425675Ssam 	dev_t dev;
92525675Ssam {
92625979Ssam 	int ycunit = YCUNIT(dev);
92725979Ssam 	register struct yc_softc *yc = &yc_softc[ycunit];
92825979Ssam 	register struct buf *bp = &ccybuf[CYUNIT(dev)];
92925979Ssam 	register callcount;
93025979Ssam 	int fcount, op;
93125979Ssam 	struct mtop *mtop;
93225979Ssam 	struct mtget *mtget;
93325979Ssam 	/* we depend of the values and order of the MT codes here */
93425979Ssam 	static cyops[] =
93525979Ssam 	{CY_WEOF,CY_SFORW,CY_SREV,CY_SFORW,CY_SREV,CY_REW,CY_OFFL,CY_SENSE};
93625675Ssam 
93725675Ssam 	switch (cmd) {
93825675Ssam 
93925979Ssam 	case MTIOCTOP:	/* tape operation */
94025979Ssam 		mtop = (struct mtop *)data;
94125979Ssam 		switch (op = mtop->mt_op) {
94225675Ssam 
94325979Ssam 		case MTWEOF:
94425979Ssam 		case MTFSR: case MTBSR:
94525979Ssam 		case MTFSF: case MTBSF:
94625979Ssam 			callcount = mtop->mt_count;
94725979Ssam 			fcount = 1;
94825979Ssam 			break;
94925675Ssam 
95025979Ssam 		case MTREW: case MTOFFL: case MTNOP:
95125979Ssam 			callcount = 1;
95225979Ssam 			fcount = 1;
95325979Ssam 			break;
95425675Ssam 
95525979Ssam 		default:
95625979Ssam 			return (ENXIO);
95725979Ssam 		}
95825979Ssam 		if (callcount <= 0 || fcount <= 0)
95925979Ssam 			return (EINVAL);
96025979Ssam 		while (--callcount >= 0) {
96125979Ssam 			/*
96225979Ssam 			 * Gagh, this controller is the pits...
96325979Ssam 			 */
96425979Ssam 			if (op == MTFSF || op == MTBSF) {
96525979Ssam 				do
96625979Ssam 					cycommand(dev, cyops[op], 1);
96725979Ssam 				while ((bp->b_flags&B_ERROR) == 0 &&
96825979Ssam 				 (yc->yc_status&(CYS_EOT|CYS_BOT|CYS_FM)) == 0);
96925979Ssam 			} else
97025979Ssam 				cycommand(dev, cyops[op], fcount);
97125979Ssam 			if ((bp->b_flags&B_ERROR) ||
97225979Ssam 			    (yc->yc_status&(CYS_BOT|CYS_EOT)))
97325979Ssam 				break;
97425979Ssam 		}
97525979Ssam 		bp->b_resid = callcount + 1;
97625979Ssam 		return (geterror(bp));
97725979Ssam 
97825979Ssam 	case MTIOCGET:
97925979Ssam 		cycommand(dev, CY_SENSE, 1);
98025979Ssam 		mtget = (struct mtget *)data;
98125979Ssam 		mtget->mt_dsreg = yc->yc_status;
98225979Ssam 		mtget->mt_erreg = yc->yc_control;
98325979Ssam 		mtget->mt_resid = yc->yc_resid;
98425979Ssam 		mtget->mt_type = MT_ISCY;
98525675Ssam 		break;
98625675Ssam 
98725675Ssam 	default:
98825675Ssam 		return (ENXIO);
98925675Ssam 	}
99025675Ssam 	return (0);
99125675Ssam }
99225675Ssam 
99325675Ssam /*
99425675Ssam  * Poll until the controller is ready.
99525675Ssam  */
99625675Ssam cywait(cp)
99725979Ssam 	register struct cyccb *cp;
99824000Ssam {
99925675Ssam 	register int i = 5000;
100024000Ssam 
100125979Ssam 	uncache(&cp->cbgate);
100225979Ssam 	while (i-- > 0 && cp->cbgate == GATE_CLOSED) {
100324000Ssam 		DELAY(1000);
100425979Ssam 		uncache(&cp->cbgate);
100524000Ssam 	}
100625675Ssam 	return (i <= 0);
100724000Ssam }
100824000Ssam 
100925675Ssam /*
101025979Ssam  * Load a 20 bit pointer into an i/o register.
101125675Ssam  */
101225979Ssam cyldmba(wreg, value)
101325979Ssam 	short *wreg;
101425979Ssam 	caddr_t value;
101524000Ssam {
101625979Ssam 	register int v = (int)value;
101725979Ssam 	register caddr_t reg = (caddr_t)wreg;
101825675Ssam 
101925979Ssam 	*reg++ = v;
102025979Ssam 	*reg++ = v >> 8;
102125979Ssam 	*reg++ = 0;
102225979Ssam 	*reg = (v&0xf0000) >> 12;
102324000Ssam }
102424000Ssam 
102525675Ssam /*
102625675Ssam  * Unconditionally reset all controllers to their initial state.
102725675Ssam  */
102825675Ssam cyreset(vba)
102925675Ssam 	int vba;
103024000Ssam {
103125675Ssam 	register caddr_t addr;
103225675Ssam 	register int ctlr;
103324000Ssam 
103425675Ssam 	for (ctlr = 0; ctlr < NCY; ctlr++)
103525675Ssam 		if (cyminfo[ctlr] && cyminfo[ctlr]->um_vbanum == vba) {
103625675Ssam 			addr = cyminfo[ctlr]->um_addr;
103725675Ssam 			CY_RESET(addr);
103825979Ssam 			if (!cyinit(ctlr)) {
103925675Ssam 				printf("cy%d: reset failed\n", ctlr);
104025675Ssam 				cyminfo[ctlr] = NULL;
104125675Ssam 			}
104225675Ssam 		}
104324000Ssam }
104425979Ssam 
104525979Ssam cyuncachetpb(cy)
104625979Ssam 	struct cy_softc *cy;
104725979Ssam {
104825979Ssam 	register long *lp = (long *)&cy->cy_tpb;
104925979Ssam 	register int i;
105025979Ssam 
105125979Ssam 	for (i = 0; i < howmany(sizeof (struct cytpb), sizeof (long)); i++)
105225979Ssam 		uncache(lp++);
105325979Ssam }
105425979Ssam 
105525979Ssam /*
105625979Ssam  * Dump routine.
105725979Ssam  */
105825979Ssam cydump(dev)
105925979Ssam 	dev_t dev;
106025979Ssam {
106125979Ssam 	register struct cy_softc *cy;
106225979Ssam 	register int bs, num, start;
106325979Ssam 	register caddr_t addr;
106425979Ssam 	int unit = CYUNIT(dev), ctlr, error;
106525979Ssam 
106625979Ssam 	if (unit >= NCY || cyminfo[unit] == 0 ||
106725979Ssam 	    (cy = &cy_softc[unit])->cy_bs == 0 || YCUNIT(dev) >= NYC)
106825979Ssam 		return (ENXIO);
106925979Ssam 	if (cywait(&cy->cy_ccb))
107025979Ssam 		return (EFAULT);
107125979Ssam #define	phys(a)	((caddr_t)((int)(a)&~0xc0000000))
107225979Ssam 	addr = phys(cyminfo[ctlr]->um_addr);
107325979Ssam 	num = maxfree, start = NBPG*2;
107425979Ssam 	while (num > 0) {
107525979Ssam 		bs = num > btoc(CYMAXIO) ? btoc(CYMAXIO) : num;
107625979Ssam 		error = cydwrite(cy, start, bs, addr);
107725979Ssam 		if (error)
107825979Ssam 			return (error);
107925979Ssam 		start += bs, num -= bs;
108025979Ssam 	}
108125979Ssam 	cyweof(cy, addr);
108225979Ssam 	cyweof(cy, addr);
108325979Ssam 	uncache(&cy->cy_tpb);
108425979Ssam 	if (cy->cy_tpb.tpstatus&CYS_ERR)
108525979Ssam 		return (EIO);
108625979Ssam 	cyrewind(cy, addr);
108725979Ssam 	return (0);
108825979Ssam }
108925979Ssam 
109025979Ssam cydwrite(cy, pf, npf, addr)
109125979Ssam 	register struct cy_softc *cy;
109225979Ssam 	int pf, npf;
109325979Ssam 	caddr_t addr;
109425979Ssam {
109525979Ssam 
109625979Ssam 	cy->cy_tpb.tpcmd = CY_WCOM;
109725979Ssam 	cy->cy_tpb.tpcontrol = CYCW_LOCK|CYCW_25IPS|CYCW_16BITS;
109825979Ssam 	cy->cy_tpb.tpstatus = 0;
109925979Ssam 	cy->cy_tpb.tpsize = htoms(npf*NBPG);
110025979Ssam 	cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
110125979Ssam 	cyldmba(cy->cy_tpb.tpdata, (caddr_t)(pf*NBPG));
110225979Ssam 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
110325979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
110425979Ssam 	CY_GO(addr);
110525979Ssam 	if (cywait(&cy->cy_ccb))
110625979Ssam 		return (EFAULT);
110725979Ssam 	uncache(&cy->cy_tpb);
110825979Ssam 	if (cy->cy_tpb.tpstatus&CYS_ERR)
110925979Ssam 		return (EIO);
111025979Ssam 	return (0);
111125979Ssam }
111225979Ssam 
111325979Ssam cyweof(cy, addr)
111425979Ssam 	register struct cy_softc *cy;
111525979Ssam 	caddr_t addr;
111625979Ssam {
111725979Ssam 
111825979Ssam 	cy->cy_tpb.tpcmd = CY_WEOF;
111925979Ssam 	cy->cy_tpb.tpcount = htoms(1);
112025979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
112125979Ssam 	CY_GO(addr);
112225979Ssam 	(void) cywait(&cy->cy_ccb);
112325979Ssam }
112425979Ssam 
112525979Ssam cyrewind(cy, addr)
112625979Ssam 	register struct cy_softc *cy;
112725979Ssam 	caddr_t addr;
112825979Ssam {
112925979Ssam 
113025979Ssam 	cy->cy_tpb.tpcmd = CY_REW;
113125979Ssam 	cy->cy_tpb.tpcount = htoms(1);
113225979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
113325979Ssam 	CY_GO(addr);
113425979Ssam 	(void) cywait(&cy->cy_ccb);
113525979Ssam }
113624000Ssam #endif
1137