xref: /openbmc/linux/arch/sh/kernel/cpu/sh3/entry.S (revision b8bb76713ec50df2f11efee386e16f93d51e1076)
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/unistd.h>
17#include <cpu/mmu_context.h>
18#include <asm/page.h>
19#include <asm/cache.h>
20
21! NOTE:
22! GNU as (as of 2.9.1) changes bf/s into bt/s and bra, when the address
23! to be jumped is too far, but it causes illegal slot exception.
24
25/*
26 * entry.S contains the system-call and fault low-level handling routines.
27 * This also contains the timer-interrupt handler, as well as all interrupts
28 * and faults that can result in a task-switch.
29 *
30 * NOTE: This code handles signal-recognition, which happens every time
31 * after a timer-interrupt and after each system call.
32 *
33 * NOTE: This code uses a convention that instructions in the delay slot
34 * of a transfer-control instruction are indented by an extra space, thus:
35 *
36 *    jmp	@k0	    ! control-transfer instruction
37 *     ldc	k1, ssr     ! delay slot
38 *
39 * Stack layout in 'ret_from_syscall':
40 * 	ptrace needs to have all regs on the stack.
41 *	if the order here is changed, it needs to be
42 *	updated in ptrace.c and ptrace.h
43 *
44 *	r0
45 *      ...
46 *	r15 = stack pointer
47 *	spc
48 *	pr
49 *	ssr
50 *	gbr
51 *	mach
52 *	macl
53 *	syscall #
54 *
55 */
56#if defined(CONFIG_KGDB)
57NMI_VEC = 0x1c0			! Must catch early for debounce
58#endif
59
60/* Offsets to the stack */
61OFF_R0  =  0		/* Return value. New ABI also arg4 */
62OFF_R1  =  4     	/* New ABI: arg5 */
63OFF_R2  =  8     	/* New ABI: arg6 */
64OFF_R3  =  12     	/* New ABI: syscall_nr */
65OFF_R4  =  16     	/* New ABI: arg0 */
66OFF_R5  =  20     	/* New ABI: arg1 */
67OFF_R6  =  24     	/* New ABI: arg2 */
68OFF_R7  =  28     	/* New ABI: arg3 */
69OFF_SP	=  (15*4)
70OFF_PC  =  (16*4)
71OFF_SR	=  (16*4+8)
72OFF_TRA	=  (16*4+6*4)
73
74
75#define k0	r0
76#define k1	r1
77#define k2	r2
78#define k3	r3
79#define k4	r4
80
81#define g_imask		r6	/* r6_bank1 */
82#define k_g_imask	r6_bank	/* r6_bank1 */
83#define current		r7	/* r7_bank1 */
84
85#include <asm/entry-macros.S>
86
87/*
88 * Kernel mode register usage:
89 *	k0	scratch
90 *	k1	scratch
91 *	k2	scratch (Exception code)
92 *	k3	scratch (Return address)
93 *	k4	scratch
94 *	k5	reserved
95 *	k6	Global Interrupt Mask (0--15 << 4)
96 *	k7	CURRENT_THREAD_INFO (pointer to current thread info)
97 */
98
99!
100! TLB Miss / Initial Page write exception handling
101!			_and_
102! TLB hits, but the access violate the protection.
103! It can be valid access, such as stack grow and/or C-O-W.
104!
105!
106! Find the pmd/pte entry and loadtlb
107! If it's not found, cause address error (SEGV)
108!
109! Although this could be written in assembly language (and it'd be faster),
110! this first version depends *much* on C implementation.
111!
112
113#if defined(CONFIG_MMU)
114	.align	2
115ENTRY(tlb_miss_load)
116	bra	call_dpf
117	 mov	#0, r5
118
119	.align	2
120ENTRY(tlb_miss_store)
121	bra	call_dpf
122	 mov	#1, r5
123
124	.align	2
125ENTRY(initial_page_write)
126	bra	call_dpf
127	 mov	#1, r5
128
129	.align	2
130ENTRY(tlb_protection_violation_load)
131	bra	call_dpf
132	 mov	#0, r5
133
134	.align	2
135ENTRY(tlb_protection_violation_store)
136	bra	call_dpf
137	 mov	#1, r5
138
139call_dpf:
140	mov.l	1f, r0
141	mov	r5, r8
142	mov.l	@r0, r6
143	mov	r6, r9
144	mov.l	2f, r0
145	sts	pr, r10
146	jsr	@r0
147	 mov	r15, r4
148	!
149	tst	r0, r0
150	bf/s	0f
151	 lds	r10, pr
152	rts
153	 nop
1540:	mov.l	3f, r0
155	mov	r9, r6
156	mov	r8, r5
157	jmp	@r0
158	 mov	r15, r4
159
160	.align 2
1611:	.long	MMU_TEA
1622:	.long	__do_page_fault
1633:	.long	do_page_fault
164
165	.align	2
166ENTRY(address_error_load)
167	bra	call_dae
168	 mov	#0,r5		! writeaccess = 0
169
170	.align	2
171ENTRY(address_error_store)
172	bra	call_dae
173	 mov	#1,r5		! writeaccess = 1
174
175	.align	2
176call_dae:
177	mov.l	1f, r0
178	mov.l	@r0, r6		! address
179	mov.l	2f, r0
180	jmp	@r0
181	 mov	r15, r4		! regs
182
183	.align 2
1841:	.long	MMU_TEA
1852:	.long   do_address_error
186#endif /* CONFIG_MMU */
187
188#if defined(CONFIG_SH_STANDARD_BIOS)
189	/* Unwind the stack and jmp to the debug entry */
190ENTRY(sh_bios_handler)
191	mov.l	1f, r8
192	bsr	restore_regs
193	 nop
194
195	lds	k2, pr			! restore pr
196	mov	k4, r15
197	!
198	mov.l	2f, k0
199	mov.l	@k0, k0
200	jmp	@k0
201	 ldc	k3, ssr
202	.align	2
2031:	.long	0x300000f0
2042:	.long	gdb_vbr_vector
205#endif /* CONFIG_SH_STANDARD_BIOS */
206
207! restore_regs()
208! - restore r0, r1, r2, r3, r4, r5, r6, r7 from the stack
209! - switch bank
210! - restore r8, r9, r10, r11, r12, r13, r14, r15 from the stack
211! - restore spc, pr*, ssr, gbr, mach, macl, skip default tra
212! k2 returns original pr
213! k3 returns original sr
214! k4 returns original stack pointer
215! r8 passes SR bitmask, overwritten with restored data on return
216! r9 trashed
217! BL=0 on entry, on exit BL=1 (depending on r8).
218
219ENTRY(restore_regs)
220	mov.l	@r15+, r0
221	mov.l	@r15+, r1
222	mov.l	@r15+, r2
223	mov.l	@r15+, r3
224	mov.l	@r15+, r4
225	mov.l	@r15+, r5
226	mov.l	@r15+, r6
227	mov.l	@r15+, r7
228	!
229	stc	sr, r9
230	or	r8, r9
231	ldc	r9, sr
232	!
233	mov.l	@r15+, r8
234	mov.l	@r15+, r9
235	mov.l	@r15+, r10
236	mov.l	@r15+, r11
237	mov.l	@r15+, r12
238	mov.l	@r15+, r13
239	mov.l	@r15+, r14
240	mov.l	@r15+, k4		! original stack pointer
241	ldc.l	@r15+, spc
242	mov.l	@r15+, k2		! original PR
243	mov.l	@r15+, k3		! original SR
244	ldc.l	@r15+, gbr
245	lds.l	@r15+, mach
246	lds.l	@r15+, macl
247	rts
248	 add	#4, r15			! Skip syscall number
249
250restore_all:
251	mov.l	7f, r8
252	bsr	restore_regs
253	 nop
254
255	lds	k2, pr			! restore pr
256	!
257#ifdef CONFIG_SH_DSP
258	mov.l	@r15+, k0		! DSP mode marker
259	mov.l	5f, k1
260	cmp/eq	k0, k1			! Do we have a DSP stack frame?
261	bf	skip_restore
262
263	stc	sr, k0			! Enable CPU DSP mode
264	or	k1, k0			! (within kernel it may be disabled)
265	ldc	k0, sr
266	mov	r2, k0			! Backup r2
267
268	! Restore DSP registers from stack
269	mov	r15, r2
270	movs.l	@r2+, a1
271	movs.l	@r2+, a0g
272	movs.l	@r2+, a1g
273	movs.l	@r2+, m0
274	movs.l	@r2+, m1
275	mov	r2, r15
276
277	lds.l	@r15+, a0
278	lds.l	@r15+, x0
279	lds.l	@r15+, x1
280	lds.l	@r15+, y0
281	lds.l	@r15+, y1
282	lds.l	@r15+, dsr
283	ldc.l	@r15+, rs
284	ldc.l	@r15+, re
285	ldc.l	@r15+, mod
286
287	mov	k0, r2			! Restore r2
288skip_restore:
289#endif
290	!
291	! Calculate new SR value
292	mov	k3, k2			! original SR value
293	mov	#0xf0, k1
294	extu.b	k1, k1
295	not	k1, k1
296	and	k1, k2			! Mask original SR value
297	!
298	mov	k3, k0			! Calculate IMASK-bits
299	shlr2	k0
300	and	#0x3c, k0
301	cmp/eq	#0x3c, k0
302	bt/s	6f
303	 shll2	k0
304	mov	g_imask, k0
305	!
3066:	or	k0, k2			! Set the IMASK-bits
307	ldc	k2, ssr
308	!
309#if defined(CONFIG_KGDB)
310	! Clear in_nmi
311	mov.l	6f, k0
312	mov	#0, k1
313	mov.b	k1, @k0
314#endif
315	mov	k4, r15
316	rte
317	 nop
318
319	.align	2
3205:	.long	0x00001000	! DSP
321#ifdef CONFIG_KGDB
3226:	.long	in_nmi
323#endif
3247:	.long	0x30000000
325
326! common exception handler
327#include "../../entry-common.S"
328
329! Exception Vector Base
330!
331!	Should be aligned page boundary.
332!
333	.balign 	4096,0,4096
334ENTRY(vbr_base)
335	.long	0
336!
337! 0x100: General exception vector
338!
339	.balign 	256,0,256
340general_exception:
341#ifndef CONFIG_CPU_SUBTYPE_SHX3
342	bra	handle_exception
343	 sts	pr, k3		! save original pr value in k3
344#else
345	mov.l	1f, k4
346	mov.l	@k4, k4
347
348	! Is EXPEVT larger than 0x800?
349	mov	#0x8, k0
350	shll8	k0
351	cmp/hs	k0, k4
352	bf	0f
353
354	! then add 0x580 (k2 is 0xd80 or 0xda0)
355	mov	#0x58, k0
356	shll2	k0
357	shll2	k0
358	add	k0, k4
3590:
360	! Setup stack and save DSP context (k0 contains original r15 on return)
361	bsr	prepare_stack_save_dsp
362	 nop
363
364	! Save registers / Switch to bank 0
365	mov		k4, k2		! keep vector in k2
366	mov.l	1f, k4		! SR bits to clear in k4
367	bsr	save_regs	! needs original pr value in k3
368	 nop
369
370	bra	handle_exception_special
371	 nop
372
373	.align	2
3741:	.long	EXPEVT
375#endif
376
377! prepare_stack_save_dsp()
378! - roll back gRB
379! - switch to kernel stack
380! - save DSP
381! k0 returns original sp (after roll back)
382! k1 trashed
383! k2 trashed
384
385prepare_stack_save_dsp:
386#ifdef CONFIG_GUSA
387	! Check for roll back gRB (User and Kernel)
388	mov	r15, k0
389	shll	k0
390	bf/s	1f
391	 shll	k0
392	bf/s	1f
393	 stc	spc, k1
394	stc	r0_bank, k0
395	cmp/hs	k0, k1		! test k1 (saved PC) >= k0 (saved r0)
396	bt/s	2f
397	 stc	r1_bank, k1
398
399	add	#-2, k0
400	add	r15, k0
401	ldc	k0, spc		! PC = saved r0 + r15 - 2
4022:	mov	k1, r15		! SP = r1
4031:
404#endif
405	! Switch to kernel stack if needed
406	stc	ssr, k0		! Is it from kernel space?
407	shll	k0		! Check MD bit (bit30) by shifting it into...
408	shll	k0		!       ...the T bit
409	bt/s	1f		! It's a kernel to kernel transition.
410	 mov	r15, k0		! save original stack to k0
411	/* User space to kernel */
412	mov	#(THREAD_SIZE >> 10), k1
413	shll8	k1		! k1 := THREAD_SIZE
414	shll2	k1
415	add	current, k1
416	mov	k1, r15		! change to kernel stack
417	!
4181:
419#ifdef CONFIG_SH_DSP
420	! Save DSP context if needed
421	stc	sr, k1
422	mov	#0x10, k2
423	shll8   k2			! DSP=1 (0x00001000)
424	tst	k2, k1			! Check if in DSP mode (passed in k2)
425	bt/s	skip_save
426	 mov	#0, k1			! Set marker for no stack frame
427
428	mov	k2, k1			! Save has-frame marker
429
430	! Save DSP registers on stack
431	stc.l	mod, @-r15
432	stc.l	re, @-r15
433	stc.l	rs, @-r15
434	sts.l	dsr, @-r15
435	sts.l	y1, @-r15
436	sts.l	y0, @-r15
437	sts.l	x1, @-r15
438	sts.l	x0, @-r15
439	sts.l	a0, @-r15
440
441	! GAS is broken, does not generate correct "movs.l Ds,@-As" instr.
442
443	! FIXME: Make sure that this is still the case with newer toolchains,
444	! as we're not at all interested in supporting ancient toolchains at
445	! this point. -- PFM.
446
447	mov	r15, k2
448	.word	0xf653			! movs.l	a1, @-r2
449	.word	0xf6f3			! movs.l	a0g, @-r2
450	.word	0xf6d3			! movs.l	a1g, @-r2
451	.word	0xf6c3			! movs.l	m0, @-r2
452	.word	0xf6e3			! movs.l	m1, @-r2
453	mov	k2, r15
454
455skip_save:
456	mov.l	k1, @-r15		! Push DSP mode marker onto stack
457#endif
458	rts
459	 nop
460!
461! 0x400: Instruction and Data TLB miss exception vector
462!
463	.balign 	1024,0,1024
464tlb_miss:
465	sts	pr, k3		! save original pr value in k3
466
467handle_exception:
468	mova	exception_data, k0
469
470	! Setup stack and save DSP context (k0 contains original r15 on return)
471	bsr	prepare_stack_save_dsp
472	 PREF(k0)
473
474	! Save registers / Switch to bank 0
475	mov.l	5f, k2		! vector register address
476	mov.l	1f, k4		! SR bits to clear in k4
477	bsr	save_regs	! needs original pr value in k3
478	 mov.l	@k2, k2		! read out vector and keep in k2
479
480handle_exception_special:
481	! Setup return address and jump to exception handler
482	mov.l	7f, r9		! fetch return address
483	stc	r2_bank, r0	! k2 (vector)
484	mov.l	6f, r10
485	shlr2	r0
486	shlr	r0
487	mov.l	@(r0, r10), r10
488	jmp	@r10
489	 lds	r9, pr		! put return address in pr
490
491	.align	L1_CACHE_SHIFT
492
493! save_regs()
494! - save default tra, macl, mach, gbr, ssr, pr* and spc on the stack
495! - save r15*, r14, r13, r12, r11, r10, r9, r8 on the stack
496! - switch bank
497! - save r7, r6, r5, r4, r3, r2, r1, r0 on the stack
498! k0 contains original stack pointer*
499! k1 trashed
500! k3 passes original pr*
501! k4 passes SR bitmask
502! BL=1 on entry, on exit BL=0.
503
504ENTRY(save_regs)
505	mov	#-1, r1
506	mov.l	k1, @-r15	! set TRA (default: -1)
507	sts.l	macl, @-r15
508	sts.l	mach, @-r15
509	stc.l	gbr, @-r15
510	stc.l	ssr, @-r15
511	mov.l	k3, @-r15	! original pr in k3
512	stc.l	spc, @-r15
513
514	mov.l	k0, @-r15	! original stack pointer in k0
515	mov.l	r14, @-r15
516	mov.l	r13, @-r15
517	mov.l	r12, @-r15
518	mov.l	r11, @-r15
519	mov.l	r10, @-r15
520	mov.l	r9, @-r15
521	mov.l	r8, @-r15
522
523	mov.l	0f, k3		! SR bits to set in k3
524
525	! fall-through
526
527! save_low_regs()
528! - modify SR for bank switch
529! - save r7, r6, r5, r4, r3, r2, r1, r0 on the stack
530! k3 passes bits to set in SR
531! k4 passes bits to clear in SR
532
533ENTRY(save_low_regs)
534	stc	sr, r8
535	or	k3, r8
536	and	k4, r8
537	ldc	r8, sr
538
539	mov.l	r7, @-r15
540	mov.l	r6, @-r15
541	mov.l	r5, @-r15
542	mov.l	r4, @-r15
543	mov.l	r3, @-r15
544	mov.l	r2, @-r15
545	mov.l	r1, @-r15
546	rts
547	 mov.l	r0, @-r15
548
549!
550! 0x600: Interrupt / NMI vector
551!
552	.balign 	512,0,512
553ENTRY(handle_interrupt)
554#if defined(CONFIG_KGDB)
555	mov.l	2f, k2
556	! Debounce (filter nested NMI)
557	mov.l	@k2, k0
558	mov.l	9f, k1
559	cmp/eq	k1, k0
560	bf	11f
561	mov.l	10f, k1
562	tas.b	@k1
563	bt	11f
564	rte
565	 nop
566	.align	2
5679:	.long	NMI_VEC
56810:	.long	in_nmi
56911:
570#endif /* defined(CONFIG_KGDB) */
571	sts	pr, k3		! save original pr value in k3
572	mova	exception_data, k0
573
574	! Setup stack and save DSP context (k0 contains original r15 on return)
575	bsr	prepare_stack_save_dsp
576	 PREF(k0)
577
578	! Save registers / Switch to bank 0
579	mov.l	1f, k4		! SR bits to clear in k4
580	bsr	save_regs	! needs original pr value in k3
581	 mov	#-1, k2		! default vector kept in k2
582
583	! Setup return address and jump to do_IRQ
584	mov.l	4f, r9		! fetch return address
585	lds	r9, pr		! put return address in pr
586	mov.l	2f, r4
587	mov.l	3f, r9
588	mov.l	@r4, r4		! pass INTEVT vector as arg0
589	jmp	@r9
590	 mov	r15, r5		! pass saved registers as arg1
591
592ENTRY(exception_none)
593	rts
594	 nop
595
596	.align	L1_CACHE_SHIFT
597exception_data:
5980:	.long	0x000080f0	! FD=1, IMASK=15
5991:	.long	0xcfffffff	! RB=0, BL=0
6002:	.long	INTEVT
6013:	.long	do_IRQ
6024:	.long	ret_from_irq
6035:	.long	EXPEVT
6046:	.long	exception_handling_table
6057:	.long	ret_from_exception
606