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