xref: /linux/arch/sh/kernel/cpu/sh3/entry.S (revision aeb3f46252e26acdc60a1a8e31fb1ca6319d9a07)
1/*
2 * arch/sh/kernel/cpu/sh3/entry.S
3 *
4 *  Copyright (C) 1999, 2000, 2002  Niibe Yutaka
5 *  Copyright (C) 2003 - 2006  Paul Mundt
6 *
7 * This file is subject to the terms and conditions of the GNU General Public
8 * License.  See the file "COPYING" in the main directory of this archive
9 * for more details.
10 */
11#include <linux/sys.h>
12#include <linux/errno.h>
13#include <linux/linkage.h>
14#include <asm/asm-offsets.h>
15#include <asm/thread_info.h>
16#include <asm/cpu/mmu_context.h>
17#include <asm/unistd.h>
18
19! NOTE:
20! GNU as (as of 2.9.1) changes bf/s into bt/s and bra, when the address
21! to be jumped is too far, but it causes illegal slot exception.
22
23/*
24 * entry.S contains the system-call and fault low-level handling routines.
25 * This also contains the timer-interrupt handler, as well as all interrupts
26 * and faults that can result in a task-switch.
27 *
28 * NOTE: This code handles signal-recognition, which happens every time
29 * after a timer-interrupt and after each system call.
30 *
31 * NOTE: This code uses a convention that instructions in the delay slot
32 * of a transfer-control instruction are indented by an extra space, thus:
33 *
34 *    jmp	@k0	    ! control-transfer instruction
35 *     ldc	k1, ssr     ! delay slot
36 *
37 * Stack layout in 'ret_from_syscall':
38 * 	ptrace needs to have all regs on the stack.
39 *	if the order here is changed, it needs to be
40 *	updated in ptrace.c and ptrace.h
41 *
42 *	r0
43 *      ...
44 *	r15 = stack pointer
45 *	spc
46 *	pr
47 *	ssr
48 *	gbr
49 *	mach
50 *	macl
51 *	syscall #
52 *
53 */
54#if defined(CONFIG_KGDB_NMI)
55NMI_VEC = 0x1c0			! Must catch early for debounce
56#endif
57
58/* Offsets to the stack */
59OFF_R0  =  0		/* Return value. New ABI also arg4 */
60OFF_R1  =  4     	/* New ABI: arg5 */
61OFF_R2  =  8     	/* New ABI: arg6 */
62OFF_R3  =  12     	/* New ABI: syscall_nr */
63OFF_R4  =  16     	/* New ABI: arg0 */
64OFF_R5  =  20     	/* New ABI: arg1 */
65OFF_R6  =  24     	/* New ABI: arg2 */
66OFF_R7  =  28     	/* New ABI: arg3 */
67OFF_SP	=  (15*4)
68OFF_PC  =  (16*4)
69OFF_SR	=  (16*4+8)
70OFF_TRA	=  (16*4+6*4)
71
72
73#define k0	r0
74#define k1	r1
75#define k2	r2
76#define k3	r3
77#define k4	r4
78
79#define g_imask		r6	/* r6_bank1 */
80#define k_g_imask	r6_bank	/* r6_bank1 */
81#define current		r7	/* r7_bank1 */
82
83#include <asm/entry-macros.S>
84
85/*
86 * Kernel mode register usage:
87 *	k0	scratch
88 *	k1	scratch
89 *	k2	scratch (Exception code)
90 *	k3	scratch (Return address)
91 *	k4	scratch
92 *	k5	reserved
93 *	k6	Global Interrupt Mask (0--15 << 4)
94 *	k7	CURRENT_THREAD_INFO (pointer to current thread info)
95 */
96
97!
98! TLB Miss / Initial Page write exception handling
99!			_and_
100! TLB hits, but the access violate the protection.
101! It can be valid access, such as stack grow and/or C-O-W.
102!
103!
104! Find the pmd/pte entry and loadtlb
105! If it's not found, cause address error (SEGV)
106!
107! Although this could be written in assembly language (and it'd be faster),
108! this first version depends *much* on C implementation.
109!
110
111#if defined(CONFIG_MMU)
112	.align	2
113ENTRY(tlb_miss_load)
114	bra	call_dpf
115	 mov	#0, r5
116
117	.align	2
118ENTRY(tlb_miss_store)
119	bra	call_dpf
120	 mov	#1, r5
121
122	.align	2
123ENTRY(initial_page_write)
124	bra	call_dpf
125	 mov	#1, r5
126
127	.align	2
128ENTRY(tlb_protection_violation_load)
129	bra	call_dpf
130	 mov	#0, r5
131
132	.align	2
133ENTRY(tlb_protection_violation_store)
134	bra	call_dpf
135	 mov	#1, r5
136
137call_dpf:
138	mov.l	1f, r0
139	mov	r5, r8
140	mov.l	@r0, r6
141	mov	r6, r9
142	mov.l	2f, r0
143	sts	pr, r10
144	jsr	@r0
145	 mov	r15, r4
146	!
147	tst	r0, r0
148	bf/s	0f
149	 lds	r10, pr
150	rts
151	 nop
1520:	sti
153	mov.l	3f, r0
154	mov	r9, r6
155	mov	r8, r5
156	jmp	@r0
157	 mov	r15, r4
158
159	.align 2
1601:	.long	MMU_TEA
1612:	.long	__do_page_fault
1623:	.long	do_page_fault
163
164	.align	2
165ENTRY(address_error_load)
166	bra	call_dae
167	 mov	#0,r5		! writeaccess = 0
168
169	.align	2
170ENTRY(address_error_store)
171	bra	call_dae
172	 mov	#1,r5		! writeaccess = 1
173
174	.align	2
175call_dae:
176	mov.l	1f, r0
177	mov.l	@r0, r6		! address
178	mov.l	2f, r0
179	jmp	@r0
180	 mov	r15, r4		! regs
181
182	.align 2
1831:	.long	MMU_TEA
1842:	.long   do_address_error
185#endif /* CONFIG_MMU */
186
187#if defined(CONFIG_SH_STANDARD_BIOS)
188	/* Unwind the stack and jmp to the debug entry */
189ENTRY(sh_bios_handler)
190	mov.l	@r15+, r0
191	mov.l	@r15+, r1
192	mov.l	@r15+, r2
193	mov.l	@r15+, r3
194	mov.l	@r15+, r4
195	mov.l	@r15+, r5
196	mov.l	@r15+, r6
197	mov.l	@r15+, r7
198	stc	sr, r8
199	mov.l	1f, r9			! BL =1, RB=1, IMASK=0x0F
200	or	r9, r8
201	ldc	r8, sr			! here, change the register bank
202	mov.l	@r15+, r8
203	mov.l	@r15+, r9
204	mov.l	@r15+, r10
205	mov.l	@r15+, r11
206	mov.l	@r15+, r12
207	mov.l	@r15+, r13
208	mov.l	@r15+, r14
209	mov.l	@r15+, k0
210	ldc.l	@r15+, spc
211	lds.l	@r15+, pr
212	mov.l	@r15+, k1
213	ldc.l	@r15+, gbr
214	lds.l	@r15+, mach
215	lds.l	@r15+, macl
216	mov	k0, r15
217	!
218	mov.l	2f, k0
219	mov.l	@k0, k0
220	jmp	@k0
221	 ldc	k1, ssr
222	.align	2
2231:	.long	0x300000f0
2242:	.long	gdb_vbr_vector
225#endif /* CONFIG_SH_STANDARD_BIOS */
226
227restore_all:
228	mov.l	@r15+, r0
229	mov.l	@r15+, r1
230	mov.l	@r15+, r2
231	mov.l	@r15+, r3
232	mov.l	@r15+, r4
233	mov.l	@r15+, r5
234	mov.l	@r15+, r6
235	mov.l	@r15+, r7
236	!
237	stc	sr, r8
238	mov.l	7f, r9
239	or	r9, r8			! BL =1, RB=1
240	ldc	r8, sr			! here, change the register bank
241	!
242	mov.l	@r15+, r8
243	mov.l	@r15+, r9
244	mov.l	@r15+, r10
245	mov.l	@r15+, r11
246	mov.l	@r15+, r12
247	mov.l	@r15+, r13
248	mov.l	@r15+, r14
249	mov.l	@r15+, k4		! original stack pointer
250	ldc.l	@r15+, spc
251	lds.l	@r15+, pr
252	mov.l	@r15+, k3		! original SR
253	ldc.l	@r15+, gbr
254	lds.l	@r15+, mach
255	lds.l	@r15+, macl
256	add	#4, r15			! Skip syscall number
257	!
258#ifdef CONFIG_SH_DSP
259	mov.l	@r15+, k0		! DSP mode marker
260	mov.l	5f, k1
261	cmp/eq	k0, k1			! Do we have a DSP stack frame?
262	bf	skip_restore
263
264	stc	sr, k0			! Enable CPU DSP mode
265	or	k1, k0			! (within kernel it may be disabled)
266	ldc	k0, sr
267	mov	r2, k0			! Backup r2
268
269	! Restore DSP registers from stack
270	mov	r15, r2
271	movs.l	@r2+, a1
272	movs.l	@r2+, a0g
273	movs.l	@r2+, a1g
274	movs.l	@r2+, m0
275	movs.l	@r2+, m1
276	mov	r2, r15
277
278	lds.l	@r15+, a0
279	lds.l	@r15+, x0
280	lds.l	@r15+, x1
281	lds.l	@r15+, y0
282	lds.l	@r15+, y1
283	lds.l	@r15+, dsr
284	ldc.l	@r15+, rs
285	ldc.l	@r15+, re
286	ldc.l	@r15+, mod
287
288	mov	k0, r2			! Restore r2
289skip_restore:
290#endif
291	!
292	! Calculate new SR value
293	mov	k3, k2			! original SR value
294	mov	#0xf0, k1
295	extu.b	k1, k1
296	not	k1, k1
297	and	k1, k2			! Mask orignal SR value
298	!
299	mov	k3, k0			! Calculate IMASK-bits
300	shlr2	k0
301	and	#0x3c, k0
302	cmp/eq	#0x3c, k0
303	bt/s	6f
304	 shll2	k0
305	mov	g_imask, k0
306	!
3076:	or	k0, k2			! Set the IMASK-bits
308	ldc	k2, ssr
309	!
310#if defined(CONFIG_KGDB_NMI)
311	! Clear in_nmi
312	mov.l	6f, k0
313	mov	#0, k1
314	mov.b	k1, @k0
315#endif
316	mov.l	@r15+, k2		! restore EXPEVT
317	mov	k4, r15
318	rte
319	 nop
320
321	.align	2
3225:	.long	0x00001000	! DSP
323#ifdef CONFIG_KGDB_NMI
3246:	.long	in_nmi
325#endif
3267:	.long	0x30000000
327
328! common exception handler
329#include "../../entry-common.S"
330
331! Exception Vector Base
332!
333!	Should be aligned page boundary.
334!
335	.balign 	4096,0,4096
336ENTRY(vbr_base)
337	.long	0
338!
339	.balign 	256,0,256
340general_exception:
341	mov.l	1f, k2
342	mov.l	2f, k3
343#ifdef CONFIG_CPU_SUBTYPE_SHX3
344	mov.l	@k2, k2
345
346	! Is EXPEVT larger than 0x800?
347	mov	#0x8, k0
348	shll8	k0
349	cmp/hs	k0, k2
350	bf	0f
351
352	! then add 0x580 (k2 is 0xd80 or 0xda0)
353	mov	#0x58, k0
354	shll2	k0
355	shll2	k0
356	add	k0, k2
3570:
358	bra	handle_exception
359	 nop
360#else
361	bra	handle_exception
362	 mov.l	@k2, k2
363#endif
364	.align	2
3651:	.long	EXPEVT
3662:	.long	ret_from_exception
367!
368!
369
370	.balign 	1024,0,1024
371tlb_miss:
372	mov.l	1f, k2
373	mov.l	4f, k3
374	bra	handle_exception
375	 mov.l	@k2, k2
376!
377	.balign 	512,0,512
378interrupt:
379	mov.l	2f, k2
380	mov.l	3f, k3
381#if defined(CONFIG_KGDB_NMI)
382	! Debounce (filter nested NMI)
383	mov.l	@k2, k0
384	mov.l	5f, k1
385	cmp/eq	k1, k0
386	bf	0f
387	mov.l	6f, k1
388	tas.b	@k1
389	bt	0f
390	rte
391	 nop
392	.align	2
3935:	.long	NMI_VEC
3946:	.long	in_nmi
3950:
396#endif /* defined(CONFIG_KGDB_NMI) */
397	bra	handle_exception
398	 mov	#-1, k2		! interrupt exception marker
399
400	.align	2
4011:	.long	EXPEVT
4022:	.long	INTEVT
4033:	.long	ret_from_irq
4044:	.long	ret_from_exception
405
406!
407!
408	.align	2
409ENTRY(handle_exception)
410	! Using k0, k1 for scratch registers (r0_bank1, r1_bank),
411	! save all registers onto stack.
412	!
413	stc	ssr, k0		! Is it from kernel space?
414	shll	k0		! Check MD bit (bit30) by shifting it into...
415	shll	k0		!       ...the T bit
416	bt/s	1f		! It's a kernel to kernel transition.
417	 mov	r15, k0		! save original stack to k0
418	/* User space to kernel */
419	mov	#(THREAD_SIZE >> 10), k1
420	shll8	k1		! k1 := THREAD_SIZE
421	shll2	k1
422	add	current, k1
423	mov	k1, r15		! change to kernel stack
424	!
4251:	mov.l	2f, k1
426	!
427#ifdef CONFIG_SH_DSP
428	mov.l	r2, @-r15		! Save r2, we need another reg
429	stc	sr, k4
430	mov.l	1f, r2
431	tst	r2, k4			! Check if in DSP mode
432	mov.l	@r15+, r2		! Restore r2 now
433	bt/s	skip_save
434	 mov	#0, k4			! Set marker for no stack frame
435
436	mov	r2, k4			! Backup r2 (in k4) for later
437
438	! Save DSP registers on stack
439	stc.l	mod, @-r15
440	stc.l	re, @-r15
441	stc.l	rs, @-r15
442	sts.l	dsr, @-r15
443	sts.l	y1, @-r15
444	sts.l	y0, @-r15
445	sts.l	x1, @-r15
446	sts.l	x0, @-r15
447	sts.l	a0, @-r15
448
449	! GAS is broken, does not generate correct "movs.l Ds,@-As" instr.
450
451	! FIXME: Make sure that this is still the case with newer toolchains,
452	! as we're not at all interested in supporting ancient toolchains at
453	! this point. -- PFM.
454
455	mov	r15, r2
456	.word	0xf653			! movs.l	a1, @-r2
457	.word	0xf6f3			! movs.l	a0g, @-r2
458	.word	0xf6d3			! movs.l	a1g, @-r2
459	.word	0xf6c3			! movs.l	m0, @-r2
460	.word	0xf6e3			! movs.l	m1, @-r2
461	mov	r2, r15
462
463	mov	k4, r2			! Restore r2
464	mov.l	1f, k4			! Force DSP stack frame
465skip_save:
466	mov.l	k4, @-r15		! Push DSP mode marker onto stack
467#endif
468	! Save the user registers on the stack.
469	mov.l	k2, @-r15	! EXPEVT
470
471	mov	#-1, k4
472	mov.l	k4, @-r15	! set TRA (default: -1)
473	!
474	sts.l	macl, @-r15
475	sts.l	mach, @-r15
476	stc.l	gbr, @-r15
477	stc.l	ssr, @-r15
478	sts.l	pr, @-r15
479	stc.l	spc, @-r15
480	!
481	lds	k3, pr		! Set the return address to pr
482	!
483	mov.l	k0, @-r15	! save orignal stack
484	mov.l	r14, @-r15
485	mov.l	r13, @-r15
486	mov.l	r12, @-r15
487	mov.l	r11, @-r15
488	mov.l	r10, @-r15
489	mov.l	r9, @-r15
490	mov.l	r8, @-r15
491	!
492	stc	sr, r8		! Back to normal register bank, and
493	or	k1, r8		! Block all interrupts
494	mov.l	3f, k1
495	and	k1, r8		! ...
496	ldc	r8, sr		! ...changed here.
497	!
498	mov.l	r7, @-r15
499	mov.l	r6, @-r15
500	mov.l	r5, @-r15
501	mov.l	r4, @-r15
502	mov.l	r3, @-r15
503	mov.l	r2, @-r15
504	mov.l	r1, @-r15
505	mov.l	r0, @-r15
506
507	/*
508	 * This gets a bit tricky.. in the INTEVT case we don't want to use
509	 * the VBR offset as a destination in the jump call table, since all
510	 * of the destinations are the same. In this case, (interrupt) sets
511	 * a marker in r2 (now r2_bank since SR.RB changed), which we check
512	 * to determine the exception type. For all other exceptions, we
513	 * forcibly read EXPEVT from memory and fix up the jump address, in
514	 * the interrupt exception case we jump to do_IRQ() and defer the
515	 * INTEVT read until there. As a bonus, we can also clean up the SR.RB
516	 * checks that do_IRQ() was doing..
517	 */
518	stc	r2_bank, r8
519	cmp/pz	r8
520	bf	interrupt_exception
521	shlr2	r8
522	shlr	r8
523	mov.l	4f, r9
524	add	r8, r9
525	mov.l	@r9, r9
526	jmp	@r9
527	 nop
528	rts
529	 nop
530
531	.align	2
5321:	.long	0x00001000	! DSP=1
5332:	.long	0x000080f0	! FD=1, IMASK=15
5343:	.long	0xcfffffff	! RB=0, BL=0
5354:	.long	exception_handling_table
536
537interrupt_exception:
538	mov.l	1f, r9
539	mov.l	2f, r4
540	mov.l	@r4, r4
541	jmp	@r9
542	 mov	r15, r5
543	rts
544	 nop
545
546	.align 2
5471:	.long	do_IRQ
5482:	.long	INTEVT
549
550	.align	2
551ENTRY(exception_none)
552	rts
553	 nop
554