maybe this time! fix rcv_xmtbuf/restor_xmtbuf bug that screws buffers
[unix-history] / usr / src / sys / tahoe / vba / vba.c
CommitLineData
36b64905 1/* vba.c 1.4 86/12/16 */
500486ea 2
9d915fad
SL
3#include "../tahoe/mtpr.h"
4#include "../tahoe/pte.h"
500486ea 5
9d915fad
SL
6#include "param.h"
7#include "buf.h"
8#include "cmap.h"
9#include "conf.h"
10#include "dir.h"
11#include "dk.h"
12#include "map.h"
13#include "systm.h"
14#include "user.h"
15#include "vmparam.h"
16#include "vmmac.h"
17#include "proc.h"
c0cfefe3 18#include "syslog.h"
9d915fad
SL
19
20#include "../tahoevba/vbavar.h"
21
22/*
23 * Tahoe VERSAbus adapator support routines.
24 */
500486ea
SL
25
26/*
27 * Next piece of logic takes care of unusual cases when less (or more) than
28 * a full block (or sector) are required. This is done by the swaping
29 * logic, when it brings page table pages from the swap device.
30 * Since some controllers can't read less than a sector, the
31 * only alternative is to read the disk to a temporary buffer and
32 * then to move the amount needed back to the process (usually proc[0]
33 * or proc[2]).
34 * On Tahoe, the virtual addresses versus physical I/O problem creates
35 * the need to move I/O data through an intermediate buffer whenever one
36 * of the following is true:
37 * 1) The data length is not a multiple of sector size
38 * 2) The base address + length cross a physical page boundary
39 * 3) The virtual address for I/O is not in the system space.
40 */
41
500486ea 42/*
c0cfefe3
SL
43 * I/O buffer preparation for possible buffered transfer.
44 * The relevant page table entries are kept in the buf structure,
45 * for later use by the driver's start or interrupt routine
46 * when user's data has to be moved to the intermediate buffer.
500486ea 47 */
9d915fad
SL
48vbasetup(bp, sectsize)
49 register struct buf *bp;
50 int sectsize; /* This disk's physical sector size */
51{
500486ea 52 caddr_t source_pte_adr;
9d915fad 53 register int v;
500486ea
SL
54
55 if ((((int)bp->b_un.b_addr & PGOFSET) + bp->b_bcount) > NBPG ||
9d915fad
SL
56 (bp->b_bcount % sectsize) != 0 ||
57 ((int)bp->b_un.b_addr & 0xc0000000) != 0xc0000000) {
500486ea 58 bp->b_flags |= B_NOT1K;
9d915fad
SL
59 v = btop(bp->b_un.b_addr);
60 source_pte_adr = (caddr_t)(bp->b_flags&B_DIRTY ?
61 vtopte(&proc[2], v) : vtopte(bp->b_proc, v));
500486ea 62 bp->b_ptecnt = (bp->b_bcount + NBPG -1 +
9d915fad
SL
63 ((int)bp->b_un.b_addr & PGOFSET)) / NBPG;
64 bcopy(source_pte_adr, (caddr_t)bp->b_upte,
65 (unsigned)bp->b_ptecnt*4);
500486ea
SL
66 }
67}
68
500486ea 69/*
c0cfefe3
SL
70 * This routine is usually called by the start routine. It
71 * returns the physical address of the first byte for i/o, to
500486ea
SL
72 * be presented to the controller. If intermediate buffering is
73 * needed and a write out is done, now is the time to get the
74 * original user's data in the buffer.
75 */
9d915fad
SL
76vbastart(bp, v, map, utl)
77 struct buf *bp;
78 caddr_t v; /* Driver's own intermediate buffer. */
79 long *map; /* A bunch of system pte's */
80 caddr_t utl; /* The system address mapped through 'map' */
500486ea
SL
81{
82 register phadr, i;
83
84 if (bp->b_flags & B_NOT1K) {
9d915fad
SL
85 phadr = vtoph(bp->b_proc, (unsigned)v);
86 if ((bp->b_flags & B_READ) == 0) {
c0cfefe3 87 for (i = 0; i < bp->b_ptecnt; i++) {
500486ea
SL
88 map[i] = bp->b_upte[i]
89 & ~PG_PROT | PG_V | PG_KR;
9d915fad
SL
90 mtpr(TBIS, utl + i*NBPG);
91 mtpr(P1DC, utl + i*NBPG);
500486ea 92 }
9d915fad
SL
93 bcopy(((int)bp->b_un.b_addr & PGOFSET) + utl,
94 v, (unsigned)bp->b_bcount);
500486ea 95 }
9d915fad
SL
96 } else
97 phadr = vtoph(bp->b_proc, (unsigned)bp->b_un.b_addr);
500486ea
SL
98 return (phadr);
99}
100
500486ea
SL
101/*
102 * Called by the driver's interrupt routine, after the data is
103 * realy in or out. If that was a read, and the NOT1K flag was on,
104 * now is the time to move the data back into user's space.
9d915fad 105 * Similar to the vbastart routine, but in the reverse direction.
500486ea 106 */
9d915fad
SL
107vbadone(bp, v, map, utl)
108 register struct buf *bp;
109 caddr_t v; /* Driver's own intermediate buffer. */
110 long *map; /* A bunch of system pte's */
111 caddr_t utl; /* The system address mapped through 'map' */
112{
500486ea
SL
113 register i, cnt;
114
115 if (bp->b_flags & B_READ)
116 if (bp->b_flags & B_NOT1K) {
c0cfefe3 117 for (cnt = bp->b_bcount; cnt >= 0; cnt -= NBPG) {
9d915fad
SL
118 mtpr(P1DC, (int)v + cnt-1);
119 mtpr(P1DC, (caddr_t)bp->b_un.b_addr + cnt-1);
500486ea 120 }
9d915fad
SL
121 if (((int)v & PGOFSET) != 0)
122 mtpr(P1DC, v);
123 if (((int)bp->b_un.b_addr & PGOFSET) != 0)
124 mtpr(P1DC, (caddr_t)bp->b_un.b_addr);
c0cfefe3 125 for (i = 0; i < bp->b_ptecnt; i++) {
500486ea
SL
126 map[i] = bp->b_upte[i]
127 & ~PG_PROT | PG_V | PG_KW;
9d915fad 128 mtpr(TBIS, utl + i*NBPG);
500486ea 129 }
9d915fad 130 bcopy(v, ((int)bp->b_un.b_addr & PGOFSET)+utl,
c0cfefe3 131 (unsigned)(bp->b_bcount - bp->b_resid));
9d915fad
SL
132 } else
133 mtpr(P1DC, bp->b_un.b_addr);
500486ea
SL
134 bp->b_flags &= ~B_NOT1K;
135}