• Home
  • History
  • Annotate
  • Line#
  • Navigate
  • Raw
  • Download
  • only in /asuswrt-rt-n18u-9.0.0.4.380.2695/release/src-rt-6.x.4708/linux/linux-2.6/arch/sparc/kernel/
1/*
2 * etrap.S: Sparc trap window preparation for entry into the
3 *          Linux kernel.
4 *
5 * Copyright (C) 1995 David S. Miller (davem@caip.rutgers.edu)
6 */
7
8#include <asm/head.h>
9#include <asm/asi.h>
10#include <asm/contregs.h>
11#include <asm/page.h>
12#include <asm/psr.h>
13#include <asm/ptrace.h>
14#include <asm/winmacro.h>
15#include <asm/asmmacro.h>
16#include <asm/thread_info.h>
17
18/* Registers to not touch at all. */
19#define t_psr        l0 /* Set by caller */
20#define t_pc         l1 /* Set by caller */
21#define t_npc        l2 /* Set by caller */
22#define t_wim        l3 /* Set by caller */
23#define t_twinmask   l4 /* Set at beginning of this entry routine. */
24#define t_kstack     l5 /* Set right before pt_regs frame is built */
25#define t_retpc      l6 /* If you change this, change winmacro.h header file */
26#define t_systable   l7 /* Never touch this, could be the syscall table ptr. */
27#define curptr       g6 /* Set after pt_regs frame is built */
28
29	.text
30	.align 4
31
32	/* SEVEN WINDOW PATCH INSTRUCTIONS */
33	.globl	tsetup_7win_patch1, tsetup_7win_patch2
34	.globl	tsetup_7win_patch3, tsetup_7win_patch4
35	.globl	tsetup_7win_patch5, tsetup_7win_patch6
36tsetup_7win_patch1:	sll	%t_wim, 0x6, %t_wim
37tsetup_7win_patch2:	and	%g2, 0x7f, %g2
38tsetup_7win_patch3:	and	%g2, 0x7f, %g2
39tsetup_7win_patch4:	and	%g1, 0x7f, %g1
40tsetup_7win_patch5:	sll	%t_wim, 0x6, %t_wim
41tsetup_7win_patch6:	and	%g2, 0x7f, %g2
42	/* END OF PATCH INSTRUCTIONS */
43
44	/* At trap time, interrupts and all generic traps do the
45	 * following:
46	 *
47	 * rd	%psr, %l0
48	 * b	some_handler
49	 * rd	%wim, %l3
50	 * nop
51	 *
52	 * Then 'some_handler' if it needs a trap frame (ie. it has
53	 * to call c-code and the trap cannot be handled in-window)
54	 * then it does the SAVE_ALL macro in entry.S which does
55	 *
56	 * sethi	%hi(trap_setup), %l4
57	 * jmpl		%l4 + %lo(trap_setup), %l6
58	 * nop
59	 */
60
61	/* 2 3 4  window number
62	 * -----
63	 * O T S  mnemonic
64	 *
65	 * O == Current window before trap
66	 * T == Window entered when trap occurred
67	 * S == Window we will need to save if (1<<T) == %wim
68	 *
69	 * Before execution gets here, it must be guaranteed that
70	 * %l0 contains trap time %psr, %l1 and %l2 contain the
71	 * trap pc and npc, and %l3 contains the trap time %wim.
72	 */
73
74	.globl	trap_setup, tsetup_patch1, tsetup_patch2
75	.globl	tsetup_patch3, tsetup_patch4
76	.globl	tsetup_patch5, tsetup_patch6
77trap_setup:
78	/* Calculate mask of trap window.  See if from user
79	 * or kernel and branch conditionally.
80	 */
81	mov	1, %t_twinmask
82	andcc	%t_psr, PSR_PS, %g0		 ! fromsupv_p = (psr & PSR_PS)
83	be	trap_setup_from_user		 ! nope, from user mode
84	 sll	%t_twinmask, %t_psr, %t_twinmask ! t_twinmask = (1 << psr)
85
86	/* From kernel, allocate more kernel stack and
87	 * build a pt_regs trap frame.
88	 */
89	sub	%fp, (STACKFRAME_SZ + TRACEREG_SZ), %t_kstack
90	STORE_PT_ALL(t_kstack, t_psr, t_pc, t_npc, g2)
91
92	/* See if we are in the trap window. */
93	andcc	%t_twinmask, %t_wim, %g0
94	bne	trap_setup_kernel_spill		! in trap window, clean up
95	 nop
96
97	/* Trap from kernel with a window available.
98	 * Just do it...
99	 */
100	jmpl	%t_retpc + 0x8, %g0	! return to caller
101	 mov	%t_kstack, %sp		! jump onto new stack
102
103trap_setup_kernel_spill:
104	ld	[%curptr + TI_UWINMASK], %g1
105	orcc	%g0, %g1, %g0
106	bne	trap_setup_user_spill	! there are some user windows, yuck
107	/* Spill from kernel, but only kernel windows, adjust
108	 * %wim and go.
109	 */
110	 srl	%t_wim, 0x1, %g2	! begin computation of new %wim
111tsetup_patch1:
112	sll	%t_wim, 0x7, %t_wim	! patched on 7 window Sparcs
113	or	%t_wim, %g2, %g2
114tsetup_patch2:
115	and	%g2, 0xff, %g2		! patched on 7 window Sparcs
116
117	save	%g0, %g0, %g0
118
119	/* Set new %wim value */
120	wr	%g2, 0x0, %wim
121
122	/* Save the kernel window onto the corresponding stack. */
123	STORE_WINDOW(sp)
124
125	restore	%g0, %g0, %g0
126
127	jmpl	%t_retpc + 0x8, %g0	! return to caller
128	 mov	%t_kstack, %sp		! and onto new kernel stack
129
130#define STACK_OFFSET (THREAD_SIZE - TRACEREG_SZ - STACKFRAME_SZ)
131
132trap_setup_from_user:
133	/* We can't use %curptr yet. */
134	LOAD_CURRENT(t_kstack, t_twinmask)
135
136	sethi	%hi(STACK_OFFSET), %t_twinmask
137	or	%t_twinmask, %lo(STACK_OFFSET), %t_twinmask
138	add	%t_kstack, %t_twinmask, %t_kstack
139
140	mov	1, %t_twinmask
141	sll	%t_twinmask, %t_psr, %t_twinmask ! t_twinmask = (1 << psr)
142
143	/* Build pt_regs frame. */
144	STORE_PT_ALL(t_kstack, t_psr, t_pc, t_npc, g2)
145
146	sethi	%hi(~(THREAD_SIZE - 1)), %curptr
147	and	%t_kstack, %curptr, %curptr
148
149	/* Clear current_thread_info->w_saved */
150	st	%g0, [%curptr + TI_W_SAVED]
151
152	/* See if we are in the trap window. */
153	andcc	%t_twinmask, %t_wim, %g0
154	bne	trap_setup_user_spill		! yep we are
155	 orn	%g0, %t_twinmask, %g1		! negate trap win mask into %g1
156
157	/* Trap from user, but not into the invalid window.
158	 * Calculate new umask.  The way this works is,
159	 * any window from the %wim at trap time until
160	 * the window right before the one we are in now,
161	 * is a user window.  A diagram:
162	 *
163	 *      7 6 5 4 3 2 1 0    window number
164	 *      ---------------
165	 *        I     L T        mnemonic
166	 *
167	 * Window 'I' is the invalid window in our example,
168	 * window 'L' is the window the user was in when
169	 * the trap occurred, window T is the trap window
170	 * we are in now.  So therefore, windows 5, 4 and
171	 * 3 are user windows.  The following sequence
172	 * computes the user winmask to represent this.
173	 */
174	subcc	%t_wim, %t_twinmask, %g2
175	bneg,a	1f
176	 sub	%g2, 0x1, %g2
1771:
178	andn	%g2, %t_twinmask, %g2
179tsetup_patch3:
180	and	%g2, 0xff, %g2			! patched on 7win Sparcs
181	st	%g2, [%curptr + TI_UWINMASK]	! store new umask
182
183	jmpl	%t_retpc + 0x8, %g0		! return to caller
184	 mov	%t_kstack, %sp			! and onto kernel stack
185
186trap_setup_user_spill:
187	/* A spill occurred from either kernel or user mode
188	 * and there exist some user windows to deal with.
189	 * A mask of the currently valid user windows
190	 * is in %g1 upon entry to here.
191	 */
192
193tsetup_patch4:
194	and	%g1, 0xff, %g1		! patched on 7win Sparcs, mask
195	srl	%t_wim, 0x1, %g2	! compute new %wim
196tsetup_patch5:
197	sll	%t_wim, 0x7, %t_wim	! patched on 7win Sparcs
198	or	%t_wim, %g2, %g2	! %g2 is new %wim
199tsetup_patch6:
200	and	%g2, 0xff, %g2		! patched on 7win Sparcs
201	andn	%g1, %g2, %g1		! clear this bit in %g1
202	st	%g1, [%curptr + TI_UWINMASK]
203
204	save	%g0, %g0, %g0
205
206	wr	%g2, 0x0, %wim
207
208	/* Call MMU-architecture dependent stack checking
209	 * routine.
210	 */
211	.globl	tsetup_mmu_patchme
212tsetup_mmu_patchme:
213	b	tsetup_sun4c_stackchk
214	 andcc	%sp, 0x7, %g0
215
216	/* Architecture specific stack checking routines.  When either
217	 * of these routines are called, the globals are free to use
218	 * as they have been safely stashed on the new kernel stack
219	 * pointer.  Thus the definition below for simplicity.
220	 */
221#define glob_tmp     g1
222
223tsetup_sun4c_stackchk:
224	/* Done by caller: andcc %sp, 0x7, %g0 */
225	bne	trap_setup_user_stack_is_bolixed
226	 sra	%sp, 29, %glob_tmp
227
228	add	%glob_tmp, 0x1, %glob_tmp
229	andncc	%glob_tmp, 0x1, %g0
230	bne	trap_setup_user_stack_is_bolixed
231	 and	%sp, 0xfff, %glob_tmp		! delay slot
232
233	/* See if our dump area will be on more than one
234	 * page.
235	 */
236	add	%glob_tmp, 0x38, %glob_tmp
237	andncc	%glob_tmp, 0xff8, %g0
238	be	tsetup_sun4c_onepage		! only one page to check
239	 lda	[%sp] ASI_PTE, %glob_tmp	! have to check first page anyways
240
241tsetup_sun4c_twopages:
242	/* Is first page ok permission wise? */
243	srl	%glob_tmp, 29, %glob_tmp
244	cmp	%glob_tmp, 0x6
245	bne	trap_setup_user_stack_is_bolixed
246	 add	%sp, 0x38, %glob_tmp		/* Is second page in vma hole? */
247
248	sra	%glob_tmp, 29, %glob_tmp
249	add	%glob_tmp, 0x1, %glob_tmp
250	andncc	%glob_tmp, 0x1, %g0
251	bne	trap_setup_user_stack_is_bolixed
252	 add	%sp, 0x38, %glob_tmp
253
254	lda	[%glob_tmp] ASI_PTE, %glob_tmp
255
256tsetup_sun4c_onepage:
257	srl	%glob_tmp, 29, %glob_tmp
258	cmp	%glob_tmp, 0x6				! can user write to it?
259	bne	trap_setup_user_stack_is_bolixed	! failure
260	 nop
261
262	STORE_WINDOW(sp)
263
264	restore %g0, %g0, %g0
265
266	jmpl	%t_retpc + 0x8, %g0
267	 mov	%t_kstack, %sp
268
269	.globl	tsetup_srmmu_stackchk
270tsetup_srmmu_stackchk:
271	/* Check results of callers andcc %sp, 0x7, %g0 */
272	bne	trap_setup_user_stack_is_bolixed
273	 sethi   %hi(PAGE_OFFSET), %glob_tmp
274
275	cmp	%glob_tmp, %sp
276	bleu,a	1f
277	 lda	[%g0] ASI_M_MMUREGS, %glob_tmp		! read MMU control
278
279trap_setup_user_stack_is_bolixed:
280	/* From user/kernel into invalid window w/bad user
281	 * stack. Save bad user stack, and return to caller.
282	 */
283	SAVE_BOLIXED_USER_STACK(curptr, g3)
284	restore	%g0, %g0, %g0
285
286	jmpl	%t_retpc + 0x8, %g0
287	 mov	%t_kstack, %sp
288
2891:
290	/* Clear the fault status and turn on the no_fault bit. */
291	or	%glob_tmp, 0x2, %glob_tmp		! or in no_fault bit
292	sta	%glob_tmp, [%g0] ASI_M_MMUREGS		! set it
293
294	/* Dump the registers and cross fingers. */
295	STORE_WINDOW(sp)
296
297	/* Clear the no_fault bit and check the status. */
298	andn	%glob_tmp, 0x2, %glob_tmp
299	sta	%glob_tmp, [%g0] ASI_M_MMUREGS
300	mov	AC_M_SFAR, %glob_tmp
301	lda	[%glob_tmp] ASI_M_MMUREGS, %g0
302	mov	AC_M_SFSR, %glob_tmp
303	lda	[%glob_tmp] ASI_M_MMUREGS, %glob_tmp	! save away status of winstore
304	andcc	%glob_tmp, 0x2, %g0			! did we fault?
305	bne	trap_setup_user_stack_is_bolixed	! failure
306	 nop
307
308	restore %g0, %g0, %g0
309
310	jmpl	%t_retpc + 0x8, %g0
311	 mov	%t_kstack, %sp
312