get rid of unused queue() and dequeue() (from sun!shannon)
[unix-history] / usr / src / sys / tahoe / vba / cy.c
CommitLineData
3590c922
SL
1/* cy.c 1.1 85/07/21 */
2/* cy.c Tahoe version Mar 1983. */
3
4#include "cy.h"
5#if NCY > 0 /* number of CYPHER tapes in system */
6/*
7 * Cypher tape driver
8 *
9 */
10#include "../h/param.h"
11#include "../h/systm.h"
12#include "../h/vm.h"
13#include "../h/buf.h"
14#include "../h/dir.h"
15#include "../h/conf.h"
16#include "../h/user.h"
17#include "../h/file.h"
18#include "../machine/pte.h"
19#include "../vba/vbavar.h"
20#include "../h/mtio.h"
21#include "../machine/mtpr.h"
22#include "../h/ioctl.h"
23#include "../h/cmap.h"
24#include "../h/uio.h"
25
26#include "../vba/cyvar.h"
27
28#define NTM 1 /* number of TAPEMASTER controllers */
29
30/*
31 * There is a ccybuf per tape controller.
32 * It is used as the token to pass to the control routines
33 * and also acts as a lock on the slaves on the
34 * controller, since there is only one per controller.
35 * In particular, when the tape is rewinding on close we release
36 * the user process but any further attempts to use the tape drive
37 * before the rewind completes will hang waiting for ccybuf.
38 */
39struct buf ccybuf[NTM];
40
41/*
42 * Raw tape operations use rcybuf. The driver
43 * notices when rcybuf is being used and allows the user
44 * program to continue after errors and read records
45 * not of the standard length (BSIZE).
46 */
47struct buf rcybuf[NTM];
48long cybufused = 0;
49
50/*
51 * Driver interface routines and variables.
52 */
53int cyprobe(), cyslave(), cyattach(), cydgo(), cyintr();
54int cywait(), cyrewind();
55unsigned tminphys();
56struct vba_ctlr *cyminfo[NTM];
57struct vba_device *cydinfo[NCY];
58struct buf cyutab[NCY];
59short cytotm[NCY];
60extern char cyutl[];
61long cystd[] = { 0x400000, 0 };
62struct vba_driver cydriver =
63 { cyprobe, cyslave, cyattach, cydgo, cystd, "yc", cydinfo, "cy",
64 cyminfo, 0 };
65
66/* bits in minor device */
67#define CYUNIT(dev) (minor(dev)&07) /* tape unit number */
68#define TMUNIT(dev) (cytotm[CYUNIT(dev)]) /* tape controller number */
69#define T_NOREWIND 0x08 /* no rewind bit */
70#define T_100IPS 0x10 /* high speed flag */
71
72int pflag; /* probe flag, set every interrupt by cyintr */
73
74#define INF (daddr_t)1000000L
75extern int hz;
76
77struct scp /* SYSTEM CONFIGUREATION POINTER */
78{
79 char sysbus ; /* width of system buss 0=8;1=16 */
80 char nu1 ;
81 char pt_scb[4] ; /* pointer to ->SYSTEM CONFIGUREATION BLOCK */
82};
83
84/* absolute address - jumpered on the controller */
85#define SCP ((struct scp *)0xc0000c06)
86
87struct Scb /* SYSTEM CONFIGUREATION BLOCK */
88{
89 char sysblk[1] ; /* 0x03 fixed value code */
90 char nu2[1] ;
91 char pt_ccb[4] ; /* pointer to ->CHANNEL CONTROL BLOCK */
92}Scb;
93
94struct ccb /* CHANNEL CONTROL BLOCK */
95{
96 char ccw[1] ; /* 0x11 normal; 0x09 clear non_vect interrupt */
97 char gate[1] ; /* This is "the" GATE */
98 char pt_tpb[4] ; /* pointer to ->TAPE OPERATION BLOCK or MOVE BLOCK */
99}ccb;
100
101struct tpb /* TAPE OPERATIONS PARAMETER BLOCK */
102{
103 long cmd ; /* COMMAND (input) */
104 char control[2] ; /* CONTROL (input) */
105 short count ; /* RETURN COUNT (output) */
106 short size ; /* BUFFER SIZE (input/output) */
107 short rec_over ; /* RECORDS/OVERRUN (input/output) */
108 char pt_data[4] ; /* pointer to ->SOURCE/DEST (input) */
109 char status[2] ; /* STATUS (output) */
110 char pt_link[4] ; /* pointer to ->INTERRUPT/PARAMETER BLOCK (input) */
111} tpb[NTM];
112
113struct tpb cycool /* tape parameter block to clear interrupts */
114= {
115 0L, /* command */
116 0, 0, /* control */
117 0, /* count */
118 0, /* size */
119 0, /* rec_over */
120 0, 0, 0, 0, /* pt_data */
121 0, 0, /* status */
122 0, 0, 0, 0 /* pt_link */
123} ;
124/*
125 * Software state per tape transport.
126 *
127 * 1. A tape drive is a unique-open device; we refuse opens when it is already.
128 * 2. We keep track of the current position on a block tape and seek
129 * before operations by forward/back spacing if necessary.
130 * 3. We remember if the last operation was a write on a tape, so if a tape
131 * is open read write and the last thing done is a write we can
132 * write a standard end of tape mark (two eofs).
133 */
134struct cy_softc {
135 char cy_openf; /* lock against multiple opens */
136 char cy_lastiow; /* last op was a write */
137 daddr_t cy_blkno; /* block number, for block device tape */
138 daddr_t cy_nxrec; /* position of end of tape, if known */
139 daddr_t cy_timo; /* time until timeout expires */
140 short cy_tact; /* timeout is active */
141 short cy_count; /* return count of last operation */
142 char cy_status[2]; /* return status of last operation */
143} cy_softc[NTM];
144
145/*
146 * I/O buffer for raw devices.
147 */
148char cybuf[TBUFSIZ*NBPG]; /* 10k buffer */
149
150/*
151 * States for um->um_tab.b_active, the per controller state flag.
152 * This is used to sequence control in the driver.
153 */
154#define SSEEK 1 /* seeking */
155#define SIO 2 /* doing seq i/o */
156#define SCOM 3 /* sending control command */
157#define SREW 4 /* sending a drive rewind */
158
159/*
160 * Determine if there is a controller for
161 * a cypher at address ctlr_vaddr.
162 * Reset the controller.
163 * Our goal is to make the device interrupt.
164 */
165cyprobe(ctlr_vaddr)
166 caddr_t ctlr_vaddr;
167{
168 int *ip;
169
170 pflag = 0; /* clear interrupt flag */
171 if (badcyaddr(ctlr_vaddr + 1)) /* check for versabuss timeout */
172 return (0);
173 /*
174 * Initialize the system configuration pointer
175 */
176 ip = (int *)vtopte(0, btop(SCP)); *ip &= ~PG_PROT; *ip |= PG_KW;
177 mtpr(SCP, TBIS);
178 SCP->sysbus = 1; /* system width = 16 bits. */
179 /* initialize the pointer to the system configuration block */
180 set_pointer((int)&Scb.sysblk[0], (char *)SCP->pt_scb);
181 /*
182 * Initialize the system configuration block.
183 */
184 Scb.sysblk[0] = 0x3; /* fixed value */
185 /* initialize the pointer to the channel control block */
186 set_pointer((int)&ccb.ccw[0], (char *)Scb.pt_ccb);
187 /*
188 * Initialize the channel control block.
189 */
190 ccb.ccw[0] = 0x11; /* normal interrupts */
191 /* initialize the pointer to the tape parameter block */
192 set_pointer((int)&tpb[0], (char *)ccb.pt_tpb);
193 /*
194 * set the command to be CONFIGURE.
195 */
196 tpb[0].cmd = CONFIG;
197 tpb[0].control[0] = CW_I; /* interrupt on completion */
198 tpb[0].control[1] = CW_16bits;
199 ccb.gate[0] = GATE_CLOSED;
200 *ip &= ~PG_PROT; *ip |= PG_KR;
201 mtpr(SCP, TBIS);
202 TM_ATTENTION(ctlr_vaddr, 0xff); /* execute! */
203 if (cywait()) return(0);
204 else return(1);
205}
206
207/*
208 * Due to a design flaw, we cannot ascertain if the tape
209 * exists or not unless it is on line - ie: unless a tape is
210 * mounted. This is too severe a restriction to bear,
211 * so all units are assumed to exist.
212 */
213/*ARGSUSED*/
214cyslave(ui, ctlr_vaddr)
215 struct vba_device *ui;
216 caddr_t ctlr_vaddr;
217{
218
219 return (1);
220}
221
222/*
223 * Record attachment of the unit to the controller.
224 */
225/*ARGSUSED*/
226cyattach(ui)
227 struct vba_device *ui;
228{
229
230 /*
231 * Cytotm is used in TMUNIT to index the ccybuf and rcybuf
232 * arrays given a cy unit number.
233 */
234 cytotm[ui->ui_unit] = ui->ui_mi->um_ctlr;
235}
236
237int cytimer();
238/*
239 * Open the device. Tapes are unique open
240 * devices, so we refuse if it is already open.
241 * We also check that a tape is available, and
242 * don't block waiting here; if you want to wait
243 * for a tape you should timeout in user code.
244 */
245cyopen(dev, flag)
246 dev_t dev;
247 int flag;
248{
249 register int cyunit, s;
250 register struct vba_device *ui;
251 register struct cy_softc *cy;
252
253 cyunit = CYUNIT(dev);
254 if (cyunit>=NCY || (cy = &cy_softc[cyunit])->cy_openf ||
255 (ui = cydinfo[cyunit]) == 0 || ui->ui_alive == 0)
256 return ENXIO;
257 cycommand(dev, (int)DRIVE_S, 1); /* drive status */
258 uncache(&tpb[cyunit].status[0]);
259 if ((tpb[cyunit].status[0]&(CS_DR|CS_OL)) != (CS_DR|CS_OL)) {
260 uprintf("cy%d: not online\n", cyunit);
261 return EIO;
262 }
263 if ((flag&FWRITE) && (tpb[cyunit].status[0]&CS_P)) {
264 uprintf("cy%d: no write ring\n", cyunit);
265 return EIO;
266 }
267 cy->cy_openf = 1;
268 cy->cy_blkno = (daddr_t)0;
269 cy->cy_nxrec = INF;
270 cy->cy_lastiow = 0;
271 s = spl8();
272 if (cy->cy_tact == 0) {
273 cy->cy_timo = INF;
274 cy->cy_tact = 1;
275 timeout(cytimer, (caddr_t)dev, 5*hz);
276 }
277 splx(s);
278 return 0;
279}
280
281/*
282 * Close tape device.
283 *
284 * If tape was open for writing or last operation was
285 * a write, then write two EOF's and backspace over the last one.
286 * Unless this is a non-rewinding special file, rewind the tape.
287 * Make the tape available to others.
288 */
289cyclose(dev, flag)
290 register dev_t dev;
291 register flag;
292{
293 register struct cy_softc *cy = &cy_softc[CYUNIT(dev)];
294
295 if (flag == FWRITE || (flag&FWRITE) && cy->cy_lastiow) {
296 cycommand(dev, (int)WRIT_FM, 1); /* write file mark */
297 cycommand(dev, (int)WRIT_FM, 1);
298 cycommand(dev, (int)SP_BACK, 1); /* space back */
299 }
300 if ((minor(dev)&T_NOREWIND) == 0)
301 /*
302 * 0 count means don't hang waiting for rewind complete
303 * rather ccybuf stays busy until the operation completes
304 * preventing further opens from completing by
305 * preventing a SENSE operation from completing.
306 */
307 cycommand(dev, (int)REWD_TA, 0);
308 cy->cy_openf = 0;
309}
310
311int commflag; /* signal cystrategy that it is called from cycommand */
312
313/*
314 * Execute a command on the tape drive
315 * a specified number of times.
316 */
317cycommand(dev, com, count)
318 dev_t dev;
319 int com, count;
320{
321 register struct buf *bp;
322 int s;
323
324 bp = &ccybuf[TMUNIT(dev)];
325 s = spl8();
326 while (bp->b_flags&B_BUSY) {
327 /*
328 * This special check is because B_BUSY never
329 * gets cleared in the non-waiting rewind case.
330 */
331 if (bp->b_repcnt == 0 && (bp->b_flags&B_DONE))
332 break;
333 bp->b_flags |= B_WANTED;
334 sleep((caddr_t)bp, PRIBIO);
335 }
336 bp->b_flags = B_BUSY|B_READ;
337 splx(s);
338 bp->b_dev = dev;
339 bp->b_repcnt = count;
340 bp->b_command = com;
341 bp->b_blkno = 0;
342 commflag = 1;
343 cystrategy(bp);
344 commflag = 0;
345 /*
346 * In case of rewind from close, don't wait.
347 * This is the only case where count can be 0.
348 */
349 if (count == 0)
350 return;
351 iowait(bp);
352 if (bp->b_flags&B_WANTED)
353 wakeup((caddr_t)bp);
354 bp->b_flags &= B_ERROR;
355}
356
357/*
358 * Queue a tape operation.
359 */
360cystrategy(bp)
361 register struct buf *bp;
362{
363 int cyunit = CYUNIT(bp->b_dev);
364 int s;
365 register struct vba_ctlr *um;
366 register struct buf *dp;
367
368 /*
369 * Put transfer at end of unit queue
370 */
371 dp = &cyutab[cyunit];
372 bp->av_forw = NULL;
373 s = spl8();
374/*
375 * Next piece of logic takes care of unusual cases when more than
376 * a full block is required.
377 * The driver reads the tape to a temporary buffer and
378 * then moves the amount needed back to the process.
379 * In this case, the flag NOT1K is set.
380 */
381
382 if (commflag == 0)
383 buf_setup(bp, 1);
384 um = cydinfo[cyunit]->ui_mi;
385 if (dp->b_actf == NULL) {
386 dp->b_actf = bp;
387 /*
388 * Transport not already active...
389 * put at end of controller queue.
390 */
391 dp->b_forw = NULL;
392 if (um->um_tab.b_actf == NULL)
393 um->um_tab.b_actf = dp;
394 else
395 um->um_tab.b_actl->b_forw = dp;
396 um->um_tab.b_actl = dp;
397 } else
398 dp->b_actl->av_forw = bp;
399 dp->b_actl = bp;
400 /*
401 * If the controller is not busy, get
402 * it going.
403 */
404 if (um->um_tab.b_active == 0)
405 cystart(um);
406 splx(s);
407}
408
409/*
410 * Start activity on a cypher controller.
411 */
412cystart(um)
413 register struct vba_ctlr *um;
414{
415 register struct buf *bp, *dp;
416 register struct tpb *tp;
417 register struct cy_softc *cy;
418 register int phadr;
419 int cyunit, timer;
420 daddr_t blkno;
421 caddr_t ctlr_vaddr;
422 ctlr_vaddr = um->um_addr;
423 /*
424 * Look for an idle transport on the controller.
425 */
426loop:
427 if ((dp = um->um_tab.b_actf) == NULL)
428 return;
429 if ((bp = dp->b_actf) == NULL) {
430 um->um_tab.b_actf = dp->b_forw;
431 goto loop;
432 }
433 cyunit = CYUNIT(bp->b_dev);
434 cy = &cy_softc[cyunit];
435 tp = &tpb[cyunit];
436 /*
437 * Default is that last command was NOT a write command;
438 * if we do a write command we will notice this in cyintr().
439 */
440 cy->cy_lastiow = 0;
441 uncache(&tp->status[0]);
442 uncache(&tp->count);
443 cy->cy_count = TM_SHORT(tp->count);
444 cy->cy_status[0] = tp->status[0];
445 cy->cy_status[1] = tp->status[1];
446 if (cy->cy_openf < 0 ||
447 (bp->b_command != DRIVE_S) &&
448 ((tp->status[0]&CS_OL) != CS_OL)) {
449 /*
450 * Have had a hard error on a non-raw tape
451 * or the tape unit is now unavailable
452 * (e.g. taken off line).
453 */
454 bp->b_flags |= B_ERROR;
455 goto next;
456 }
457 if (bp == &ccybuf[TMUNIT(bp->b_dev)]) {
458 /*
459 * Execute control operation with the specified count.
460 * Set next state; give 5 minutes to complete
461 * rewind, or 10 seconds per iteration (minimum 60
462 * seconds and max 5 minutes) to complete other ops.
463 */
464 if (bp->b_command == REWD_TA) {
465 um->um_tab.b_active = SREW;
466 cy->cy_timo = 5 * 60;
467 } else {
468 um->um_tab.b_active = SCOM;
469 cy->cy_timo = imin(imax(10*(int)bp->b_repcnt, 60), 5*60);
470 }
471 /*
472 * Prepare parameter block for controller
473 */
474 tp->cmd = bp->b_command;
475 tp->control[0] = (CW_I | (cyunit<<CW_TSs));
476 if (minor(bp->b_dev)&T_100IPS)
477 tp->control[1] = (CW_100ips | CW_16bits);
478 else tp->control[1] = (CW_25ips | CW_16bits);
479 if (bp->b_command == SP_BACK) {
480 tp->control[1] |= CW_R;
481 tp->cmd = SPACE;
482 tp->rec_over = TM_SHORT((short)bp->b_repcnt);
483 }
484 if (bp->b_command == SP_FORW)
485 tp->rec_over = TM_SHORT((short)bp->b_repcnt);
486 if (bp->b_command == SRFM_BK) {
487 tp->control[1] |= CW_R;
488 tp->cmd = SERH_FM;
489 tp->rec_over = TM_SHORT((short)bp->b_repcnt);
490 }
491 if (bp->b_command == SRFM_FD)
492 tp->rec_over = TM_SHORT((short)bp->b_repcnt);
493 tp->status[0] = tp->status[1] = 0;
494 tp->count = 0;
495 set_pointer((int)&tpb[cyunit], (char *)ccb.pt_tpb);
496 goto dobpcmd;
497 }
498 /*
499 * The following checks handle boundary cases for operation
500 * on non-raw tapes. On raw tapes the initialization of
501 * cy->cy_nxrec by cyphys causes them to be skipped normally
502 */
503 if (bdbtofsb(bp->b_blkno) > cy->cy_nxrec) {
504 /*
505 * Can't read past known end-of-file.
506 */
507 bp->b_flags |= B_ERROR;
508 bp->b_error = ENXIO;
509 goto next;
510 }
511 if (bdbtofsb(bp->b_blkno) == cy->cy_nxrec &&
512 bp->b_flags&B_READ) {
513 /*
514 * Reading at end of file returns 0 bytes.
515 */
516 bp->b_resid = bp->b_bcount;
517 clrbuf(bp);
518 goto next;
519 }
520 if ((bp->b_flags&B_READ) == 0)
521 /*
522 * Writing sets EOF
523 */
524 cy->cy_nxrec = bdbtofsb(bp->b_blkno) + 1;
525 /*
526 * If the data transfer command is in the correct place,
527 * set up the tape parameter block, and start the i/o.
528 */
529 if ((blkno = cy->cy_blkno) == bdbtofsb(bp->b_blkno)) {
530 um->um_tab.b_active = SIO;
531 cy->cy_timo = 60; /* premature, but should serve */
532
533 phadr = get_ioadr(bp, cybuf, CYmap, cyutl);
534
535 if ( (bp->b_flags & B_READ) == 0)
536 tp->cmd = WRIT_BU;
537 else tp->cmd = READ_BU;
538 tp->control[0] = (CW_I | (cyunit<<CW_TSs));
539 if (minor(bp->b_dev)&T_100IPS)
540 tp->control[1] = (CW_100ips | CW_16bits);
541 else tp->control[1] = (CW_25ips | CW_16bits);
542 tp->status[0] = tp->status[1] = 0;
543 tp->count = 0;
544 tp->size = TM_SHORT(bp->b_bcount);
545 set_pointer(phadr, (char *)tp->pt_data);
546 set_pointer((int)&tpb[cyunit], (char *)ccb.pt_tpb);
547 goto dobpcmd;
548 }
549 /*
550 * Tape positioned incorrectly;
551 * set to seek forwards or backwards to the correct spot.
552 */
553 um->um_tab.b_active = SSEEK;
554 tp->cmd = SPACE;
555 tp->control[0] = (CW_I | (cyunit<<CW_TSs));
556 if (minor(bp->b_dev)&T_100IPS)
557 tp->control[1] = (CW_100ips | CW_16bits);
558 else tp->control[1] = (CW_25ips | CW_16bits);
559 tp->status[0] = tp->status[1] = 0;
560 set_pointer((int)&tpb[cyunit], (char *)ccb.pt_tpb);
561 if (blkno < bdbtofsb(bp->b_blkno))
562 tp->rec_over = TM_SHORT((short)(blkno - bdbtofsb(bp->b_blkno)));
563 else {
564 tp->rec_over = TM_SHORT((short)(bdbtofsb(bp->b_blkno) - blkno));
565 tp->control[1] |= CW_R;
566 }
567 cy->cy_timo = imin(imax(10 * (int)TM_SHORT(tp->rec_over), 60), 5 * 60);
568dobpcmd:
569 /*
570 * Do the command in bp.
571 */
572 timer = 8000; /* software tolerance for gate open */
573 uncache(&ccb.gate[0]);
574 while (ccb.gate[0] != GATE_OPEN) {
575 if (--timer == 0) {
576 ccb.ccw[0] = 0x9; /* forget it...... */
577 TM_RESET(ctlr_vaddr, 0xff);
578 bp->b_flags |= B_ERROR;
579 goto next;
580 }
581 uncache(&ccb.gate[0]);
582 }
583 ccb.ccw[0] = 0x11; /* normal mode */
584 ccb.gate[0] = GATE_CLOSED;
585 TM_ATTENTION(ctlr_vaddr, 0xff); /* execute! */
586 return;
587
588next:
589 /*
590 * Done with this operation due to error or
591 * the fact that it doesn't do anything.
592 * dequeue the transfer and continue processing this slave.
593 */
594 um->um_tab.b_errcnt = 0;
595 dp->b_actf = bp->av_forw;
596 iodone(bp);
597 goto loop;
598}
599
600/*
601 * Kept for historical reasons. Probably not neccessary.
602 */
603cydgo(um)
604 struct vba_ctlr *um;
605{
606}
607
608/*
609 * Cy interrupt routine.
610 */
611/*ARGSUSED*/
612cyintr(ctlr)
613 int ctlr;
614{
615 struct buf *dp;
616 register struct buf *bp;
617 register struct tpb *tp;
618 register struct vba_ctlr *um = cyminfo[ctlr];
619 register struct cy_softc *cy;
620 caddr_t ctlr_vaddr;
621 int cyunit;
622 register state;
623
624 /*
625 * First we clear the interrupt and close the gate.
626 */
627 ctlr_vaddr = um->um_addr;
628 ccb.ccw[0] = 0x9; /* clear the interrupt */
629 ccb.gate[0] = GATE_CLOSED;
630 set_pointer((int)&cycool, (char *)ccb.pt_tpb);
631 cycool.cmd = NO_OP; /* no operation */
632 cycool.control[0] = 0; /* No INTERRUPTS */
633 cycool.control[1] = 0;
634 TM_ATTENTION(ctlr_vaddr, 0xff); /* cool it ! */
635 cywait();
636 /*
637 * Now we can start handling the interrupt.
638 */
639 pflag = 1; /* set for the probe routine */
640 if (intenable == 0) return; /* ignore all interrupts */
641 if ((dp = um->um_tab.b_actf) == NULL)
642 return;
643 bp = dp->b_actf;
644 cyunit = CYUNIT(bp->b_dev);
645 tp = &tpb[cyunit];
646 cy = &cy_softc[cyunit];
647 /*
648 * If last command was a rewind, and tape is still
649 * rewinding, wait for the rewind complete interrupt.
650 */
651 if (um->um_tab.b_active == SREW) {
652 um->um_tab.b_active = SCOM;
653 /* uncache(&tp->status[1]); */
654 /* if (tp->status[1]&CS_CC != CS_CC) { */ /* not completed */
655 /* cy->cy_timo = 5*60; */ /* 5 minutes */
656 /* return; */
657 /* } */
658 }
659 /*
660 * An operation completed... update status
661 */
662 cy->cy_timo = INF;
663 uncache(&tp->count);
664 uncache(&tp->status[0]);
665 cy->cy_count = TM_SHORT(tp->count);
666 cy->cy_status[0] = tp->status[0];
667 cy->cy_status[1] = tp->status[1];
668 if ((bp->b_flags & B_READ) == 0)
669 cy->cy_lastiow = 1;
670 state = um->um_tab.b_active;
671 um->um_tab.b_active = 0;
672 /*
673 * Check for errors.
674 */
675 if (tp->status[1] & CS_ERm) {
676 /*
677 * If we hit the end of the tape file, update our position.
678 */
679 if (tp->status[0] & CS_FM)
680 {
681 cyseteof(bp); /* set blkno and nxrec */
682 state = SCOM;
683 goto opdone;
684 }
685 /* If reading raw device and block was too short ignore the
686 * error and let the user program decide what to do.
687 */
688 if ((tp->status[0] & ER_TOF) && /* (bp->b_flags & B_PHYS) && */
689 (bp->b_flags & B_READ)) goto cont;
690 cy->cy_openf = -1; /* cause to close */
691 printf("cy%d: hard error bn %d er=%x\n", cyunit,
692 bp->b_blkno, tp->status[1]&CS_ERm);
693 bp->b_flags |= B_ERROR;
694 goto opdone;
695 }
696 /*
697 * If we were reading block tape and the record
698 * was too long, we consider this an error.
699 */
700cont:
701 uncache(&tp->count);
702 uncache(&tp->cmd);
703 if (bp != &rcybuf[TMUNIT(bp->b_dev)] && (tp->cmd == READ_BU) &&
704 bp->b_bcount < TM_SHORT(tp->count)) {
705 cy->cy_openf = -1; /* cause to close */
706 printf("cy%d: error - tape block too long \n", cyunit);
707 bp->b_flags |= B_ERROR;
708 goto opdone;
709 }
710 /*
711 * No errors.
712 * Advance tape control FSM.
713 */
714 switch (state) {
715
716 case SIO:
717 /*
718 * Read/write increments tape block number
719 */
720 cy->cy_blkno++;
721 end_transfer(bp, cybuf, CYmap, cyutl);
722 goto opdone;
723
724 case SCOM:
725 /*
726 * For forward/backward space record update current position.
727 */
728 if (bp == &ccybuf[TMUNIT(bp->b_dev)])
729 switch (bp->b_command) {
730
731 case SP_FORW:
732 cy->cy_blkno += bp->b_repcnt;
733 break;
734
735 case SP_BACK:
736 cy->cy_blkno -= bp->b_repcnt;
737 break;
738 }
739 goto opdone;
740
741 case SSEEK:
742 cy->cy_blkno = bdbtofsb(bp->b_blkno);
743 goto opcont;
744
745 default:
746 panic("cyintr");
747 }
748opdone:
749 /*
750 * Reset error count and remove
751 * from device queue.
752 */
753 um->um_tab.b_errcnt = 0;
754 dp->b_actf = bp->av_forw;
755 uncache(&tp->count);
756 bp->b_resid = bp->b_bcount - TM_SHORT(tp->count);
757 iodone(bp);
758 /*
759 * Circulate slave to end of controller
760 * queue to give other slaves a chance.
761 */
762 um->um_tab.b_actf = dp->b_forw;
763 if (dp->b_actf) {
764 dp->b_forw = NULL;
765 if (um->um_tab.b_actf == NULL)
766 um->um_tab.b_actf = dp;
767 else
768 um->um_tab.b_actl->b_forw = dp;
769 um->um_tab.b_actl = dp;
770 }
771 if (um->um_tab.b_actf == 0)
772 return;
773opcont:
774 cystart(um);
775}
776
777cytimer(dev)
778 int dev;
779{
780 register struct cy_softc *cy = &cy_softc[CYUNIT(dev)];
781 int s;
782
783 if (cy->cy_timo != INF && (cy->cy_timo -= 5) < 0) {
784 printf("cy%d: lost interrupt\n", CYUNIT(dev));
785 cy->cy_timo = INF;
786 s = spl8();
787 cyintr(TMUNIT(dev));
788 splx(s);
789 return;
790 }
791 if (cy->cy_timo != INF ) timeout(cytimer, (caddr_t)dev, 5*hz);
792}
793
794cyseteof(bp)
795 register struct buf *bp;
796{
797 register int cyunit = CYUNIT(bp->b_dev);
798 register struct cy_softc *cy = &cy_softc[cyunit];
799 register struct tpb *tp;
800
801 tp = &tpb[cyunit];
802 uncache(&tp->rec_over);
803 if (bp == &ccybuf[TMUNIT(bp->b_dev)]) {
804 if (cy->cy_blkno > bdbtofsb(bp->b_blkno)) {
805 /* reversing */
806 cy->cy_nxrec = bdbtofsb(bp->b_blkno) - (int)TM_SHORT(tp->rec_over);
807 cy->cy_blkno = cy->cy_nxrec;
808 } else {
809 /* spacing forward */
810 cy->cy_blkno = bdbtofsb(bp->b_blkno) + (int)TM_SHORT(tp->rec_over);
811 cy->cy_nxrec = cy->cy_blkno - 1;
812 }
813 return;
814 }
815 /* eof on read */
816 cy->cy_nxrec = bdbtofsb(bp->b_blkno);
817}
818
819cyread(dev, uio)
820dev_t dev;
821struct uio *uio;
822{
823 register error;
824
825 error = cyphys(dev, uio);
826 if (error)
827 return error;
828 while (cybufused) sleep (&cybufused, PRIBIO+1);
829 cybufused = 1;
830 error = physio(cystrategy, &rcybuf[TMUNIT(dev)], dev, B_READ, tminphys, uio);
831 cybufused = 0;
832 wakeup (&cybufused);
833 return error;
834}
835
836cywrite(dev, uio)
837dev_t dev;
838struct uio *uio;
839{
840 register error;
841
842 error = cyphys(dev, uio);
843 if (error)
844 return error;
845 while (cybufused) sleep (&cybufused, PRIBIO+1);
846 cybufused = 1;
847 error = physio(cystrategy, &rcybuf[TMUNIT(dev)], dev, B_WRITE, tminphys, uio);
848 cybufused = 0;
849 wakeup (&cybufused);
850 return error;
851}
852
853
854cyreset(uban)
855 int uban;
856{
857 register struct vba_ctlr *um;
858 register cy0f, cyunit;
859 register struct vba_device *ui;
860 register struct buf *dp;
861
862 for (cy0f = 0; cy0f < NTM; cy0f++) {
863 if ((um = cyminfo[cy0f]) == 0 || um->um_alive == 0 ||
864 um->um_vbanum != uban)
865 continue;
866 printf(" cy%d", cy0f);
867 um->um_tab.b_active = 0;
868 um->um_tab.b_actf = um->um_tab.b_actl = 0;
869 for (cyunit = 0; cyunit < NCY; cyunit++) {
870 if ((ui = cydinfo[cyunit]) == 0 || ui->ui_mi != um ||
871 ui->ui_alive == 0)
872 continue;
873 dp = &cyutab[cyunit];
874 dp->b_active = 0;
875 dp->b_forw = 0;
876 dp->b_command = DRIVE_R;
877 if (um->um_tab.b_actf == NULL)
878 um->um_tab.b_actf = dp;
879 else
880 um->um_tab.b_actl->b_forw = dp;
881 um->um_tab.b_actl = dp;
882 if (cy_softc[cyunit].cy_openf > 0)
883 cy_softc[cyunit].cy_openf = -1;
884 }
885 cystart(um);
886 }
887}
888
889
890cyioctl(dev, cmd, data, flag)
891 caddr_t data;
892 dev_t dev;
893{
894 int cyunit = CYUNIT(dev);
895 register struct cy_softc *cy = &cy_softc[cyunit];
896 register struct buf *bp = &ccybuf[TMUNIT(dev)];
897 register callcount;
898 int fcount;
899 struct mtop *mtop;
900 struct mtget *mtget;
901 /* we depend of the values and order of the MT codes here */
902 static cyops[] =
903 {WRIT_FM, SRFM_FD, SRFM_BK, SP_FORW, SP_BACK, REWD_TA, OFF_UNL, NO_OP};
904
905 switch (cmd) {
906 case MTIOCTOP: /* tape operation */
907 mtop = (struct mtop *)data;
908 switch(mtop->mt_op) {
909 case MTWEOF:
910 callcount = mtop->mt_count;
911 fcount = 1;
912 break;
913 case MTFSF: case MTBSF:
914 callcount = mtop->mt_count;
915 fcount = INF;
916 break;
917 case MTFSR: case MTBSR:
918 callcount = 1;
919 fcount = mtop->mt_count;
920 break;
921 case MTREW: case MTOFFL: case MTNOP:
922 callcount = 1;
923 fcount = 1;
924 break;
925 default:
926 return ENXIO;
927 }
928 if (callcount <= 0 || fcount <= 0)
929 return EINVAL;
930 while (--callcount >= 0) {
931 cycommand(dev, cyops[mtop->mt_op], fcount);
932 if ((bp->b_flags&B_ERROR) || cy->cy_status[1]&CS_ERm)
933 break;
934 }
935 return geterror(bp);
936 case MTIOCGET:
937 mtget = (struct mtget *)data;
938 mtget->mt_dsreg = cy->cy_status[0];
939 mtget->mt_erreg = cy->cy_status[1];
940 mtget->mt_resid = cy->cy_count;
941 mtget->mt_type = MT_ISCY;
942 break;
943 default:
944 return ENXIO;
945 }
946 return 0;
947}
948
949
950
951/*
952 * Check that a raw device exists.
953 * If it does, set up cy_blkno and cy_nxrec
954 * so that the tape will appear positioned correctly.
955 */
956cyphys(dev, uio)
957dev_t dev;
958struct uio *uio;
959{
960 register int cyunit = CYUNIT(dev);
961 register daddr_t a;
962 register struct cy_softc *cy;
963 register struct vba_device *ui;
964
965 if (cyunit >= NCY || (ui=cydinfo[cyunit]) == 0 || ui->ui_alive == 0)
966 return ENXIO;
967 cy = &cy_softc[cyunit];
968 a = bdbtofsb(uio->uio_offset >> PGSHIFT);
969 cy->cy_blkno = a;
970 cy->cy_nxrec = a + 1;
971 return 0;
972}
973
974/*
975 * Set a TAPEMASTER pointer (first parameter), into the
976 * 4 bytes array pointed by the second parameter.
977 */
978set_pointer(pointer, dest)
979int pointer;
980char * dest;
981{
982 *dest++ = pointer & 0xff; /* low byte - offset */
983 *dest++ = (pointer >> 8) & 0xff; /* high byte - offset */
984 *dest++ = 0;
985 *dest = (pointer & 0xf0000) >> 12; /* base */
986}
987
988cydump(dev)
989dev_t dev;
990{
991 register struct vba_device *ui;
992 register struct tpb *tp;
993 int cyunit = CYUNIT(dev);
994 int blk, num;
995 int start;
996
997 start = 0x800;
998 num = maxfree;
999 tp = &tpb[cyunit];
1000 if (cyunit >= NCY || (ui=cydinfo[cyunit]) == 0 || ui->ui_alive == 0)
1001 return(ENXIO);
1002 if (cywait) return(EFAULT);
1003 while (num > 0) {
1004 blk = num > TBUFSIZ ? TBUFSIZ : num;
1005 bcopy(start*NBPG, cybuf, blk*NBPG);
1006 tp->cmd = WRIT_BU;
1007 tp->control[0] = cyunit<<CW_TSs;
1008 tp->control[1] = (CW_100ips | CW_16bits);
1009 tp->status[0] = tp->status[1] = 0;
1010 tp->size = TM_SHORT(blk*NBPG);
1011 set_pointer((int)cybuf, (char *)tp->pt_data);
1012 set_pointer((int)&tpb[cyunit], (char *)ccb.pt_tpb);
1013 ccb.gate[0] = GATE_CLOSED;
1014 TM_ATTENTION(cyaddr, 0xff); /* execute! */
1015 start += blk;
1016 num -= blk;
1017 if (cywait) return(EFAULT);
1018 uncache(&tp->status[1]);
1019 if (tp->status[1]&CS_ERm) /* error */
1020 return (EIO);
1021 }
1022 cyeof(tp, cyunit);
1023 if (cywait) return(EFAULT);
1024 cyeof(tp, cyunit);
1025 if (cywait) return(EFAULT);
1026 uncache(&tp->status[1]);
1027 if (tp->status[1]&CS_ERm) /* error */
1028 return (EIO);
1029 cyrewind(tp, cyunit);
1030 return (0);
1031}
1032
1033cywait()
1034{
1035 register cnt;
1036
1037 cnt = 5000; /* 5 seconds timeout */
1038 do {
1039 --cnt;
1040 DELAY(1000);
1041 uncache(&ccb.gate[0]);
1042 }
1043 while (cnt>0 && ccb.gate[0] == GATE_CLOSED);
1044 if (cnt == 0) return(1); /* timeout */
1045 else return(0);
1046}
1047
1048cyeof(tp, unit)
1049 register struct tpb *tp;
1050 int unit;
1051{
1052 tp->cmd = WRIT_FM;
1053 tp->control[0] = unit<<CW_TSs;
1054 tp->control[1] = (CW_100ips | CW_16bits);
1055 tp->status[0] = tp->status[1] = 0;
1056 tp->rec_over = TM_SHORT(1);
1057 set_pointer((int)&tpb[unit], (char *)ccb.pt_tpb);
1058 ccb.gate[0] = GATE_CLOSED;
1059 TM_ATTENTION(cyaddr, 0xff); /* execute! */
1060}
1061
1062
1063cyrewind(tp, unit)
1064 register struct tpb *tp;
1065 int unit;
1066{
1067 tp->cmd = REWD_TA;
1068 tp->control[0] = unit<<CW_TSs;
1069 tp->control[1] = (CW_100ips | CW_16bits);
1070 tp->status[0] = tp->status[1] = 0;
1071 set_pointer((int)&tpb[unit], (char *)ccb.pt_tpb);
1072 ccb.gate[0] = GATE_CLOSED;
1073 TM_ATTENTION(cyaddr, 0xff); /* execute! */
1074}
1075
1076unsigned
1077tminphys(bp)
1078register struct buf *bp;
1079{
1080
1081 if (bp->b_bcount > sizeof cybuf)
1082 bp->b_bcount = sizeof cybuf;
1083}
1084#endif