xref: /csrg-svn/sys/tahoe/vba/cy.c (revision 34487)
1 /*
2  * Copyright (c) 1988 Regents of the University of California.
3  * All rights reserved.
4  *
5  * This code is derived from software contributed to Berkeley by
6  * Computer Consoles Inc.
7  *
8  * Redistribution and use in source and binary forms are permitted
9  * provided that this notice is preserved and that due credit is given
10  * to the University of California at Berkeley. The name of the University
11  * may not be used to endorse or promote products derived from this
12  * software without specific prior written permission. This software
13  * is provided ``as is'' without express or implied warranty.
14  *
15  *	@(#)cy.c	1.16 (Berkeley) 05/25/88
16  */
17 
18 #include "yc.h"
19 #if NCY > 0
20 /*
21  * Cipher Tapemaster driver.
22  */
23 #define CYDEBUG
24 #ifdef	CYDEBUG
25 int	cydebug = 0;
26 #define	dlog(params)	if (cydebug) log params
27 #else
28 #define dlog(params)	/* */
29 #endif
30 
31 #include "param.h"
32 #include "systm.h"
33 #include "vm.h"
34 #include "buf.h"
35 #include "file.h"
36 #include "dir.h"
37 #include "user.h"
38 #include "proc.h"
39 #include "signal.h"
40 #include "uio.h"
41 #include "ioctl.h"
42 #include "mtio.h"
43 #include "errno.h"
44 #include "cmap.h"
45 #include "kernel.h"
46 #include "syslog.h"
47 #include "tty.h"
48 
49 #include "../tahoe/cpu.h"
50 #include "../tahoe/mtpr.h"
51 #include "../tahoe/pte.h"
52 
53 #include "../tahoevba/vbavar.h"
54 #define	CYERROR
55 #include "../tahoevba/cyreg.h"
56 
57 /*
58  * There is a ccybuf per tape controller.
59  * It is used as the token to pass to the internal routines
60  * to execute tape ioctls, and also acts as a lock on the slaves
61  * on the controller, since there is only one per controller.
62  * In particular, when the tape is rewinding on close we release
63  * the user process but any further attempts to use the tape drive
64  * before the rewind completes will hang waiting for ccybuf.
65  */
66 struct	buf ccybuf[NCY];
67 
68 /*
69  * Raw tape operations use rcybuf.  The driver notices when
70  * rcybuf is being used and allows the user program to contine
71  * after errors and read records not of the standard length.
72  */
73 struct	buf rcybuf[NCY];
74 
75 int	cyprobe(), cyslave(), cyattach();
76 struct	buf ycutab[NYC];
77 short	yctocy[NYC];
78 struct	vba_ctlr *cyminfo[NCY];
79 struct	vba_device *ycdinfo[NYC];
80 long	cystd[] = { 0 };
81 struct	vba_driver cydriver =
82    { cyprobe, cyslave, cyattach, 0, cystd, "yc", ycdinfo, "cy", cyminfo };
83 
84 /* bits in minor device */
85 #define	YCUNIT(dev)	(minor(dev)&03)
86 #define	CYUNIT(dev)	(yctocy[YCUNIT(dev)])
87 #define	T_NOREWIND	0x04
88 #define	T_1600BPI	0x00		/* pseudo */
89 #define	T_3200BPI	0x08		/* unused */
90 
91 #define	INF	1000000L		/* close to infinity */
92 
93 /*
94  * Software state and shared command areas per controller.
95  *
96  * The i/o intermediate buffer must be allocated in startup()
97  * so its address will fit in 20-bits (YECH!!!!!!!!!!!!!!).
98  */
99 struct cy_softc {
100 	int	cy_bs;		/* controller's buffer size */
101 	struct	cyscp *cy_scp;	/* system configuration block address */
102 	struct	cyccb cy_ccb;	/* channel control block */
103 	struct	cyscb cy_scb;	/* system configuration block */
104 	struct	cytpb cy_tpb;	/* tape parameter block */
105 	struct	cytpb cy_nop;	/* nop parameter block for cyintr */
106 	struct	vb_buf cy_rbuf;	/* vba resources */
107 } cy_softc[NCY];
108 
109 /*
110  * Software state per tape transport.
111  */
112 struct	yc_softc {
113 	char	yc_openf;	/* lock against multiple opens */
114 	char	yc_lastiow;	/* last operation was a write */
115 	short	yc_tact;	/* timeout is active */
116 	long	yc_timo;	/* time until timeout expires */
117 	u_short	yc_control;	/* copy of last tpcb.tpcontrol */
118 	u_short	yc_status;	/* copy of last tpcb.tpstatus */
119 	u_short	yc_resid;	/* copy of last bc */
120 	u_short	yc_dens;	/* prototype control word with density info */
121 	struct	tty *yc_ttyp;	/* user's tty for errors */
122 	daddr_t	yc_blkno;	/* block number, for block device tape */
123 	daddr_t	yc_nxrec;	/* position of end of tape, if known */
124 	int	yc_blksize;	/* current tape blocksize estimate */
125 	int	yc_blks;	/* number of I/O operations since open */
126 	int	yc_softerrs;	/* number of soft I/O errors since open */
127 } yc_softc[NYC];
128 
129 /*
130  * States for vm->um_tab.b_active, the per controller state flag.
131  * This is used to sequence control in the driver.
132  */
133 #define	SSEEK	1		/* seeking */
134 #define	SIO	2		/* doing seq i/o */
135 #define	SCOM	3		/* sending control command */
136 #define	SREW	4		/* sending a rewind */
137 #define	SERASE	5		/* erase inter-record gap */
138 #define	SERASED	6		/* erased inter-record gap */
139 
140 /* there's no way to figure these out dynamically? -- yech */
141 struct	cyscp *cyscp[] =
142     { (struct cyscp *)0xc0000c06, (struct cyscp *)0xc0000c16 };
143 #define	NCYSCP	(sizeof (cyscp) / sizeof (cyscp[0]))
144 
145 cyprobe(reg, vm)
146 	caddr_t reg;
147 	struct vba_ctlr *vm;
148 {
149 	register br, cvec;			/* must be r12, r11 */
150 	register struct cy_softc *cy;
151 	int ctlr = vm->um_ctlr;
152 
153 #ifdef lint
154 	br = 0; cvec = br; br = cvec;
155 	cyintr(0);
156 #endif
157 	if (badcyaddr(reg+1))
158 		return (0);
159 	if (ctlr > NCYSCP || cyscp[ctlr] == 0)		/* XXX */
160 		return (0);
161 	cy = &cy_softc[ctlr];
162 	cy->cy_scp = cyscp[ctlr];			/* XXX */
163 	/*
164 	 * Tapemaster controller must have interrupt handler
165 	 * disable interrupt, so we'll just kludge things
166 	 * (stupid multibus non-vectored interrupt crud).
167 	 */
168 	if (cyinit(ctlr, reg)) {
169 		uncache(&cy->cy_tpb.tpcount);
170 		cy->cy_bs = htoms(cy->cy_tpb.tpcount);
171 		/*
172 		 * Setup nop parameter block for clearing interrupts.
173 		 */
174 		cy->cy_nop.tpcmd = CY_NOP;
175 		cy->cy_nop.tpcontrol = 0;
176 		/*
177 		 * Allocate page tables.
178 		 */
179 		if (cybuf == 0) {
180 			printf("no cy buffer!!!\n");
181 			return (0);
182 		}
183 		cy->cy_rbuf.vb_rawbuf = cybuf + ctlr * CYMAXIO;
184 		if (vbainit(&cy->cy_rbuf, CYMAXIO, VB_20BIT) == 0) {
185 			printf("cy%d: vbainit failed\n", ctlr);
186 			return (0);
187 		}
188 
189 		br = 0x13, cvec = 0x80;			/* XXX */
190 		return (sizeof (struct cyccb));
191 	} else
192 		return (0);
193 }
194 
195 /*
196  * Check to see if a drive is attached to a controller.
197  * Since we can only tell that a drive is there if a tape is loaded and
198  * the drive is placed online, we always indicate the slave is present.
199  */
200 cyslave(vi, addr)
201 	struct vba_device *vi;
202 	caddr_t addr;
203 {
204 
205 #ifdef lint
206 	vi = vi; addr = addr;
207 #endif
208 	return (1);
209 }
210 
211 cyattach(vi)
212 	struct vba_device *vi;
213 {
214 	register struct cy_softc *cy;
215 	int ctlr = vi->ui_mi->um_ctlr;
216 
217 	yctocy[vi->ui_unit] = ctlr;
218 	cy = &cy_softc[ctlr];
219 	if (vi->ui_slave == 0 && cy->cy_bs)
220 		printf("; %dkb buffer", cy->cy_bs/1024);
221 }
222 
223 /*
224  * Initialize the controller after a controller reset or
225  * during autoconfigure.  All of the system control blocks
226  * are initialized and the controller is asked to configure
227  * itself for later use.
228  */
229 cyinit(ctlr, addr)
230 	int ctlr;
231 	register caddr_t addr;
232 {
233 	register struct cy_softc *cy = &cy_softc[ctlr];
234 	register int *pte;
235 
236 	/*
237 	 * Initialize the system configuration pointer.
238 	 */
239 	/* make kernel writable */
240 	pte = (int *)&Sysmap[btop((int)cy->cy_scp &~ KERNBASE)];
241 	*pte &= ~PG_PROT; *pte |= PG_KW;
242 	mtpr(TBIS, cy->cy_scp);
243 	/* load the correct values in the scp */
244 	cy->cy_scp->csp_buswidth = CSP_16BITS;
245 	cyldmba(cy->cy_scp->csp_scb, (caddr_t)&cy->cy_scb);
246 	/* put it back to read-only */
247 	*pte &= ~PG_PROT; *pte |= PG_KR;
248 	mtpr(TBIS, cy->cy_scp);
249 
250 	/*
251 	 * Init system configuration block.
252 	 */
253 	cy->cy_scb.csb_fixed = CSB_FIXED;
254 	/* set pointer to the channel control block */
255 	cyldmba(cy->cy_scb.csb_ccb, (caddr_t)&cy->cy_ccb);
256 
257 	/*
258 	 * Initialize the chanel control block.
259 	 */
260 	cy->cy_ccb.cbcw = CBCW_CLRINT;
261 	cy->cy_ccb.cbgate = GATE_OPEN;
262 	/* set pointer to the tape parameter block */
263 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
264 
265 	/*
266 	 * Issue a nop cmd and get the internal buffer size for buffered i/o.
267 	 */
268 	cy->cy_tpb.tpcmd = CY_NOP;
269 	cy->cy_tpb.tpcontrol = CYCW_16BITS;
270 	cy->cy_ccb.cbgate = GATE_CLOSED;
271 	CY_GO(addr);
272 	if (cywait(&cy->cy_ccb) || (cy->cy_tpb.tpstatus&CYS_ERR)) {
273 		uncache(&cy->cy_tpb.tpstatus);
274 		printf("cy%d: timeout or err during init, status=%b\n", ctlr,
275 		    cy->cy_tpb.tpstatus, CYS_BITS);
276 		return (0);
277 	}
278 	cy->cy_tpb.tpcmd = CY_CONFIG;
279 	cy->cy_tpb.tpcontrol = CYCW_16BITS;
280 	cy->cy_ccb.cbgate = GATE_CLOSED;
281 	CY_GO(addr);
282 	if (cywait(&cy->cy_ccb) || (cy->cy_tpb.tpstatus&CYS_ERR)) {
283 		uncache(&cy->cy_tpb.tpstatus);
284 		printf("cy%d: configuration failure, status=%b\n", ctlr,
285 		    cy->cy_tpb.tpstatus, CYS_BITS);
286 		return (0);
287 	}
288 	return (1);
289 }
290 
291 int	cytimer();
292 /*
293  * Open the device.  Tapes are unique open
294  * devices, so we refuse if it is already open.
295  * We also check that a tape is available, and
296  * don't block waiting here; if you want to wait
297  * for a tape you should timeout in user code.
298  */
299 cyopen(dev, flag)
300 	dev_t dev;
301 	register int flag;
302 {
303 	register int ycunit;
304 	register struct vba_device *vi;
305 	register struct yc_softc *yc;
306 
307 	ycunit = YCUNIT(dev);
308 	if (ycunit >= NYC || (vi = ycdinfo[ycunit]) == 0 || vi->ui_alive == 0)
309 		return (ENXIO);
310 	if ((yc = &yc_softc[ycunit])->yc_openf)
311 		return (EBUSY);
312 	yc->yc_openf = 1;
313 #define	PACKUNIT(vi) \
314     (((vi->ui_slave&1)<<11)|((vi->ui_slave&2)<<9)|((vi->ui_slave&4)>>2))
315 	/* no way to select density */
316 	yc->yc_dens = PACKUNIT(vi)|CYCW_IE|CYCW_16BITS;
317 	if (yc->yc_tact == 0) {
318 		yc->yc_timo = INF;
319 		yc->yc_tact = 1;
320 		timeout(cytimer, (caddr_t)dev, 5*hz);
321 	}
322 	cycommand(dev, CY_SENSE, 1);
323 	if ((yc->yc_status&CYS_OL) == 0) {	/* not on-line */
324 		uprintf("cy%d: not online\n", ycunit);
325 		yc->yc_openf = 0;
326 		return (EIO);
327 	}
328 	if ((flag&FWRITE) && (yc->yc_status&CYS_WP)) {
329 		uprintf("cy%d: no write ring\n", ycunit);
330 		yc->yc_openf = 0;
331 		return (EIO);
332 	}
333 	yc->yc_blkno = (daddr_t)0;
334 	yc->yc_nxrec = INF;
335 	yc->yc_lastiow = 0;
336 	yc->yc_blksize = CYMAXIO;		/* guess > 0 */
337 	yc->yc_blks = 0;
338 	yc->yc_softerrs = 0;
339 	yc->yc_ttyp = u.u_ttyp;
340 	return (0);
341 }
342 
343 /*
344  * Close tape device.
345  *
346  * If tape was open for writing or last operation was a write,
347  * then write two EOF's and backspace over the last one.
348  * Unless this is a non-rewinding special file, rewind the tape.
349  * Make the tape available to others.
350  */
351 cyclose(dev, flag)
352 	dev_t dev;
353 	int flag;
354 {
355 	struct yc_softc *yc = &yc_softc[YCUNIT(dev)];
356 
357 	if (flag == FWRITE || (flag&FWRITE) && yc->yc_lastiow) {
358 		cycommand(dev, CY_WEOF, 1);	/* can't use count with WEOF */
359 		cycommand(dev, CY_WEOF, 1);
360 		cycommand(dev, CY_SREV, 1);
361 	}
362 	if ((minor(dev)&T_NOREWIND) == 0)
363 		/*
364 		 * 0 count means don't hang waiting for rewind complete
365 		 * rather ccybuf stays busy until the operation completes
366 		 * preventing further opens from completing by preventing
367 		 * a CY_SENSE from completing.
368 		 */
369 		cycommand(dev, CY_REW, 0);
370 	if (yc->yc_blks > 10 && yc->yc_softerrs > yc->yc_blks / 10)
371 		log(LOG_INFO, "yc%d: %d soft errors in %d blocks\n",
372 		    YCUNIT(dev), yc->yc_softerrs, yc->yc_blks);
373 	dlog((LOG_INFO, "%d soft errors in %d blocks\n",
374 	    yc->yc_softerrs, yc->yc_blks));
375 	yc->yc_openf = 0;
376 	return (0);
377 }
378 
379 /*
380  * Execute a command on the tape drive a specified number of times.
381  */
382 cycommand(dev, com, count)
383 	dev_t dev;
384 	int com, count;
385 {
386 	register struct buf *bp;
387 	int s;
388 
389 	bp = &ccybuf[CYUNIT(dev)];
390 	s = spl3();
391 	dlog((LOG_INFO, "cycommand(%o, %x, %d), b_flags %x\n",
392 	    dev, com, count, bp->b_flags));
393 	while (bp->b_flags&B_BUSY) {
394 		/*
395 		 * This special check is because B_BUSY never
396 		 * gets cleared in the non-waiting rewind case.
397 		 */
398 		if (bp->b_repcnt == 0 && (bp->b_flags&B_DONE))
399 			break;
400 		bp->b_flags |= B_WANTED;
401 		sleep((caddr_t)bp, PRIBIO);
402 	}
403 	bp->b_flags = B_BUSY|B_READ;
404 	splx(s);
405 	bp->b_dev = dev;
406 	bp->b_repcnt = count;
407 	bp->b_command = com;
408 	bp->b_blkno = 0;
409 	cystrategy(bp);
410 	/*
411 	 * In case of rewind from close; don't wait.
412 	 * This is the only case where count can be 0.
413 	 */
414 	if (count == 0)
415 		return;
416 	biowait(bp);
417 	if (bp->b_flags&B_WANTED)
418 		wakeup((caddr_t)bp);
419 	bp->b_flags &= B_ERROR;
420 }
421 
422 cystrategy(bp)
423 	register struct buf *bp;
424 {
425 	int ycunit = YCUNIT(bp->b_dev);
426 	register struct vba_ctlr *vm;
427 	register struct buf *dp;
428 	int s;
429 
430 	/*
431 	 * Put transfer at end of unit queue.
432 	 */
433 	dlog((LOG_INFO, "cystrategy(%o, %x)\n", bp->b_dev, bp->b_command));
434 	dp = &ycutab[ycunit];
435 	bp->av_forw = NULL;
436 	vm = ycdinfo[ycunit]->ui_mi;
437 	/* BEGIN GROT */
438 	if (bp == &rcybuf[CYUNIT(bp->b_dev)]) {
439 		if (bp->b_bcount >= CYMAXIO) {
440 			uprintf("cy%d: i/o size too large\n", vm->um_ctlr);
441 			bp->b_error = EINVAL;
442 			bp->b_resid = bp->b_bcount;
443 			bp->b_flags |= B_ERROR;
444 			biodone(bp);
445 			return;
446 		}
447 	}
448 	/* END GROT */
449 	s = spl3();
450 	if (dp->b_actf == NULL) {
451 		dp->b_actf = bp;
452 		/*
453 		 * Transport not already active...
454 		 * put at end of controller queue.
455 		 */
456 		 dp->b_forw = NULL;
457 		 if (vm->um_tab.b_actf == NULL)
458 			vm->um_tab.b_actf = dp;
459 		else
460 			vm->um_tab.b_actl->b_forw = dp;
461 	} else
462 		dp->b_actl->av_forw = bp;
463 	dp->b_actl = bp;
464 	/*
465 	 * If the controller is not busy, get it going.
466 	 */
467 	if (vm->um_tab.b_active == 0)
468 		cystart(vm);
469 	splx(s);
470 }
471 
472 /*
473  * Start activity on a cy controller.
474  */
475 cystart(vm)
476 	register struct vba_ctlr *vm;
477 {
478 	register struct buf *bp, *dp;
479 	register struct yc_softc *yc;
480 	register struct cy_softc *cy;
481 	int ycunit;
482 	daddr_t blkno;
483 
484 	dlog((LOG_INFO, "cystart()\n"));
485 	/*
486 	 * Look for an idle transport on the controller.
487 	 */
488 loop:
489 	if ((dp = vm->um_tab.b_actf) == NULL)
490 		return;
491 	if ((bp = dp->b_actf) == NULL) {
492 		vm->um_tab.b_actf = dp->b_forw;
493 		goto loop;
494 	}
495 	ycunit = YCUNIT(bp->b_dev);
496 	yc = &yc_softc[ycunit];
497 	cy = &cy_softc[CYUNIT(bp->b_dev)];
498 	/*
499 	 * Default is that last command was NOT a write command;
500 	 * if we do a write command we will notice this in cyintr().
501 	 */
502 	yc->yc_lastiow = 0;
503 	if (yc->yc_openf < 0 ||
504 	    (bp->b_command != CY_SENSE && (cy->cy_tpb.tpstatus&CYS_OL) == 0)) {
505 		/*
506 		 * Have had a hard error on a non-raw tape
507 		 * or the tape unit is now unavailable (e.g.
508 		 * taken off line).
509 		 */
510 		dlog((LOG_INFO, "openf %d command %x status %b\n",
511 		   yc->yc_openf, bp->b_command, cy->cy_tpb.tpstatus, CYS_BITS));
512 		bp->b_flags |= B_ERROR;
513 		goto next;
514 	}
515 	if (bp == &ccybuf[CYUNIT(bp->b_dev)]) {
516 		/*
517 		 * Execute control operation with the specified count.
518 		 *
519 		 * Set next state; give 5 minutes to complete
520 		 * rewind or file mark search, or 10 seconds per
521 		 * iteration (minimum 60 seconds and max 5 minutes)
522 		 * to complete other ops.
523 		 */
524 		if (bp->b_command == CY_REW) {
525 			vm->um_tab.b_active = SREW;
526 			yc->yc_timo = 5*60;
527 		} else if (bp->b_command == CY_FSF ||
528 		    bp->b_command == CY_BSF) {
529 			vm->um_tab.b_active = SCOM;
530 			yc->yc_timo = 5*60;
531 		} else {
532 			vm->um_tab.b_active = SCOM;
533 			yc->yc_timo = imin(imax(10*(int)bp->b_repcnt,60),5*60);
534 		}
535 		cy->cy_tpb.tprec = htoms(bp->b_repcnt);
536 		dlog((LOG_INFO, "bpcmd "));
537 		goto dobpcmd;
538 	}
539 	/*
540 	 * The following checks handle boundary cases for operation
541 	 * on no-raw tapes.  On raw tapes the initialization of
542 	 * yc->yc_nxrec by cyphys causes them to be skipped normally
543 	 * (except in the case of retries).
544 	 */
545 	if (bp->b_blkno > yc->yc_nxrec) {
546 		/*
547 		 * Can't read past known end-of-file.
548 		 */
549 		bp->b_flags |= B_ERROR;
550 		bp->b_error = ENXIO;
551 		goto next;
552 	}
553 	if (bp->b_blkno == yc->yc_nxrec && bp->b_flags&B_READ) {
554 		/*
555 		 * Reading at end of file returns 0 bytes.
556 		 */
557 		bp->b_resid = bp->b_bcount;
558 		clrbuf(bp);
559 		goto next;
560 	}
561 	if ((bp->b_flags&B_READ) == 0)
562 		/*
563 		 * Writing sets EOF.
564 		 */
565 		yc->yc_nxrec = bp->b_blkno + 1;
566 	if ((blkno = yc->yc_blkno) == bp->b_blkno) {
567 		caddr_t addr;
568 		int cmd;
569 
570 		/*
571 		 * Choose the appropriate i/o command based on the
572 		 * transfer size, the estimated block size,
573 		 * and the controller's internal buffer size.
574 		 * If the request length is longer than the tape
575 		 * block length, a buffered read will fail,
576 		 * thus, we request at most the size that we expect.
577 		 * We then check for larger records when the read completes.
578 		 * If we're retrying a read on a raw device because
579 		 * the original try was a buffer request which failed
580 		 * due to a record length error, then we force the use
581 		 * of the raw controller read (YECH!!!!).
582 		 */
583 		if (bp->b_flags&B_READ) {
584 			if (yc->yc_blksize <= cy->cy_bs &&
585 			    vm->um_tab.b_errcnt == 0)
586 				cmd = CY_BRCOM;
587 			else
588 				cmd = CY_RCOM;
589 		} else {
590 			/*
591 			 * On write error retries erase the
592 			 * inter-record gap before rewriting.
593 			 */
594 			if (vm->um_tab.b_errcnt &&
595 			    vm->um_tab.b_active != SERASED) {
596 				vm->um_tab.b_active = SERASE;
597 				bp->b_command = CY_ERASE;
598 				yc->yc_timo = 60;
599 				goto dobpcmd;
600 			}
601 			cmd = (bp->b_bcount > cy->cy_bs) ? CY_WCOM : CY_BWCOM;
602 		}
603 		vm->um_tab.b_active = SIO;
604 		addr = (caddr_t)vbasetup(bp, &cy->cy_rbuf, 1);
605 		cy->cy_tpb.tpcmd = cmd;
606 		cy->cy_tpb.tpcontrol = yc->yc_dens;
607 		if (cmd == CY_RCOM || cmd == CY_WCOM)
608 			cy->cy_tpb.tpcontrol |= CYCW_LOCK;
609 		cy->cy_tpb.tpstatus = 0;
610 		cy->cy_tpb.tpcount = 0;
611 		cyldmba(cy->cy_tpb.tpdata, (caddr_t)addr);
612 		cy->cy_tpb.tprec = 0;
613 		if (cmd == CY_BRCOM)
614 			cy->cy_tpb.tpsize = htoms(imin(yc->yc_blksize,
615 			    (int)bp->b_bcount));
616 		else
617 			cy->cy_tpb.tpsize = htoms(bp->b_bcount);
618 		cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
619 		do
620 			uncache(&cy->cy_ccb.cbgate);
621 		while (cy->cy_ccb.cbgate == GATE_CLOSED);
622 		cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
623 		cy->cy_ccb.cbcw = CBCW_IE;
624 		cy->cy_ccb.cbgate = GATE_CLOSED;
625 		dlog((LOG_INFO, "CY_GO(%x) cmd %x control %x size %d\n",
626 		    vm->um_addr, cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol,
627 		    htoms(cy->cy_tpb.tpsize)));
628 		CY_GO(vm->um_addr);
629 		return;
630 	}
631 	/*
632 	 * Tape positioned incorrectly; set to seek forwards
633 	 * or backwards to the correct spot.  This happens
634 	 * for raw tapes only on error retries.
635 	 */
636 	vm->um_tab.b_active = SSEEK;
637 	if (blkno < bp->b_blkno) {
638 		bp->b_command = CY_SFORW;
639 		cy->cy_tpb.tprec = htoms(bp->b_blkno - blkno);
640 	} else {
641 		bp->b_command = CY_SREV;
642 		cy->cy_tpb.tprec = htoms(blkno - bp->b_blkno);
643 	}
644 	yc->yc_timo = imin(imax((int)(10 * htoms(cy->cy_tpb.tprec)), 60), 5*60);
645 dobpcmd:
646 	/*
647 	 * Do the command in bp.  Reverse direction commands
648 	 * are indicated by having CYCW_REV or'd into their
649 	 * value.  For these we must set the appropriate bit
650 	 * in the control field.
651 	 */
652 	if (bp->b_command&CYCW_REV) {
653 		cy->cy_tpb.tpcmd = bp->b_command &~ CYCW_REV;
654 		cy->cy_tpb.tpcontrol = yc->yc_dens | CYCW_REV;
655 dlog((LOG_INFO, "cmd %x control %x\n", cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol));
656 	} else {
657 		cy->cy_tpb.tpcmd = bp->b_command;
658 		cy->cy_tpb.tpcontrol = yc->yc_dens;
659 dlog((LOG_INFO, "cmd %x control %x\n", cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol));
660 	}
661 	cy->cy_tpb.tpstatus = 0;
662 	cy->cy_tpb.tpcount = 0;
663 	cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
664 	do
665 		uncache(&cy->cy_ccb.cbgate);
666 	while (cy->cy_ccb.cbgate == GATE_CLOSED);
667 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
668 	cy->cy_ccb.cbcw = CBCW_IE;
669 	cy->cy_ccb.cbgate = GATE_CLOSED;
670 	dlog((LOG_INFO, "CY_GO(%x) cmd %x control %x rec %d\n",
671 	    vm->um_addr, cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol,
672 	    htoms(cy->cy_tpb.tprec)));
673 	CY_GO(vm->um_addr);
674 	return;
675 next:
676 	/*
677 	 * Done with this operation due to error or the
678 	 * fact that it doesn't do anything.
679 	 * Dequeue the transfer and continue
680 	 * processing this slave.
681 	 */
682 	vm->um_tab.b_errcnt = 0;
683 	dp->b_actf = bp->av_forw;
684 	biodone(bp);
685 	goto loop;
686 }
687 
688 /*
689  * Cy interrupt routine.
690  */
691 cyintr(cyunit)
692 	int cyunit;
693 {
694 	struct buf *dp;
695 	register struct buf *bp;
696 	register struct vba_ctlr *vm = cyminfo[cyunit];
697 	register struct cy_softc *cy;
698 	register struct yc_softc *yc;
699 	int err;
700 	register state;
701 
702 	dlog((LOG_INFO, "cyintr(%d)\n", cyunit));
703 	/*
704 	 * First, turn off the interrupt from the controller
705 	 * (device uses Multibus non-vectored interrupts...yech).
706 	 */
707 	cy = &cy_softc[vm->um_ctlr];
708 	cy->cy_ccb.cbcw = CBCW_CLRINT;
709 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_nop);
710 	cy->cy_ccb.cbgate = GATE_CLOSED;
711 	CY_GO(vm->um_addr);
712 	if ((dp = vm->um_tab.b_actf) == NULL) {
713 		dlog((LOG_ERR, "cy%d: stray interrupt", vm->um_ctlr));
714 		return;
715 	}
716 	bp = dp->b_actf;
717 	cy = &cy_softc[cyunit];
718 	cyuncachetpb(cy);
719 	yc = &yc_softc[YCUNIT(bp->b_dev)];
720 	/*
721 	 * If last command was a rewind and tape is
722 	 * still moving, wait for the operation to complete.
723 	 */
724 	if (vm->um_tab.b_active == SREW) {
725 		vm->um_tab.b_active = SCOM;
726 		if ((cy->cy_tpb.tpstatus&CYS_RDY) == 0) {
727 			yc->yc_timo = 5*60;	/* 5 minutes */
728 			return;
729 		}
730 	}
731 	/*
732 	 * An operation completed...record status.
733 	 */
734 	yc->yc_timo = INF;
735 	yc->yc_control = cy->cy_tpb.tpcontrol;
736 	yc->yc_status = cy->cy_tpb.tpstatus;
737 	yc->yc_resid = bp->b_bcount - htoms(cy->cy_tpb.tpcount);
738 	dlog((LOG_INFO, "cmd %x control %b status %b resid %d\n",
739 	    cy->cy_tpb.tpcmd, yc->yc_control, CYCW_BITS,
740 	    yc->yc_status, CYS_BITS, yc->yc_resid));
741 	if ((bp->b_flags&B_READ) == 0)
742 		yc->yc_lastiow = 1;
743 	state = vm->um_tab.b_active;
744 	vm->um_tab.b_active = 0;
745 	/*
746 	 * Check for errors.
747 	 */
748 	if (cy->cy_tpb.tpstatus&CYS_ERR) {
749 		err = cy->cy_tpb.tpstatus&CYS_ERR;
750 		dlog((LOG_INFO, "error %d\n", err));
751 		/*
752 		 * If we hit the end of tape file, update our position.
753 		 */
754 		if (err == CYER_FM) {
755 			yc->yc_status |= CYS_FM;
756 			state = SCOM;		/* force completion */
757 			cyseteof(bp);		/* set blkno and nxrec */
758 			goto opdone;
759 		}
760 		/*
761 		 * Fix up errors which occur due to backspacing over
762 		 * the beginning of the tape.
763 		 */
764 		if (err == CYER_BOT && cy->cy_tpb.tpcontrol&CYCW_REV) {
765 			yc->yc_status |= CYS_BOT;
766 			goto ignoreerr;
767 		}
768 		/*
769 		 * If we were reading raw tape and the only error was that the
770 		 * record was too long, then we don't consider this an error.
771 		 */
772 		if (bp == &rcybuf[cyunit] && (bp->b_flags&B_READ) &&
773 		    err == CYER_STROBE) {
774 			/*
775 			 * Retry reads with the command changed to
776 			 * a raw read if necessary.  Setting b_errcnt
777 			 * here causes cystart (above) to force a CY_RCOM.
778 			 */
779 			if (cy->cy_tpb.tpcmd == CY_BRCOM &&
780 			    vm->um_tab.b_errcnt++ == 0) {
781 				yc->yc_blkno++;
782 				goto opcont;
783 			} else
784 				goto ignoreerr;
785 		}
786 		/*
787 		 * If error is not hard, and this was an i/o operation
788 		 * retry up to 8 times.
789 		 */
790 		if (state == SIO && (CYMASK(err) &
791 		    ((bp->b_flags&B_READ) ? CYER_RSOFT : CYER_WSOFT))) {
792 			if (++vm->um_tab.b_errcnt < 7) {
793 				yc->yc_blkno++;
794 				goto opcont;
795 			}
796 		} else
797 			/*
798 			 * Hard or non-i/o errors on non-raw tape
799 			 * cause it to close.
800 			 */
801 			if (yc->yc_openf > 0 && bp != &rcybuf[cyunit])
802 				yc->yc_openf = -1;
803 		/*
804 		 * Couldn't recover from error.
805 		 */
806 		tprintf(yc->yc_ttyp,
807 		    "yc%d: hard error bn%d status=%b, %s\n", YCUNIT(bp->b_dev),
808 		    bp->b_blkno, yc->yc_status, CYS_BITS,
809 		    (err < NCYERROR) ? cyerror[err] : "");
810 		bp->b_flags |= B_ERROR;
811 		goto opdone;
812 	} else if (cy->cy_tpb.tpcmd == CY_BRCOM) {
813 		int reclen = htoms(cy->cy_tpb.tprec);
814 
815 		/*
816 		 * If we did a buffered read, check whether the read
817 		 * was long enough.  If we asked the controller for less
818 		 * than the user asked for because the previous record
819 		 * was shorter, update our notion of record size
820 		 * and retry.  If the record is longer than the buffer,
821 		 * bump the errcnt so the retry will use direct read.
822 		 */
823 		if (reclen > yc->yc_blksize && bp->b_bcount > yc->yc_blksize) {
824 			yc->yc_blksize = reclen;
825 			if (reclen > cy->cy_bs)
826 				vm->um_tab.b_errcnt++;
827 			yc->yc_blkno++;
828 			goto opcont;
829 		}
830 	}
831 	/*
832 	 * Advance tape control FSM.
833 	 */
834 ignoreerr:
835 	/*
836 	 * If we hit a tape mark update our position.
837 	 */
838 	if (yc->yc_status&CYS_FM && bp->b_flags&B_READ) {
839 		cyseteof(bp);
840 		goto opdone;
841 	}
842 	switch (state) {
843 
844 	case SIO:
845 		/*
846 		 * Read/write increments tape block number.
847 		 */
848 		yc->yc_blkno++;
849 		yc->yc_blks++;
850 		if (vm->um_tab.b_errcnt || yc->yc_status & CYS_CR)
851 			yc->yc_softerrs++;
852 		yc->yc_blksize = htoms(cy->cy_tpb.tpcount);
853 		dlog((LOG_ERR, "blocksize %d", yc->yc_blksize));
854 		goto opdone;
855 
856 	case SCOM:
857 		/*
858 		 * For forward/backward space record update current position.
859 		 */
860 		if (bp == &ccybuf[CYUNIT(bp->b_dev)])
861 			switch ((int)bp->b_command) {
862 
863 			case CY_SFORW:
864 				yc->yc_blkno -= bp->b_repcnt;
865 				break;
866 
867 			case CY_SREV:
868 				yc->yc_blkno += bp->b_repcnt;
869 				break;
870 			}
871 		goto opdone;
872 
873 	case SSEEK:
874 		yc->yc_blkno = bp->b_blkno;
875 		goto opcont;
876 
877 	case SERASE:
878 		/*
879 		 * Completed erase of the inter-record gap due to a
880 		 * write error; now retry the write operation.
881 		 */
882 		vm->um_tab.b_active = SERASED;
883 		goto opcont;
884 	}
885 
886 opdone:
887 	/*
888 	 * Reset error count and remove from device queue.
889 	 */
890 	vm->um_tab.b_errcnt = 0;
891 	dp->b_actf = bp->av_forw;
892 	/*
893 	 * Save resid and release resources.
894 	 */
895 	bp->b_resid = bp->b_bcount - htoms(cy->cy_tpb.tpcount);
896 	if (bp != &ccybuf[cyunit])
897 		vbadone(bp, &cy->cy_rbuf);
898 	biodone(bp);
899 	/*
900 	 * Circulate slave to end of controller
901 	 * queue to give other slaves a chance.
902 	 */
903 	vm->um_tab.b_actf = dp->b_forw;
904 	if (dp->b_actf) {
905 		dp->b_forw = NULL;
906 		if (vm->um_tab.b_actf == NULL)
907 			vm->um_tab.b_actf = dp;
908 		else
909 			vm->um_tab.b_actl->b_forw = dp;
910 	}
911 	if (vm->um_tab.b_actf == 0)
912 		return;
913 opcont:
914 	cystart(vm);
915 }
916 
917 cytimer(dev)
918 	int dev;
919 {
920 	register struct yc_softc *yc = &yc_softc[YCUNIT(dev)];
921 	int s;
922 
923 	if (yc->yc_openf == 0 && yc->yc_timo == INF) {
924 		yc->yc_tact = 0;
925 		return;
926 	}
927 	if (yc->yc_timo != INF && (yc->yc_timo -= 5) < 0) {
928 		printf("yc%d: lost interrupt\n", YCUNIT(dev));
929 		yc->yc_timo = INF;
930 		s = spl3();
931 		cyintr(CYUNIT(dev));
932 		splx(s);
933 	}
934 	timeout(cytimer, (caddr_t)dev, 5*hz);
935 }
936 
937 cyseteof(bp)
938 	register struct buf *bp;
939 {
940 	register int cyunit = CYUNIT(bp->b_dev);
941 	register struct cy_softc *cy = &cy_softc[cyunit];
942 	register struct yc_softc *yc = &yc_softc[YCUNIT(bp->b_dev)];
943 
944 	if (bp == &ccybuf[cyunit]) {
945 		if (yc->yc_blkno > bp->b_blkno) {
946 			/* reversing */
947 			yc->yc_nxrec = bp->b_blkno - htoms(cy->cy_tpb.tpcount);
948 			yc->yc_blkno = yc->yc_nxrec;
949 		} else {
950 			yc->yc_blkno = bp->b_blkno + htoms(cy->cy_tpb.tpcount);
951 			yc->yc_nxrec = yc->yc_blkno - 1;
952 		}
953 		return;
954 	}
955 	/* eof on read */
956 	yc->yc_nxrec = bp->b_blkno;
957 }
958 
959 cyread(dev, uio)
960 	dev_t dev;
961 	struct uio *uio;
962 {
963 	int errno;
964 
965 	errno = cyphys(dev, uio);
966 	if (errno)
967 		return (errno);
968 	return (physio(cystrategy, &rcybuf[CYUNIT(dev)], dev, B_READ, minphys, uio));
969 }
970 
971 cywrite(dev, uio)
972 	dev_t dev;
973 	struct uio *uio;
974 {
975 	int errno;
976 
977 	errno = cyphys(dev, uio);
978 	if (errno)
979 		return (errno);
980 	return (physio(cystrategy, &rcybuf[CYUNIT(dev)], dev, B_WRITE, minphys, uio));
981 }
982 
983 /*
984  * Check that a raw device exits.
985  * If it does, set up the yc_blkno and yc_nxrec
986  * so that the tape will appear positioned correctly.
987  */
988 cyphys(dev, uio)
989 	dev_t dev;
990 	struct uio *uio;
991 {
992 	register int ycunit = YCUNIT(dev);
993 	register daddr_t a;
994 	register struct yc_softc *yc;
995 	register struct vba_device *vi;
996 
997 	if (ycunit >= NYC || (vi = ycdinfo[ycunit]) == 0 || vi->ui_alive == 0)
998 		return (ENXIO);
999 	yc = &yc_softc[ycunit];
1000 	a = uio->uio_offset >> DEV_BSHIFT;
1001 	yc->yc_blkno = a;
1002 	yc->yc_nxrec = a + 1;
1003 	return (0);
1004 }
1005 
1006 /*ARGSUSED*/
1007 cyioctl(dev, cmd, data, flag)
1008 	caddr_t data;
1009 	dev_t dev;
1010 {
1011 	int ycunit = YCUNIT(dev);
1012 	register struct yc_softc *yc = &yc_softc[ycunit];
1013 	register struct buf *bp = &ccybuf[CYUNIT(dev)];
1014 	register callcount;
1015 	int fcount, op;
1016 	struct mtop *mtop;
1017 	struct mtget *mtget;
1018 	/* we depend of the values and order of the MT codes here */
1019 	static cyops[] =
1020 	{CY_WEOF,CY_FSF,CY_BSF,CY_SFORW,CY_SREV,CY_REW,CY_OFFL,CY_SENSE};
1021 
1022 	switch (cmd) {
1023 
1024 	case MTIOCTOP:	/* tape operation */
1025 		mtop = (struct mtop *)data;
1026 		switch (op = mtop->mt_op) {
1027 
1028 		case MTWEOF:
1029 			callcount = mtop->mt_count;
1030 			fcount = 1;
1031 			break;
1032 
1033 		case MTFSR: case MTBSR:
1034 			callcount = 1;
1035 			fcount = mtop->mt_count;
1036 			break;
1037 
1038 		case MTFSF: case MTBSF:
1039 			callcount = mtop->mt_count;
1040 			fcount = 1;
1041 			break;
1042 
1043 		case MTREW: case MTOFFL: case MTNOP:
1044 			callcount = 1;
1045 			fcount = 1;
1046 			break;
1047 
1048 		default:
1049 			return (ENXIO);
1050 		}
1051 		if (callcount <= 0 || fcount <= 0)
1052 			return (EINVAL);
1053 		while (--callcount >= 0) {
1054 #ifdef notdef
1055 			/*
1056 			 * Gagh, this controller is the pits...
1057 			 */
1058 			if (op == MTFSF || op == MTBSF) {
1059 				do
1060 					cycommand(dev, cyops[op], 1);
1061 				while ((bp->b_flags&B_ERROR) == 0 &&
1062 				 (yc->yc_status&(CYS_EOT|CYS_BOT|CYS_FM)) == 0);
1063 			} else
1064 #endif
1065 				cycommand(dev, cyops[op], fcount);
1066 			dlog((LOG_INFO,
1067 			    "cyioctl: status %x, b_flags %x, resid %d\n",
1068 			    yc->yc_status, bp->b_flags, bp->b_resid));
1069 			if ((bp->b_flags&B_ERROR) ||
1070 			    (yc->yc_status&(CYS_BOT|CYS_EOT)))
1071 				break;
1072 		}
1073 		bp->b_resid = callcount + 1;
1074 		return (geterror(bp));
1075 
1076 	case MTIOCGET:
1077 		cycommand(dev, CY_SENSE, 1);
1078 		mtget = (struct mtget *)data;
1079 		mtget->mt_dsreg = yc->yc_status;
1080 		mtget->mt_erreg = yc->yc_control;
1081 		mtget->mt_resid = yc->yc_resid;
1082 		mtget->mt_type = MT_ISCY;
1083 		break;
1084 
1085 	default:
1086 		return (ENXIO);
1087 	}
1088 	return (0);
1089 }
1090 
1091 /*
1092  * Poll until the controller is ready.
1093  */
1094 cywait(cp)
1095 	register struct cyccb *cp;
1096 {
1097 	register int i = 5000;
1098 
1099 	uncache(&cp->cbgate);
1100 	while (i-- > 0 && cp->cbgate == GATE_CLOSED) {
1101 		DELAY(1000);
1102 		uncache(&cp->cbgate);
1103 	}
1104 	return (i <= 0);
1105 }
1106 
1107 /*
1108  * Load a 20 bit pointer into a Tapemaster pointer.
1109  */
1110 cyldmba(reg, value)
1111 	register u_char *reg;
1112 	caddr_t value;
1113 {
1114 	register int v = (int)value;
1115 
1116 	*reg++ = v;
1117 	*reg++ = v >> 8;
1118 	*reg++ = 0;
1119 	*reg = (v&0xf0000) >> 12;
1120 }
1121 
1122 /*
1123  * Unconditionally reset all controllers to their initial state.
1124  */
1125 cyreset(vba)
1126 	int vba;
1127 {
1128 	register caddr_t addr;
1129 	register int ctlr;
1130 
1131 	for (ctlr = 0; ctlr < NCY; ctlr++)
1132 		if (cyminfo[ctlr] && cyminfo[ctlr]->um_vbanum == vba) {
1133 			addr = cyminfo[ctlr]->um_addr;
1134 			CY_RESET(addr);
1135 			if (!cyinit(ctlr, addr)) {
1136 				printf("cy%d: reset failed\n", ctlr);
1137 				cyminfo[ctlr] = NULL;
1138 			}
1139 		}
1140 }
1141 
1142 cyuncachetpb(cy)
1143 	struct cy_softc *cy;
1144 {
1145 	register long *lp = (long *)&cy->cy_tpb;
1146 	register int i;
1147 
1148 	for (i = 0; i < howmany(sizeof (struct cytpb), sizeof (long)); i++)
1149 		uncache(lp++);
1150 }
1151 
1152 /*
1153  * Dump routine.
1154  */
1155 #define	DUMPREC	(32*1024)
1156 cydump(dev)
1157 	dev_t dev;
1158 {
1159 	register struct cy_softc *cy;
1160 	register int bs, num, start;
1161 	register caddr_t addr;
1162 	int unit = CYUNIT(dev), error;
1163 
1164 	if (unit >= NCY || cyminfo[unit] == 0 ||
1165 	    (cy = &cy_softc[unit])->cy_bs == 0 || YCUNIT(dev) >= NYC)
1166 		return (ENXIO);
1167 	if (cywait(&cy->cy_ccb))
1168 		return (EFAULT);
1169 #define	phys(a)	((caddr_t)((int)(a)&~0xc0000000))
1170 	addr = phys(cyminfo[unit]->um_addr);
1171 	num = maxfree, start = NBPG*2;
1172 	while (num > 0) {
1173 		bs = num > btoc(DUMPREC) ? btoc(DUMPREC) : num;
1174 		error = cydwrite(cy, start, bs, addr);
1175 		if (error)
1176 			return (error);
1177 		start += bs, num -= bs;
1178 	}
1179 	cyweof(cy, addr);
1180 	cyweof(cy, addr);
1181 	uncache(&cy->cy_tpb);
1182 	if (cy->cy_tpb.tpstatus&CYS_ERR)
1183 		return (EIO);
1184 	cyrewind(cy, addr);
1185 	return (0);
1186 }
1187 
1188 cydwrite(cy, pf, npf, addr)
1189 	register struct cy_softc *cy;
1190 	int pf, npf;
1191 	caddr_t addr;
1192 {
1193 
1194 	cy->cy_tpb.tpcmd = CY_WCOM;
1195 	cy->cy_tpb.tpcontrol = CYCW_LOCK|CYCW_25IPS|CYCW_16BITS;
1196 	cy->cy_tpb.tpstatus = 0;
1197 	cy->cy_tpb.tpsize = htoms(npf*NBPG);
1198 	cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
1199 	cyldmba(cy->cy_tpb.tpdata, (caddr_t)(pf*NBPG));
1200 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
1201 	cy->cy_ccb.cbgate = GATE_CLOSED;
1202 	CY_GO(addr);
1203 	if (cywait(&cy->cy_ccb))
1204 		return (EFAULT);
1205 	uncache(&cy->cy_tpb);
1206 	if (cy->cy_tpb.tpstatus&CYS_ERR)
1207 		return (EIO);
1208 	return (0);
1209 }
1210 
1211 cyweof(cy, addr)
1212 	register struct cy_softc *cy;
1213 	caddr_t addr;
1214 {
1215 
1216 	cy->cy_tpb.tpcmd = CY_WEOF;
1217 	cy->cy_tpb.tpcount = htoms(1);
1218 	cy->cy_ccb.cbgate = GATE_CLOSED;
1219 	CY_GO(addr);
1220 	(void) cywait(&cy->cy_ccb);
1221 }
1222 
1223 cyrewind(cy, addr)
1224 	register struct cy_softc *cy;
1225 	caddr_t addr;
1226 {
1227 
1228 	cy->cy_tpb.tpcmd = CY_REW;
1229 	cy->cy_tpb.tpcount = htoms(1);
1230 	cy->cy_ccb.cbgate = GATE_CLOSED;
1231 	CY_GO(addr);
1232 	(void) cywait(&cy->cy_ccb);
1233 }
1234 #endif
1235