xref: /csrg-svn/sys/tahoe/vba/cy.c (revision 25857)
1 /*	cy.c	1.3	86/01/12	*/
2 
3 #include "cy.h"
4 #if NCY > 0
5 /*
6  * Cipher Tapemaster driver.
7  */
8 int	cydebug = 0;
9 
10 #include "../tahoe/mtpr.h"
11 #include "../tahoe/pte.h"
12 
13 #include "param.h"
14 #include "systm.h"
15 #include "vm.h"
16 #include "buf.h"
17 #include "file.h"
18 #include "dir.h"
19 #include "user.h"
20 #include "proc.h"
21 #include "signal.h"
22 #include "uio.h"
23 #include "ioctl.h"
24 #include "mtio.h"
25 #include "errno.h"
26 #include "cmap.h"
27 
28 #include "../tahoevba/vbavar.h"
29 #include "../tahoevba/cyreg.h"
30 
31 #define	MAXCONTROLLERS		4
32 #define MAX_BLOCKSIZE		(TBUFSIZ*NBPG)
33 #define NUM_UNIT		(NCY * 4)
34 
35 #define	TRUE			1
36 #define	FALSE			0
37 
38 #define	RETRY			1
39 #define EXTEND			2
40 #define	FATAL			3
41 
42 #define	MAINTAIN_POSITION	0
43 #define	DONT_MAINTAIN_POSITION	1
44 
45 #define	PROCESSED		0x80000000
46 #define	SLEEPING		0x80000000
47 #define	b_cmd	av_back		/* only unused word in request */
48 
49 extern	int cywrite_filemark(), cysearch_fm_forw(), cysearch_fm_back();
50 extern	int cy_space_forw(), cy_space_back(), cyrewind_tape_ta();
51 extern	int cyrewind_tape_unl(), cydrive_status(), cyrewind_tape_ov();
52 extern	int cyraw_read(), cyraw_write(), cybuf_read(), cybuf_write();
53 extern	int cywait_until_ready(), cywrite_0_fm(), cywrite_1_fm();
54 extern	int cywrite_2_fm(), cyno_op(), cywrite_eov();
55 
56 static	int (*cmd_tbl[15])() = {
57 	cywrite_filemark,
58 #define	DO_W_FM	0
59 	cysearch_fm_forw,
60 #define	DO_SFMF	1
61 	cysearch_fm_back,
62 #define	DO_SFMB	2
63 	cy_space_forw,
64 #define	DO_SPF	3
65 	cy_space_back,
66 #define	DO_SPB	4
67 	cyrewind_tape_ta,
68 #define	DO_RWTA	5
69 	cyrewind_tape_unl,
70 #define	DO_RWUN	6
71 	cydrive_status,
72 #define	DO_STAT	7
73 	cyrewind_tape_ov,
74 #define	DO_RWOV	8
75 	cywait_until_ready,
76 #define DO_WAIT 9
77 	cywrite_eov,
78 #define DO_WEOV	10
79 	cyraw_read,
80 #define DO_RRD	11
81 	cyraw_write,
82 #define DO_RWT	12
83 	cybuf_read,
84 #define DO_BRD	13
85 	cybuf_write
86 #define DO_BWT	14
87 };
88 
89 #if NCY > 0
90 extern	char	cy0utl[];
91 #endif
92 #if NCY > 1
93 extern	char	cy1utl[];
94 #endif
95 struct	vba_ctlr *cyminfo[NCY];
96 struct	vba_device *cydinfo[NUM_UNIT];
97 long	cystd[] = { 0 };
98 int cyprobe(), cyslave(), cyattach(), cydgo();
99 struct	vba_driver cydriver =
100    { cyprobe, cyslave, cyattach, cydgo, cystd, "yc", cydinfo, "cy", cyminfo };
101 fmt_scp	*cyscp[] = { (fmt_scp *)0xc0000c06, (fmt_scp *)0xc0000c16 };
102 unsigned cyminsize();
103 
104 /*
105  * Per-controller data structure.
106  */
107 typedef struct {
108 	struct pte	*map;
109 	char		*utl;
110 	int		(*interupt_path)();
111 	label_t		environ;  /* Environment variable for longjmps */
112 	struct buf	*my_request;
113 	struct buf	*wakeup_request;
114 	short		bs;	  /* buffer size */
115 	fmt_ccb		ccb;	  /* Channel control blocks */
116 	fmt_scb		scb;	  /* System configuration blocks */
117 	fmt_tpb		tpb;	  /* Tape parameter blocks */
118 	fmt_tpb		last;	  /* Tape parameter blocks */
119 	fmt_tpb		noop;	  /* Tape parameter blocks */
120 	long		rawbuf[MAX_BLOCKSIZE/sizeof(long)+1];
121 } ctlr_tab;
122 
123 extern	int cy_normal_path();
124 ctlr_tab ctlr_info[NCY] = {
125 #if NCY > 0
126 	{CY0map, cy0utl, cy_normal_path},
127 #endif
128 #if NCY > 1
129 	{CY1map, cy1utl, cy_normal_path},
130 #endif
131 };
132 
133 /*
134  * Per-drive information.
135  */
136 typedef struct {
137 	int		(*cleanup)();
138 	struct buf	u_queue;
139 	struct buf	rawbp;
140 	long		blkno;
141 	long		file_number;
142 	short		last_control;
143 	short		last_status;
144 	short		last_resid;
145 	unsigned long	bad_count;
146 	unsigned	control_proto: 16;
147 	unsigned	error_count  : 8;
148 	unsigned	open	     : 1;
149 	unsigned	eof	     : 1;
150 	unsigned	bot	     : 1;
151 	unsigned	eot	     : 1;
152 	char		*message;
153 } unit_tab;
154 unit_tab unit_info[NUM_UNIT];
155 
156 cyprobe(reg, vm)
157 	caddr_t reg;
158 	struct vba_ctlr *vm;
159 {
160 	register br, cvec;			/* must be r12, r11 */
161 
162 	if (badcyaddr(reg+1))
163 		return (0);
164 	br = 0x13, cvec = 0x80;			/* XXX */
165 	return (sizeof (caddr_t));		/* XXX */
166 }
167 
168 /*
169  * Check to see if a drive is attached to a controller.
170  * Since we can only tell that a drive is there if a tape is loaded and
171  * the drive is placed online, we always indicate the slave is present.
172  */
173 cyslave(vi, addr)
174 	struct vba_device *vi;
175 	caddr_t addr;
176 {
177 
178 #ifdef lint
179 	vi = vi; addr = addr;
180 #endif
181 	return (1);
182 }
183 
184 /* THIS NEEDS TO BE REWRITTEN TO MOVE STUFF TO CYPROBE */
185 cyattach(vi)
186 	struct vba_device *vi;
187 {
188 	register unit_tab *ui = &unit_info[vi->ui_unit];
189 	register struct buf *cq = &vi->ui_mi->um_tab;
190 	register struct buf *uq = cq->b_forw;
191 	register struct buf *start_queue = uq;
192 
193 	(void) cy_init_controller(vi->ui_addr, vi->ui_ctlr, 1);
194 	/* Add unit to controllers queue */
195 	if (cq->b_forw == NULL) {
196 		cq->b_forw = &ui->u_queue;
197 		ui->u_queue.b_forw = &ui->u_queue;
198 	} else {
199 		while (uq->b_forw != start_queue)
200 			uq = uq->b_forw;
201 		ui->u_queue.b_forw = start_queue;
202 		uq->b_forw = &ui->u_queue;
203 	}
204 	ui->cleanup = cyno_op;
205 	ui->last_status = 0;
206 	ui->last_control = 0;
207 	ui->file_number = 0;
208 	ui->bad_count = 0;
209 	ui->blkno = 0;
210 	ui->open = 0;
211 	ui->bot = 1;
212 	ui->eot = 0;
213 	ui->eof = 0;
214 	ui->message = NULL;
215 }
216 
217 /*
218  * Initialize the controller after a controller reset or
219  * during autoconfigure.  All of the system control blocks
220  * are initialized and the controller is asked to configure
221  * itself for later use.
222  */
223 cy_init_controller(addr, ctlr, print)
224 	caddr_t addr;
225 	int ctlr, print;
226 {
227 	register int *pte;
228 	register fmt_scp *SCP;
229 	register fmt_scb *SCB;
230 	register fmt_ccb *CCB;
231 	register ctlr_tab *ci;
232 
233 	/*
234 	 * Initialize the system configuration pointer.
235 	 */
236 	SCP = cyscp[ctlr];
237 	/* make kernel writable */
238 	pte = (int *)vtopte((struct proc *)0, btop(SCP));
239 	*pte &= ~PG_PROT; *pte |= PG_KW;
240 	mtpr(TBIS, SCP);
241 	/* load the correct values in the scp */
242 	SCP->bus_size = _16_BITS;
243 	load_mbus_addr((caddr_t)&ctlr_info[ctlr].scb, SCP->scb_ptr);
244 	/* put it back to read-only */
245 	*pte &= ~PG_PROT; *pte |= PG_KR;
246 	mtpr(TBIS, SCP);
247 
248 	/*
249 	 * Init system configuration block.
250 	 */
251 	SCB = &ctlr_info[ctlr].scb;
252 	SCB->fixed_value = 0x3;
253 	/* set pointer to the channel control block */
254 	load_mbus_addr((caddr_t)&ctlr_info[ctlr].ccb, SCB->ccb_ptr);
255 
256 	/*
257 	 * Initialize the chanel control block.
258 	 */
259 	CCB = &ctlr_info[ctlr].ccb;
260 	CCB->ccw = CLEAR_INTERUPT;
261 	CCB->gate = GATE_OPEN;
262 	/* set pointer to the tape parameter block */
263 	load_mbus_addr((caddr_t)&ctlr_info[ctlr].tpb, CCB->tpb_ptr);
264 
265 	/*
266 	 * Issue a noop cmd and get the internal buffer size for buffered i/o.
267 	 */
268 	ci = &ctlr_info[ctlr];
269 	/* set command to be CONFIGURE */
270 	ci->tpb.cmd = NO_OP;
271 	ci->tpb.control = CW_16bits;
272 	ci->ccb.gate = GATE_CLOSED;
273 	CY_ATTENTION(addr);	/* execute! */
274 	if (cywait(&ci->ccb) || (ci->tpb.status & CS_ERm)) {
275 		printf("cy%d: time-out during init\n", ctlr);
276 		return (0);
277 	}
278 	ci->tpb.cmd = CONFIG;
279 	ci->tpb.control = CW_16bits;
280 	ci->ccb.gate = GATE_CLOSED;
281 	CY_ATTENTION(addr);		/* execute! */
282 	if (cywait(&ci->ccb) || (ci->tpb.status & CS_ERm)) {
283 		cyprint_err("Tapemaster configuration failure",
284 		    0, ci->tpb.status);
285 		return (0);
286 	}
287 	uncache(&ci->tpb.count);
288 	ci->bs = MULTIBUS_SHORT(ci->tpb.count);
289 	if (print)
290 		printf("cy%d: %dKb buffer\n", ctlr, ci->bs/1024);
291 	return (1);
292 }
293 
294 cydgo()
295 {
296 
297 }
298 
299 /* macro to pack the unit number into Tapemaster format */
300 #define	UNIT(unit) \
301     (((cydinfo[unit]->ui_slave & 1) << 11) | \
302      ((cydinfo[unit]->ui_slave & 2) << 9) | \
303      ((cydinfo[unit]->ui_slave & 4) >> 2))
304 
305 cyopen(dev, flag)
306 	register int flag;
307 	register dev_t dev;
308 {
309 	register int unit = CYUNIT(dev);
310 	register unit_tab *ui;
311 
312 	if (unit >= NUM_UNIT || cydinfo[unit] == 0 ||
313 	    (ui = &unit_info[unit])->open)
314 		return (ENXIO);
315 	ui->control_proto = UNIT(unit) | CW_INTR | CW_16bits;
316 	ui->blkno = 0;
317 	ui->bad_count = 0;
318 	ui->eof = 0;
319 	ui->open = 1;
320 	cycmd(dev, DO_WAIT, 1);			/* wait for tape to rewind */
321 	if ((ui->last_status&CS_OL) == 0) {	/* not on-line */
322 		ui->open = 0;
323 		return (ENXIO);
324 	}
325 	if ((flag&FWRITE) && (ui->last_status&CS_P)) {
326 		uprintf("cy%d: write protected\n", unit);
327 		ui->open = 0;
328 		return (ENXIO);
329 	}
330 	if (ui->last_status&CS_LP) {
331 		ui->file_number = 0;
332 		ui->bot = 1;
333 		ui->eof = ui->eot = 0;
334 	}
335 	return (0);
336 }
337 
338 cyclose(dev, flag)
339 	register dev_t dev;
340 	register flag;
341 {
342 	register int unit = CYUNIT(dev);
343 	register unit_tab *ui = &unit_info[unit];
344 
345 	if (ui->last_status&CS_OL) {
346 		if ((flag&FWRITE) && (minor(dev)&T_NOREWIND))
347 			cycmd(dev, DO_WEOV, 1);
348 		else if ((minor(dev) & T_NOREWIND) == 0)
349 			cycmd(dev, DO_RWOV, 1);
350 	}
351 	if (ui->bad_count != 0) {
352 #ifdef notdef
353 		ui->bad_count *= 889;
354 		uprintf("cy%d: Warning - %d.%dcm of tape were used for recovering bad spots.\n", unit, ui->bad_count/100, ui->bad_count%100);
355 #endif
356 		ui->bad_count = 0;
357 	}
358 	ui->open = 0;
359 }
360 
361 /*
362  * Cycmd is used internally to implement all the ioctl functions.
363  * We duplicate the code in physio
364  * that is used for syncronizing the processes (sleep / wakeup) so
365  * that we can treat our internal command requests exactly like
366  * regular reads and writes.  They get put on the controller queue,
367  * start processes them and iodone is called to wake us up on completion.
368  *
369  * We don't call physio directly because it expects data to be moved
370  * and has a lot more overhead than we really need.
371  */
372 cycmd(dev, command, count)
373 	register dev_t dev;
374 	register int command, count;
375 {
376 	register int unit = CYUNIT(dev);
377 	register unit_tab *ui = &unit_info[unit];
378 	register struct buf *uq;
379 	int s;
380 
381 	s = spl3();
382 	while (ui->rawbp.b_flags & B_BUSY) {
383 		ui->rawbp.b_flags |= B_WANTED;
384 		sleep((caddr_t)&ui->rawbp, PRIBIO+1);
385 	}
386 	splx(s);
387 	/* load the request queue element */
388 	ui->rawbp.b_error = 0;
389 	ui->rawbp.b_dev = dev;
390 	ui->rawbp.b_cmd = (struct buf *)command;
391 	ui->rawbp.b_bcount = count;
392 	ui->rawbp.b_flags = B_PHYS | B_BUSY;
393 	s = spl3();
394 	uq = &ui->u_queue;
395 	ui->rawbp.av_forw = NULL;
396 	if (uq->av_forw == NULL)
397 		uq->av_forw = &ui->rawbp;
398 	else
399 		uq->av_back->av_forw = &ui->rawbp;
400 	uq->av_back = &ui->rawbp;
401 	cystart(cydinfo[unit]->ui_mi, &ui->rawbp, s);
402 
403 	/* wait for operation to complete */
404 	while ((ui->rawbp.b_flags&B_DONE) == 0)
405 		sleep((caddr_t)&ui->rawbp, PRIBIO);
406 	ui->rawbp.b_flags &= ~(B_PHYS | B_BUSY);
407 	if (ui->rawbp.b_flags & B_WANTED)
408 		wakeup((caddr_t)&ui->rawbp);
409 	return (geterror(&ui->rawbp));
410 }
411 
412 cystrategy(bp)
413 	register struct buf *bp;
414 {
415 	register int unit = CYUNIT(bp->b_dev);
416 	register unit_tab *ui = &unit_info[unit];
417 	register struct buf *uq;
418 	int s;
419 
420 	/* check the validity of the request */
421 	if (bp->b_bcount > MAX_BLOCKSIZE) {
422 		uprintf("cy%d: Maximum block size is %dk!\n",
423 		    unit, MAX_BLOCKSIZE/1024);
424 		bp->b_error = EIO;
425 		bp->b_resid = bp->b_bcount;
426 		bp->b_flags |= B_ERROR;
427 		iodone(bp);
428 		return;
429 	}
430 	vbasetup(bp, MAX_BLOCKSIZE);
431 	if (bp->b_flags & B_PHYS)
432 		bp->b_cmd = (struct buf *)(bp->b_flags&B_READ? DO_RRD : DO_RWT);
433 	else
434 		bp->b_cmd = (struct buf *)(bp->b_flags&B_READ? DO_BRD : DO_BWT);
435 	/* place request on queue and start it */
436 	s = spl3();
437 	uq = &ui->u_queue;
438 	bp->av_forw = NULL;
439 	if (uq->av_forw == NULL)
440 		uq->av_forw = bp;
441 	else
442 		uq->av_back->av_forw = bp;
443 	uq->av_back = bp;
444 	cystart(cydinfo[unit]->ui_mi, bp, s);
445 }
446 
447 struct	buf *cyget_next();
448 int	cystart_timeout();
449 /*
450  * Cystart is called once for every request that is placed on a
451  * controller's queue.  Start is responsible for fetching requests for
452  * a controller queue, starting the operation, and waiting for completion,
453  * and releasing the buf structure back to UNIX or cycmd, before fetching
454  * the next request.
455  *
456  * The controller's queue looks like this:
457  *
458  *                      +---------------------------------------+
459  *                      |                                       |
460  *      +-----------+   |   +-----------+        +-----------+  |
461  *      |  b_forw   |---+-->|  b_forw   |--~ ~-->|  b_forw   |--+
462  *      +-----------+       +-----------+        +-----------+
463  *      |  b_back   |       | ......... |        | ......... |
464  *      +-----------+       +-----------+        +-----------+
465  *      | ......... |      First unit queue     Last unit queue
466  *      +-----------+          element              element
467  * head of controller queue
468  *  (cyminfo[ctlr].um_tab)
469  */
470 cystart(vi, bp, s)
471 	register struct vba_ctlr *vi;
472 	register struct buf *bp;
473 {
474 	int unit = CYUNIT(bp->b_dev), ctlr = vi->um_ctlr;
475 	register struct buf *next, *cq = &vi->um_tab;
476 	register unit_tab *ui = &unit_info[unit];
477 	register ctlr_tab *ci = &ctlr_info[ctlr];
478 
479 	if (cq->b_active&SLEEPING) {
480 		untimeout(cystart_timeout, (caddr_t)cq);
481 		cystart_timeout(cq);
482 	}
483 	if (cq->b_active) {
484 		sleep((caddr_t)bp, PRIBIO-1);
485 		if (bp->b_flags&PROCESSED) {
486 			if (ui->message) {
487 				uprintf("cy%d: %s\n", unit, ui->message);
488 				ui->message = 0;
489 			}
490 			bp->b_flags &= ~PROCESSED;
491 			iodone(bp);
492 			return;
493 		}
494 	}
495 	cq->b_active = 1;
496 	splx(s);
497 	ci->my_request = bp;
498 	cydo_my_command(ctlr, cq, ci);
499 	if (ui->message) {
500 		uprintf("cy%d: %s\n", unit, ui->message);
501 		ui->message = 0;
502 	}
503 	bp->b_flags &= ~PROCESSED;
504 	iodone(bp);
505 	if ((next = cyget_next(cq)) != NULL)
506 		wakeup((caddr_t)next);
507 	else
508 		cq->b_active = 0;
509 }
510 
511 /*
512  * Cystart_timeout wakes up the start routine after it's 3
513  * second wait time is up or when a new command enters the queue.
514  * The timer is used to give up the processor while all drives
515  * on the queue are rewinding and we need to wait for them to be dome.
516  */
517 cystart_timeout(cq)
518 	register struct buf *cq;
519 {
520 
521 	cq->b_active &= ~SLEEPING;
522 	wakeup((caddr_t)cq);
523 }
524 
525 /*
526  * Cydo_my command scans the request queues once for a
527  * particular controller and calls the appropriate processing routine
528  * each time we find a request that can be started.
529  */
530 cydo_my_command(ctlr, cq, ci)
531 	register struct buf *cq;
532 	register ctlr_tab *ci;
533 {
534 	register struct buf *next;
535 
536 	while ((next = cyget_next(cq)) != NULL) {
537 		if (cq->b_forw->b_active&SLEEPING) {
538 			cq->b_active |= SLEEPING;
539 			timeout(cystart_timeout, (caddr_t)cq, 1*60);
540 			sleep((caddr_t)cq, PRIBIO);
541 			continue;
542 		}
543 		if (setjmp(&ctlr_info[ctlr].environ))
544 			cydone(cq);
545 		else {
546 			register int cmd = (int)next->b_cmd;
547 
548 			(*cmd_tbl[cmd])(next, cq);
549 		}
550 		if (next->b_flags & PROCESSED) {
551 			if (ci->my_request == next)
552 				break;
553 			wakeup((caddr_t)next);
554 		}
555 	}
556 }
557 
558 struct buf *
559 cyget_next(cq)
560 	register struct	buf *cq;
561 {
562 	register struct buf *bp, *uq, *next = NULL;
563 
564 	cq->b_forw = cq->b_forw->b_forw;
565 	uq = cq->b_forw;
566 	do {
567 		if ((bp = uq->av_forw) != NULL) {
568 			if ((uq->b_active&SLEEPING) == 0) {
569 				cq->b_forw = uq;
570 				return (bp);
571 			}
572 			next = uq;
573 		}
574 		uq = uq->b_forw;
575 	} while(uq != cq->b_forw);
576 	if (next != NULL) {
577 		cq->b_forw = next;
578 		return (next->av_forw);
579 	}
580 	return (NULL);
581 }
582 
583 /*
584  * Mark the current command on the controller's q completed and remove it.
585  */
586 cydone(cq)
587 	struct buf *cq;
588 {
589 	register struct buf *uq = cq->b_forw;
590 	int s;
591 
592 	uq->av_forw->b_flags |= PROCESSED;
593 	s = spl3();
594 	if ((uq->av_forw = uq->av_forw->av_forw) == NULL)
595 		uq->av_back = NULL;
596 	splx(s);
597 }
598 
599 /*
600  * The following routines implement the individual commands.
601  *
602  * Each command is responsible for a few things. 1) Each has to keep
603  * track of special cases that are related to the individual command and
604  * the previous commands sequence, 2) each is required to call iodone when
605  * command is actually finished, 3) it must use cyexecute to actually
606  * start the controller, and 4) they are required to keep the tape in
607  * a consistant state so that other commands will not be messed up.
608  */
609 
610 /*
611  * Read requests from the raw device.
612  * The special cases are:
613  *  1) we can not read after a write.  (writting defines end of file)
614  *  2) reading past end of file returns 0 bytes;
615  */
616 cyraw_read(bp, cq)
617 	register struct buf *bp;
618 	struct buf *cq;
619 {
620 	int unit = CYUNIT(bp->b_dev);
621 	register unit_tab *ui = &unit_info[unit];
622 	register ctlr_tab *ci = &ctlr_info[cydinfo[unit]->ui_ctlr];
623 	int addr, lock_flag, command;
624 
625 	if (ui->cleanup != cyno_op || ui->eof) {
626 		bp->b_resid = bp->b_bcount;
627 		bp->b_error = ENXIO, bp->b_flags |= B_ERROR;
628 		cydone(cq);
629 		return;
630 	}
631 	if (bp->b_bcount > ci->bs)
632 		command = READ_TA, lock_flag = CW_LOCK;
633 	else
634 		command = READ_BU, lock_flag = 0;
635 	ui->blkno++;
636 	addr = vbastart(bp, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl);
637 	cyexecute(command, bp->b_bcount, addr, lock_flag, unit, 10, FALSE);
638 	vbadone(bp, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl);
639 	cydone(cq);
640 }
641 
642 /*
643  * Write requests from the raw device.
644  * The special cases are:
645  *  1) we don't allow writes after end of tape is reached.
646  */
647 cyraw_write(bp, cq)
648 	register struct buf *bp;
649 	struct buf *cq;
650 {
651 	int unit = CYUNIT(bp->b_dev);
652 	register unit_tab *ui = &unit_info[CYUNIT(unit)];
653 	register ctlr_tab *ci = &ctlr_info[cydinfo[unit]->ui_ctlr];
654 	int addr, lock_flag, command;
655 
656 	if (ui->eot) {
657 		bp->b_resid = bp->b_bcount;
658 		bp->b_error = ENXIO, bp->b_flags |= B_ERROR;
659 		longjmp(&ci->environ);
660 	}
661 	ui->cleanup = cywrite_2_fm;
662 	if (bp->b_bcount > ci->bs)
663 		command = WRIT_TA, lock_flag = CW_LOCK;
664 	else
665 		command = WRIT_BU, lock_flag = 0;
666 	ui->blkno++;
667 	addr = vbastart(bp, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl);
668 	cyexecute(command, bp->b_bcount, addr, lock_flag, unit, 10, FALSE);
669 	vbadone(bp, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl);
670 	cydone(cq);
671 }
672 
673 /*
674  * Write a filemark on a tape.
675  */
676 cywrite_filemark(bp, cq)
677 	register struct buf *bp;
678 	struct buf *cq;
679 {
680 	int unit = CYUNIT(bp->b_dev);
681 	register unit_tab *ui = &unit_info[CYUNIT(unit)];
682 
683 	if (bp->b_bcount == 0) {
684 		cydone(cq);
685 		return;
686 	}
687 	bp->b_bcount--;
688 	if (ui->cleanup == cywrite_1_fm)
689 		ui->cleanup = cywrite_0_fm;
690 	if (ui->cleanup == cywrite_2_fm || ui->cleanup == cyno_op)
691 		ui->cleanup = cywrite_1_fm;
692 	ui->file_number++;
693 	ui->eof = 1;
694 	ui->blkno = 0;
695 	cyexecute(WRIT_FM, (long)1, 0, 0, unit, 10, FALSE);
696 }
697 
698 /*
699 **	cysearch_fm_forw is the ioctl to search for a filemark in the
700 **  forward direction on tape.
701 **
702 **	Since only one device can be active on a given controller at any
703 **  given instant in time, we try to be nice and let onther devices  on
704 **  this controller be scheduled after we space over each record.  This will
705 **  at least give the apperance of overlapped operations on the controller.
706 **
707 **  The special cases are:
708 **  1) if the last command was a write the we can't search.
709 */
710 
711 cysearch_fm_forw(request, cq)
712 register struct buf	*request;
713 register struct buf	*cq;
714 {
715 	register int		unit = CYUNIT(request->b_dev);
716 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
717 	register int		ctlr = cydinfo[unit]->ui_ctlr;
718 	register ctlr_tab	*ci = &ctlr_info[ctlr];
719 
720 	if((ui->cleanup != cyno_op) || ui->eot) {
721 		request->b_resid = request->b_bcount;
722 		request->b_error = ENXIO, request->b_flags |= B_ERROR;
723 		longjmp(&ci->environ);
724 	}
725 	if(request->b_bcount && !ui->eot) {
726 		if(!ui->eot) {
727 			ui->blkno++;
728 			cyexecute(SPAC_FM, (long)1, 0, 0, unit, 5, FALSE);
729 			if(!(ui->eof || ui->eot))
730 				return;
731 		}
732 		request->b_bcount--;
733 		ui->eof = FALSE;
734 		if(!ui->eot) {
735 			ui->file_number++;
736 			ui->blkno = 0;
737 			return;
738 		}
739 	}
740 	if(ui->eot) {
741 		request->b_resid = request->b_bcount;
742 		request->b_flags |= B_ERROR, request->b_error = ENXIO;
743 	}
744 	cydone(cq);
745 }
746 
747 
748 /*
749 **	cysearch_fm_back is the ioctl to search for a filemark in the
750 **  reverse direction on tape.
751 **
752 **	Since only one device can be active on a given controller at any
753 **  given instant in time, we try to be nice and let onther devices  on
754 **  this controller be scheduled after we space over each record.  This will
755 **  at least give the apperance of overlapped operations on the controller.
756 **
757 **  The special cases are:
758 **  1) can't search past begining of tape.
759 **  2) if the lasr operation was a write data then we need to add
760 **     an end of volume record before we start searching.
761 */
762 
763 cysearch_fm_back(request, cq)
764 register struct buf	*request;
765 register struct buf	*cq;
766 {
767 	register int		unit = CYUNIT(request->b_dev);
768 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
769 
770 	if(!ui->bot) {
771 		(*ui->cleanup)(unit, MAINTAIN_POSITION);
772 		if(ui->blkno == 0)
773 			request->b_bcount++;
774 		ui->blkno = 0xffffffff;
775 		if(request->b_bcount && !ui->bot) {
776 			cyexecute(SPAC_FM, (long)1, 0, CW_REV, unit, 6, FALSE);
777 			if(ui->eof) {
778 				ui->eof = FALSE;
779 				ui->file_number--;
780 				request->b_bcount--;
781 			}
782 			return;
783 		}
784 		if(ui->bot) {
785 			ui->file_number = 0;
786 			if(request->b_bcount) {
787 				request->b_resid = request->b_bcount;
788 				request->b_error = ENXIO;
789 				request->b_flags |= B_ERROR;
790 			}
791 		}
792 		else {
793 			request->b_cmd = (struct buf *)DO_SFMF;
794 			request->b_bcount = 1;
795 			return;
796 		}
797 	}
798 	ui->blkno = 0;
799 	ui->eof = FALSE;
800 	cydone(cq);
801 }
802 
803 
804 /*
805 **	cy_space_forw is used to search forward a given number of records on
806 **  tape.
807 **
808 **	Since only one device can be active on a given controller at any
809 **  given instant in time, we try to be nice and let onther devices  on
810 **  this controller be scheduled after we space over each record.  This will
811 **  at least give the apperance of overlapped operations on the controller.
812 **
813 **  The special cases are:
814 **  1) we can't space over a filemark.
815 **  2) if the last command was a write data or filemark we can't space forward.
816 */
817 
818 cy_space_forw(request, cq)
819 register struct buf	*request;
820 register struct buf	*cq;
821 {
822 	register int		unit = CYUNIT(request->b_dev);
823 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
824 	register int		ctlr = cydinfo[unit]->ui_ctlr;
825 	register ctlr_tab	*ci = &ctlr_info[ctlr];
826 
827 	if((ui->cleanup != cyno_op) || ui->eof) {
828 		request->b_resid = request->b_bcount;
829 		request->b_error = ENXIO, request->b_flags |= B_ERROR;
830 		longjmp(&ci->environ);
831 	}
832 	if(request->b_bcount) {
833 		ui->blkno++;
834 		cyexecute(SPAC_FM, (long)1, 0, 0, unit, 10, FALSE);
835 		if(!ui->eof && request->b_bcount) {
836 			request->b_bcount--;
837 			return;
838 		}
839 	}
840 	if(ui->eof) {
841 		request->b_resid = request->b_bcount;
842 		request->b_error = ENXIO, request->b_flags |= B_ERROR;
843 	}
844 	cydone(cq);
845 }
846 
847 
848 /*
849 **	Cy_space_back spaces backward a given number of records.
850 **
851 **	Since only one device can be active on a given controller at any
852 **  given instant in time, we try to be nice and let onther devices  on
853 **  this controller be scheduled after we space over each record.  This will
854 **  at least give the apperance of overlapped operations on the controller.
855 **
856 **  The special cases are:
857 **  1) we can't space over a filemark.
858 **  2) we can't space past the beginning of tape.
859 **  3) if the last operation was a write data then we need to add
860 **     an end of volume record before we start searching.
861 */
862 
863 cy_space_back(request, cq)
864 register struct buf	*request;
865 register struct buf	*cq;
866 {
867 	register int		unit = CYUNIT(request->b_dev);
868 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
869 
870 	if(!ui->bot) {
871 		(*ui->cleanup)(unit, MAINTAIN_POSITION);
872 		if(request->b_bcount+1 && !ui->bot && !ui->eof) {
873 			request->b_bcount--;
874 			ui->blkno--;
875 			cyexecute(SPACE, (long)1, 0, CW_REV, unit, 15, FALSE);
876 			return;
877 		}
878 		if(!ui->bot) {
879 			request->b_bcount = 1;
880 			cy_space_forw(request, cq);
881 		}
882 		ui->eof = FALSE;
883 	}
884 	cydone(cq);
885 }
886 
887 /*
888  * Rewind tape and wait for completion.
889  * An overlapped rewind is issued and then we change the command type to
890  * a wait for ready ioctl.  Wait for ready contains the logic to poll
891  * without blocking anything in the system, until the drive becomes ready or
892  * drops off line whichever comes first.
893  */
894 /*ARGSUSED*/
895 cyrewind_tape_ta(bp, cq)
896 	struct buf *bp, *cq;
897 {
898 
899 	cyrewind_tape(bp, REWD_OV);
900 	bp->b_cmd = (struct buf *)DO_WAIT;
901 }
902 
903 /*
904  * Do an overlapped rewind and then unload the tape.
905  * This feature is handled by the individual tape drive and
906  * in some cases can not be performed.
907  */
908 cyrewind_tape_unl(bp, cq)
909 	struct buf *bp, *cq;
910 {
911 
912 	cyrewind_tape(bp, OFF_UNL);
913 	cydone(cq);
914 }
915 
916 /*
917  * Do an overlapped rewind.
918  */
919 cyrewind_tape_ov(bp, cq)
920 	struct buf *bp, *cq;
921 {
922 
923 	cyrewind_tape(bp, REWD_OV);
924 	cydone(cq);
925 }
926 
927 /*
928  * Common code for all rewind commands.
929  * The special cases are:
930  *  3) if the last operation was a write data then we need to add
931  *     an end of volume record before we start searching.
932  */
933 cyrewind_tape(bp, cmd)
934 	register struct buf *bp;
935 	int cmd;
936 {
937 	register int unit = CYUNIT(bp->b_dev);
938 	register unit_tab *ui = &unit_info[unit];
939 
940 	(*ui->cleanup)(unit, DONT_MAINTAIN_POSITION);
941 	ui->blkno = 0;
942 	ui->eof = FALSE;
943 	ui->bot = TRUE;
944 	ui->eot = FALSE;
945 	ui->file_number = 0;
946 	bp->b_resid = 0;
947 	ui->cleanup = cyno_op;
948 	cyexecute(cmd, (long)0, 0, 0, unit, cmd == REWD_OV ? 10 : 10*60, 0);
949 }
950 
951 /*
952 **	Cywait_until_ready is used to wait for rewinds to complete.
953 **  We check the status and if the tape is still rewinding we re-enter ourself
954 **  on the activity queue to give other requests a chance to execute before we
955 **  check the status again.  One other thing is that we only want to  check
956 **  the status every five seconds.  so we set a timer for five seconds and
957 **  check the time left every time we enter this routine.  If there is still
958 **  time left then we simply reinsert ourself on the queue again and wait
959 **  until next time ..
960 */
961 cywait_until_ready(request, cq)
962 register struct buf	*request;
963 register struct buf	*cq;
964 {
965 	extern int		cywait_timeout();
966 	register int		unit = CYUNIT(request->b_dev);
967 	register unit_tab	*ui = &unit_info[unit];
968 
969 	cyexecute(DRIVE_S, (long)0, 0, 0, unit, 10, FALSE);
970 	if((!(ui->last_status & CS_OL)) || (ui->last_status & CS_RDY)) {
971 		cydone(cq);
972 		return;
973 	}
974 	cq->b_forw->b_active |= SLEEPING;
975 	timeout(cywait_timeout, (caddr_t)cq->b_forw, 2*60);
976 }
977 
978 /*
979  * Reset the timing flag for nice_wait after 3 seconds.
980  * This makes this drive eligible for scheduling again.
981  */
982 cywait_timeout(uq)
983 	struct buf *uq;
984 {
985 
986 	uq->b_active &= ~SLEEPING;
987 }
988 
989 /*
990  * Process a status ioctl request.
991  * It depends entirly on the interupt routines to load the last_XXX
992  * registers in unit_info[].
993  */
994 cydrive_status(bp, cq)
995 	struct buf *bp, *cq;
996 {
997 
998 	cyexecute(DRIVE_S, (long)0, 0, 0, CYUNIT(bp->b_dev), 10, FALSE);
999 	cydone(cq);
1000 }
1001 
1002 /*
1003 **	cybuf_read handles the read requests from the block device.
1004 **
1005 **  The special cases are:
1006 **  1)	we can not read after a write.  (writting defines end of file)
1007 **  2)  reading past end of file returns 0 bytes;
1008 **  3)  if we are mispositioned we have to seek to the correct block.
1009 **  4)  we can hit end of tape while seeking.
1010 **  5)  we want to be nice to other processes while seeking so we
1011 **  	break the request up into smaller requests.
1012 **  6)  returns error if the block was larger than requested.
1013 */
1014 cybuf_read(request, cq)
1015 register struct buf	*request;
1016 register struct buf	*cq;
1017 {
1018 	register int		unit = CYUNIT(request->b_dev);
1019 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
1020 	register int		ctlr = cydinfo[unit]->ui_ctlr;
1021 	register ctlr_tab	*ci = &ctlr_info[ctlr];
1022 	register int		addr, command, bus_lock;
1023 
1024 	cydebug = 1;
1025 	if(cyseek(request, cq)) {
1026 		if(ui->cleanup != cyno_op) {
1027 			clrbuf(request);
1028 			longjmp(&ci->environ);
1029 		}
1030 		if(request->b_bcount > ci->bs)
1031 			command = READ_TA, bus_lock = CW_LOCK;
1032 		else
1033 			command = READ_BU, bus_lock = 0;
1034 		ui->blkno++;
1035 		addr = vbastart(request, (caddr_t)ci->rawbuf, (long *)ci->map,
1036 		    ci->utl);
1037 		cyexecute(command,request->b_bcount,addr,bus_lock,unit,8,FALSE);
1038 		vbadone(request, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl);
1039 		cydone(cq);
1040 	}
1041 }
1042 
1043 
1044 /*
1045 **	cybuf_write handles the write requests from the block device.
1046 **
1047 **  The special cases are:
1048 **  1)  if we are mispositioned we have to seek to the correct block.
1049 **  2)  we can hit end of tape while seeking.
1050 **  3)  we want to be nice to other processes while seeking so we
1051 **  	break the request up into smaller requests.
1052 **  4) we don't allow writes after end of tape is reached.
1053 */
1054 
1055 cybuf_write(request, cq)
1056 register struct buf	*request;
1057 register struct buf	*cq;
1058 {
1059 	register int		unit = CYUNIT(request->b_dev);
1060 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
1061 	register int		ctlr = cydinfo[unit]->ui_ctlr;
1062 	register ctlr_tab	*ci = &ctlr_info[ctlr];
1063 	register int		addr, command, bus_lock;
1064 
1065 	if(ui->eot && (request->b_blkno >= ui->blkno)) {
1066 		request->b_error = ENXIO, request->b_flags |= B_ERROR;
1067 		request->b_resid = request->b_bcount;
1068 		longjmp(&ci->environ);
1069 	}
1070 	if(cyseek(request, cq)) {
1071 		ui->cleanup = cywrite_2_fm;
1072 		ui->blkno++;
1073 		if(request->b_bcount > ci->bs)
1074 			command = WRIT_TA, bus_lock = CW_LOCK;
1075 		else
1076 			command = WRIT_BU, bus_lock = 0;
1077 		addr = vbastart(request, (caddr_t)ci->rawbuf, (long *)ci->map,
1078 		    ci->utl);
1079 		load_mbus_addr((caddr_t)addr, (short *)&ci->tpb.data_ptr);
1080 		cyexecute(command,request->b_bcount,addr,bus_lock,unit,5,FALSE);
1081 		vbadone(request, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl);
1082 		cydone(cq);
1083 	}
1084 }
1085 
1086 
1087 /*
1088 **	cyseek is used by the block device to position the tape correctly
1089 **  before each read or write request.
1090 **
1091 **  The special cases are:
1092 **  1)  we can hit end of tape while seeking.
1093 **  2)  we want to be nice to other processes while seeking so we
1094 **  	break the request up into smaller requests.
1095 */
1096 cyseek(request, cq)
1097 register struct buf	*request;
1098 register struct buf	*cq;
1099 {
1100 	register int		unit = CYUNIT(request->b_dev);
1101 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
1102 	register int		ctlr = cydinfo[unit]->ui_ctlr;
1103 	register ctlr_tab	*ci = &ctlr_info[ctlr];
1104 
1105 #ifdef lint
1106 	cq = cq;
1107 #endif
1108 	if(request->b_blkno < ui->blkno) {
1109 		register int	count;
1110 
1111 		(*ui->cleanup)(unit, MAINTAIN_POSITION);
1112 		count = ((request->b_blkno+1) == ui->blkno) ? 2 : 1;
1113 		ui->blkno -= count;
1114 		cyexecute(SPAC_FM, (long)1, 0, CW_REV, unit, 10, FALSE);
1115 		if(!ui->eof)
1116 			return FALSE;
1117 		ui->eof = FALSE;
1118 		request->b_blkno = ui->blkno + 1;
1119 	}
1120 	if(request->b_blkno > ui->blkno) {
1121 		if((ui->cleanup != cyno_op) || ui->eof || ui->eot) {
1122 			request->b_resid = request->b_bcount;
1123 			request->b_error = ENXIO, request->b_flags |= B_ERROR;
1124 			longjmp(&ci->environ);
1125 		}
1126 		ui->blkno++;
1127 		cyexecute(SPAC_FM, (long)1, 0, 0, unit, 10, FALSE);
1128 		return FALSE;
1129 	}
1130 	return TRUE;
1131 }
1132 
1133 
1134 /*
1135 */
1136 
1137 cywrite_eov(request, cq)
1138 register struct buf	*request;
1139 register struct buf	*cq;
1140 {
1141 	extern int		cyno_op();
1142 	register int		unit = CYUNIT(request->b_dev);
1143 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
1144 
1145 	if(ui->cleanup != cyno_op) {
1146 		(*ui->cleanup)(unit, DONT_MAINTAIN_POSITION);
1147 		cyexecute(SPACE, (long)2, 0, CW_REV, unit, 10, FALSE);
1148 		cyexecute(SPACE, (long)1, 0, 0, unit, 10, FALSE);
1149 		unit_info[unit].cleanup = cyno_op;
1150 		ui->blkno = 0;
1151 	}
1152 	cydone(cq);
1153 }
1154 
1155 
1156 /*
1157 **	Do nothing
1158 */
1159 /*ARGSUSED*/
1160 cyno_op(unit, action)
1161 int	unit, action;
1162 {
1163 }
1164 
1165 
1166 /*
1167 **	Write 0 file marks to tape
1168 */
1169 /*ARGSUSED*/
1170 cywrite_0_fm(unit, action)
1171 int	unit, action;
1172 {
1173 	unit_info[unit].cleanup = cyno_op;
1174 }
1175 
1176 
1177 /*
1178 **	Write 1 file mark to tape
1179 */
1180 
1181 cywrite_1_fm(unit, action)
1182 int	unit, action;
1183 {
1184 
1185 	cyexecute(WRIT_FM, (long)1, 0, 0, unit, 5, FALSE);
1186 	if(action == MAINTAIN_POSITION) {
1187 		cyexecute(SPACE, (long)2, 0, CW_REV, unit, 10, FALSE);
1188 		cyexecute(SPACE, (long)1, 0, 0, unit, 10, FALSE);
1189 	}
1190 	unit_info[unit].cleanup = cyno_op;
1191 }
1192 
1193 
1194 /*
1195 **	Write 2 file marks to tape
1196 */
1197 
1198 cywrite_2_fm(unit, action)
1199 int	unit, action;
1200 {
1201 
1202 	cyexecute(WRIT_FM, (long)1, 0, 0, unit, 5, FALSE);
1203 	cyexecute(WRIT_FM, (long)1, 0, 0, unit, 5, FALSE);
1204 	if(action == MAINTAIN_POSITION) {
1205 		cyexecute(SPACE, (long)3, 0, CW_REV, unit, 10, FALSE);
1206 		cyexecute(SPACE, (long)1, 0, 0, unit, 2, FALSE);
1207 	}
1208 	unit_info[unit].cleanup = cyno_op;
1209 }
1210 
1211 
1212 extern	int cytimeout();
1213 extern	int cy_normal_path();
1214 /*
1215 **	Cyexecute is used to start all commands to the controller.  We
1216 **  do all common code here before starting.
1217 */
1218 
1219 cyexecute(command, count, addr, control_flags, unit, time, interupt_routine)
1220 	register int command;
1221 	long count;
1222 	int addr, control_flags, unit, time, interupt_routine;
1223 {
1224 	register int		priority;
1225 	register int		ctlr = cydinfo[unit]->ui_ctlr;
1226 	register unit_tab	*ui = &unit_info[unit];
1227 	register ctlr_tab	*ci = &ctlr_info[ctlr];
1228 	register struct buf	*request = ui->u_queue.av_forw;
1229 
1230 	ci->tpb.cmd = command;
1231 	ci->tpb.control = ui->control_proto | control_flags;
1232 	ci->tpb.status = ci->tpb.count = (short)0;
1233 	load_mbus_addr((caddr_t)addr, (short *)&ci->tpb.data_ptr);
1234 	switch(command) {
1235 		case READ_BU:
1236 		case READ_TA:
1237 		case WRIT_BU:
1238 		case WRIT_TA:
1239 			ci->tpb.size = MULTIBUS_SHORT((short)count);
1240 			ci->tpb.rec_over = (short)0;
1241 			break;
1242 		default:
1243 			ci->tpb.size = (short)0;
1244 			ci->tpb.rec_over = MULTIBUS_SHORT((short)count);
1245 			break;
1246 	}
1247 	load_mbus_addr((caddr_t)0, ci->tpb.link_ptr);
1248 	if(!interupt_routine)
1249 		ci->last = ci->tpb;
1250 	/*
1251 	gag! but it the last possible moment to wait
1252 	for this controller to get out of it's own way.....
1253 	*/
1254 	uncache(&ci->ccb.gate);
1255 	while(ci->ccb.gate == GATE_CLOSED)
1256 		uncache(&ci->ccb.gate);
1257 	load_mbus_addr((caddr_t)&ci->tpb, ci->ccb.tpb_ptr);
1258 	ci->ccb.ccw = NORMAL_INTERUPT;
1259 	ci->ccb.gate = GATE_CLOSED;
1260 	if(!interupt_routine)
1261 		ci->interupt_path = cy_normal_path;
1262 	timeout(cytimeout, (caddr_t)ctlr, time*60);
1263 	priority = spl3();
1264 	CY_ATTENTION(cyminfo[ctlr]->um_addr);
1265 	if(!interupt_routine) {
1266 		sleep((caddr_t)ci, PRIBIO+3);
1267 		splx(priority);
1268 		if(request->b_flags & B_ERROR) {
1269 			if((command == READ_BU) || (command == READ_TA) ||
1270 			    (command == WRIT_BU) || (command == WRIT_TA))
1271 				vbadone(request, (caddr_t)ci->rawbuf,
1272 				     (long *)ci->map,ci->utl);
1273 			longjmp(&ci->environ);
1274 		}
1275 		return;
1276 	}
1277 	splx(priority);
1278 }
1279 
1280 
1281 /*
1282 **	cytimeout is the interupt timeout routine.  We assume that a
1283 **  particular command has gone astray, so we completely reset the controller,
1284 **  and call the interupt routine to help us clean up.  Before the interupt
1285 **  routine is called we jam a controller timeout value in the status register
1286 **  to fake out the calling routines.
1287 */
1288 
1289 cytimeout(ctlr)
1290 register int	ctlr;
1291 {
1292 	register int	priority = spl3();
1293 	register char	*ctlr_vaddr = cyminfo[ctlr]->um_addr;
1294 	register int	tmp_stat;
1295 
1296 	uncache(&ctlr_info[ctlr].tpb.status);
1297 	tmp_stat = ctlr_info[ctlr].tpb.status;
1298 	CY_RESET(ctlr_vaddr);
1299 	cy_init_controller(ctlr_vaddr, ctlr, 0);
1300 	splx(priority);
1301 	ctlr_info[ctlr].tpb = ctlr_info[ctlr].last;
1302 	ctlr_info[ctlr].tpb.status = (tmp_stat & ~CS_ERm) | CS_OL | ER_TIMOUT;
1303 	cyintr(ctlr);
1304 }
1305 
1306 /*
1307 **	Cyintr is the interupt routine for the Tapemaster controller.
1308 **
1309 **	Due to controller problems, the first thing we have to do is turn
1310 **  off the Tapemaster interupting mechanism.  If we don't we will be flooded
1311 **  with bogus interupts and the system will spend all it's time processing
1312 **  them.  To Turn the interupts off we issue a NOOP command with the 'turn
1313 **  off interupts' code in the ccb.
1314 **
1315 **	  take note that since this command TURNS OFF the interupts it
1316 **	  itself CANNOT interupt...  This means that polling must be done
1317 **	  at sometime to make sure that tis command is completed.  The polling
1318 **	  is done before the next command is issued to reduce polling (halting
1319 **	  UNIX) time.
1320 **
1321 **	After we turn off interupts we uncache all the values in the tpb
1322 **  and call the correct processing routine.  This routine can be for normal
1323 **  interupts or for interupts generated during a retry operation.
1324 */
1325 
1326 cyintr(ctlr)
1327 register int ctlr;
1328 {
1329 	extern int		cytimeout();
1330 	register ctlr_tab	*ci = &ctlr_info[ctlr];
1331 
1332 	untimeout(cytimeout, (caddr_t)ctlr);
1333 	/* turn off interupts for the stupid controller */
1334 	ci->ccb.ccw = CLEAR_INTERUPT;
1335 	ci->noop.cmd = NO_OP;
1336 	ci->noop.control = (short)0;
1337 	load_mbus_addr((caddr_t)&ci->noop, ci->ccb.tpb_ptr);
1338 	ci->ccb.gate = GATE_CLOSED;
1339 	CY_ATTENTION(cyminfo[ctlr]->um_addr);
1340 	uncache_tpb(ci);
1341 	(*ci->interupt_path)(ctlr);
1342 }
1343 
1344 
1345 /*
1346 **	This is the portion of the interupt routine that processes all
1347 **  normal cases i.e. non retry cases.   We check the operations status
1348 **  if it is retryable we set the interupt path to the retry routines and
1349 **  start the backward spaceing.  when the spacing is done the retry logic
1350 **  will be called and this routine will be skipped entirely.
1351 **
1352 **	If the command is ok or not retryable we set the status accordingly
1353 **  and wakeup cyexecute to continue processing.
1354 */
1355 
1356 cy_normal_path(ctlr)
1357 register int ctlr;
1358 {
1359 	extern int		cy_retry_path();
1360 	extern int		cy_extended_gap_path();
1361 	register int		error;
1362 	register struct buf	*cq = &cyminfo[ctlr]->um_tab;
1363 	register struct buf	*uq = cq->b_forw;
1364 	register struct buf	*request = uq->av_forw;
1365 	register int		unit = CYUNIT(request->b_dev);
1366 	register unit_tab	*ui = &unit_info[unit];
1367 	register ctlr_tab	*ci = &ctlr_info[ctlr];
1368 
1369 	if (error = cydecode_error(unit, ci->tpb.status)) {
1370 		if(error != FATAL) {
1371 			if (error == RETRY)
1372 				ci->interupt_path = cy_retry_path;
1373 			else
1374 				ci->interupt_path = cy_extended_gap_path;
1375 			cyexecute(SPACE, (long)2, 0, CW_REV, unit, 5, TRUE);
1376 			return;
1377 		}
1378 	}
1379 	request->b_resid=request->b_bcount-MULTIBUS_SHORT(ci->tpb.count);
1380 	ui->error_count = 0;
1381 	ui->last_resid = request->b_resid;
1382 	ui->last_status = ci->tpb.status;
1383 	ui->last_control = ci->tpb.control;
1384 	if (error == FATAL)
1385 		request->b_flags |= B_ERROR, request->b_error = EIO;
1386 	wakeup((caddr_t)ci);
1387 }
1388 
1389 
1390 /*
1391 **	Cy_retry_path finishes up the retry sequence for the tape.
1392 ** If we were going in the reverse direction it means that we have to
1393 ** space forward to correctly position ourselfs in back of the tape gap
1394 ** instead of in front of it.  If we were going forward it means that
1395 ** we are positioned correctly and we can actually restart the instruction
1396 ** that failed before.
1397 */
1398 
1399 cy_retry_path(ctlr)
1400 register int	ctlr;
1401 {
1402 	extern int		cy_do_again_path();
1403 	register struct buf	*cq = &cyminfo[ctlr]->um_tab;
1404 	register struct buf	*uq = cq->b_forw;
1405 	register struct buf	*request = uq->av_forw;
1406 	register int		unit = CYUNIT(request->b_dev);
1407 	register ctlr_tab	*ci = &ctlr_info[ctlr];
1408 
1409 	if(!(ci->tpb.status & CS_OL)) {
1410 		ci->interupt_path = cy_normal_path;
1411 		cy_normal_path(ctlr);
1412 		return;
1413 	}
1414 	if(ci->tpb.control & CW_REV) {
1415 		if(!(ci->tpb.status & CS_LP)) {
1416 			ci->interupt_path = cy_do_again_path;
1417 			cyexecute(SPACE, (long)1, 0, 0, unit, 5, TRUE);
1418 			return;
1419 		}
1420 		cy_do_again_path(ctlr);
1421 	}
1422 }
1423 
1424 
1425 /*
1426 **
1427 */
1428 
1429 cy_extended_gap_path(ctlr)
1430 register int	ctlr;
1431 {
1432 	extern int		cy_do_again_path();
1433 	register ctlr_tab	*ci = &ctlr_info[ctlr];
1434 	register struct buf	*cq = &cyminfo[ctlr]->um_tab;
1435 	register struct buf	*uq = cq->b_forw;
1436 	register struct buf	*request = uq->av_forw;
1437 	register int		unit = CYUNIT(request->b_dev);
1438 
1439 	if(!(ci->tpb.status & CS_OL)) {
1440 		ci->interupt_path = cy_normal_path;
1441 		cy_normal_path(ctlr);
1442 		return;
1443 	}
1444 	if(ci->tpb.control & CW_REV) {
1445 		if(!(ci->tpb.status & CS_LP)) {
1446 			cyexecute(SPACE, (long)1, 0, 0, unit, 5, TRUE);
1447 			return;
1448 		}
1449 	}
1450 	ci->interupt_path = cy_do_again_path;
1451 	cyexecute(ERASE_F, (long)unit_info[unit].error_count, 0, 0,
1452 	    unit, 5, TRUE);
1453 }
1454 
1455 
1456 /*
1457 **
1458 */
1459 
1460 cy_do_again_path(ctlr)
1461 register int	ctlr;
1462 {
1463 	extern int		cy_normal_path();
1464 	register ctlr_tab	*ci = &ctlr_info[ctlr];
1465 
1466 	if(!(ci->tpb.status & CS_OL)) {
1467 		ci->interupt_path = cy_normal_path;
1468 		cy_normal_path(ctlr);
1469 		return;
1470 	}
1471 	ci->tpb = ci->last;
1472 	uncache(&ci->ccb.gate);
1473 	while(ci->ccb.gate == GATE_CLOSED)
1474 		uncache(&ci->ccb.gate);
1475 	load_mbus_addr((caddr_t)&ci->tpb, ci->ccb.tpb_ptr);
1476 	ci->ccb.ccw = NORMAL_INTERUPT;
1477 	ci->ccb.gate = GATE_CLOSED;
1478 	ci->interupt_path = cy_normal_path;
1479 	CY_ATTENTION(cyminfo[ctlr]->um_addr);
1480 }
1481 
1482 
1483 /*
1484 **	for each longword in the tpb we call uncache to  purge it from
1485 **  the cache.  This is done so that we can correctly access tpb data
1486 **  that was placed there by the controller.
1487 */
1488 
1489 uncache_tpb(ci)
1490 ctlr_tab	*ci;
1491 {
1492 	register long	*ptr = (long *)&ci->tpb;
1493 	register int	i;
1494 
1495 	for(i=0; i<((sizeof(fmt_tpb)+sizeof(long)-1)/sizeof(long)); i++)
1496 		uncache(ptr++);
1497 }
1498 
1499 
1500 /*
1501 **	Cyprint_error is the common printing routine for all messages
1502 **  that need to print the tape status along with it.  This is so we
1503 **  we can save space, have consistant messages, and we can send the messages
1504 **  to the correct places.
1505 */
1506 
1507 cyprint_err(message, unit, status)
1508 register char	*message;
1509 register int	unit, status;
1510 {
1511 	status &= 0xffff;
1512 	printf("cy%d: %s!   Status = %x\n", unit, message, status);
1513 }
1514 
1515 /*
1516 **	Decode the error to determine whether the previous command was
1517 **  ok, retryable, or fatal and return the value.  If it was a hardware
1518 **  problem we print the message to the console, otherwise we print it
1519 **  to the user's terminal later when execute returns.
1520 */
1521 
1522 cydecode_error(unit, status)
1523 register int	unit,	status;
1524 {
1525 	register unit_tab	*ui = &unit_info[unit];
1526 	register ctlr_tab	*ci = &ctlr_info[cydinfo[unit]->ui_ctlr];
1527 
1528 	if(!(status & CS_OL) && (ci->tpb.cmd != OFF_UNL)) {
1529 		ui->message = "Drive is not on-line";
1530 		cyprint_err(ui->message, unit, status);
1531 		return FATAL;
1532 	}
1533 	ui->bot = ((status & CS_LP) != 0);
1534 	ui->eof = ((status & CS_FM) != 0);
1535 	switch(status & CS_ERm) {
1536 	case ER_EOT:
1537 		if(ci->tpb.control & CW_REV) {
1538 			ui->bot = TRUE;
1539 			ui->eot = FALSE;
1540 		}
1541 		else if(!ui->eot){
1542 			ui->message = "End of tape";
1543 			ui->bot = FALSE;
1544 			ui->eot = TRUE;
1545 		}
1546 	case 0 :
1547 	case ER_FM:
1548 	case ER_NOSTRM:
1549 		return	0;
1550 	case ER_TIMOUT:
1551 	case ER_TIMOUT1:
1552 	case ER_TIMOUT2:
1553 	case ER_TIMOUT3:
1554 	case ER_TIMOUT4:
1555 		ui->message = "Drive timed out during transfer";
1556 		cyprint_err(ui->message, unit, status);
1557 		return FATAL;
1558 	case ER_NEX:
1559 		ui->message =
1560 		    "Controller referenced non-existant system memory";
1561 		cyprint_err(ui->message, unit, status);
1562 		return FATAL;
1563 	case ER_DIAG:
1564 	case ER_JUMPER:
1565 		ui->message = "Controller diagnostics failed";
1566 		cyprint_err(ui->message, unit, status);
1567 		return FATAL;
1568 	case ER_STROBE:
1569 		if (ci->tpb.cmd == READ_BU) {
1570 			ci->last.cmd = READ_TA;
1571 			return RETRY;
1572 		}
1573 		if(ci->tpb.cmd == READ_TA)
1574 			return 0;
1575 		ui->message = "Unsatisfactory media found";
1576 		return	FATAL;
1577 	case ER_FIFO:
1578 	case ER_NOTRDY:
1579 		ui->error_count = 1;
1580 		return RETRY;
1581 	case ER_PROT:
1582 		ui->message = "Tape is write protected";
1583 		return FATAL;
1584 	case ER_CHKSUM:
1585 		ui->message = "Checksum error in controller proms";
1586 		cyprint_err(ui->message, unit, status);
1587 		return FATAL;
1588 	case ER_HARD:
1589 		ui->error_count++;
1590 		if((ci->tpb.cmd == WRIT_TA) ||
1591 		    (ci->tpb.cmd == WRIT_BU) ||
1592 		    (ci->tpb.cmd == WRIT_FM)) {
1593 			ui->bad_count++;
1594 			return EXTEND;
1595 		}
1596 		ui->message = "Unrecoverable media error during read";
1597 		return FATAL;
1598 	case ER_PARITY:
1599 		if(++ui->error_count < 8)
1600 			return	RETRY;
1601 		ui->message = "Unrecoverable tape parity error";
1602 		return FATAL;
1603 	case ER_BLANK:
1604 		ui->message="Blank tape found (data expected)";
1605 		return FATAL;
1606 	case ER_HDWERR:
1607 	default:
1608 		ui->message = "Unrecoverble hardware error";
1609 		cyprint_err(ui->message, unit, status);
1610 		return FATAL;
1611 	}
1612 }
1613 
1614 cyread(dev, uio)
1615 	dev_t dev;
1616 	struct uio *uio;
1617 {
1618 	unit_tab *ui = &unit_info[CYUNIT(dev)];
1619 
1620 	return (physio(cystrategy, &ui->rawbp, dev, B_READ, cyminsize, uio));
1621 }
1622 
1623 
1624 cywrite(dev, uio)
1625 	dev_t dev;
1626 	struct uio *uio;
1627 {
1628 	unit_tab *ui = &unit_info[CYUNIT(dev)];
1629 
1630 	return (physio(cystrategy,&ui->rawbp, dev, B_WRITE, cyminsize, uio));
1631 }
1632 
1633 /*ARGSUSED*/
1634 cyioctl(dev, cmd, data, flag)
1635 	dev_t dev;
1636 	caddr_t data;
1637 {
1638 
1639 	switch (cmd) {
1640 
1641 	case MTIOCTOP: {
1642 		struct mtop *mp = (struct mtop *)data;
1643 
1644 		if (mp->mt_op <= DO_WAIT)
1645 			return (cycmd(dev, (int)mp->mt_op, (int)mp->mt_count));
1646 		return (EIO);
1647 	}
1648 
1649 	case MTIOCGET: {
1650 		register unit_tab *ui = &unit_info[CYUNIT(dev)];
1651 		register struct mtget *mp = (struct mtget *)data;
1652 
1653 		mp->mt_type = MT_ISCY;
1654 		mp->mt_dsreg = ui->last_control;
1655 		mp->mt_erreg = ui->last_status;
1656 		mp->mt_resid = ui->last_resid;
1657 		mp->mt_fileno = ui->file_number;
1658 		mp->mt_blkno = ui->blkno;
1659 		cycmd(dev, DO_STAT, 1);
1660 		break;
1661 	}
1662 
1663 	default:
1664 		return (ENXIO);
1665 	}
1666 	return (0);
1667 }
1668 
1669 /*
1670  * Dump routine.
1671  */
1672 cydump(dev)
1673 	dev_t dev;
1674 {
1675 	register int		unit = CYUNIT(dev);
1676 	register int		ctlr = cydinfo[unit]->ui_ctlr;
1677 	register unit_tab	*ui = &unit_info[unit];
1678 	register ctlr_tab	*ci = &ctlr_info[ctlr];
1679 	register int		blk_siz;
1680 	register int		num = maxfree;
1681 	register int		start = 0x800;
1682 
1683 	if ((unit >= NCY) || cydinfo[unit])
1684 		return(ENXIO);
1685 	ui->control_proto = CW_LOCK | CW_25ips | CW_16bits;
1686 	if (cywait(&ci->ccb))
1687 		return(EFAULT);
1688 	while (num > 0) {
1689 		blk_siz = num > TBUFSIZ ? TBUFSIZ : num;
1690 		bcopy((caddr_t)(start*NBPG), (caddr_t)ci->rawbuf,
1691 		    (unsigned)(blk_siz*NBPG));
1692 		ci->tpb.cmd = WRIT_TA;
1693 		ci->tpb.control = ui->control_proto;
1694 		ci->tpb.status = 0;
1695 		ci->tpb.size = MULTIBUS_SHORT(blk_siz*NBPG);
1696 		load_mbus_addr((caddr_t)0, ci->tpb.link_ptr);
1697 		load_mbus_addr((caddr_t)ci->rawbuf, (short *)&ci->tpb.data_ptr);
1698 		load_mbus_addr((caddr_t)&ci->tpb, ci->ccb.tpb_ptr);
1699 		ci->ccb.gate = GATE_CLOSED;
1700 		CY_ATTENTION(cyminfo[ctlr]->um_addr);
1701 		start += blk_siz;
1702 		num -= blk_siz;
1703 		if (cywait(&ci->ccb))
1704 			return(EFAULT);
1705 		uncache(&ci->tpb);
1706 		if (ci->tpb.status&CS_ERm)		/* error */
1707 			return (EIO);
1708 	}
1709 	for(num=0; num<2; num++) {
1710 		ci->tpb.cmd = WRIT_FM;
1711 		ci->tpb.control = ui->control_proto;
1712 		ci->tpb.status = ci->tpb.size = 0;
1713 		ci->tpb.count = MULTIBUS_SHORT(1);
1714 		load_mbus_addr((caddr_t)0, ci->tpb.link_ptr);
1715 		load_mbus_addr((caddr_t)ci->rawbuf, (short *)&ci->tpb.data_ptr);
1716 		load_mbus_addr((caddr_t)&ci->tpb, ci->ccb.tpb_ptr);
1717 		ci->ccb.gate = GATE_CLOSED;
1718 		CY_ATTENTION(cyminfo[ctlr]->um_addr);
1719 		if (cywait(&ci->ccb))
1720 			return(EFAULT);
1721 		uncache(&ci->tpb);
1722 		if (ci->tpb.status&CS_ERm)		/* error */
1723 			return (EIO);
1724 	}
1725 	ci->tpb.cmd = REWD_OV;
1726 	ci->tpb.control = ui->control_proto;
1727 	ci->tpb.status = ci->tpb.size = 0;
1728 	ci->tpb.count = MULTIBUS_SHORT(1);
1729 	load_mbus_addr((caddr_t)0, ci->tpb.link_ptr);
1730 	load_mbus_addr((caddr_t)ci->rawbuf, (short *)&ci->tpb.data_ptr);
1731 	load_mbus_addr((caddr_t)&ci->tpb, ci->ccb.tpb_ptr);
1732 	ci->ccb.gate = GATE_CLOSED;
1733 	CY_ATTENTION(cyminfo[ctlr]->um_addr);
1734 	if (cywait(&ci->ccb))
1735 		return EFAULT;
1736 	uncache(&ci->tpb);
1737 	return 0;
1738 }
1739 
1740 /*
1741  * Poll until the controller is ready.
1742  */
1743 cywait(cp)
1744 	register fmt_ccb *cp;
1745 {
1746 	register int i = 5000;
1747 
1748 	uncache(&cp->gate);
1749 	while (i-- > 0 && cp->gate == GATE_CLOSED) {
1750 		DELAY(1000);
1751 		uncache(&cp->gate);
1752 	}
1753 	return (i <= 0);
1754 }
1755 
1756 /*
1757  * Load a 20 bit pointer into the i/o registers.
1758  */
1759 load_mbus_addr(in, out)
1760 	caddr_t in;
1761 	short *out;
1762 {
1763 	register int tmp_in = (int)in;
1764 	register char *out_ptr = (char *)out;
1765 
1766 	*out_ptr++ = (char)(tmp_in & 0xff);
1767 	*out_ptr++ = (char)((tmp_in >> 8) & 0xff);
1768 	*out_ptr++ = (char)0;
1769 	*out_ptr++ = (char)((tmp_in & 0xf0000) >> 12);
1770 }
1771 
1772 /*
1773 **	CYMINSIZE s supposed to adjust the buffer size for any raw i/o.
1774 **  since tapes can not read  the tail end of partial blocks we ignore
1775 **  this request and strategy will return an appropriate error message later.
1776 **
1777 **	If this is not done UNIX will lose data that is on the tape.
1778 */
1779 unsigned
1780 cyminsize(bp)
1781 	struct buf *bp;
1782 {
1783 	if (bp->b_bcount > MAX_BLOCKSIZE)
1784 		bp->b_bcount = MAX_BLOCKSIZE;
1785 }
1786 
1787 /*
1788  * Unconditionally reset all controllers to their initial state.
1789  */
1790 cyreset(vba)
1791 	int vba;
1792 {
1793 	register caddr_t addr;
1794 	register int ctlr;
1795 
1796 	for (ctlr = 0; ctlr < NCY; ctlr++)
1797 		if (cyminfo[ctlr] && cyminfo[ctlr]->um_vbanum == vba) {
1798 			addr = cyminfo[ctlr]->um_addr;
1799 			CY_RESET(addr);
1800 			if (!cy_init_controller(addr, ctlr, 0)) {
1801 				printf("cy%d: reset failed\n", ctlr);
1802 				cyminfo[ctlr] = NULL;
1803 			}
1804 		}
1805 }
1806 #endif
1807