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