xref: /csrg-svn/sys/tahoe/vba/cy.c (revision 25979)
1*25979Ssam /*	cy.c	1.4	86/01/26	*/
224000Ssam 
324000Ssam #include "cy.h"
4*25979Ssam #include "yc.h"
525675Ssam #if NCY > 0
624000Ssam /*
725675Ssam  * Cipher Tapemaster driver.
824000Ssam  */
925675Ssam int	cydebug = 0;
10*25979Ssam #define	dlog	if (cydebug) log
1124000Ssam 
1225675Ssam #include "../tahoe/mtpr.h"
1325675Ssam #include "../tahoe/pte.h"
1424000Ssam 
1525675Ssam #include "param.h"
1625675Ssam #include "systm.h"
1725675Ssam #include "vm.h"
1825675Ssam #include "buf.h"
1925675Ssam #include "file.h"
2025675Ssam #include "dir.h"
2125675Ssam #include "user.h"
2225675Ssam #include "proc.h"
2325675Ssam #include "signal.h"
2425675Ssam #include "uio.h"
2525675Ssam #include "ioctl.h"
2625675Ssam #include "mtio.h"
2725675Ssam #include "errno.h"
2825675Ssam #include "cmap.h"
29*25979Ssam #include "kernel.h"
30*25979Ssam #include "syslog.h"
3124000Ssam 
3225675Ssam #include "../tahoevba/vbavar.h"
33*25979Ssam #define	CYERROR
3425675Ssam #include "../tahoevba/cyreg.h"
3524000Ssam 
36*25979Ssam /*
37*25979Ssam  * There is a ccybuf per tape controller.
38*25979Ssam  * It is used as the token to pass to the internal routines
39*25979Ssam  * to execute tape ioctls, and also acts as a lock on the slaves
40*25979Ssam  * on the controller, since there is only one per controller.
41*25979Ssam  * In particular, when the tape is rewinding on close we release
42*25979Ssam  * the user process but any further attempts to use the tape drive
43*25979Ssam  * before the rewind completes will hang waiting for ccybuf.
44*25979Ssam  */
45*25979Ssam struct	buf ccybuf[NCY];
4624000Ssam 
47*25979Ssam /*
48*25979Ssam  * Raw tape operations use rcybuf.  The driver notices when
49*25979Ssam  * rcybuf is being used and allows the user program to contine
50*25979Ssam  * after errors and read records not of the standard length.
51*25979Ssam  */
52*25979Ssam struct	buf rcybuf[NCY];
5324000Ssam 
54*25979Ssam int	cyprobe(), cyslave(), cyattach();
55*25979Ssam struct	buf ycutab[NYC];
56*25979Ssam short	yctocy[NYC];
5725675Ssam struct	vba_ctlr *cyminfo[NCY];
58*25979Ssam struct	vba_device *ycdinfo[NYC];
5925857Ssam long	cystd[] = { 0 };
6025857Ssam struct	vba_driver cydriver =
61*25979Ssam    { cyprobe, cyslave, cyattach, 0, cystd, "yc", ycdinfo, "cy", cyminfo };
6224000Ssam 
63*25979Ssam /* bits in minor device */
64*25979Ssam #define	YCUNIT(dev)	(minor(dev)&03)
65*25979Ssam #define	CYUNIT(dev)	(yctocy[YCUNIT(dev)])
66*25979Ssam #define	T_NOREWIND	0x04
67*25979Ssam #define	T_1600BPI	0x08
68*25979Ssam #define	T_3200BPI	0x10
69*25979Ssam 
70*25979Ssam #define	INF	1000000L		/* close to infinity */
71*25979Ssam #define	CYMAXIO	(32*NBPG)		/* max i/o size */
72*25979Ssam 
7324000Ssam /*
74*25979Ssam  * Software state and shared command areas per controller.
75*25979Ssam  *
76*25979Ssam  * The i/o buffer must be defined statically to insure
77*25979Ssam  * it's address will fit in 20-bits (YECH!!!!!!!!!!!!!!)
7824000Ssam  */
79*25979Ssam struct cy_softc {
80*25979Ssam 	struct	pte *cy_map;	/* pte's for mapped buffer i/o */
81*25979Ssam 	caddr_t	cy_utl;		/* mapped virtual address */
82*25979Ssam 	int	cy_bs;		/* controller's buffer size */
83*25979Ssam 	char	cy_buf[CYMAXIO];/* intermediate buffer */
84*25979Ssam 	struct	cyscp *cy_scp;	/* system configuration block address */
85*25979Ssam 	struct	cyccb cy_ccb;	/* channel control block */
86*25979Ssam 	struct	cyscb cy_scb;	/* system configuration block */
87*25979Ssam 	struct	cytpb cy_tpb;	/* tape parameter block */
88*25979Ssam 	struct	cytpb cy_nop;	/* nop parameter block for cyintr */
89*25979Ssam } cy_softc[NCY];
9024000Ssam 
91*25979Ssam /*
92*25979Ssam  * Software state per tape transport.
93*25979Ssam  */
94*25979Ssam struct	yc_softc {
95*25979Ssam 	char	yc_openf;	/* lock against multiple opens */
96*25979Ssam 	char	yc_lastiow;	/* last operation was a write */
97*25979Ssam 	short	yc_tact;	/* timeout is active */
98*25979Ssam 	long	yc_timo;	/* time until timeout expires */
99*25979Ssam 	u_short	yc_control;	/* copy of last tpcb.tpcontrol */
100*25979Ssam 	u_short	yc_status;	/* copy of last tpcb.tpstatus */
101*25979Ssam 	u_short	yc_resid;	/* copy of last bc */
102*25979Ssam 	u_short	yc_dens;	/* prototype control word with density info */
103*25979Ssam 	struct	tty *yc_ttyp;	/* user's tty for errors */
104*25979Ssam 	daddr_t	yc_blkno;	/* block number, for block device tape */
105*25979Ssam 	daddr_t	yc_nxrec;	/* position of end of tape, if known */
106*25979Ssam } yc_softc[NYC];
10724000Ssam 
10824000Ssam /*
109*25979Ssam  * States for vm->um_tab.b_active, the per controller state flag.
110*25979Ssam  * This is used to sequence control in the driver.
11124000Ssam  */
112*25979Ssam #define	SSEEK	1		/* seeking */
113*25979Ssam #define	SIO	2		/* doing seq i/o */
114*25979Ssam #define	SCOM	3		/* sending control command */
115*25979Ssam #define	SREW	4		/* sending a rewind */
116*25979Ssam #define	SERASE	5		/* erase inter-record gap */
117*25979Ssam #define	SERASED	6		/* erased inter-record gap */
11824000Ssam 
119*25979Ssam /* there's no way to figure these out dynamically? -- yech */
120*25979Ssam struct	cyscp *cyscp[] =
121*25979Ssam     { (struct cyscp *)0xc0000c06, (struct cyscp *)0xc0000c16 };
122*25979Ssam #define	NCYSCP	(sizeof (cyscp) / sizeof (cyscp[0]))
123*25979Ssam 
12425857Ssam cyprobe(reg, vm)
12525857Ssam 	caddr_t reg;
12625857Ssam 	struct vba_ctlr *vm;
12725675Ssam {
12825857Ssam 	register br, cvec;			/* must be r12, r11 */
129*25979Ssam 	struct cy_softc *cy;
13025675Ssam 
13125857Ssam 	if (badcyaddr(reg+1))
13225675Ssam 		return (0);
133*25979Ssam 	if (vm->um_ctlr > NCYSCP || cyscp[vm->um_ctlr] == 0)	/* XXX */
134*25979Ssam 		return (0);					/* XXX */
135*25979Ssam 	cy_softc[vm->um_ctlr].cy_scp = cyscp[vm->um_ctlr];	/* XXX */
136*25979Ssam 	/*
137*25979Ssam 	 * Tapemaster controller must have interrupt handler
138*25979Ssam 	 * disable interrupt, so we'll just kludge things
139*25979Ssam 	 * (stupid multibus non-vectored interrupt crud).
140*25979Ssam 	 */
141*25979Ssam 	br = 0x13, cvec = 0x80;					/* XXX */
142*25979Ssam 	return (sizeof (struct cyccb));
14325675Ssam }
14425675Ssam 
14524000Ssam /*
14625857Ssam  * Check to see if a drive is attached to a controller.
14725857Ssam  * Since we can only tell that a drive is there if a tape is loaded and
14825857Ssam  * the drive is placed online, we always indicate the slave is present.
14924000Ssam  */
15025857Ssam cyslave(vi, addr)
15125857Ssam 	struct vba_device *vi;
15225857Ssam 	caddr_t addr;
15324000Ssam {
15425857Ssam 
15525857Ssam #ifdef lint
15625857Ssam 	vi = vi; addr = addr;
15725857Ssam #endif
15825857Ssam 	return (1);
15925857Ssam }
16025857Ssam 
16125857Ssam cyattach(vi)
16225857Ssam 	struct vba_device *vi;
16325857Ssam {
164*25979Ssam 	register struct cy_softc *cy;
165*25979Ssam 	int ctlr = vi->ui_mi->um_ctlr;
16625857Ssam 
167*25979Ssam 	yctocy[vi->ui_unit] = ctlr;
168*25979Ssam 	cy = &cy_softc[ctlr];
169*25979Ssam 	if (cy->cy_bs == 0 && cyinit(ctlr)) {
170*25979Ssam 		uncache(&cy->cy_tpb.tpcount);
171*25979Ssam 		cy->cy_bs = htoms(cy->cy_tpb.tpcount);
172*25979Ssam 		printf("cy%d: %dkb buffer\n", ctlr, cy->cy_bs/1024);
173*25979Ssam 		/*
174*25979Ssam 		 * Setup nop parameter block for clearing interrupts.
175*25979Ssam 		 */
176*25979Ssam 		cy->cy_nop.tpcmd = CY_NOP;
177*25979Ssam 		cy->cy_nop.tpcontrol = 0;
178*25979Ssam 		/*
179*25979Ssam 		 * Allocate page tables.
180*25979Ssam 		 */
181*25979Ssam 		vbmapalloc(btoc(CYMAXIO)+1, &cy->cy_map, &cy->cy_utl);
18225857Ssam 	}
18325857Ssam }
18425857Ssam 
18525857Ssam /*
18625857Ssam  * Initialize the controller after a controller reset or
18725857Ssam  * during autoconfigure.  All of the system control blocks
18825857Ssam  * are initialized and the controller is asked to configure
18925857Ssam  * itself for later use.
19025857Ssam  */
191*25979Ssam cyinit(ctlr)
192*25979Ssam 	int ctlr;
19325857Ssam {
194*25979Ssam 	register struct cy_softc *cy = &cy_softc[ctlr];
195*25979Ssam 	register caddr_t addr = cyminfo[ctlr]->um_addr;
19625675Ssam 	register int *pte;
19724000Ssam 
19824000Ssam 	/*
19925675Ssam 	 * Initialize the system configuration pointer.
20024000Ssam 	 */
20125675Ssam 	/* make kernel writable */
202*25979Ssam 	pte = (int *)vtopte((struct proc *)0, btop(cy->cy_scp));
20325675Ssam 	*pte &= ~PG_PROT; *pte |= PG_KW;
204*25979Ssam 	mtpr(TBIS, cy->cy_scp);
20525675Ssam 	/* load the correct values in the scp */
206*25979Ssam 	cy->cy_scp->csp_buswidth = CSP_16BITS;
207*25979Ssam 	cyldmba(cy->cy_scp->csp_scb, (caddr_t)&cy->cy_scb);
20825675Ssam 	/* put it back to read-only */
20925675Ssam 	*pte &= ~PG_PROT; *pte |= PG_KR;
210*25979Ssam 	mtpr(TBIS, cy->cy_scp);
21125675Ssam 
21224000Ssam 	/*
21325675Ssam 	 * Init system configuration block.
21424000Ssam 	 */
215*25979Ssam 	cy->cy_scb.csb_fixed = 0x3;
21625675Ssam 	/* set pointer to the channel control block */
217*25979Ssam 	cyldmba(cy->cy_scb.csb_ccb, (caddr_t)&cy->cy_ccb);
21825675Ssam 
21924000Ssam 	/*
22025675Ssam 	 * Initialize the chanel control block.
22124000Ssam 	 */
222*25979Ssam 	cy->cy_ccb.cbcw = CBCW_CLRINT;
223*25979Ssam 	cy->cy_ccb.cbgate = GATE_OPEN;
22425675Ssam 	/* set pointer to the tape parameter block */
225*25979Ssam 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
22625675Ssam 
22724000Ssam 	/*
228*25979Ssam 	 * Issue a nop cmd and get the internal buffer size for buffered i/o.
22924000Ssam 	 */
230*25979Ssam 	cy->cy_tpb.tpcmd = CY_NOP;
231*25979Ssam 	cy->cy_tpb.tpcontrol = CYCW_16BITS;
232*25979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
233*25979Ssam 	CY_GO(addr);
234*25979Ssam 	if (cywait(&cy->cy_ccb) || (cy->cy_tpb.tpstatus&CYS_ERR)) {
235*25979Ssam 		uncache(&cy->cy_tpb.tpstatus);
236*25979Ssam 		printf("cy%d: timeout or err during init, status=%b\n", ctlr,
237*25979Ssam 		    cy->cy_tpb.tpstatus, CYS_BITS);
23825675Ssam 		return (0);
23925675Ssam 	}
240*25979Ssam 	cy->cy_tpb.tpcmd = CY_CONFIG;
241*25979Ssam 	cy->cy_tpb.tpcontrol = CYCW_16BITS;
242*25979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
243*25979Ssam 	CY_GO(addr);
244*25979Ssam 	if (cywait(&cy->cy_ccb) || (cy->cy_tpb.tpstatus&CYS_ERR)) {
245*25979Ssam 		uncache(&cy->cy_tpb.tpstatus);
246*25979Ssam 		printf("cy%d: configuration failure, status=%b\n", ctlr,
247*25979Ssam 		    cy->cy_tpb.tpstatus, CYS_BITS);
24825675Ssam 		return (0);
24925675Ssam 	}
25025675Ssam 	return (1);
25124000Ssam }
25224000Ssam 
253*25979Ssam int	cytimer();
254*25979Ssam /*
255*25979Ssam  * Open the device.  Tapes are unique open
256*25979Ssam  * devices, so we refuse if it is already open.
257*25979Ssam  * We also check that a tape is available, and
258*25979Ssam  * don't block waiting here; if you want to wait
259*25979Ssam  * for a tape you should timeout in user code.
260*25979Ssam  */
26125675Ssam cyopen(dev, flag)
262*25979Ssam 	dev_t dev;
26325675Ssam 	register int flag;
26425675Ssam {
265*25979Ssam 	register int ycunit;
266*25979Ssam 	register struct vba_device *vi;
267*25979Ssam 	register struct yc_softc *yc;
268*25979Ssam 	int s;
26925675Ssam 
270*25979Ssam 	ycunit = YCUNIT(dev);
271*25979Ssam 	if (ycunit >= NYC || (vi = ycdinfo[ycunit]) == 0 || vi->ui_alive == 0)
27225675Ssam 		return (ENXIO);
273*25979Ssam 	if ((yc = &yc_softc[ycunit])->yc_openf)
274*25979Ssam 		return (EBUSY);
275*25979Ssam #define	PACKUNIT(vi) \
276*25979Ssam     (((vi->ui_slave&1)<<11)|((vi->ui_slave&2)<<9)|((vi->ui_slave&4)>>2))
277*25979Ssam 	/* no way to select density */
278*25979Ssam 	yc->yc_dens = PACKUNIT(vi)|CYCW_IE|CYCW_16BITS;
279*25979Ssam 	cycommand(dev, CY_SENSE, 1);
280*25979Ssam 	if ((yc->yc_status&CYS_OL) == 0) {	/* not on-line */
281*25979Ssam 		uprintf("yc%d: not online\n", ycunit);
28225675Ssam 		return (ENXIO);
28325675Ssam 	}
284*25979Ssam 	if ((flag&FWRITE) && (yc->yc_status&CYS_WP)) {
285*25979Ssam 		uprintf("yc%d: no write ring\n", ycunit);
28625675Ssam 		return (ENXIO);
28725675Ssam 	}
288*25979Ssam 	yc->yc_openf = 1;
289*25979Ssam 	yc->yc_blkno = (daddr_t)0;
290*25979Ssam 	yc->yc_nxrec = INF;
291*25979Ssam 	yc->yc_lastiow = 0;
292*25979Ssam 	yc->yc_ttyp = u.u_ttyp;
293*25979Ssam 	s = splclock();
294*25979Ssam 	if (yc->yc_tact == 0) {
295*25979Ssam 		yc->yc_timo = INF;
296*25979Ssam 		yc->yc_tact = 1;
297*25979Ssam 		timeout(cytimer, (caddr_t)dev, 5*hz);
29825675Ssam 	}
299*25979Ssam 	splx(s);
30025675Ssam 	return (0);
30125675Ssam }
30225675Ssam 
303*25979Ssam /*
304*25979Ssam  * Close tape device.
305*25979Ssam  *
306*25979Ssam  * If tape was open for writing or last operation was a write,
307*25979Ssam  * then write two EOF's and backspace over the last one.
308*25979Ssam  * Unless this is a non-rewinding special file, rewind the tape.
309*25979Ssam  * Make the tape available to others.
310*25979Ssam  */
31125675Ssam cyclose(dev, flag)
312*25979Ssam 	dev_t dev;
313*25979Ssam 	register int flag;
31425675Ssam {
315*25979Ssam 	register struct yc_softc *yc = &yc_softc[YCUNIT(dev)];
31625675Ssam 
317*25979Ssam 	if (flag == FWRITE || (flag&FWRITE) && yc->yc_lastiow) {
318*25979Ssam 		cycommand(dev, CY_WEOF, 2);
319*25979Ssam 		cycommand(dev, CY_SREV, 1);
32025675Ssam 	}
321*25979Ssam 	if ((minor(dev)&T_NOREWIND) == 0)
322*25979Ssam 		/*
323*25979Ssam 		 * 0 count means don't hang waiting for rewind complete
324*25979Ssam 		 * rather ccybuf stays busy until the operation completes
325*25979Ssam 		 * preventing further opens from completing by preventing
326*25979Ssam 		 * a CY_SENSE from completing.
327*25979Ssam 		 */
328*25979Ssam 		cycommand(dev, CY_REW, 0);
329*25979Ssam 	yc->yc_openf = 0;
33025675Ssam }
33125675Ssam 
33224000Ssam /*
333*25979Ssam  * Execute a command on the tape drive a specified number of times.
33424000Ssam  */
335*25979Ssam cycommand(dev, com, count)
336*25979Ssam 	dev_t dev;
337*25979Ssam 	int com, count;
33824000Ssam {
33925675Ssam 	register int unit = CYUNIT(dev);
340*25979Ssam 	register struct buf *bp;
34125675Ssam 	int s;
34225675Ssam 
343*25979Ssam 	bp = &ccybuf[CYUNIT(dev)];
34425675Ssam 	s = spl3();
345*25979Ssam 	dlog(LOG_INFO, "cycommand(%o, %x, %d), b_flags %x\n",
346*25979Ssam 	    dev, com, count, bp->b_flags);
347*25979Ssam 	while (bp->b_flags&B_BUSY) {
348*25979Ssam 		/*
349*25979Ssam 		 * This special check is because B_BUSY never
350*25979Ssam 		 * gets cleared in the non-waiting rewind case.
351*25979Ssam 		 */
352*25979Ssam 		if (bp->b_repcnt == 0 && (bp->b_flags&B_DONE))
353*25979Ssam 			break;
354*25979Ssam 		bp->b_flags |= B_WANTED;
355*25979Ssam 		sleep((caddr_t)bp, PRIBIO);
35625675Ssam 	}
357*25979Ssam 	bp->b_flags = B_BUSY|B_READ;
35825675Ssam 	splx(s);
359*25979Ssam 	bp->b_dev = dev;
360*25979Ssam 	bp->b_repcnt = count;
361*25979Ssam 	bp->b_command = com;
362*25979Ssam 	bp->b_blkno = 0;
363*25979Ssam 	cystrategy(bp);
364*25979Ssam 	/*
365*25979Ssam 	 * In case of rewind from close; don't wait.
366*25979Ssam 	 * This is the only case where count can be 0.
367*25979Ssam 	 */
368*25979Ssam 	if (count == 0)
369*25979Ssam 		return;
370*25979Ssam 	iowait(bp);
371*25979Ssam 	if (bp->b_flags&B_WANTED)
372*25979Ssam 		wakeup((caddr_t)bp);
373*25979Ssam 	bp->b_flags &= B_ERROR;
37424000Ssam }
37524000Ssam 
37625675Ssam cystrategy(bp)
37725675Ssam 	register struct buf *bp;
37825675Ssam {
379*25979Ssam 	int ycunit = YCUNIT(bp->b_dev);
380*25979Ssam 	register struct vba_ctlr *vm;
381*25979Ssam 	register struct buf *dp;
38225675Ssam 	int s;
38325675Ssam 
384*25979Ssam 	/*
385*25979Ssam 	 * Put transfer at end of unit queue.
386*25979Ssam 	 */
387*25979Ssam 	dlog(LOG_INFO, "cystrategy(%o, %x)\n", bp->b_dev, bp->b_command);
388*25979Ssam 	dp = &ycutab[ycunit];
38925675Ssam 	bp->av_forw = NULL;
390*25979Ssam 	vm = ycdinfo[ycunit]->ui_mi;
391*25979Ssam 	/* BEGIN GROT */
392*25979Ssam 	if (bp == &rcybuf[CYUNIT(bp->b_dev)]) {
393*25979Ssam 		if (bp->b_bcount > CYMAXIO) {
394*25979Ssam 			uprintf("cy%d: i/o size too large\n", vm->um_ctlr);
395*25979Ssam 			bp->b_error = EIO;
396*25979Ssam 			bp->b_resid = bp->b_bcount;
397*25979Ssam 			bp->b_flags |= B_ERROR;
39825675Ssam 			iodone(bp);
39925675Ssam 			return;
40025675Ssam 		}
401*25979Ssam 		vbasetup(bp, CYMAXIO);
40224000Ssam 	}
403*25979Ssam 	/* END GROT */
40425675Ssam 	s = spl3();
405*25979Ssam 	if (dp->b_actf == NULL) {
406*25979Ssam 		dp->b_actf = bp;
407*25979Ssam 		/*
408*25979Ssam 		 * Transport not already active...
409*25979Ssam 		 * put at end of controller queue.
410*25979Ssam 		 */
411*25979Ssam 		 dp->b_forw = NULL;
412*25979Ssam 		 if (vm->um_tab.b_actf == NULL)
413*25979Ssam 			vm->um_tab.b_actf = dp;
414*25979Ssam 		else
415*25979Ssam 			vm->um_tab.b_actl->b_forw = dp;
416*25979Ssam 	} else
417*25979Ssam 		dp->b_actl->av_forw = bp;
418*25979Ssam 	dp->b_actl = bp;
419*25979Ssam 	/*
420*25979Ssam 	 * If the controller is not busy, get it going.
421*25979Ssam 	 */
422*25979Ssam 	if (vm->um_tab.b_active == 0)
423*25979Ssam 		cystart(vm);
42424000Ssam 	splx(s);
42524000Ssam }
42624000Ssam 
42724000Ssam /*
428*25979Ssam  * Start activity on a cy controller.
42924000Ssam  */
430*25979Ssam cystart(vm)
431*25979Ssam 	register struct vba_ctlr *vm;
43224000Ssam {
433*25979Ssam 	register struct buf *bp, *dp;
434*25979Ssam 	register struct yc_softc *yc;
435*25979Ssam 	register struct cy_softc *cy;
436*25979Ssam 	register struct vba_device *vi;
437*25979Ssam 	int ycunit;
438*25979Ssam 	daddr_t blkno;
43924000Ssam 
440*25979Ssam 	dlog(LOG_INFO, "cystart()\n");
441*25979Ssam 	/*
442*25979Ssam 	 * Look for an idle transport on the controller.
443*25979Ssam 	 */
444*25979Ssam loop:
445*25979Ssam 	if ((dp = vm->um_tab.b_actf) == NULL)
44625675Ssam 		return;
447*25979Ssam 	if ((bp = dp->b_actf) == NULL) {
448*25979Ssam 		vm->um_tab.b_actf = dp->b_forw;
449*25979Ssam 		goto loop;
45025675Ssam 	}
451*25979Ssam 	ycunit = YCUNIT(bp->b_dev);
452*25979Ssam 	yc = &yc_softc[ycunit];
453*25979Ssam 	cy = &cy_softc[CYUNIT(bp->b_dev)];
454*25979Ssam 	/*
455*25979Ssam 	 * Default is that last command was NOT a write command;
456*25979Ssam 	 * if we do a write command we will notice this in cyintr().
457*25979Ssam 	 */
458*25979Ssam 	yc->yc_lastiow = 0;
459*25979Ssam 	if (yc->yc_openf < 0 ||
460*25979Ssam 	    (bp->b_command != CY_SENSE && (cy->cy_tpb.tpstatus&CYS_OL) == 0)) {
461*25979Ssam 		/*
462*25979Ssam 		 * Have had a hard error on a non-raw tape
463*25979Ssam 		 * or the tape unit is now unavailable (e.g.
464*25979Ssam 		 * taken off line).
465*25979Ssam 		 */
466*25979Ssam 		dlog(LOG_INFO, "openf %d command %x status %b\n",
467*25979Ssam 		    yc->yc_openf, bp->b_command, cy->cy_tpb.tpstatus, CYS_BITS);
468*25979Ssam 		bp->b_flags |= B_ERROR;
469*25979Ssam 		goto next;
47025675Ssam 	}
471*25979Ssam 	if (bp == &ccybuf[CYUNIT(bp->b_dev)]) {
472*25979Ssam 		/*
473*25979Ssam 		 * Execute control operation with the specified count.
474*25979Ssam 		 *
475*25979Ssam 		 * Set next state; give 5 minutes to complete
476*25979Ssam 		 * rewind or file mark search, or 10 seconds per
477*25979Ssam 		 * iteration (minimum 60 seconds and max 5 minutes)
478*25979Ssam 		 * to complete other ops.
479*25979Ssam 		 */
480*25979Ssam 		if (bp->b_command == CY_REW) {
481*25979Ssam 			vm->um_tab.b_active = SREW;
482*25979Ssam 			yc->yc_timo = 5*60;
483*25979Ssam 		} else {
484*25979Ssam 			vm->um_tab.b_active = SCOM;
485*25979Ssam 			yc->yc_timo = imin(imax(10*(int)bp->b_repcnt,60),5*60);
486*25979Ssam 		}
487*25979Ssam 		cy->cy_tpb.tprec = htoms(bp->b_repcnt);
488*25979Ssam 		goto dobpcmd;
48924000Ssam 	}
490*25979Ssam 	/*
491*25979Ssam 	 * The following checks handle boundary cases for operation
492*25979Ssam 	 * on no-raw tapes.  On raw tapes the initialization of
493*25979Ssam 	 * yc->yc_nxrec by cyphys causes them to be skipped normally
494*25979Ssam 	 * (except in the case of retries).
495*25979Ssam 	 */
496*25979Ssam 	if (bdbtofsb(bp->b_blkno) > yc->yc_nxrec) {
497*25979Ssam 		/*
498*25979Ssam 		 * Can't read past known end-of-file.
499*25979Ssam 		 */
500*25979Ssam 		bp->b_flags |= B_ERROR;
501*25979Ssam 		bp->b_error = ENXIO;
502*25979Ssam 		goto next;
50324000Ssam 	}
504*25979Ssam 	if (bdbtofsb(bp->b_blkno) == yc->yc_nxrec && bp->b_flags&B_READ) {
505*25979Ssam 		/*
506*25979Ssam 		 * Reading at end of file returns 0 bytes.
507*25979Ssam 		 */
508*25979Ssam 		bp->b_resid = bp->b_bcount;
509*25979Ssam 		clrbuf(bp);
510*25979Ssam 		goto next;
51124000Ssam 	}
512*25979Ssam 	if ((bp->b_flags&B_READ) == 0)
513*25979Ssam 		/*
514*25979Ssam 		 * Writing sets EOF.
515*25979Ssam 		 */
516*25979Ssam 		yc->yc_nxrec = bdbtofsb(bp->b_blkno) + 1;
517*25979Ssam 	if ((blkno = yc->yc_blkno) == bdbtofsb(bp->b_blkno)) {
518*25979Ssam 		caddr_t addr;
519*25979Ssam 		int cmd;
52025675Ssam 
521*25979Ssam 		/*
522*25979Ssam 		 * Choose the appropriate i/o command based on the
523*25979Ssam 		 * transfer size and the controller's internal buffer.
524*25979Ssam 		 * If we're retrying a read on a raw device because
525*25979Ssam 		 * the original try was a buffer request which failed
526*25979Ssam 		 * due to a record length error, then we force the use
527*25979Ssam 		 * of the raw controller read (YECH!!!!).
528*25979Ssam 		 */
529*25979Ssam 		if (bp->b_flags&B_READ) {
530*25979Ssam 			if (bp->b_bcount > cy->cy_bs || bp->b_errcnt)
531*25979Ssam 				cmd = CY_RCOM;
532*25979Ssam 			else
533*25979Ssam 				cmd = CY_BRCOM;
534*25979Ssam 		} else {
535*25979Ssam 			/*
536*25979Ssam 			 * On write error retries erase the
537*25979Ssam 			 * inter-record gap before rewriting.
538*25979Ssam 			 */
539*25979Ssam 			if (vm->um_tab.b_errcnt &&
540*25979Ssam 			    vm->um_tab.b_active != SERASED) {
541*25979Ssam 				vm->um_tab.b_active = SERASE;
542*25979Ssam 				bp->b_command = CY_ERASE;
543*25979Ssam 				yc->yc_timo = 60;
544*25979Ssam 				goto dobpcmd;
54525675Ssam 			}
546*25979Ssam 			cmd = (bp->b_bcount > cy->cy_bs) ? CY_WCOM : CY_BWCOM;
54725675Ssam 		}
548*25979Ssam 		vm->um_tab.b_active = SIO;
549*25979Ssam 		addr = (caddr_t)vbastart(bp, cy->cy_buf,
550*25979Ssam 		    (long *)cy->cy_map, cy->cy_utl);
551*25979Ssam 		cy->cy_tpb.tpcmd = cmd;
552*25979Ssam 		cy->cy_tpb.tpcontrol = yc->yc_dens;
553*25979Ssam 		if (cmd == CY_RCOM || cmd == CY_WCOM)
554*25979Ssam 			cy->cy_tpb.tpcontrol |= CYCW_LOCK;
555*25979Ssam 		cy->cy_tpb.tpstatus = 0;
556*25979Ssam 		cy->cy_tpb.tpcount = 0;
557*25979Ssam 		cyldmba(cy->cy_tpb.tpdata, (caddr_t)addr);
558*25979Ssam 		cy->cy_tpb.tprec = 0;
559*25979Ssam 		cy->cy_tpb.tpsize = htoms(bp->b_bcount);
560*25979Ssam 		cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
561*25979Ssam 		do
562*25979Ssam 			uncache(&cy->cy_ccb.cbgate);
563*25979Ssam 		while (cy->cy_ccb.cbgate == GATE_CLOSED);
564*25979Ssam 		cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
565*25979Ssam 		cy->cy_ccb.cbcw = CBCW_IE;
566*25979Ssam 		cy->cy_ccb.cbgate = GATE_CLOSED;
567*25979Ssam 		dlog(LOG_INFO, "CY_GO(%x) cmd %x control %x size %d\n",
568*25979Ssam 		    vm->um_addr, cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol,
569*25979Ssam 		    htoms(cy->cy_tpb.tpsize));
570*25979Ssam 		CY_GO(vm->um_addr);
571*25979Ssam 		return;
57224000Ssam 	}
573*25979Ssam 	/*
574*25979Ssam 	 * Tape positioned incorrectly; set to seek forwards
575*25979Ssam 	 * or backwards to the correct spot.  This happens
576*25979Ssam 	 * for raw tapes only on error retries.
577*25979Ssam 	 */
578*25979Ssam 	vm->um_tab.b_active = SSEEK;
579*25979Ssam 	if (blkno < bdbtofsb(bp->b_blkno)) {
580*25979Ssam 		bp->b_command = CY_SFORW;
581*25979Ssam 		cy->cy_tpb.tprec = htoms(bdbtofsb(bp->b_blkno) - blkno);
582*25979Ssam 	} else {
583*25979Ssam 		bp->b_command = CY_SREV;
584*25979Ssam 		cy->cy_tpb.tprec = htoms(blkno - bdbtofsb(bp->b_blkno));
58524000Ssam 	}
586*25979Ssam 	yc->yc_timo = imin(imax(10 * htoms(cy->cy_tpb.tprec), 60), 5*60);
587*25979Ssam dobpcmd:
588*25979Ssam 	/*
589*25979Ssam 	 * Do the command in bp.  Reverse direction commands
590*25979Ssam 	 * are indicated by having CYCW_REV or'd into their
591*25979Ssam 	 * value.  For these we must set the appropriate bit
592*25979Ssam 	 * in the control field.
593*25979Ssam 	 */
594*25979Ssam 	if (bp->b_command&CYCW_REV) {
595*25979Ssam 		cy->cy_tpb.tpcmd = bp->b_command &~ CYCW_REV;
596*25979Ssam 		cy->cy_tpb.tpcontrol = yc->yc_dens | CYCW_REV;
597*25979Ssam 	} else {
598*25979Ssam 		cy->cy_tpb.tpcmd = bp->b_command;
599*25979Ssam 		cy->cy_tpb.tpcontrol = yc->yc_dens;
60024000Ssam 	}
601*25979Ssam 	cy->cy_tpb.tpstatus = 0;
602*25979Ssam 	cy->cy_tpb.tpcount = 0;
603*25979Ssam 	cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
604*25979Ssam 	do
605*25979Ssam 		uncache(&cy->cy_ccb.cbgate);
606*25979Ssam 	while (cy->cy_ccb.cbgate == GATE_CLOSED);
607*25979Ssam 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
608*25979Ssam 	cy->cy_ccb.cbcw = CBCW_IE;
609*25979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
610*25979Ssam 	dlog(LOG_INFO, "CY_GO(%x) cmd %x control %x rec %d\n",
611*25979Ssam 	    vm->um_addr, cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol,
612*25979Ssam 	    htoms(cy->cy_tpb.tprec));
613*25979Ssam 	CY_GO(vm->um_addr);
614*25979Ssam 	return;
615*25979Ssam next:
616*25979Ssam 	/*
617*25979Ssam 	 * Done with this operation due to error or the
618*25979Ssam 	 * fact that it doesn't do anything.  Release VERSAbus
619*25979Ssam 	 * resource (if any), dequeue the transfer and continue
620*25979Ssam 	 * processing this slave.
621*25979Ssam 	 */
622*25979Ssam 	if (bp == &rcybuf[CYUNIT(bp->b_dev)])
623*25979Ssam 		vbadone(bp, cy->cy_buf, (long *)cy->cy_map, cy->cy_utl);
624*25979Ssam 	vm->um_tab.b_errcnt = 0;
625*25979Ssam 	dp->b_actf = bp->av_forw;
626*25979Ssam 	iodone(bp);
627*25979Ssam 	goto loop;
62825675Ssam }
62925675Ssam 
63025675Ssam /*
631*25979Ssam  * Cy interrupt routine.
63225675Ssam  */
633*25979Ssam cyintr(cipher)
634*25979Ssam 	int cipher;
63525675Ssam {
636*25979Ssam 	struct buf *dp;
63724000Ssam 	register struct buf *bp;
638*25979Ssam 	register struct vba_ctlr *vm = cyminfo[cipher];
639*25979Ssam 	register struct cy_softc *cy;
640*25979Ssam 	register struct yc_softc *yc;
641*25979Ssam 	int cyunit, err;
642*25979Ssam 	register state;
64324000Ssam 
644*25979Ssam 	dlog(LOG_INFO, "cyintr(%d)\n", cipher);
645*25979Ssam 	/*
646*25979Ssam 	 * First, turn off the interrupt from the controller
647*25979Ssam 	 * (device uses Multibus non-vectored interrupts...yech).
648*25979Ssam 	 */
649*25979Ssam 	cy = &cy_softc[vm->um_ctlr];
650*25979Ssam 	cy->cy_ccb.cbcw = CBCW_CLRINT;
651*25979Ssam 	cyldmba(cy->cy_ccb.cbtpb, &cy->cy_nop);
652*25979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
653*25979Ssam 	CY_GO(vm->um_addr);
654*25979Ssam 	if ((dp = vm->um_tab.b_actf) == NULL) {
655*25979Ssam 		dlog(LOG_ERR, "cy%d: stray interrupt", vm->um_ctlr);
65624000Ssam 		return;
65724000Ssam 	}
658*25979Ssam 	bp = dp->b_actf;
659*25979Ssam 	cyunit = CYUNIT(bp->b_dev);
660*25979Ssam 	cy = &cy_softc[cyunit];
661*25979Ssam 	cyuncachetpb(cy);
662*25979Ssam 	/*
663*25979Ssam 	 * If last command was a rewind or file mark search, and
664*25979Ssam 	 * tape is still moving, wait for the operation to complete.
665*25979Ssam 	 */
666*25979Ssam 	if (vm->um_tab.b_active == SREW) {
667*25979Ssam 		vm->um_tab.b_active = SCOM;
668*25979Ssam 		if ((cy->cy_tpb.tpstatus&CYS_RDY) == 0) {
669*25979Ssam 			yc->yc_timo = 5*60;	/* 5 minutes */
670*25979Ssam 			return;
67124000Ssam 		}
67224000Ssam 	}
673*25979Ssam 	/*
674*25979Ssam 	 * An operation completed...record status.
675*25979Ssam 	 */
676*25979Ssam 	yc = &yc_softc[YCUNIT(bp->b_dev)];
677*25979Ssam 	yc->yc_timo = INF;
678*25979Ssam 	yc->yc_control = cy->cy_tpb.tpcontrol;
679*25979Ssam 	yc->yc_status = cy->cy_tpb.tpstatus;
680*25979Ssam 	yc->yc_resid = bp->b_bcount - htoms(cy->cy_tpb.tpcount);
681*25979Ssam 	dlog(LOG_INFO, "cmd %x control %b status %b resid %d\n",
682*25979Ssam 	    cy->cy_tpb.tpcmd, yc->yc_control, CYCW_BITS,
683*25979Ssam 	    yc->yc_status, CYS_BITS, yc->yc_resid);
684*25979Ssam 	if ((bp->b_flags&B_READ) == 0)
685*25979Ssam 		yc->yc_lastiow = 1;
686*25979Ssam 	state = vm->um_tab.b_active;
687*25979Ssam 	vm->um_tab.b_active = 0;
688*25979Ssam 	/*
689*25979Ssam 	 * Check for errors.
690*25979Ssam 	 */
691*25979Ssam 	if (cy->cy_tpb.tpstatus&CYS_ERR) {
692*25979Ssam 		err = cy->cy_tpb.tpstatus&CYS_ERR;
693*25979Ssam 		dlog(LOG_INFO, "error %d\n", err);
694*25979Ssam 		/*
695*25979Ssam 		 * If we hit the end of tape file, update our position.
696*25979Ssam 		 */
697*25979Ssam 		if (err == CYER_FM) {
698*25979Ssam 			yc->yc_status |= CYS_FM;
699*25979Ssam 			state = SCOM;		/* force completion */
700*25979Ssam 			cyseteof(bp);		/* set blkno and nxrec */
701*25979Ssam 			goto opdone;
702*25979Ssam 		}
703*25979Ssam 		/*
704*25979Ssam 		 * Fix up errors which occur due to backspacing over
705*25979Ssam 		 * the beginning of the tape.
706*25979Ssam 		 */
707*25979Ssam 		if (err == CYER_BOT && cy->cy_tpb.tpcontrol&CYCW_REV) {
708*25979Ssam 			yc->yc_status |= CYS_BOT;
709*25979Ssam 			goto ignoreerr;
710*25979Ssam 		}
711*25979Ssam 		/*
712*25979Ssam 		 * If we were reading raw tape and the only error was that the
713*25979Ssam 		 * record was too long, then we don't consider this an error.
714*25979Ssam 		 */
715*25979Ssam 		if (bp == &rcybuf[cyunit] && (bp->b_flags&B_READ) &&
716*25979Ssam 		    err == CYER_STROBE) {
717*25979Ssam 			/*
718*25979Ssam 			 * Retry reads once with the command changed to
719*25979Ssam 			 * a raw read (if possible).  Setting b_errcnt
720*25979Ssam 			 * here causes cystart (above) to force a CY_RCOM.
721*25979Ssam 			 */
722*25979Ssam 			if (bp->b_errcnt++ != 0)
723*25979Ssam 				goto ignoreerr;
724*25979Ssam 			yc->yc_blkno++;
725*25979Ssam 			goto opcont;
726*25979Ssam 		}
727*25979Ssam 		/*
728*25979Ssam 		 * If error is not hard, and this was an i/o operation
729*25979Ssam 		 * retry up to 8 times.
730*25979Ssam 		 */
731*25979Ssam 		err = 1 << err;
732*25979Ssam 		if ((err&CYER_SOFT) && state == SIO) {
733*25979Ssam 			if (++vm->um_tab.b_errcnt < 7) {
734*25979Ssam 				yc->yc_blkno++;
735*25979Ssam 				goto opcont;
736*25979Ssam 			}
737*25979Ssam 		} else
738*25979Ssam 			/*
739*25979Ssam 			 * Hard or non-i/o errors on non-raw tape
740*25979Ssam 			 * cause it to close.
741*25979Ssam 			 */
742*25979Ssam 			if (yc->yc_openf>0 && bp != &rcybuf[cyunit])
743*25979Ssam 				yc->yc_openf = -1;
744*25979Ssam 		/*
745*25979Ssam 		 * Couldn't recover from error.
746*25979Ssam 		 */
747*25979Ssam 		tprintf(yc->yc_ttyp,
748*25979Ssam 		    "yc%d: hard error bn%d status=%b", YCUNIT(bp->b_dev),
749*25979Ssam 		    bp->b_blkno, yc->yc_status, CYS_BITS);
750*25979Ssam 		if (err < NCYERROR)
751*25979Ssam 			tprintf(yc->yc_ttyp, ", %s", cyerror[err]);
752*25979Ssam 		tprintf(yc->yc_ttyp, "\n");
753*25979Ssam 		bp->b_flags |= B_ERROR;
754*25979Ssam 		goto opdone;
75524000Ssam 	}
756*25979Ssam 	/*
757*25979Ssam 	 * Advance tape control FSM.
758*25979Ssam 	 */
759*25979Ssam ignoreerr:
760*25979Ssam 	/*
761*25979Ssam 	 * If we hit a tape mark update our position.
762*25979Ssam 	 */
763*25979Ssam 	if (yc->yc_status&CYS_FM && bp->b_flags&B_READ) {
764*25979Ssam 		cyseteof(bp);
765*25979Ssam 		goto opdone;
76625675Ssam 	}
767*25979Ssam 	switch (state) {
76824000Ssam 
769*25979Ssam 	case SIO:
770*25979Ssam 		/*
771*25979Ssam 		 * Read/write increments tape block number.
772*25979Ssam 		 */
773*25979Ssam 		yc->yc_blkno++;
774*25979Ssam 		goto opdone;
77524000Ssam 
776*25979Ssam 	case SCOM:
777*25979Ssam 		/*
778*25979Ssam 		 * For forward/backward space record update current position.
779*25979Ssam 		 */
780*25979Ssam 		if (bp == &ccybuf[CYUNIT(bp->b_dev)]) switch (bp->b_command) {
78124000Ssam 
782*25979Ssam 		case CY_SFORW:
783*25979Ssam 			yc->yc_blkno -= bp->b_repcnt;
784*25979Ssam 			break;
78524000Ssam 
786*25979Ssam 		case CY_SREV:
787*25979Ssam 			yc->yc_blkno += bp->b_repcnt;
788*25979Ssam 			break;
78924000Ssam 		}
790*25979Ssam 		goto opdone;
791*25979Ssam 
792*25979Ssam 	case SSEEK:
793*25979Ssam 		yc->yc_blkno = bdbtofsb(bp->b_blkno);
794*25979Ssam 		goto opcont;
79524000Ssam 
796*25979Ssam 	case SERASE:
797*25979Ssam 		/*
798*25979Ssam 		 * Completed erase of the inter-record gap due to a
799*25979Ssam 		 * write error; now retry the write operation.
800*25979Ssam 		 */
801*25979Ssam 		vm->um_tab.b_active = SERASED;
802*25979Ssam 		goto opcont;
80324000Ssam 	}
80425675Ssam 
805*25979Ssam opdone:
806*25979Ssam 	/*
807*25979Ssam 	 * Reset error count and remove from device queue.
808*25979Ssam 	 */
809*25979Ssam 	vm->um_tab.b_errcnt = 0;
810*25979Ssam 	dp->b_actf = bp->av_forw;
811*25979Ssam 	/*
812*25979Ssam 	 * Save resid and release resources.
813*25979Ssam 	 */
814*25979Ssam 	bp->b_resid = bp->b_bcount - htoms(cy->cy_tpb.tpcount);
815*25979Ssam 	if (bp == &rcybuf[CYUNIT(bp->b_dev)])
816*25979Ssam 		vbadone(bp, cy->cy_buf, (long *)cy->cy_map, cy->cy_utl);
817*25979Ssam 	iodone(bp);
818*25979Ssam 	/*
819*25979Ssam 	 * Circulate slave to end of controller
820*25979Ssam 	 * queue to give other slaves a chance.
821*25979Ssam 	 */
822*25979Ssam 	vm->um_tab.b_actf = dp->b_forw;
823*25979Ssam 	if (dp->b_actf) {
824*25979Ssam 		dp->b_forw = NULL;
825*25979Ssam 		if (vm->um_tab.b_actf == NULL)
826*25979Ssam 			vm->um_tab.b_actf = dp;
827*25979Ssam 		else
828*25979Ssam 			vm->um_tab.b_actl->b_forw = dp;
82924000Ssam 	}
830*25979Ssam 	if (vm->um_tab.b_actf == 0)
83124000Ssam 		return;
832*25979Ssam opcont:
833*25979Ssam 	cystart(vm);
83424000Ssam }
83524000Ssam 
836*25979Ssam cytimer(dev)
837*25979Ssam 	int dev;
83824000Ssam {
839*25979Ssam 	register struct yc_softc *yc = &yc_softc[YCUNIT(dev)];
840*25979Ssam 	int s;
84124000Ssam 
842*25979Ssam 	if (yc->yc_timo != INF && (yc->yc_timo -= 5) < 0) {
843*25979Ssam 		printf("yc%d: lost interrupt\n", YCUNIT(dev));
844*25979Ssam 		yc->yc_timo = INF;
845*25979Ssam 		s = spl3();
846*25979Ssam 		cyintr(CYUNIT(dev));
847*25979Ssam 		splx(s);
84824000Ssam 	}
849*25979Ssam 	timeout(cytimer, (caddr_t)dev, 5*hz);
85024000Ssam }
85124000Ssam 
852*25979Ssam cyseteof(bp)
853*25979Ssam 	register struct buf *bp;
85424000Ssam {
855*25979Ssam 	register int cyunit = CYUNIT(bp->b_dev);
856*25979Ssam 	register struct cy_softc *cy = &cy_softc[cyunit];
857*25979Ssam 	register struct yc_softc *yc = &yc_softc[YCUNIT(bp->b_dev)];
85824000Ssam 
859*25979Ssam 	if (bp == &ccybuf[cyunit]) {
860*25979Ssam 		if (yc->yc_blkno > bdbtofsb(bp->b_blkno)) {
861*25979Ssam 			/* reversing */
862*25979Ssam 			yc->yc_nxrec = bdbtofsb(bp->b_blkno) -
863*25979Ssam 			    htoms(cy->cy_tpb.tpcount);
864*25979Ssam 			yc->yc_blkno = yc->yc_nxrec;
865*25979Ssam 		} else {
866*25979Ssam 			yc->yc_blkno = bdbtofsb(bp->b_blkno) +
867*25979Ssam 			    htoms(cy->cy_tpb.tpcount);
868*25979Ssam 			yc->yc_nxrec = yc->yc_blkno - 1;
86924000Ssam 		}
87025675Ssam 		return;
87125675Ssam 	}
872*25979Ssam 	/* eof on read */
873*25979Ssam 	yc->yc_nxrec = bdbtofsb(bp->b_blkno);
87424000Ssam }
87524000Ssam 
876*25979Ssam cyread(dev, uio)
877*25979Ssam 	dev_t dev;
878*25979Ssam 	struct uio *uio;
87925675Ssam {
880*25979Ssam 	int errno;
88125675Ssam 
882*25979Ssam 	errno = cyphys(dev, uio);
883*25979Ssam 	if (errno)
884*25979Ssam 		return (errno);
885*25979Ssam 	return (physio(cystrategy, &rcybuf[CYUNIT(dev)], dev, B_READ, minphys, uio));
88625675Ssam }
88725675Ssam 
888*25979Ssam cywrite(dev, uio)
889*25979Ssam 	dev_t dev;
890*25979Ssam 	struct uio *uio;
89124000Ssam {
892*25979Ssam 	int errno;
89324000Ssam 
894*25979Ssam 	errno = cyphys(dev, uio);
895*25979Ssam 	if (errno)
896*25979Ssam 		return (errno);
897*25979Ssam 	return (physio(cystrategy, &rcybuf[CYUNIT(dev)], dev, B_WRITE, minphys, uio));
89824000Ssam }
89924000Ssam 
90024000Ssam /*
901*25979Ssam  * Check that a raw device exits.
902*25979Ssam  * If it does, set up the yc_blkno and yc_nxrec
903*25979Ssam  * so that the tape will appear positioned correctly.
904*25979Ssam  */
905*25979Ssam cyphys(dev, uio)
90625675Ssam 	dev_t dev;
90725675Ssam 	struct uio *uio;
90825675Ssam {
909*25979Ssam 	register int ycunit = YCUNIT(dev);
910*25979Ssam 	register daddr_t a;
911*25979Ssam 	register struct yc_softc *yc;
912*25979Ssam 	register struct vba_device *vi;
91325675Ssam 
914*25979Ssam 	if (ycunit >= NYC || (vi = ycdinfo[ycunit]) == 0 || vi->ui_alive == 0)
915*25979Ssam 		return (ENXIO);
916*25979Ssam 	yc = &yc_softc[ycunit];
917*25979Ssam 	a = bdbtofsb(uio->uio_offset >> DEV_BSHIFT);
918*25979Ssam 	yc->yc_blkno = a;
919*25979Ssam 	yc->yc_nxrec = a + 1;
920*25979Ssam 	return (0);
92125675Ssam }
92225675Ssam 
92325675Ssam /*ARGSUSED*/
92425675Ssam cyioctl(dev, cmd, data, flag)
925*25979Ssam 	caddr_t data;
92625675Ssam 	dev_t dev;
92725675Ssam {
928*25979Ssam 	int ycunit = YCUNIT(dev);
929*25979Ssam 	register struct yc_softc *yc = &yc_softc[ycunit];
930*25979Ssam 	register struct buf *bp = &ccybuf[CYUNIT(dev)];
931*25979Ssam 	register callcount;
932*25979Ssam 	int fcount, op;
933*25979Ssam 	struct mtop *mtop;
934*25979Ssam 	struct mtget *mtget;
935*25979Ssam 	/* we depend of the values and order of the MT codes here */
936*25979Ssam 	static cyops[] =
937*25979Ssam 	{CY_WEOF,CY_SFORW,CY_SREV,CY_SFORW,CY_SREV,CY_REW,CY_OFFL,CY_SENSE};
93825675Ssam 
93925675Ssam 	switch (cmd) {
94025675Ssam 
941*25979Ssam 	case MTIOCTOP:	/* tape operation */
942*25979Ssam 		mtop = (struct mtop *)data;
943*25979Ssam 		switch (op = mtop->mt_op) {
94425675Ssam 
945*25979Ssam 		case MTWEOF:
946*25979Ssam 		case MTFSR: case MTBSR:
947*25979Ssam 		case MTFSF: case MTBSF:
948*25979Ssam 			callcount = mtop->mt_count;
949*25979Ssam 			fcount = 1;
950*25979Ssam 			break;
95125675Ssam 
952*25979Ssam 		case MTREW: case MTOFFL: case MTNOP:
953*25979Ssam 			callcount = 1;
954*25979Ssam 			fcount = 1;
955*25979Ssam 			break;
95625675Ssam 
957*25979Ssam 		default:
958*25979Ssam 			return (ENXIO);
959*25979Ssam 		}
960*25979Ssam 		if (callcount <= 0 || fcount <= 0)
961*25979Ssam 			return (EINVAL);
962*25979Ssam 		while (--callcount >= 0) {
963*25979Ssam 			/*
964*25979Ssam 			 * Gagh, this controller is the pits...
965*25979Ssam 			 */
966*25979Ssam 			if (op == MTFSF || op == MTBSF) {
967*25979Ssam 				do
968*25979Ssam 					cycommand(dev, cyops[op], 1);
969*25979Ssam 				while ((bp->b_flags&B_ERROR) == 0 &&
970*25979Ssam 				 (yc->yc_status&(CYS_EOT|CYS_BOT|CYS_FM)) == 0);
971*25979Ssam 			} else
972*25979Ssam 				cycommand(dev, cyops[op], fcount);
973*25979Ssam 			if ((bp->b_flags&B_ERROR) ||
974*25979Ssam 			    (yc->yc_status&(CYS_BOT|CYS_EOT)))
975*25979Ssam 				break;
976*25979Ssam 		}
977*25979Ssam 		bp->b_resid = callcount + 1;
978*25979Ssam 		return (geterror(bp));
979*25979Ssam 
980*25979Ssam 	case MTIOCGET:
981*25979Ssam 		cycommand(dev, CY_SENSE, 1);
982*25979Ssam 		mtget = (struct mtget *)data;
983*25979Ssam 		mtget->mt_dsreg = yc->yc_status;
984*25979Ssam 		mtget->mt_erreg = yc->yc_control;
985*25979Ssam 		mtget->mt_resid = yc->yc_resid;
986*25979Ssam 		mtget->mt_type = MT_ISCY;
98725675Ssam 		break;
98825675Ssam 
98925675Ssam 	default:
99025675Ssam 		return (ENXIO);
99125675Ssam 	}
99225675Ssam 	return (0);
99325675Ssam }
99425675Ssam 
99525675Ssam /*
99625675Ssam  * Poll until the controller is ready.
99725675Ssam  */
99825675Ssam cywait(cp)
999*25979Ssam 	register struct cyccb *cp;
100024000Ssam {
100125675Ssam 	register int i = 5000;
100224000Ssam 
1003*25979Ssam 	uncache(&cp->cbgate);
1004*25979Ssam 	while (i-- > 0 && cp->cbgate == GATE_CLOSED) {
100524000Ssam 		DELAY(1000);
1006*25979Ssam 		uncache(&cp->cbgate);
100724000Ssam 	}
100825675Ssam 	return (i <= 0);
100924000Ssam }
101024000Ssam 
101125675Ssam /*
1012*25979Ssam  * Load a 20 bit pointer into an i/o register.
101325675Ssam  */
1014*25979Ssam cyldmba(wreg, value)
1015*25979Ssam 	short *wreg;
1016*25979Ssam 	caddr_t value;
101724000Ssam {
1018*25979Ssam 	register int v = (int)value;
1019*25979Ssam 	register caddr_t reg = (caddr_t)wreg;
102025675Ssam 
1021*25979Ssam 	*reg++ = v;
1022*25979Ssam 	*reg++ = v >> 8;
1023*25979Ssam 	*reg++ = 0;
1024*25979Ssam 	*reg = (v&0xf0000) >> 12;
102524000Ssam }
102624000Ssam 
102725675Ssam /*
102825675Ssam  * Unconditionally reset all controllers to their initial state.
102925675Ssam  */
103025675Ssam cyreset(vba)
103125675Ssam 	int vba;
103224000Ssam {
103325675Ssam 	register caddr_t addr;
103425675Ssam 	register int ctlr;
103524000Ssam 
103625675Ssam 	for (ctlr = 0; ctlr < NCY; ctlr++)
103725675Ssam 		if (cyminfo[ctlr] && cyminfo[ctlr]->um_vbanum == vba) {
103825675Ssam 			addr = cyminfo[ctlr]->um_addr;
103925675Ssam 			CY_RESET(addr);
1040*25979Ssam 			if (!cyinit(ctlr)) {
104125675Ssam 				printf("cy%d: reset failed\n", ctlr);
104225675Ssam 				cyminfo[ctlr] = NULL;
104325675Ssam 			}
104425675Ssam 		}
104524000Ssam }
1046*25979Ssam 
1047*25979Ssam cyuncachetpb(cy)
1048*25979Ssam 	struct cy_softc *cy;
1049*25979Ssam {
1050*25979Ssam 	register long *lp = (long *)&cy->cy_tpb;
1051*25979Ssam 	register int i;
1052*25979Ssam 
1053*25979Ssam 	for (i = 0; i < howmany(sizeof (struct cytpb), sizeof (long)); i++)
1054*25979Ssam 		uncache(lp++);
1055*25979Ssam }
1056*25979Ssam 
1057*25979Ssam /*
1058*25979Ssam  * Dump routine.
1059*25979Ssam  */
1060*25979Ssam cydump(dev)
1061*25979Ssam 	dev_t dev;
1062*25979Ssam {
1063*25979Ssam 	register struct cy_softc *cy;
1064*25979Ssam 	register int bs, num, start;
1065*25979Ssam 	register caddr_t addr;
1066*25979Ssam 	int unit = CYUNIT(dev), ctlr, error;
1067*25979Ssam 
1068*25979Ssam 	if (unit >= NCY || cyminfo[unit] == 0 ||
1069*25979Ssam 	    (cy = &cy_softc[unit])->cy_bs == 0 || YCUNIT(dev) >= NYC)
1070*25979Ssam 		return (ENXIO);
1071*25979Ssam 	if (cywait(&cy->cy_ccb))
1072*25979Ssam 		return (EFAULT);
1073*25979Ssam #define	phys(a)	((caddr_t)((int)(a)&~0xc0000000))
1074*25979Ssam 	addr = phys(cyminfo[ctlr]->um_addr);
1075*25979Ssam 	num = maxfree, start = NBPG*2;
1076*25979Ssam 	while (num > 0) {
1077*25979Ssam 		bs = num > btoc(CYMAXIO) ? btoc(CYMAXIO) : num;
1078*25979Ssam 		error = cydwrite(cy, start, bs, addr);
1079*25979Ssam 		if (error)
1080*25979Ssam 			return (error);
1081*25979Ssam 		start += bs, num -= bs;
1082*25979Ssam 	}
1083*25979Ssam 	cyweof(cy, addr);
1084*25979Ssam 	cyweof(cy, addr);
1085*25979Ssam 	uncache(&cy->cy_tpb);
1086*25979Ssam 	if (cy->cy_tpb.tpstatus&CYS_ERR)
1087*25979Ssam 		return (EIO);
1088*25979Ssam 	cyrewind(cy, addr);
1089*25979Ssam 	return (0);
1090*25979Ssam }
1091*25979Ssam 
1092*25979Ssam cydwrite(cy, pf, npf, addr)
1093*25979Ssam 	register struct cy_softc *cy;
1094*25979Ssam 	int pf, npf;
1095*25979Ssam 	caddr_t addr;
1096*25979Ssam {
1097*25979Ssam 
1098*25979Ssam 	cy->cy_tpb.tpcmd = CY_WCOM;
1099*25979Ssam 	cy->cy_tpb.tpcontrol = CYCW_LOCK|CYCW_25IPS|CYCW_16BITS;
1100*25979Ssam 	cy->cy_tpb.tpstatus = 0;
1101*25979Ssam 	cy->cy_tpb.tpsize = htoms(npf*NBPG);
1102*25979Ssam 	cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
1103*25979Ssam 	cyldmba(cy->cy_tpb.tpdata, (caddr_t)(pf*NBPG));
1104*25979Ssam 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
1105*25979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
1106*25979Ssam 	CY_GO(addr);
1107*25979Ssam 	if (cywait(&cy->cy_ccb))
1108*25979Ssam 		return (EFAULT);
1109*25979Ssam 	uncache(&cy->cy_tpb);
1110*25979Ssam 	if (cy->cy_tpb.tpstatus&CYS_ERR)
1111*25979Ssam 		return (EIO);
1112*25979Ssam 	return (0);
1113*25979Ssam }
1114*25979Ssam 
1115*25979Ssam cyweof(cy, addr)
1116*25979Ssam 	register struct cy_softc *cy;
1117*25979Ssam 	caddr_t addr;
1118*25979Ssam {
1119*25979Ssam 
1120*25979Ssam 	cy->cy_tpb.tpcmd = CY_WEOF;
1121*25979Ssam 	cy->cy_tpb.tpcount = htoms(1);
1122*25979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
1123*25979Ssam 	CY_GO(addr);
1124*25979Ssam 	(void) cywait(&cy->cy_ccb);
1125*25979Ssam }
1126*25979Ssam 
1127*25979Ssam cyrewind(cy, addr)
1128*25979Ssam 	register struct cy_softc *cy;
1129*25979Ssam 	caddr_t addr;
1130*25979Ssam {
1131*25979Ssam 
1132*25979Ssam 	cy->cy_tpb.tpcmd = CY_REW;
1133*25979Ssam 	cy->cy_tpb.tpcount = htoms(1);
1134*25979Ssam 	cy->cy_ccb.cbgate = GATE_CLOSED;
1135*25979Ssam 	CY_GO(addr);
1136*25979Ssam 	(void) cywait(&cy->cy_ccb);
1137*25979Ssam }
113824000Ssam #endif
1139