1/* $Id: wof.S,v 1.1.1.1 2007-08-03 18:52:17 $
2 * wof.S: Sparc window overflow handler.
3 *
4 * Copyright (C) 1995 David S. Miller (davem@caip.rutgers.edu)
5 */
6
7#include <asm/contregs.h>
8#include <asm/page.h>
9#include <asm/ptrace.h>
10#include <asm/psr.h>
11#include <asm/smp.h>
12#include <asm/asi.h>
13#include <asm/winmacro.h>
14#include <asm/asmmacro.h>
15#include <asm/thread_info.h>
16
17/* WARNING: This routine is hairy and _very_ complicated, but it
18 *          must be as fast as possible as it handles the allocation
19 *          of register windows to the user and kernel.  If you touch
20 *          this code be _very_ careful as many other pieces of the
21 *          kernel depend upon how this code behaves.  You have been
22 *          duly warned...
23 */
24
25/* We define macro's for registers which have a fixed
26 * meaning throughout this entire routine.  The 'T' in
27 * the comments mean that the register can only be
28 * accessed when in the 'trap' window, 'G' means
29 * accessible in any window.  Do not change these registers
30 * after they have been set, until you are ready to return
31 * from the trap.
32 */
33#define t_psr       l0 /* %psr at trap time                     T */
34#define t_pc        l1 /* PC for trap return                    T */
35#define t_npc       l2 /* NPC for trap return                   T */
36#define t_wim       l3 /* %wim at trap time                     T */
37#define saved_g5    l5 /* Global save register                  T */
38#define saved_g6    l6 /* Global save register                  T */
39#define curptr      g6 /* Gets set to 'current' then stays      G */
40
41/* Now registers whose values can change within the handler.      */
42#define twin_tmp    l4 /* Temp reg, only usable in trap window  T */
43#define glob_tmp    g5 /* Global temporary reg, usable anywhere G */
44
45	.text
46	.align	4
47	/* BEGINNING OF PATCH INSTRUCTIONS */
48	/* On a 7-window Sparc the boot code patches spnwin_*
49	 * instructions with the following ones.
50	 */
51	.globl	spnwin_patch1_7win, spnwin_patch2_7win, spnwin_patch3_7win
52spnwin_patch1_7win:	sll	%t_wim, 6, %glob_tmp
53spnwin_patch2_7win:	and	%glob_tmp, 0x7f, %glob_tmp
54spnwin_patch3_7win:	and	%twin_tmp, 0x7f, %twin_tmp
55	/* END OF PATCH INSTRUCTIONS */
56
57	/* The trap entry point has done the following:
58	 *
59	 * rd    %psr, %l0
60	 * rd    %wim, %l3
61	 * b     spill_window_entry
62	 * andcc %l0, PSR_PS, %g0
63	 */
64
65	/* Datum current_thread_info->uwinmask contains at all times a bitmask
66	 * where if any user windows are active, at least one bit will
67	 * be set in to mask.  If no user windows are active, the bitmask
68	 * will be all zeroes.
69	 */
70	.globl	spill_window_entry
71	.globl	spnwin_patch1, spnwin_patch2, spnwin_patch3
72spill_window_entry:
73	/* LOCATION: Trap Window */
74
75	mov	%g5, %saved_g5		! save away global temp register
76	mov	%g6, %saved_g6		! save away 'current' ptr register
77
78	/* Compute what the new %wim will be if we save the
79	 * window properly in this trap handler.
80	 *
81	 * newwim = ((%wim>>1) | (%wim<<(nwindows - 1)));
82	 */
83		srl	%t_wim, 0x1, %twin_tmp
84spnwin_patch1:	sll	%t_wim, 7, %glob_tmp
85		or	%glob_tmp, %twin_tmp, %glob_tmp
86spnwin_patch2:	and	%glob_tmp, 0xff, %glob_tmp
87
88	/* The trap entry point has set the condition codes
89	 * up for us to see if this is from user or kernel.
90	 * Get the load of 'curptr' out of the way.
91	 */
92	LOAD_CURRENT(curptr, twin_tmp)
93
94	andcc	%t_psr, PSR_PS, %g0
95	be,a	spwin_fromuser				! all user wins, branch
96	 save	%g0, %g0, %g0				! Go where saving will occur
97
98	/* See if any user windows are active in the set. */
99	ld	[%curptr + TI_UWINMASK], %twin_tmp	! grab win mask
100	orcc	%g0, %twin_tmp, %g0			! check for set bits
101	bne	spwin_exist_uwins			! yep, there are some
102	 andn	%twin_tmp, %glob_tmp, %twin_tmp		! compute new uwinmask
103
104	/* Save into the window which must be saved and do it.
105	 * Basically if we are here, this means that we trapped
106	 * from kernel mode with only kernel windows in the register
107	 * file.
108	 */
109	save	%g0, %g0, %g0		! save into the window to stash away
110	wr	%glob_tmp, 0x0, %wim	! set new %wim, this is safe now
111
112spwin_no_userwins_from_kernel:
113	/* LOCATION: Window to be saved */
114
115	STORE_WINDOW(sp)		! stash the window
116	restore	%g0, %g0, %g0		! go back into trap window
117
118	/* LOCATION: Trap window */
119	mov	%saved_g5, %g5		! restore %glob_tmp
120	mov	%saved_g6, %g6		! restore %curptr
121	wr	%t_psr, 0x0, %psr	! restore condition codes in %psr
122	WRITE_PAUSE			! waste some time
123	jmp	%t_pc			! Return from trap
124	rett	%t_npc			! we are done
125
126spwin_exist_uwins:
127	/* LOCATION: Trap window */
128
129	/* Wow, user windows have to be dealt with, this is dirty
130	 * and messy as all hell.  And difficult to follow if you
131	 * are approaching the infamous register window trap handling
132	 * problem for the first time. DON'T LOOK!
133	 *
134	 * Note that how the execution path works out, the new %wim
135	 * will be left for us in the global temporary register,
136	 * %glob_tmp.  We cannot set the new %wim first because we
137	 * need to save into the appropriate window without inducing
138	 * a trap (traps are off, we'd get a watchdog wheee)...
139	 * But first, store the new user window mask calculated
140	 * above.
141	 */
142	st	%twin_tmp, [%curptr + TI_UWINMASK]
143	save	%g0, %g0, %g0		! Go to where the saving will occur
144
145spwin_fromuser:
146	/* LOCATION: Window to be saved */
147	wr	%glob_tmp, 0x0, %wim	! Now it is safe to set new %wim
148
149	/* LOCATION: Window to be saved */
150
151	/* This instruction branches to a routine which will check
152	 * to validity of the users stack pointer by whatever means
153	 * are necessary.  This means that this is architecture
154	 * specific and thus this branch instruction will need to
155	 * be patched at boot time once the machine type is known.
156	 * This routine _shall not_ touch %curptr under any
157	 * circumstances whatsoever!  It will branch back to the
158	 * label 'spwin_good_ustack' if the stack is ok but still
159	 * needs to be dumped (SRMMU for instance will not need to
160	 * do this) or 'spwin_finish_up' if the stack is ok and the
161	 * registers have already been saved.  If the stack is found
162	 * to be bogus for some reason the routine shall branch to
163	 * the label 'spwin_user_stack_is_bolixed' which will take
164	 * care of things at that point.
165	 */
166	.globl	spwin_mmu_patchme
167spwin_mmu_patchme:	b	spwin_sun4c_stackchk
168				 andcc	%sp, 0x7, %g0
169
170spwin_good_ustack:
171	/* LOCATION: Window to be saved */
172
173	/* The users stack is ok and we can safely save it at
174	 * %sp.
175	 */
176	STORE_WINDOW(sp)
177
178spwin_finish_up:
179	restore	%g0, %g0, %g0		/* Back to trap window. */
180
181	/* LOCATION: Trap window */
182
183	/* We have spilled successfully, and we have properly stored
184	 * the appropriate window onto the stack.
185	 */
186
187	/* Restore saved globals */
188	mov	%saved_g5, %g5
189	mov	%saved_g6, %g6
190
191	wr	%t_psr, 0x0, %psr
192	WRITE_PAUSE
193	jmp	%t_pc
194	rett	%t_npc
195
196spwin_user_stack_is_bolixed:
197	/* LOCATION: Window to be saved */
198
199	/* Wheee, user has trashed his/her stack.  We have to decide
200	 * how to proceed based upon whether we came from kernel mode
201	 * or not.  If we came from kernel mode, toss the window into
202	 * a special buffer and proceed, the kernel _needs_ a window
203	 * and we could be in an interrupt handler so timing is crucial.
204	 * If we came from user land we build a full stack frame and call
205	 * c-code to gun down the process.
206	 */
207	rd	%psr, %glob_tmp
208	andcc	%glob_tmp, PSR_PS, %g0
209	bne	spwin_bad_ustack_from_kernel
210	 nop
211
212	/* Oh well, throw this one window into the per-task window
213	 * buffer, the first one.
214	 */
215	st	%sp, [%curptr + TI_RWIN_SPTRS]
216	STORE_WINDOW(curptr + TI_REG_WINDOW)
217	restore	%g0, %g0, %g0
218
219	/* LOCATION: Trap Window */
220
221	/* Back in the trap window, update winbuffer save count. */
222	mov	1, %twin_tmp
223	st	%twin_tmp, [%curptr + TI_W_SAVED]
224
225		/* Compute new user window mask.  What we are basically
226		 * doing is taking two windows, the invalid one at trap
227		 * time and the one we attempted to throw onto the users
228		 * stack, and saying that everything else is an ok user
229		 * window.  umask = ((~(%t_wim | %wim)) & valid_wim_bits)
230		 */
231		rd	%wim, %twin_tmp
232		or	%twin_tmp, %t_wim, %twin_tmp
233		not	%twin_tmp
234spnwin_patch3:	and	%twin_tmp, 0xff, %twin_tmp	! patched on 7win Sparcs
235		st	%twin_tmp, [%curptr + TI_UWINMASK]
236
237#define STACK_OFFSET (THREAD_SIZE - TRACEREG_SZ - STACKFRAME_SZ)
238
239	sethi	%hi(STACK_OFFSET), %sp
240	or	%sp, %lo(STACK_OFFSET), %sp
241	add	%curptr, %sp, %sp
242
243	/* Restore the saved globals and build a pt_regs frame. */
244	mov	%saved_g5, %g5
245	mov	%saved_g6, %g6
246	STORE_PT_ALL(sp, t_psr, t_pc, t_npc, g1)
247
248	sethi	%hi(STACK_OFFSET), %g6
249	or	%g6, %lo(STACK_OFFSET), %g6
250	sub	%sp, %g6, %g6		! curptr
251
252	/* Turn on traps and call c-code to deal with it. */
253	wr	%t_psr, PSR_ET, %psr
254	nop
255	call	window_overflow_fault
256	 nop
257
258	/* Return from trap if C-code actually fixes things, if it
259	 * doesn't then we never get this far as the process will
260	 * be given the look of death from Commander Peanut.
261	 */
262	b	ret_trap_entry
263	 clr	%l6
264
265spwin_bad_ustack_from_kernel:
266	/* LOCATION: Window to be saved */
267
268	/* The kernel provoked a spill window trap, but the window we
269	 * need to save is a user one and the process has trashed its
270	 * stack pointer.  We need to be quick, so we throw it into
271	 * a per-process window buffer until we can properly handle
272	 * this later on.
273	 */
274	SAVE_BOLIXED_USER_STACK(curptr, glob_tmp)
275	restore	%g0, %g0, %g0
276
277	/* LOCATION: Trap window */
278
279	/* Restore globals, condition codes in the %psr and
280	 * return from trap.  Note, restoring %g6 when returning
281	 * to kernel mode is not necessarily these days. ;-)
282	 */
283	mov	%saved_g5, %g5
284	mov	%saved_g6, %g6
285
286	wr	%t_psr, 0x0, %psr
287	WRITE_PAUSE
288
289	jmp	%t_pc
290	rett	%t_npc
291
292/* Undefine the register macros which would only cause trouble
293 * if used below.  This helps find 'stupid' coding errors that
294 * produce 'odd' behavior.  The routines below are allowed to
295 * make usage of glob_tmp and t_psr so we leave them defined.
296 */
297#undef twin_tmp
298#undef curptr
299#undef t_pc
300#undef t_npc
301#undef t_wim
302#undef saved_g5
303#undef saved_g6
304
305/* Now come the per-architecture window overflow stack checking routines.
306 * As noted above %curptr cannot be touched by this routine at all.
307 */
308
309	.globl	spwin_sun4c_stackchk
310spwin_sun4c_stackchk:
311	/* LOCATION: Window to be saved on the stack */
312
313	/* See if the stack is in the address space hole but first,
314	 * check results of callers andcc %sp, 0x7, %g0
315	 */
316	be	1f
317	 sra	%sp, 29, %glob_tmp
318
319	rd	%psr, %glob_tmp
320	b	spwin_user_stack_is_bolixed + 0x4
321	 nop
322
3231:
324	add	%glob_tmp, 0x1, %glob_tmp
325	andncc	%glob_tmp, 0x1, %g0
326	be	1f
327	 and	%sp, 0xfff, %glob_tmp		! delay slot
328
329	rd	%psr, %glob_tmp
330	b	spwin_user_stack_is_bolixed + 0x4
331	 nop
332
333	/* See if our dump area will be on more than one
334	 * page.
335	 */
3361:
337	add	%glob_tmp, 0x38, %glob_tmp
338	andncc	%glob_tmp, 0xff8, %g0
339	be	spwin_sun4c_onepage		! only one page to check
340	 lda	[%sp] ASI_PTE, %glob_tmp	! have to check first page anyways
341
342spwin_sun4c_twopages:
343	/* Is first page ok permission wise? */
344	srl	%glob_tmp, 29, %glob_tmp
345	cmp	%glob_tmp, 0x6
346	be	1f
347	 add	%sp, 0x38, %glob_tmp	/* Is second page in vma hole? */
348
349	rd	%psr, %glob_tmp
350	b	spwin_user_stack_is_bolixed + 0x4
351	 nop
352
3531:
354	sra	%glob_tmp, 29, %glob_tmp
355	add	%glob_tmp, 0x1, %glob_tmp
356	andncc	%glob_tmp, 0x1, %g0
357	be	1f
358	 add	%sp, 0x38, %glob_tmp
359
360	rd	%psr, %glob_tmp
361	b	spwin_user_stack_is_bolixed + 0x4
362	 nop
363
3641:
365	lda	[%glob_tmp] ASI_PTE, %glob_tmp
366
367spwin_sun4c_onepage:
368	srl	%glob_tmp, 29, %glob_tmp
369	cmp	%glob_tmp, 0x6				! can user write to it?
370	be	spwin_good_ustack			! success
371	 nop
372
373	rd	%psr, %glob_tmp
374	b	spwin_user_stack_is_bolixed + 0x4
375	 nop
376
377	/* This is a generic SRMMU routine.  As far as I know this
378	 * works for all current v8/srmmu implementations, we'll
379	 * see...
380	 */
381	.globl	spwin_srmmu_stackchk
382spwin_srmmu_stackchk:
383	/* LOCATION: Window to be saved on the stack */
384
385	/* Because of SMP concerns and speed we play a trick.
386	 * We disable fault traps in the MMU control register,
387	 * Execute the stores, then check the fault registers
388	 * to see what happens.  I can hear Linus now
389	 * "disgusting... broken hardware...".
390	 *
391	 * But first, check to see if the users stack has ended
392	 * up in kernel vma, then we would succeed for the 'wrong'
393	 * reason... ;(  Note that the 'sethi' below assumes the
394	 * kernel is page aligned, which should always be the case.
395	 */
396	/* Check results of callers andcc %sp, 0x7, %g0 */
397	bne	spwin_user_stack_is_bolixed
398	 sethi   %hi(PAGE_OFFSET), %glob_tmp
399	cmp	%glob_tmp, %sp
400	bleu	spwin_user_stack_is_bolixed
401	 mov	AC_M_SFSR, %glob_tmp
402
403	/* Clear the fault status and turn on the no_fault bit. */
404	lda	[%glob_tmp] ASI_M_MMUREGS, %g0		! eat SFSR
405
406	lda	[%g0] ASI_M_MMUREGS, %glob_tmp		! read MMU control
407	or	%glob_tmp, 0x2, %glob_tmp		! or in no_fault bit
408	sta	%glob_tmp, [%g0] ASI_M_MMUREGS		! set it
409
410	/* Dump the registers and cross fingers. */
411	STORE_WINDOW(sp)
412
413	/* Clear the no_fault bit and check the status. */
414	andn	%glob_tmp, 0x2, %glob_tmp
415	sta	%glob_tmp, [%g0] ASI_M_MMUREGS
416
417	mov	AC_M_SFAR, %glob_tmp
418	lda	[%glob_tmp] ASI_M_MMUREGS, %g0
419
420	mov	AC_M_SFSR, %glob_tmp
421	lda	[%glob_tmp] ASI_M_MMUREGS, %glob_tmp
422	andcc	%glob_tmp, 0x2, %g0			! did we fault?
423	be,a	spwin_finish_up + 0x4			! cool beans, success
424	 restore %g0, %g0, %g0
425
426	rd	%psr, %glob_tmp
427	b	spwin_user_stack_is_bolixed + 0x4	! we faulted, ugh
428	 nop
429