xref: /csrg-svn/sys/tahoe/vba/vba.c (revision 25675)
1 /*	vba.c	1.2	86/01/05	*/
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 
19 #include "../tahoevba/vbavar.h"
20 
21 /*
22  * Tahoe VERSAbus adapator support routines.
23  */
24 
25 /*
26  * Next piece of logic takes care of unusual cases when less (or more) than
27  * a full block (or sector) are required. This is done by the swaping
28  * logic, when it brings page table pages from the swap device.
29  * Since some controllers can't read less than a sector, the
30  * only alternative is to read the disk to a temporary buffer and
31  * then to move the amount needed back to the process (usually proc[0]
32  * or proc[2]).
33  * On Tahoe, the virtual addresses versus physical I/O problem creates
34  * the need to move I/O data through an intermediate buffer whenever one
35  * of the following is true:
36  *	1) The data length is not a multiple of sector size
37  *	2) The base address + length cross a physical page boundary
38  *	3) The virtual address for I/O is not in the system space.
39  */
40 
41 /*
42  * IO buffer preparation for possible buffered transfer.
43  * The relevant page table entries are kept in the 'buf' structure,
44  * for later use by the driver's 'start' routine or 'interrupt'
45  * routine, when user's data has to be moved to the intermediate
46  * buffer.
47  */
48 vbasetup(bp, sectsize)
49 	register struct buf *bp;
50 	int sectsize;	/* This disk's physical sector size */
51 {
52 	caddr_t	source_pte_adr;
53 	register int v;
54 
55 	if ((((int)bp->b_un.b_addr & PGOFSET) + bp->b_bcount) > NBPG ||
56 	    (bp->b_bcount % sectsize) != 0 ||
57 	    ((int)bp->b_un.b_addr & 0xc0000000) != 0xc0000000) {
58 		bp->b_flags |= B_NOT1K;
59 		v = btop(bp->b_un.b_addr);
60 		source_pte_adr = (caddr_t)(bp->b_flags&B_DIRTY ?
61 		    vtopte(&proc[2], v) : vtopte(bp->b_proc, v));
62 		bp->b_ptecnt = (bp->b_bcount + NBPG -1 +
63 		    ((int)bp->b_un.b_addr & PGOFSET)) / NBPG;
64 		bcopy(source_pte_adr, (caddr_t)bp->b_upte,
65 		    (unsigned)bp->b_ptecnt*4);
66 	}
67 }
68 
69 /*
70  * This routine is usually called by the 'start' routine. It
71  * returns the physical address of the first byte for IO, to
72  * be presented to the controller. If intermediate buffering is
73  * needed and a write out is done, now is the time to get the
74  * original user's data in the buffer.
75  */
76 vbastart(bp, v, map, utl)
77 	struct buf *bp;
78 	caddr_t v;		/* Driver's own intermediate buffer. */
79 	long *map;		/* A bunch of system pte's */
80 	caddr_t utl;	/* The system address mapped through 'map' */
81 {
82 	register phadr, i;
83 
84 	if (bp->b_flags & B_NOT1K) {
85 		phadr = vtoph(bp->b_proc, (unsigned)v);
86 		if ((bp->b_flags & B_READ) == 0) {
87 			for (i=0; i<bp->b_ptecnt; i++) {
88 				map[i] = bp->b_upte[i]
89 					& ~PG_PROT | PG_V | PG_KR;
90 				mtpr(TBIS, utl + i*NBPG);
91 				mtpr(P1DC, utl + i*NBPG);
92 			}
93 			bcopy(((int)bp->b_un.b_addr & PGOFSET) + utl,
94 			    v, (unsigned)bp->b_bcount);
95 		}
96 	} else
97 		phadr = vtoph(bp->b_proc, (unsigned)bp->b_un.b_addr);
98 	return (phadr);
99 }
100 
101 /*
102  * Called by the driver's interrupt routine, after the data is
103  * realy in or out. If that was a read, and the NOT1K flag was on,
104  * now is the time to move the data back into user's space.
105  * Similar to the vbastart routine, but in the reverse direction.
106  */
107 vbadone(bp, v, map, utl)
108 	register struct buf *bp;
109 	caddr_t v;	/* Driver's own intermediate buffer. */
110 	long *map;	/* A bunch of system pte's */
111 	caddr_t utl;	/* The system address mapped through 'map' */
112 {
113 	register i, cnt;
114 
115 	if (bp->b_flags & B_READ)
116 		if (bp->b_flags & B_NOT1K) {
117 			for (cnt = bp->b_bcount ; cnt >= 0; cnt -= NBPG) {
118 				mtpr(P1DC, (int)v + cnt-1);
119 				mtpr(P1DC, (caddr_t)bp->b_un.b_addr + cnt-1);
120 			}
121 			if (((int)v & PGOFSET) != 0)
122 				mtpr(P1DC, v);
123 			if (((int)bp->b_un.b_addr & PGOFSET) != 0)
124 				mtpr(P1DC, (caddr_t)bp->b_un.b_addr);
125 			for (i=0; i<bp->b_ptecnt; i++) {
126 				map[i] = bp->b_upte[i]
127 					& ~PG_PROT | PG_V | PG_KW;
128 				mtpr(TBIS, utl + i*NBPG);
129 			}
130 			bcopy(v, ((int)bp->b_un.b_addr & PGOFSET)+utl,
131 			    (unsigned)bp->b_bcount);
132 		} else
133 			mtpr(P1DC, bp->b_un.b_addr);
134 	bp->b_flags &= ~B_NOT1K;
135 }
136