calloc => malloc
[unix-history] / usr / src / sys / tahoe / vba / vba.c
CommitLineData
fcba03fb 1/* vba.c 1.8 87/06/06 */
d0afb218
MK
2
3/*
4 * Tahoe VERSAbus adapator support routines.
5 */
500486ea 6
9d915fad
SL
7#include "../tahoe/mtpr.h"
8#include "../tahoe/pte.h"
500486ea 9
9d915fad
SL
10#include "param.h"
11#include "buf.h"
12#include "cmap.h"
13#include "conf.h"
14#include "dir.h"
15#include "dk.h"
16#include "map.h"
17#include "systm.h"
18#include "user.h"
19#include "vmparam.h"
20#include "vmmac.h"
21#include "proc.h"
c0cfefe3 22#include "syslog.h"
fcba03fb 23#include "malloc.h"
9d915fad
SL
24
25#include "../tahoevba/vbavar.h"
26
1f9a1539 27#define kvtopte(v) (&Sysmap[btop((int)(v) &~ KERNBASE)])
d0afb218 28
9d915fad 29/*
d0afb218
MK
30 * Allocate private page map and intermediate buffer
31 * for a VERSAbus device, large enough for maximum transfer size.
32 * Intermediate buffer
33 * Make intermediate buffer uncacheable.
9d915fad 34 */
1f9a1539
MK
35vbainit(vb, xsize, flags)
36 register struct vb_buf *vb;
37 int xsize, flags;
38{
39 register struct pte *pte;
40 register n;
41
42 vb->vb_flags = flags;
d0afb218 43 vbmapalloc(btoc(xsize) + 1, &vb->vb_map, &vb->vb_utl);
1f9a1539 44 n = roundup(xsize, NBPG);
ef2ed459 45 vb->vb_bufsize = n;
1f9a1539 46 if (vb->vb_rawbuf == 0)
fcba03fb 47 vb->vb_rawbuf = (caddr_t)malloc(n, M_DEVBUF, M_NOWAIT);
1f9a1539 48 if ((int)vb->vb_rawbuf & PGOFSET)
d0afb218 49 panic("vbinit pgoff");
1f9a1539
MK
50 vb->vb_physbuf = vtoph((struct proc *)0, vb->vb_rawbuf);
51 if (flags & VB_20BIT)
52 vb->vb_maxphys = btoc(VB_MAXADDR20);
53 else if (flags & VB_24BIT)
54 vb->vb_maxphys = btoc(VB_MAXADDR24);
55 else
56 vb->vb_maxphys = btoc(VB_MAXADDR32);
d0afb218
MK
57 if (btoc(vb->vb_physbuf + n) > vb->vb_maxphys)
58 panic("vbinit physbuf");
1f9a1539
MK
59
60 /*
61 * Make raw buffer pages uncacheable.
62 */
63 pte = kvtopte(vb->vb_rawbuf);
64 for (n = btoc(n); n--; pte++)
65 pte->pg_nc = 1;
66 mtpr(TBIA, 0);
67}
68
500486ea 69/*
d0afb218
MK
70 * Check a transfer to see whether it can be done directly
71 * to the destination buffer, or whether it must be copied.
72 * On Tahoe, the lack of a bus I/O map forces data to be copied
73 * to a physically-contiguous buffer whenever one of the following is true:
74 * 1) The data length is not a multiple of sector size.
75 * (The swapping code does this, unfortunately.)
1f9a1539
MK
76 * 2) The buffer is not physically contiguous and the controller
77 * does not support scatter-gather operations.
78 * 3) The physical address for I/O is higher than addressible
79 * by the device.
d0afb218
MK
80 * This routine is called by the start routine.
81 * If copying is necessary, the intermediate buffer is mapped;
82 * if the operation is a write, the data is copied into the buffer.
83 * It returns the physical address of the first byte for DMA, to
84 * be presented to the controller.
500486ea 85 */
1f9a1539
MK
86u_long
87vbasetup(bp, vb, sectsize)
88 register struct buf *bp;
89 register struct vb_buf *vb;
90 int sectsize;
500486ea 91{
1f9a1539
MK
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;
d0afb218 97 npf = btoc(bp->b_bcount + o);
1f9a1539
MK
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;
d0afb218
MK
109 p = (dpte++)->pg_pfnum;
110 for (i = npf; --i > 0; dpte++) {
111 if ((v = dpte->pg_pfnum) != p + CLSIZE &&
1f9a1539
MK
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;
ef2ed459
MK
122 if (vb->vb_iskernel)
123 vbastat.k_raw++;
124 else
125 vbastat.u_raw++;
1f9a1539 126 return ((spte->pg_pfnum << PGSHIFT) + o);
500486ea 127
1f9a1539
MK
128copy:
129 vb->vb_copy = 1;
ef2ed459
MK
130 if (bp->b_bcount > vb->vb_bufsize)
131 panic("vba xfer too large");
1f9a1539 132 if (vb->vb_iskernel) {
ef2ed459 133 if ((bp->b_flags & B_READ) == 0)
1f9a1539
MK
134 bcopy(bp->b_un.b_addr, vb->vb_rawbuf,
135 (unsigned)bp->b_bcount);
ef2ed459 136 vbastat.k_copy++;
1f9a1539
MK
137 } else {
138 dpte = vb->vb_map;
139 for (i = npf, p = (int)vb->vb_utl; i--; p += NBPG) {
d0afb218
MK
140 *(int *)dpte++ = (spte++)->pg_pfnum |
141 PG_V | PG_KW | PG_N;
1f9a1539 142 mtpr(TBIS, p);
500486ea 143 }
ef2ed459 144 if ((bp->b_flags & B_READ) == 0)
1f9a1539
MK
145 bcopy(vb->vb_utl + o, vb->vb_rawbuf,
146 (unsigned)bp->b_bcount);
ef2ed459 147 vbastat.u_copy++;
1f9a1539
MK
148 }
149 return (vb->vb_physbuf);
500486ea
SL
150}
151
500486ea 152/*
1f9a1539
MK
153 * Called by the driver's interrupt routine, after DMA is completed.
154 * If the operation was a read, copy data to final buffer if necessary
155 * or invalidate data cache for cacheable direct buffers.
9d915fad 156 * Similar to the vbastart routine, but in the reverse direction.
500486ea 157 */
1f9a1539 158vbadone(bp, vb)
9d915fad 159 register struct buf *bp;
1f9a1539 160 register struct vb_buf *vb;
9d915fad 161{
1f9a1539
MK
162 register npf;
163 register caddr_t v;
164 int o;
500486ea 165
1f9a1539
MK
166 if (bp->b_flags & B_READ) {
167 o = (int)bp->b_un.b_addr & PGOFSET;
168 if (vb->vb_copy) {
ef2ed459 169 if (vb->vb_iskernel)
1f9a1539
MK
170 bcopy(vb->vb_rawbuf, bp->b_un.b_addr,
171 (unsigned)(bp->b_bcount - bp->b_resid));
ef2ed459 172 else {
1f9a1539
MK
173 bcopy(vb->vb_rawbuf, vb->vb_utl + o,
174 (unsigned)(bp->b_bcount - bp->b_resid));
175 dkeyinval(bp->b_proc);
500486ea 176 }
1f9a1539
MK
177 } else {
178 if (vb->vb_iskernel) {
179 npf = btoc(bp->b_bcount + o);
180 for (v = bp->b_un.b_addr; npf--; v += NBPG)
181 mtpr(P1DC, (int)v);
ef2ed459 182 } else
1f9a1539 183 dkeyinval(bp->b_proc);
1f9a1539
MK
184 }
185 }
500486ea 186}
ef2ed459
MK
187
188/*
189 * Set up a scatter-gather operation for SMD/E controller.
190 * This code belongs half-way between vd.c and this file.
191 */
192#include "vdreg.h"
193
194vba_sgsetup(bp, vb, sg)
195 register struct buf *bp;
196 struct vb_buf *vb;
197 struct trsg *sg;
198{
199 register struct pte *spte;
200 register struct addr_chain *adr;
201 register int npf, i;
202 int o;
203
204 o = (int)bp->b_un.b_addr & PGOFSET;
205 npf = btoc(bp->b_bcount + o);
206 vb->vb_iskernel = (((int)bp->b_un.b_addr & KERNBASE) == KERNBASE);
207 vb->vb_copy = 0;
208 if (vb->vb_iskernel) {
209 spte = kvtopte(bp->b_un.b_addr);
210 vbastat.k_sg++;
211 } else {
212 spte = vtopte((bp->b_flags&B_DIRTY) ? &proc[2] : bp->b_proc,
213 btop(bp->b_un.b_addr));
214 vbastat.u_sg++;
215 }
216
217 i = min(NBPG - o, bp->b_bcount);
218 sg->start_addr.wcount = (i + 1) >> 1;
219 sg->start_addr.memadr = ((spte++)->pg_pfnum << PGSHIFT) + o;
220 i = bp->b_bcount - i;
221 if (i > VDMAXPAGES * NBPG)
222 panic("vba xfer too large");
223 i = (i + 1) >> 1;
224 for (adr = sg->addr_chain; i > 0; adr++, i -= NBPG / 2) {
225 adr->nxt_addr = (spte++)->pg_pfnum << PGSHIFT;
226 adr->nxt_len = min(i, NBPG / 2);
227 }
228 adr->nxt_addr = 0;
229 adr++->nxt_len = 0;
230 return ((adr - sg->addr_chain) * sizeof(*adr) / sizeof(long));
231}