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