date and time created 86/07/20 11:25:59 by sam
[unix-history] / usr / src / sys / tahoe / vba / dr.c
CommitLineData
20340301
SL
1/* dr.c 1.1 86/07/20 */
2
3#include "dr.h"
4#if NDR > 0
5
6/* DRV11-W DMA interface driver.
7 */
8
9#include "../machine/mtpr.h"
10#include "../machine/pte.h"
11
12#include "param.h"
13#include "conf.h"
14#include "dir.h"
15#include "user.h"
16#include "proc.h"
17#include "map.h"
18#include "ioctl.h"
19#include "buf.h"
20#include "vm.h"
21#include "uio.h"
22
23#include "../tahoevba/vbavar.h"
24#include "../tahoevba/drreg.h"
25
26#define YES 1
27#define NO 0
28
29struct vba_device *drinfo[NDR];
30struct dr_aux dr_aux[NDR];
31
32caddr_t vtoph();
33unsigned drminphys();
34int drprobe(), drintr(), drattach(), drtime(), drrwtimo();
35int drstrategy();
36extern struct vba_device *drinfo[];
37static long drstd[] = { 0 };
38struct vba_driver drdriver =
39 { drprobe, 0, drattach, 0, drstd, "rs", drinfo };
40extern long hz;
41
42#define RSUNIT(dev) (minor(dev) & 7)
43#define SPL_UP spl5
44
45/* -------- Per-unit data -------- */
46
47extern struct dr_aux dr_aux[];
48
49struct rs_data {
50 struct buf rs_buf;
51 int rs_ubainfo;
52 short rs_debug;
53 short rs_busy;
54 short rs_tout;
55 short rs_uid;
56 short rs_isopen;
57 short rs_func;
58} rs_data[NDR];
59
60
61#ifdef DR_DEBUG
62long DR11 = 0;
63#endif
64
65drprobe(reg, vi)
66 caddr_t reg;
67 struct vba_device *vi;
68{
69 register int br, cvec; /* must be r12, r11 */
70 register struct rsdevice *dr;
71 register ushort status;
72
73 dr = (struct rsdevice *)reg;
74#ifdef notdef
75 dr->dr_intvec = --vi->ui_hd->vh_lastiv;
76#else
77 dr->dr_intvec = DRINTV+vi->ui_unit;
78#endif
79#ifdef DR_DEBUG
80 printf("dprobe: Set interrupt vector %lx and init\n",dr->dr_intvec);
81#endif
82 /* generate interrupt here for autoconfig */
83 dr->dr_cstat = MCLR; /* init board and device */
84 status = dr->dr_cstat; /* read initial status */
85#ifdef DR_DEBUG
86 printf("drprobe: Initial status %lx\n",status & 0xffff);
87#endif
88 br = 0x18, cvec = dr->dr_intvec; /* XXX */
89 return (sizeof (struct rsdevice)); /* DR11 exist */
90}
91
92/* ARGSUSED */
93drattach(ui)
94struct vba_device *ui;
95{
96 register struct dr_aux *rsd;
97
98 rsd = &dr_aux[ui->ui_unit];
99 rsd->dr_flags = DR_PRES; /* This dr11 is present */
100 rsd->dr_addr = (struct rsdevice *)ui->ui_addr; /* Save addr of this dr11 */
101 rsd->dr_istat = 0;
102 rsd->dr_bycnt = 0;
103 rsd->dr_cmd = 0;
104 rsd->currenttimo = 0;
105 return;
106}
107
108dropen (dev, flag)
109dev_t dev;
110int flag;
111{
112 register int unit = RSUNIT(dev);
113 register struct rsdevice *dr;
114 register struct dr_aux *rsd;
115
116 if ((drinfo[unit] == 0) || (!drinfo[unit]->ui_alive))
117 return ENXIO;
118
119 dr = RSADDR(unit);
120 rsd = &dr_aux[unit];
121 if (rsd->dr_flags & DR_OPEN) {
122#ifdef DR_DEBUG
123 printf("\ndropen: dr11 unit %ld already open",unit);
124#endif
125 return ENXIO; /* DR11 already open */
126 }
127 rsd->dr_flags |= DR_OPEN; /* Mark it OPEN */
128 rsd->dr_istat = 0; /* Clear status of previous interrupt */
129 rsd->rtimoticks = hz; /* Set read no stall timout to 1 sec */
130 rsd->wtimoticks = hz*60; /* Set write no stall timout to 1 min */
131 dr->dr_cstat = DR_ZERO; /* Clear function & latches */
132 dr->dr_pulse = (RDMA | RATN); /* clear leftover attn & e-o-r flags */
133 drtimo(dev); /* start the self kicker */
134 return 0;
135}
136
137drclose (dev)
138dev_t dev;
139{
140 register int unit = RSUNIT(dev);
141 register struct dr_aux *dra;
142 register struct rsdevice *rs;
143 register short s;
144
145 dra = &dr_aux[unit];
146 if (!(dra->dr_flags & DR_OPEN)) {
147#ifdef DR_DEBUG
148 printf("\ndrclose: DR11 device %ld not open",unit);
149#endif
150 return;
151 }
152 dra->dr_flags &= ~(DR_OPEN|DR_ACTV);
153 rs = dra->dr_addr;
154 s=SPL_UP();
155 rs->dr_cstat = DR_ZERO;
156 if (dra->dr_buf.b_flags & B_BUSY) {
157 dra->dr_buf.b_flags &= ~B_BUSY;
158 wakeup(&dra->dr_buf.b_flags);
159 }
160 splx(s);
161 return;
162}
163
164
165/* drread() works exactly like drwrite() except that the
166 B_READ flag is used when physio() is called
167*/
168drread (dev, uio)
169dev_t dev;
170struct uio *uio;
171{ register struct dr_aux *dra;
172 register struct buf *bp;
173 register long spl, err;
174 register int unit = RSUNIT(dev);
175
176 if ( uio->uio_iov->iov_len <= 0 /* Negative count */
177 || uio->uio_iov->iov_len & 1 /* odd count */
178 || (int)uio->uio_iov->iov_base & 1 /* odd destination address */
179 )
180 return EINVAL;
181
182#ifdef DR_DEBUG
183 if (DR11 & 8) {
184 printf("\ndrread: (len:%ld)(base:%lx)",
185 uio->uio_iov->iov_len,(int)uio->uio_iov->iov_base);
186 }
187#endif
188
189 dra = &dr_aux[RSUNIT(dev)];
190 dra->dr_op = DR_READ;
191 bp = &dra->dr_buf;
192 bp->b_resid = 0;
193 if (dra->dr_flags & DR_NORSTALL) {
194 /* We are in no stall mode, start the timer, raise IPL so nothing
195 can stop us once the timer's running */
196 spl = SPL_UP();
197 timeout(drrwtimo,(caddr_t)((dra->currenttimo<<8) | unit),
198 dra->rtimoticks);
199 err = physio (drstrategy, bp, dev,B_READ, drminphys, uio);
200 splx(spl);
201 if (err)
202 return(err);
203 dra->currenttimo++; /* Update current timeout number */
204 /* Did we timeout */
205 if (dra->dr_flags & DR_TMDM) {
206 dra->dr_flags &= ~DR_TMDM; /* Clear timeout flag */
207 u.u_error = 0; /* Made the error ourself, ignore it */
208 }
209 }
210 else {
211 return physio (drstrategy, bp, dev,B_READ, drminphys, uio);
212 }
213}
214
215drwrite (dev, uio)
216dev_t dev;
217struct uio *uio;
218{ register struct dr_aux *dra;
219 register struct buf *bp;
220 register int unit = RSUNIT(dev);
221 register long spl, err;
222
223 if ( uio->uio_iov->iov_len <= 0
224 || uio->uio_iov->iov_len & 1
225 || (int)uio->uio_iov->iov_base & 1
226 )
227 return EINVAL;
228
229#ifdef DR_DEBUG
230 if (DR11 & 4) {
231 printf("\ndrwrite: (len:%ld)(base:%lx)",
232 uio->uio_iov->iov_len,(int)uio->uio_iov->iov_base);
233 }
234#endif
235
236 dra = &dr_aux[RSUNIT(dev)];
237 dra->dr_op = DR_WRITE;
238 bp = &dra->dr_buf;
239 bp->b_resid = 0;
240 if (dra->dr_flags & DR_NOWSTALL) {
241 /* We are in no stall mode, start the timer, raise IPL so nothing
242 can stop us once the timer's running */
243 spl = SPL_UP();
244 timeout(drrwtimo,(caddr_t)((dra->currenttimo<<8) | unit),
245 dra->wtimoticks);
246 err = physio (drstrategy, bp, dev,B_WRITE, drminphys, uio);
247 splx(spl);
248 if (err)
249 return(err);
250 dra->currenttimo++; /* Update current timeout number */
251 /* Did we timeout */
252 if (dra->dr_flags & DR_TMDM) {
253 dra->dr_flags &= ~DR_TMDM; /* Clear timeout flag */
254 u.u_error = 0; /* Made the error ourself, ignore it */
255 }
256 }
257 else {
258 return physio (drstrategy, bp, dev,B_WRITE, drminphys, uio);
259 }
260}
261
262/* Routine used by calling program to issue commands to dr11 driver and
263 through it to the device.
264 It is also used to read status from the device and driver and to wait
265 for attention interrupts.
266 Status is returned in an 8 elements unsigned short integer array, the
267 first two elements of the array are also used to pass arguments to
268 drioctl() if required.
269 The function bits to be written to the dr11 are included in the cmd
270 argument. Even if they are not being written to the dr11 in a particular
271 drioctl() call, they will update the copy of cmd that is stored in the
272 driver. When drstrategy() is called, this updated copy is used if a
273 deferred function bit write has been specified. The "side effect" of
274 calls to the drioctl() requires that the last call prior to a read or
275 write has an appropriate copy of the function bits in cmd if they are
276 to be used in drstrategy().
277 When used as command value, the contents of data[0] is the command
278 parameter.
279*/
280
281drioctl(dev, cmd, data, flag)
282dev_t dev;
283int cmd;
284long *data;
285int flag;
286{
287 register int unit = RSUNIT(dev);
288 register struct dr_aux *dra;
289 register struct rsdevice *rsaddr = RSADDR(unit);
290 struct dr11io dio;
291 ushort s, errcode, status;
292 long temp;
293
294#ifdef DR_DEBUG
295 if (DR11 & 0x10)
296 printf("\ndrioctl: (dev:%lx)(cmd:%lx)(data:%lx)(data[0]:%lx)",
297 dev,cmd,data,data[0]);
298#endif
299
300 dra = &dr_aux[unit];
301 dra->dr_cmd = 0; /* Fresh copy; clear all previous flags */
302
303 switch (cmd) {
304
305 case DRWAIT:
306 /* Wait for attention interrupt */
307#ifdef DR_DEBUG
308 printf("\ndrioctl: wait for attention interrupt");
309#endif
310 s = SPL_UP();
311 /* If the attention flag in dr_flags is set, it probably means that
312 an attention has arrived by the time a previous DMA end-of-range
313 interrupt was serviced. If ATRX is set, we will return with out
314 sleeping, since we have received an attention since the last call
315 to wait on attention.
316 This may not be appropriate for some applications.
317 */
318 if (!(dra->dr_flags & DR_ATRX)) {
319 dra->dr_flags |= DR_ATWT; /* Set waiting flag */
320 rsaddr->dr_pulse = IENB; /* Enable interrupt; use pulse
321 reg. so function bits are
322 not changed */
323 sleep((caddr_t)&dra->dr_cmd,DRPRI);
324 }
325 splx(s);
326 break;
327
328 case DRPIOW:
329 /* Write to p-i/o register */
330 rsaddr->dr_data = data[0];
331 break;
332
333 case DRPACL:
334 /* Send pulse to device */
335 rsaddr->dr_pulse = FCN2;
336 break;
337
338 case DRDACL:
339 /* Defer alco pulse until go */
340 dra->dr_cmd |= DR_DACL;
341 break;
342
343 case DRPCYL:
344 /* Set cycle with next go */
345 dra->dr_cmd |= DR_PCYL;
346 break;
347
348 case DRDFCN:
349 /* Do not update function bits until next go issued */
350 dra->dr_cmd |= DR_DFCN;
351 break;
352
353 case DRRATN:
354 /* Reset attention flag -- use with extreme caution */
355 rsaddr->dr_pulse = RATN;
356 break;
357
358 case DRRDMA:
359 /* Reset DMA e-o-r flag -- should never used */
360 rsaddr->dr_pulse = RDMA;
361 break;
362
363 case DRSFCN:
364 /* Set function bits */
365 temp = data[0] & DR_FMSK;
366 rsaddr->dr_cstat = temp; /* Write to control register */
367 /* This has a very important side effect -- It clears the interrupt
368 enable flag. That is fine for this driver, but if it is desired
369 to leave interrupt enable at all times, it will be necessary to
370 to read the status register first to get IENB, or carry a software
371 flag that indicates whether interrupts are set, and or this into
372 the controll register value being written.
373 */
374 break;
375
376 case DRRPER:
377 /* Clear parity flag */
378 rsaddr->dr_pulse = RPER;
379 break;
380
381 case DRSETRSTALL:
382 /* Set read stall mode. */
383 dra->dr_flags &= (~DR_NORSTALL);
384 break;
385
386 case DRSETNORSTALL:
387 /* Set no stall read mode. */
388 dra->dr_flags |= DR_NORSTALL;
389 break;
390
391 case DRGETRSTALL:
392 /* Returns true if in read stall mode. */
393 data[0] = (dra->dr_flags & DR_NORSTALL)? 0 : 1;
394 break;
395
396 case DRSETRTIMEOUT:
397 /* Set the number of ticks before a no stall read times out.
398 The argument is given in tenths of a second. */
399 if (data[0] < 1) {
400 u.u_error = EINVAL;
401 temp = 1;
402 }
403 dra->rtimoticks = (data[0] * hz )/10;
404 break;
405
406 case DRGETRTIMEOUT:
407 /* Returns the number of tenths of seconds before
408 a no stall read times out. */
409 /* The argument is given in tenths of a second. */
410 data[0] = ((dra->rtimoticks)*10)/hz;
411 break;
412
413 case DRSETWSTALL:
414 /* Set write stall mode. */
415 dra->dr_flags &= (~DR_NOWSTALL);
416 break;
417
418 case DRSETNOWSTALL:
419 /* Set write stall mode. */
420 dra->dr_flags |= DR_NOWSTALL;
421 break;
422
423 case DRGETWSTALL:
424 /* Returns true if in write stall mode. */
425 data[0] = (dra->dr_flags & DR_NOWSTALL)? 0 : 1;
426 break;
427
428 case DRSETWTIMEOUT:
429 /* Set the number of ticks before a no stall write times out.
430 The argument is given in tenths of a second. */
431 if (data[0] < 1) {
432 u.u_error = EINVAL;
433 temp = 1;
434 }
435 dra->wtimoticks = (data[0] * hz )/10;
436 break;
437
438 case DRGETWTIMEOUT:
439 /* Returns the number of tenths of seconds before
440 a no stall write times out. */
441 /* The argument is given in tenths of a second. */
442 data[0] = ((dra->wtimoticks)*10)/hz;
443 break;
444
445 case DRWRITEREADY:
446 /* Returns a value of 1 if the device can accept
447 data, 0 otherwise. Internally this is the
448 DR11-W STAT A bit. */
449
450 data[0] = (rsaddr->dr_cstat & STTA)? 1 : 0;
451 break;
452
453 case DRREADREADY:
454 /* Returns a value of 1 if the device has data
455 for host to be read, 0 otherwise. Internally
456 this is the DR11-W STAT B bit. */
457 data[0] = (rsaddr->dr_cstat & STTB)? 1 : 0;
458 break;
459
460 case DRBUSY:
461 /* Returns a value of 1 if the device is busy,
462 0 otherwise. Internally this is the DR11-W
463 STAT C bit, but there is a bug in the Omega 500/FIFO interface
464 board that it cannot drive this signal low for certain DR11-W
465 ctlr such as the Ikon. We use the REDY signal of the CSR on
466 the Ikon DR11-W instead.
467
468 data[0] = (rsaddr->dr_cstat & STTC)? 1 : 0;
469 */
470
471 data[0] = ((rsaddr->dr_cstat & REDY)? 0 : 1);
472 break;
473
474 case DRRESET:
475 rsaddr->dr_pulse = (MCLR|RDMA|RATN|RPER);/* Reset DMA ATN RPER flag */
476 DELAY(0x1f000);
477 while (!(rsaddr->dr_cstat & REDY)) {
478 sleep((caddr_t)dra, DRPRI); /* Wakeup by drtimo() */
479 }
480 dra->dr_istat = 0;
481 dra->dr_cmd = 0;
482 dra->currenttimo = 0;
483 break;
484
485 default:
486 printf("\ndrioctl: Invalid ioctl cmd : %lx",cmd);
487 return EINVAL;
488 }
489
490#ifdef DR_DEBUG
491 if (DR11 & 0x10)
492 printf("**** (data[0]:%lx)",data[0]);
493#endif
494 return 0;
495}
496
497/* Reset state on Unibus reset */
498drreset(uban)
499int uban;
500{
501 register int i;
502 register struct vba_device *ui;
503 register struct dr_aux *dra;
504
505 for (i = 0; i < NDR; i++, dra++) {
506 if ( (ui = drinfo[i]) == 0
507 || !ui->ui_alive
508 || ui->ui_vbanum != uban
509 )
510 continue;
511 printf("\ndrreset: %ld",i);
512 /* Do something; reset board */
513 }
514 return;
515}
516
517/*
518 * An interrupt is caused either by an error,
519 * base address overflow, or transfer complete
520 */
521drintr (unit)
522register long unit;
523{
524 register struct dr_aux *dra = &dr_aux[unit];
525 register struct rsdevice *rsaddr = RSADDR(unit);
526 register struct buf *bp;
527 register short status, csrtmp;
528
529 status = rsaddr->dr_cstat & 0xffff; /* get board status register */
530 dra->dr_istat = status;
531
532#ifdef DR_DEBUG
533 if (DR11 & 2)
534 printf("\ndrintr: dr11 status : %lx",status & 0xffff);
535#endif
536
537 if (dra->dr_flags & DR_LOOPTST) {
538 /* Controller is doing loopback test */
539 dra->dr_flags &= ~DR_LOOPTST;
540 return;
541 }
542
543 /* Make sure this is not a stray interrupt; at least one of dmaf or attf
544 must be set. Note that if the dr11 interrupt enable latch is reset
545 during a hardware interrupt ack sequence, and by the we get to this
546 point in the interrupt code it will be 0. This is done to give the
547 programmer some control over how the two more-or-less independent
548 interrupt sources on the board are handled.
549 If the attention flag is set when drstrategy() is called to start a
550 dma read or write an interrupt will be generated as soon as the
551 strategy routine enables interrupts for dma end-of-range. This will
552 cause execution of the interrupt routine (not necessarily bad) and
553 will cause the interrupt enable mask to be reset (very bad since the
554 dma end-of-range condition will not be able to generate an interrupt
555 when it occurs) causing the dma operation to time-out (even though
556 the dma transfer will be done successfully) or hang the process if a
557 software time-out capability is not implemented. One way to avoid
558 this situation is to check for a pending attention interrupt (attf
559 set) by calling drioctl() before doing a read or a write. For the
560 time being this driver will solve the problem by clearing the attf
561 flag in the status register before enabling interrupts in drstrategy().
562
563 **** The IKON 10084 for which this driver is written will set both
564 attf and dmaf if dma is terminated by an attention pulse. This will
565 cause a wakeup(&dr_aux), which will be ignored since it is not being
566 waited on, and an iodone(bp) which is the desired action. Some other
567 dr11 emulators, in particular the IKON 10077 for the Multibus, donot
568 dmaf in this case. This may require some addtional code in the inter-
569 rupt routine to ensure that en iodone(bp) is issued when dma is term-
570 inated by attention.
571 */
572
573 bp = dra->dr_actf;
574 if (!(status & (ATTF | DMAF))) {
575 printf("\ndrintr: Stray interrupt, dr11 status : %lx",status);
576 return;
577 }
578 if (status & DMAF) {
579 /* End-of-range interrupt */
580 dra->dr_flags |= DR_DMAX;
581
582#ifdef DR_DEBUG
583 if (DR11 & 2)
584 printf("\ndrintr: e-o-r interrupt,cstat:%lx,dr_flags:%lx",
585 status&0xffff,dra->dr_flags & DR_ACTV);
586#endif
587 if (!(dra->dr_flags & DR_ACTV)) {
588 /* We are not doing DMA !! */
589 bp->b_flags |= B_ERROR;
590 }
591 else {
592 if (dra->dr_op == DR_READ) mtpr(bp->b_un.b_addr,P1DC);
593 dra->dr_bycnt -= bp->b_bcount;
594 if (dra->dr_bycnt >0) {
595 bp->b_un.b_addr += bp->b_bcount;
596 bp->b_bcount = (dra->dr_bycnt > NBPG) ? NBPG:
597 dra->dr_bycnt;
598 drstart(rsaddr,dra,bp);
599 return;
600 }
601 }
602 dra->dr_flags &= ~DR_ACTV;
603 wakeup(dra); /* Wakeup proc waiting in drwait() */
604 rsaddr->dr_pulse = (RPER|RDMA|RATN); /* reset dma e-o-r flag */
605 }
606
607 /* Now test for attention interrupt -- It may be set in addition to
608 the dma e-o-r interrupt. If we get one we will issue a wakeup to
609 the drioctl() routine which is presumable waiting for one.
610 The program may have to monitor the attention interrupt received
611 flag in addition to doing waits for the interrupt. Futhermore,
612 interrupts are not enabled unless dma is in progress or drioctl()
613 has been called to wait for attention -- this may produce some
614 strange results if attf is set on the dr11 when a read or a write
615 is initiated, since that will enables interrupts.
616 **** The appropriate code for this interrupt routine will probably
617 be rather application dependent.
618 */
619
620 if (status & ATTF) {
621 dra->dr_flags |= DR_ATRX;
622 dra->dr_flags &= ~DR_ATWT;
623 rsaddr->dr_cstat = RATN; /* reset attention flag */
624 wakeup((caddr_t)&dra->dr_cmd);
625 /* Some applications which use attention to terminate dma may also
626 want to issue an iodone() here to wakeup physio().
627 */
628 }
629 return;
630}
631
632unsigned
633drminphys(bp)
634struct buf *bp;
635{
636 if (bp->b_bcount > 65536)
637 bp->b_bcount = 65536;
638}
639
640/*
641 * This routine performs the device unique operations on the DR11W
642 * it is passed as an argument to and invoked by physio
643 */
644drstrategy (bp)
645register struct buf *bp;
646{
647 register int s;
648 int unit = RSUNIT(bp->b_dev);
649 register struct rsdevice *rsaddr = RSADDR(unit);
650 register struct dr_aux *dra = &dr_aux[unit];
651 register short go = 0;
652 register long baddr, ok;
653#ifdef DR_DEBUG
654 register char *caddr;
655 long drva();
656#endif
657
658
659 if (!(dra->dr_flags & DR_OPEN)) {
660 /* Device not open */
661 bp->b_error = ENXIO;
662 bp->b_flags |= B_ERROR;
663 iodone (bp);
664 return;
665 }
666
667 while (dra->dr_flags & DR_ACTV) {
668 /* Device is active; should never be in here... */
669 sleep((caddr_t)&dra->dr_flags,DRPRI);
670 }
671
672 dra->dr_actf = bp;
673
674#ifdef DR_DEBUG
675 drva(dra,bp->b_proc,bp->b_un.b_addr,bp->b_bcount);
676#endif
677
678 dra->dr_oba = bp->b_un.b_addr; /* Save original addr, count */
679 dra->dr_obc = bp->b_bcount;
680 dra->dr_bycnt = bp->b_bcount; /* Save xfer count used by drintr() */
681
682 if ((((long)bp->b_un.b_addr & 0x3fffffff) >> PGSHIFT) !=
683 ((((long)bp->b_un.b_addr & 0x3fffffff) + bp->b_bcount) >> PGSHIFT)) {
684 bp->b_bcount = NBPG - (((long)bp->b_un.b_addr) & PGOFSET);
685 }
686
687 dra->dr_flags |= DR_ACTV; /* Mark it active (use in intr handler) */
688 s = SPL_UP();
689 drstart(rsaddr,dra,bp);
690 splx(s);
691
692 ok = drwait(rsaddr,dra);
693#ifdef DR_DEBUG
694 if (DR11 & 0x40) {
695 caddr = (char *)dra->dr_oba;
696 if (dra->dr_op == DR_READ)
697 printf("\nAfter read: (%lx)(%lx)",caddr[0]&0xff,caddr[1]&0xff);
698 }
699#endif
700 dra->dr_flags &= ~DR_ACTV; /* Clear active flag */
701 bp->b_un.b_addr = dra->dr_oba; /* Restore original addr, count */
702 bp->b_bcount = dra->dr_obc;
703
704 if (!ok) bp->b_flags |= B_ERROR;
705 iodone(bp); /* Mark buffer B_DONE,so physstrat()
706 in ml/machdep.c won't sleep */
707 wakeup((caddr_t)&dra->dr_flags);
708
709 /* Return to the calling program (physio()). Physio() will sleep
710 until awaken by a call to iodone() in the interupt handler --
711 which will be called by the dispatcher when it receives dma
712 end-of-range interrupt.
713 */
714 return;
715}
716
717drwait(rs,dr)
718register struct rsdevice *rs;
719register struct dr_aux *dr;
720{
721 register long status, s;
722
723 s = SPL_UP();
724 while (dr->dr_flags & DR_ACTV)
725 sleep((caddr_t)dr,DRPRI);
726 splx(s);
727
728 if (dr->dr_flags & DR_TMDM) {
729 /* DMA timed out */
730 dr->dr_flags &= ~DR_TMDM;
731 return(0);
732 }
733 else {
734 if (rs->dr_cstat & (PERR|BERR|TERR)) {
735 (dr->dr_actf)->b_flags |= B_ERROR;
736 return(0);
737 }
738 }
739 dr->dr_flags &= ~DR_DMAX;
740 return(1);
741}
742
743
744drrwtimo(tinfo)
745register unsigned long tinfo;
746/*
747 * The lower 8-bit of tinfo is the minor device number, the
748 * remaining higher 8-bit is the current timout number
749*/
750{ register long unit = tinfo & 0xff;
751 register struct dr_aux *dr = &dr_aux[unit];
752 register struct rsdevice *rs = dr->dr_addr;
753
754 /* If this is not the timeout that drwrite/drread is waiting
755 for then we should just go away */
756 if ((tinfo & (~0xff)) != (dr->currenttimo << 8)) return;
757
758 /* Mark the device timed out */
759 dr->dr_flags |= DR_TMDM;
760 dr->dr_flags &= ~DR_ACTV;
761 rs->dr_pulse = RMSK; /* Inihibit interrupt */
762 rs->dr_pulse = (RPER|RDMA|RATN|IENB); /* Clear DMA logic */
763
764 /* Some applications will not issue a master after dma timeout,
765 since doing so sends an INIT H pulse to the external device,
766 which may produce undesirable side-effects. */
767
768 /* Wake up process waiting in drwait() and flag the error */
769 (dr->dr_actf)->b_flags |= B_ERROR;
770 wakeup((caddr_t)dr->dr_cmd);
771}
772
773
774/*
775 * Kick the driver every second
776*/
777drtimo(dev)
778dev_t dev;
779{
780 register int unit = RSUNIT(dev);
781 register struct dr_aux *dr;
782
783 dr = &dr_aux[unit];
784 if (dr->dr_flags & DR_OPEN)
785 timeout(drtimo,(caddr_t)dev,hz);
786 wakeup((caddr_t)dr); /* Wakeup any process waiting for interrupt */
787}
788
789
790#ifdef DR_DEBUG
791
792drva(dra,p,va,bcnt)
793struct dr_aux *dra;
794struct proc *p;
795char *va;
796long bcnt;
797{ register long first, last , np;
798
799 if (DR11 & 0x20) {
800 first = ((long)(vtoph(p,va))) >> 10;
801 last = ((long)(vtoph(p,va+bcnt))) >> 10;
802 np = bcnt / 0x3ff;
803 printf("\ndrva: (op:%ld)(first:%ld)(last:%ld)(np:%ld)(cnt:%ld)",
804 dra->dr_op,first,last,np,bcnt);
805 }
806}
807#endif
808
809
810drstart(rsaddr,dra,bp)
811register struct rsdevice *rsaddr;
812register struct dr_aux *dra;
813register struct buf *bp;
814{ register long baddr;
815 ushort go;
816 register char *caddr;
817
818#ifdef DR_DEBUG
819 if ((dra->dr_op == DR_READ) && (DR11 & 8)) {
820 printf("\ndrstart: READ, bcnt:%ld",bp->b_bcount);
821 caddr = (char *)bp->b_un.b_addr;
822 printf(",(%lx)(%lx)",caddr[0]&0xff,caddr[1]&0xff);
823 }
824#endif
825 /* we are doing raw IO, bp->b_un.b_addr is user's address */
826 baddr = (long)vtoph(bp->b_proc,(caddr_t)bp->b_un.b_addr);
827
828 /* Set DMA address into DR11 interace registers: DR11 requires that
829 the address be right shifted 1 bit position before it is written
830 to the board (The board will left shift it one bit position before
831 it places the address on the bus
832 */
833 rsaddr->dr_walo = (ushort)((baddr >> 1) & 0xffff);
834 rsaddr->dr_wahi = (ushort)((baddr >> 17) & 0x7fff);
835
836 /* Set DMA range count: (number of words - 1) */
837 rsaddr->dr_range = (ushort)((bp->b_bcount >> 1) - 1);
838
839 /* Set address modifier code to be used for DMA access to memory */
840 rsaddr->dr_addmod = (char)DRADDMOD;
841
842 /* Now determine whether this is a read or a write. ***** This is
843 probably only usefull for link mode operation, since dr11 doesnot
844 controll the direction of data transfer. The C1 control input
845 controls whether the hardware is doing a read or a write. In link
846 mode this is controlled by function 1 latch (looped back by the
847 cable) and could be set the program. In the general case, the dr11
848 doesnot know in advance what the direction of transfer is - although
849 the program and protocol logic probably is
850 */
851
852#ifdef DR_DEBUG
853 if (DR11 & 1)
854 printf("\ndrstrat: about to GO..,dr_cmd:%lx,drstat:%lx,drcnt:%ld,cdata:%lx,OP:%ld",
855 dra->dr_cmd,rsaddr->dr_cstat,rsaddr->dr_range,rsaddr->dr_data,dra->dr_op);
856#endif
857
858 /* Update function latches may have been done already by drioctl() if
859 request from drioctl()
860 */
861 if (dra->dr_cmd & DR_DFCN) {
862 /* deferred function write */
863 dra->dr_cmd &= ~DR_DFCN; /* Clear request */
864 go = dra->dr_cmd & DR_FMSK; /* mask out fcn bits */
865 rsaddr->dr_cstat = go; /* Write it to the board */
866 }
867
868 /* Clear dmaf and attf to assure a clean dma start */
869 rsaddr->dr_pulse = (ushort)(RATN|RDMA|RPER);
870 rsaddr->dr_cstat = (ushort)(IENB|GO|CYCL|dra->dr_op); /* GO...... */
871
872 /* Now check for software cycle request -- usually by transmitter in
873 link mode.
874 */
875 if (dra->dr_cmd & DR_PCYL) {
876 dra->dr_cmd &= ~DR_PCYL; /* Clear request */
877 rsaddr->dr_pulse = CYCL; /* Use pulse register again */
878 }
879
880 /* Now check for deferred ACLO FCNT2 pulse request -- usually to tell
881 the transmitter (via its attention) that we have enabled dma.
882 */
883 if (dra->dr_cmd & DR_DACL) {
884 dra->dr_cmd &= ~DR_DACL; /* Clear request */
885 rsaddr->dr_pulse = FCN2; /* Use pulse register again */
886 }
887}
888
889#endif NDR