xref: /csrg-svn/sys/tahoe/vba/vba.c (revision 30718)
1 /*	vba.c	1.6	87/04/01	*/
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 	vb->vb_bufsize = n;
38 	if (vb->vb_rawbuf == 0)
39 		vb->vb_rawbuf = calloc(n);
40 	if ((int)vb->vb_rawbuf & PGOFSET)
41 		panic("vbinit");
42 	vb->vb_physbuf = vtoph((struct proc *)0, vb->vb_rawbuf);
43 	if (flags & VB_20BIT)
44 		vb->vb_maxphys = btoc(VB_MAXADDR20);
45 	else if (flags & VB_24BIT)
46 		vb->vb_maxphys = btoc(VB_MAXADDR24);
47 	else
48 		vb->vb_maxphys = btoc(VB_MAXADDR32);
49 
50 	/*
51 	 * Make raw buffer pages uncacheable.
52 	 */
53 	pte = kvtopte(vb->vb_rawbuf);
54 	for (n = btoc(n); n--; pte++)
55 		pte->pg_nc = 1;
56 	mtpr(TBIA, 0);
57 }
58 
59 /*
60  * Next piece of logic takes care of unusual cases when less (or more) than
61  * a full block (or sector) are required. This is done by the swapping
62  * logic, when it brings page table pages from the swap device.
63  * Since some controllers can't read less than a sector, the
64  * only alternative is to read the disk to a temporary buffer and
65  * then to move the amount needed back to the process (usually proc[0]
66  * or proc[2]).
67  * On Tahoe, the virtual addresses versus physical I/O problem creates
68  * the need to move I/O data through an intermediate buffer whenever one
69  * of the following is true:
70  *	1) The data length is not a multiple of sector size (?)
71  *	2) The buffer is not physically contiguous and the controller
72  *	   does not support scatter-gather operations.
73  *	3) The physical address for I/O is higher than addressible
74  *	   by the device.
75  */
76 
77 /*
78  * Check a transfer to see whether it can be done directly
79  * to the destination buffer, or whether it must be copied.
80  * If copying is necessary, the intermediate buffer is mapped.
81  * This routine is called by the start routine. It
82  * returns the physical address of the first byte for i/o, to
83  * be presented to the controller. If intermediate buffering is
84  * needed and a write out is done, now is the time to get the
85  * original user's data in the buffer.
86  */
87 u_long
88 vbasetup(bp, vb, sectsize)
89 	register struct buf *bp;
90 	register struct vb_buf *vb;
91 	int sectsize;
92 {
93 	register struct pte *spte, *dpte;
94 	register int p, i;
95 	int npf, o, v;
96 
97 	o = (int)bp->b_un.b_addr & PGOFSET;
98 	npf = i = btoc(bp->b_bcount + o);
99 	vb->vb_iskernel = (((int)bp->b_un.b_addr & KERNBASE) == KERNBASE);
100 	if (vb->vb_iskernel)
101 		spte = kvtopte(bp->b_un.b_addr);
102 	else
103 		spte = vtopte((bp->b_flags&B_DIRTY) ? &proc[2] : bp->b_proc,
104 		    btop(bp->b_un.b_addr));
105 	if (bp->b_bcount % sectsize)
106 		goto copy;
107 	else if ((vb->vb_flags & VB_SCATTER) == 0 ||
108 	    vb->vb_maxphys != VB_MAXADDR32) {
109 		dpte = spte;
110 		for (p = (dpte++)->pg_pfnum; --i; dpte++) {
111 			if ((v = dpte->pg_pfnum) != p + NBPG &&
112 			    (vb->vb_flags & VB_SCATTER) == 0)
113 				goto copy;
114 			if (p >= vb->vb_maxphys)
115 				goto copy;
116 			p = v;
117 		}
118 		if (p >= vb->vb_maxphys)
119 			goto copy;
120 	}
121 	vb->vb_copy = 0;
122 	if (vb->vb_iskernel)
123 		vbastat.k_raw++;
124 	else
125 		vbastat.u_raw++;
126 	return ((spte->pg_pfnum << PGSHIFT) + o);
127 
128 copy:
129 	vb->vb_copy = 1;
130 	if (bp->b_bcount > vb->vb_bufsize)
131 		panic("vba xfer too large");
132 	if (vb->vb_iskernel) {
133 		if ((bp->b_flags & B_READ) == 0)
134 			bcopy(bp->b_un.b_addr, vb->vb_rawbuf,
135 			    (unsigned)bp->b_bcount);
136 		vbastat.k_copy++;
137 	} else  {
138 		dpte = vb->vb_map;
139 		for (i = npf, p = (int)vb->vb_utl; i--; p += NBPG) {
140 			*(int *)dpte++ = (spte++)->pg_pfnum | PG_V | PG_KW;
141 			mtpr(TBIS, p);
142 		}
143 		if ((bp->b_flags & B_READ) == 0)
144 			bcopy(vb->vb_utl + o, vb->vb_rawbuf,
145 			    (unsigned)bp->b_bcount);
146 		vbastat.u_copy++;
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 			else {
172 				bcopy(vb->vb_rawbuf, vb->vb_utl + o,
173 				    (unsigned)(bp->b_bcount - bp->b_resid));
174 				dkeyinval(bp->b_proc);
175 			}
176 		} else {
177 			if (vb->vb_iskernel) {
178 				npf = btoc(bp->b_bcount + o);
179 				for (v = bp->b_un.b_addr; npf--; v += NBPG)
180 					mtpr(P1DC, (int)v);
181 			} else
182 				dkeyinval(bp->b_proc);
183 		}
184 	}
185 }
186 
187 /*
188  * Set up a scatter-gather operation for SMD/E controller.
189  * This code belongs half-way between vd.c and this file.
190  */
191 #include "vdreg.h"
192 
193 vba_sgsetup(bp, vb, sg)
194 	register struct buf *bp;
195 	struct vb_buf *vb;
196 	struct trsg *sg;
197 {
198 	register struct pte *spte;
199 	register struct addr_chain *adr;
200 	register int npf, i;
201 	int o;
202 
203 	o = (int)bp->b_un.b_addr & PGOFSET;
204 	npf = btoc(bp->b_bcount + o);
205 	vb->vb_iskernel = (((int)bp->b_un.b_addr & KERNBASE) == KERNBASE);
206 	vb->vb_copy = 0;
207 	if (vb->vb_iskernel) {
208 		spte = kvtopte(bp->b_un.b_addr);
209 		vbastat.k_sg++;
210 	} else {
211 		spte = vtopte((bp->b_flags&B_DIRTY) ? &proc[2] : bp->b_proc,
212 		    btop(bp->b_un.b_addr));
213 		vbastat.u_sg++;
214 	}
215 
216 	i = min(NBPG - o, bp->b_bcount);
217 	sg->start_addr.wcount = (i + 1) >> 1;
218 	sg->start_addr.memadr = ((spte++)->pg_pfnum << PGSHIFT) + o;
219 	i = bp->b_bcount - i;
220 	if (i > VDMAXPAGES * NBPG)
221 		panic("vba xfer too large");
222 	i = (i + 1) >> 1;
223 	for (adr = sg->addr_chain; i > 0; adr++, i -= NBPG / 2) {
224 		adr->nxt_addr = (spte++)->pg_pfnum << PGSHIFT;
225 		adr->nxt_len = min(i, NBPG / 2);
226 	}
227 	adr->nxt_addr = 0;
228 	adr++->nxt_len = 0;
229 	return ((adr - sg->addr_chain) * sizeof(*adr) / sizeof(long));
230 }
231