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