xref: /csrg-svn/sys/tahoe/vba/vba.c (revision 30601)
1 /*	vba.c	1.5	87/03/10	*/
2 
3 #include "../tahoe/mtpr.h"
4 #include "../tahoe/pte.h"
5 
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"
18 #include "syslog.h"
19 
20 #include "../tahoevba/vbavar.h"
21 
22 #define	kvtopte(v) (&Sysmap[btop((int)(v) &~ KERNBASE)])
23 /*
24  * Tahoe VERSAbus adapator support routines.
25  */
26 
27 vbainit(vb, xsize, flags)
28 	register struct vb_buf *vb;
29 	int xsize, flags;
30 {
31 	register struct pte *pte;
32 	register n;
33 
34 	vb->vb_flags = flags;
35 	vbmapalloc(btoc(xsize)+1, &vb->vb_map, &vb->vb_utl);
36 	n = roundup(xsize, NBPG);
37 	if (vb->vb_rawbuf == 0)
38 		vb->vb_rawbuf = calloc(n);
39 	if ((int)vb->vb_rawbuf & PGOFSET)
40 		panic("vbinit");
41 	vb->vb_physbuf = vtoph((struct proc *)0, vb->vb_rawbuf);
42 	if (flags & VB_20BIT)
43 		vb->vb_maxphys = btoc(VB_MAXADDR20);
44 	else if (flags & VB_24BIT)
45 		vb->vb_maxphys = btoc(VB_MAXADDR24);
46 	else
47 		vb->vb_maxphys = btoc(VB_MAXADDR32);
48 
49 	/*
50 	 * Make raw buffer pages uncacheable.
51 	 */
52 	pte = kvtopte(vb->vb_rawbuf);
53 	for (n = btoc(n); n--; pte++)
54 		pte->pg_nc = 1;
55 	mtpr(TBIA, 0);
56 }
57 
58 /*
59  * Next piece of logic takes care of unusual cases when less (or more) than
60  * a full block (or sector) are required. This is done by the swaping
61  * logic, when it brings page table pages from the swap device.
62  * Since some controllers can't read less than a sector, the
63  * only alternative is to read the disk to a temporary buffer and
64  * then to move the amount needed back to the process (usually proc[0]
65  * or proc[2]).
66  * On Tahoe, the virtual addresses versus physical I/O problem creates
67  * the need to move I/O data through an intermediate buffer whenever one
68  * of the following is true:
69  *	1) The data length is not a multiple of sector size (?)
70  *	2) The buffer is not physically contiguous and the controller
71  *	   does not support scatter-gather operations.
72  *	3) The physical address for I/O is higher than addressible
73  *	   by the device.
74  */
75 
76 /*
77  * Check a transfer to see whether it can be done directly
78  * to the destination buffer, or whether it must be copied.
79  * If copying is necessary, the intermediate buffer is mapped.
80  * This routine is called by the start routine. It
81  * returns the physical address of the first byte for i/o, to
82  * be presented to the controller. If intermediate buffering is
83  * needed and a write out is done, now is the time to get the
84  * original user's data in the buffer.
85  */
86 u_long
87 vbasetup(bp, vb, sectsize)
88 	register struct buf *bp;
89 	register struct vb_buf *vb;
90 	int sectsize;
91 {
92 	register struct pte *spte, *dpte;
93 	register int p, i;
94 	int npf, o, v;
95 
96 	o = (int)bp->b_un.b_addr & PGOFSET;
97 	npf = i = btoc(bp->b_bcount + o);
98 	vb->vb_iskernel = (((int)bp->b_un.b_addr & KERNBASE) == KERNBASE);
99 	if (vb->vb_iskernel)
100 		spte = kvtopte(bp->b_un.b_addr);
101 	else
102 		spte = vtopte((bp->b_flags&B_DIRTY) ? &proc[2] : bp->b_proc,
103 		    btop(bp->b_un.b_addr));
104 	if (bp->b_bcount % sectsize)
105 		goto copy;
106 	else if ((vb->vb_flags & VB_SCATTER) == 0 ||
107 	    vb->vb_maxphys != VB_MAXADDR32) {
108 		dpte = spte;
109 		for (p = (dpte++)->pg_pfnum; --i; dpte++) {
110 			if ((v = dpte->pg_pfnum) != p + NBPG &&
111 			    (vb->vb_flags & VB_SCATTER) == 0)
112 				goto copy;
113 			if (p >= vb->vb_maxphys)
114 				goto copy;
115 			p = v;
116 		}
117 		if (p >= vb->vb_maxphys)
118 			goto copy;
119 	}
120 	vb->vb_copy = 0;
121 	if ((bp->b_flags & BREAD) == 0)
122 		if (vb->vb_iskernel)
123 			vbastat.kw_raw++;
124 		else
125 			vbastat.uw_raw++;
126 	return ((spte->pg_pfnum << PGSHIFT) + o);
127 
128 copy:
129 	vb->vb_copy = 1;
130 	if (vb->vb_iskernel) {
131 		if ((bp->b_flags & B_READ) == 0) {
132 			bcopy(bp->b_un.b_addr, vb->vb_rawbuf,
133 			    (unsigned)bp->b_bcount);
134 			vbastat.kw_copy++;
135 		}
136 	} else  {
137 		dpte = vb->vb_map;
138 		for (i = npf, p = (int)vb->vb_utl; i--; p += NBPG) {
139 			*(int *)dpte++ = (spte++)->pg_pfnum | PG_V | PG_KW;
140 			mtpr(TBIS, p);
141 		}
142 		if ((bp->b_flags & B_READ) == 0) {
143 			bcopy(vb->vb_utl + o, vb->vb_rawbuf,
144 			    (unsigned)bp->b_bcount);
145 			vbastat.uw_copy++;
146 		}
147 	}
148 	return (vb->vb_physbuf);
149 }
150 
151 /*
152  * Called by the driver's interrupt routine, after DMA is completed.
153  * If the operation was a read, copy data to final buffer if necessary
154  * or invalidate data cache for cacheable direct buffers.
155  * Similar to the vbastart routine, but in the reverse direction.
156  */
157 vbadone(bp, vb)
158 	register struct buf *bp;
159 	register struct vb_buf *vb;
160 {
161 	register npf;
162 	register caddr_t v;
163 	int o;
164 
165 	if (bp->b_flags & B_READ) {
166 		o = (int)bp->b_un.b_addr & PGOFSET;
167 		if (vb->vb_copy) {
168 			if (vb->vb_iskernel) {
169 				bcopy(vb->vb_rawbuf, bp->b_un.b_addr,
170 				    (unsigned)(bp->b_bcount - bp->b_resid));
171 				vbastat.kr_copy++;
172 			} else {
173 				bcopy(vb->vb_rawbuf, vb->vb_utl + o,
174 				    (unsigned)(bp->b_bcount - bp->b_resid));
175 				dkeyinval(bp->b_proc);
176 				vbastat.ur_copy++;
177 			}
178 		} else {
179 			if (vb->vb_iskernel) {
180 				npf = btoc(bp->b_bcount + o);
181 				for (v = bp->b_un.b_addr; npf--; v += NBPG)
182 					mtpr(P1DC, (int)v);
183 				vbastat.kr_raw++;
184 			} else {
185 				dkeyinval(bp->b_proc);
186 				vbastat.ur_raw++;
187 			}
188 		}
189 	}
190 }
191