add CCI credit, rm unneeded wakup; how can 2 closes
[unix-history] / usr / src / sys / tahoe / vba / vba.c
CommitLineData
2fb1eb99 1/*
5db86c85
MK
2 * Copyright (c) 1987, 1988 Regents of the University of California.
3 * All rights reserved.
2fb1eb99 4 *
5db86c85 5 * Redistribution and use in source and binary forms are permitted
616d42db
KB
6 * provided that the above copyright notice and this paragraph are
7 * duplicated in all such forms and that any documentation,
8 * advertising materials, and other materials related to such
9 * distribution and use acknowledge that the software was developed
10 * by the University of California, Berkeley. The name of the
11 * University may not be used to endorse or promote products derived
12 * from this software without specific prior written permission.
13 * THIS SOFTWARE IS PROVIDED ``AS IS'' AND WITHOUT ANY EXPRESS OR
14 * IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED
15 * WARRANTIES OF MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE.
5db86c85 16 *
616d42db 17 * @(#)vba.c 7.2 (Berkeley) %G%
2fb1eb99 18 */
d0afb218
MK
19
20/*
21 * Tahoe VERSAbus adapator support routines.
22 */
500486ea 23
9d915fad
SL
24#include "param.h"
25#include "buf.h"
26#include "cmap.h"
27#include "conf.h"
28#include "dir.h"
29#include "dk.h"
30#include "map.h"
31#include "systm.h"
32#include "user.h"
33#include "vmparam.h"
34#include "vmmac.h"
35#include "proc.h"
c0cfefe3 36#include "syslog.h"
fcba03fb 37#include "malloc.h"
9d915fad 38
8a59a1ef
MK
39#include "../tahoe/mtpr.h"
40#include "../tahoe/pte.h"
9d915fad 41
8a59a1ef 42#include "../tahoevba/vbavar.h"
d0afb218 43
9d915fad 44/*
d0afb218
MK
45 * Allocate private page map and intermediate buffer
46 * for a VERSAbus device, large enough for maximum transfer size.
47 * Intermediate buffer
48 * Make intermediate buffer uncacheable.
9d915fad 49 */
1f9a1539
MK
50vbainit(vb, xsize, flags)
51 register struct vb_buf *vb;
52 int xsize, flags;
53{
54 register struct pte *pte;
55 register n;
56
57 vb->vb_flags = flags;
5db86c85 58 if (vbmapalloc((int)btoc(xsize) + 1, &vb->vb_map, &vb->vb_utl) == 0) {
c7af6552
MK
59 printf("vbmap exhausted\n");
60 return (0);
61 }
1f9a1539 62 n = roundup(xsize, NBPG);
ef2ed459 63 vb->vb_bufsize = n;
1f9a1539 64 if (vb->vb_rawbuf == 0)
5db86c85 65 vb->vb_rawbuf = (caddr_t)malloc((u_long)n, M_DEVBUF, M_NOWAIT);
c7af6552
MK
66 if (vb->vb_rawbuf == 0) {
67 printf("no memory for device buffer\n");
68 return (0);
69 }
1f9a1539 70 if ((int)vb->vb_rawbuf & PGOFSET)
d0afb218 71 panic("vbinit pgoff");
5db86c85 72 vb->vb_physbuf = (u_long)kvtophys(vb->vb_rawbuf);
1f9a1539
MK
73 if (flags & VB_20BIT)
74 vb->vb_maxphys = btoc(VB_MAXADDR20);
75 else if (flags & VB_24BIT)
76 vb->vb_maxphys = btoc(VB_MAXADDR24);
77 else
78 vb->vb_maxphys = btoc(VB_MAXADDR32);
d0afb218
MK
79 if (btoc(vb->vb_physbuf + n) > vb->vb_maxphys)
80 panic("vbinit physbuf");
1f9a1539
MK
81
82 /*
83 * Make raw buffer pages uncacheable.
84 */
85 pte = kvtopte(vb->vb_rawbuf);
86 for (n = btoc(n); n--; pte++)
87 pte->pg_nc = 1;
88 mtpr(TBIA, 0);
c7af6552 89 return (1);
1f9a1539
MK
90}
91
52ad577b
MK
92/*
93 * Due to unknown hardware or software errors, some sites have problems
94 * with strange crashes or corruption of text images when DMA is attempted
95 * to kernel addresses spanning a page boundary, or to user addresses
96 * (even if the buffer is physically contiguous). To avoid this behavior,
97 * the following toggles inhibit such transfers when set.
98 * vba_copyk: copy transfers to kernel address that span a page boundary
99 * vba_copyu: copy transfers to user addresses
100 */
101#ifndef VBA_TRICKY
102int vba_copyk = 1;
103int vba_copyu = 1;
104#else
105int vba_copyk = 0;
106int vba_copyu = 0;
107#endif
108
500486ea 109/*
d0afb218
MK
110 * Check a transfer to see whether it can be done directly
111 * to the destination buffer, or whether it must be copied.
112 * On Tahoe, the lack of a bus I/O map forces data to be copied
113 * to a physically-contiguous buffer whenever one of the following is true:
114 * 1) The data length is not a multiple of sector size.
115 * (The swapping code does this, unfortunately.)
1f9a1539
MK
116 * 2) The buffer is not physically contiguous and the controller
117 * does not support scatter-gather operations.
118 * 3) The physical address for I/O is higher than addressible
119 * by the device.
d0afb218
MK
120 * This routine is called by the start routine.
121 * If copying is necessary, the intermediate buffer is mapped;
122 * if the operation is a write, the data is copied into the buffer.
123 * It returns the physical address of the first byte for DMA, to
124 * be presented to the controller.
500486ea 125 */
1f9a1539
MK
126u_long
127vbasetup(bp, vb, sectsize)
128 register struct buf *bp;
129 register struct vb_buf *vb;
130 int sectsize;
500486ea 131{
1f9a1539
MK
132 register struct pte *spte, *dpte;
133 register int p, i;
134 int npf, o, v;
135
136 o = (int)bp->b_un.b_addr & PGOFSET;
d0afb218 137 npf = btoc(bp->b_bcount + o);
1f9a1539 138 vb->vb_iskernel = (((int)bp->b_un.b_addr & KERNBASE) == KERNBASE);
52ad577b 139 if (vb->vb_iskernel) {
1f9a1539 140 spte = kvtopte(bp->b_un.b_addr);
52ad577b
MK
141if (vba_copyk && (o != 0 || npf > 1)) goto copy;
142 } else {
1f9a1539
MK
143 spte = vtopte((bp->b_flags&B_DIRTY) ? &proc[2] : bp->b_proc,
144 btop(bp->b_un.b_addr));
52ad577b
MK
145if (vba_copyu) goto copy;
146 }
147 if (bp->b_bcount % sectsize != 0 || (o & (sizeof(long) - 1)) != 0)
1f9a1539
MK
148 goto copy;
149 else if ((vb->vb_flags & VB_SCATTER) == 0 ||
52ad577b 150 vb->vb_maxphys != btoc(VB_MAXADDR32)) {
1f9a1539 151 dpte = spte;
d0afb218
MK
152 p = (dpte++)->pg_pfnum;
153 for (i = npf; --i > 0; dpte++) {
154 if ((v = dpte->pg_pfnum) != p + CLSIZE &&
1f9a1539
MK
155 (vb->vb_flags & VB_SCATTER) == 0)
156 goto copy;
157 if (p >= vb->vb_maxphys)
158 goto copy;
159 p = v;
160 }
161 if (p >= vb->vb_maxphys)
162 goto copy;
163 }
164 vb->vb_copy = 0;
ef2ed459
MK
165 if (vb->vb_iskernel)
166 vbastat.k_raw++;
167 else
168 vbastat.u_raw++;
1f9a1539 169 return ((spte->pg_pfnum << PGSHIFT) + o);
500486ea 170
1f9a1539
MK
171copy:
172 vb->vb_copy = 1;
ef2ed459
MK
173 if (bp->b_bcount > vb->vb_bufsize)
174 panic("vba xfer too large");
1f9a1539 175 if (vb->vb_iskernel) {
ef2ed459 176 if ((bp->b_flags & B_READ) == 0)
1f9a1539
MK
177 bcopy(bp->b_un.b_addr, vb->vb_rawbuf,
178 (unsigned)bp->b_bcount);
ef2ed459 179 vbastat.k_copy++;
1f9a1539
MK
180 } else {
181 dpte = vb->vb_map;
182 for (i = npf, p = (int)vb->vb_utl; i--; p += NBPG) {
d0afb218
MK
183 *(int *)dpte++ = (spte++)->pg_pfnum |
184 PG_V | PG_KW | PG_N;
1f9a1539 185 mtpr(TBIS, p);
500486ea 186 }
ef2ed459 187 if ((bp->b_flags & B_READ) == 0)
1f9a1539
MK
188 bcopy(vb->vb_utl + o, vb->vb_rawbuf,
189 (unsigned)bp->b_bcount);
ef2ed459 190 vbastat.u_copy++;
1f9a1539
MK
191 }
192 return (vb->vb_physbuf);
500486ea
SL
193}
194
500486ea 195/*
1f9a1539
MK
196 * Called by the driver's interrupt routine, after DMA is completed.
197 * If the operation was a read, copy data to final buffer if necessary
198 * or invalidate data cache for cacheable direct buffers.
9d915fad 199 * Similar to the vbastart routine, but in the reverse direction.
500486ea 200 */
1f9a1539 201vbadone(bp, vb)
9d915fad 202 register struct buf *bp;
1f9a1539 203 register struct vb_buf *vb;
9d915fad 204{
1f9a1539
MK
205 register npf;
206 register caddr_t v;
207 int o;
500486ea 208
1f9a1539
MK
209 if (bp->b_flags & B_READ) {
210 o = (int)bp->b_un.b_addr & PGOFSET;
211 if (vb->vb_copy) {
ef2ed459 212 if (vb->vb_iskernel)
1f9a1539
MK
213 bcopy(vb->vb_rawbuf, bp->b_un.b_addr,
214 (unsigned)(bp->b_bcount - bp->b_resid));
ef2ed459 215 else {
1f9a1539
MK
216 bcopy(vb->vb_rawbuf, vb->vb_utl + o,
217 (unsigned)(bp->b_bcount - bp->b_resid));
218 dkeyinval(bp->b_proc);
500486ea 219 }
1f9a1539
MK
220 } else {
221 if (vb->vb_iskernel) {
222 npf = btoc(bp->b_bcount + o);
223 for (v = bp->b_un.b_addr; npf--; v += NBPG)
224 mtpr(P1DC, (int)v);
ef2ed459 225 } else
1f9a1539 226 dkeyinval(bp->b_proc);
1f9a1539
MK
227 }
228 }
500486ea 229}
ef2ed459
MK
230
231/*
232 * Set up a scatter-gather operation for SMD/E controller.
233 * This code belongs half-way between vd.c and this file.
234 */
235#include "vdreg.h"
236
237vba_sgsetup(bp, vb, sg)
238 register struct buf *bp;
239 struct vb_buf *vb;
240 struct trsg *sg;
241{
242 register struct pte *spte;
243 register struct addr_chain *adr;
5db86c85 244 register int i;
ef2ed459
MK
245 int o;
246
247 o = (int)bp->b_un.b_addr & PGOFSET;
ef2ed459
MK
248 vb->vb_iskernel = (((int)bp->b_un.b_addr & KERNBASE) == KERNBASE);
249 vb->vb_copy = 0;
250 if (vb->vb_iskernel) {
251 spte = kvtopte(bp->b_un.b_addr);
252 vbastat.k_sg++;
253 } else {
254 spte = vtopte((bp->b_flags&B_DIRTY) ? &proc[2] : bp->b_proc,
255 btop(bp->b_un.b_addr));
256 vbastat.u_sg++;
257 }
258
259 i = min(NBPG - o, bp->b_bcount);
260 sg->start_addr.wcount = (i + 1) >> 1;
261 sg->start_addr.memadr = ((spte++)->pg_pfnum << PGSHIFT) + o;
262 i = bp->b_bcount - i;
263 if (i > VDMAXPAGES * NBPG)
264 panic("vba xfer too large");
265 i = (i + 1) >> 1;
266 for (adr = sg->addr_chain; i > 0; adr++, i -= NBPG / 2) {
267 adr->nxt_addr = (spte++)->pg_pfnum << PGSHIFT;
5db86c85 268 adr->nxt_len = imin(i, NBPG / 2);
ef2ed459
MK
269 }
270 adr->nxt_addr = 0;
271 adr++->nxt_len = 0;
272 return ((adr - sg->addr_chain) * sizeof(*adr) / sizeof(long));
273}