2014-11-06 10:19:38 +03:00
/ *
* linux/ a r c h / n i o s2 / k e r n e l / e n t r y . S
*
* Copyright ( C ) 2 0 1 3 - 2 0 1 4 A l t e r a C o r p o r a t i o n
* Copyright ( C ) 2 0 0 9 , W i n d R i v e r S y s t e m s I n c
*
* Implemented b y f r e d r i k . m a r k s t r o m @gmail.com and ivarholmqvist@gmail.com
*
* Copyright ( C ) 1 9 9 9 - 2 0 0 2 , G r e g U n g e r e r ( g e r g @snapgear.com)
* Copyright ( C ) 1 9 9 8 D . J e f f D i o n n e < j e f f @lineo.ca>,
* Kenneth A l b a n o w s k i < k j a h d s @kjahds.com>,
* Copyright ( C ) 2 0 0 0 L i n e o I n c . ( w w w . l i n e o . c o m )
* Copyright ( C ) 2 0 0 4 M i c r o t r o n i x D a t a c o m L t d .
*
* This f i l e i s s u b j e c t t o t h e t e r m s a n d c o n d i t i o n s o f t h e G N U G e n e r a l P u b l i c
* License. S e e t h e f i l e " C O P Y I N G " i n t h e m a i n d i r e c t o r y o f t h i s a r c h i v e
* for m o r e d e t a i l s .
*
* Linux/ m 6 8 k s u p p o r t b y H a m i s h M a c d o n a l d
*
* 6 8 0 6 0 fixes b y J e s p e r S k o v
* ColdFire s u p p o r t b y G r e g U n g e r e r ( g e r g @snapgear.com)
* 5 3 0 7 fixes b y D a v i d W . M i l l e r
* linux 2 . 4 s u p p o r t D a v i d M c C u l l o u g h < d a v i d m @snapgear.com>
* /
# include < l i n u x / s y s . h >
# include < l i n u x / l i n k a g e . h >
# include < a s m / a s m - o f f s e t s . h >
# include < a s m / a s m - m a c r o s . h >
# include < a s m / t h r e a d _ i n f o . h >
# include < a s m / e r r n o . h >
# include < a s m / s e t u p . h >
# include < a s m / e n t r y . h >
# include < a s m / u n i s t d . h >
# include < a s m / p r o c e s s o r . h >
.macro GET_THREAD_INFO reg
.if THREAD_SIZE & 0 xffff0 0 0 0
andhi \ r e g , s p , % h i ( ~ ( T H R E A D _ S I Z E - 1 ) )
.else
addi \ r e g , r0 , % l o ( ~ ( T H R E A D _ S I Z E - 1 ) )
and \ r e g , \ r e g , s p
.endif
.endm
.macro kuser_cmpxchg_check
/ *
* Make s u r e o u r u s e r s p a c e a t o m i c h e l p e r i s r e s t a r t e d i f i t w a s
* interrupted i n a c r i t i c a l r e g i o n .
* ea- 4 = a d d r e s s o f i n t e r r u p t e d i n s n ( e a m u s t b e p r e s e r v e d ) .
* sp = s a v e d r e g s .
* cmpxchg_ l d w = f i r s t c r i t i c a l i n s n , c m p x c h g _ s t w = l a s t c r i t i c a l i n s n .
* If e a < = c m p x c h g _ s t w a n d e a > c m p x c h g _ l d w t h e n s a v e d E A i s s e t t o
* cmpxchg_ l d w + 4 .
* /
/* et = cmpxchg_stw + 4 */
movui e t , ( K U S E R _ B A S E + 4 + ( c m p x c h g _ s t w - _ _ k u s e r _ h e l p e r _ s t a r t ) )
bgtu e a , e t , 1 f
subi e t , e t , ( c m p x c h g _ s t w - c m p x c h g _ l d w ) / * e t = c m p x c h g _ l d w + 4 * /
bltu e a , e t , 1 f
stw e t , P T _ E A ( s p ) / * f i x u p E A * /
mov e a , e t
1 :
.endm
.section .rodata
.align 4
exception_table :
.word unhandled_exception /* 0 - Reset */
.word unhandled_exception /* 1 - Processor-only Reset */
.word external_interrupt /* 2 - Interrupt */
.word handle_trap /* 3 - Trap Instruction */
.word instruction_trap /* 4 - Unimplemented instruction */
.word handle_illegal /* 5 - Illegal instruction */
.word handle_unaligned /* 6 - Misaligned data access */
.word handle_unaligned /* 7 - Misaligned destination address */
.word handle_diverror /* 8 - Division error */
.word protection_exception_ba /* 9 - Supervisor-only instr. address */
.word protection_exception_instr /* 10 - Supervisor only instruction */
.word protection_exception_ba /* 11 - Supervisor only data address */
.word unhandled_exception /* 12 - Double TLB miss (data) */
.word protection_exception_pte /* 13 - TLB permission violation (x) */
.word protection_exception_pte /* 14 - TLB permission violation (r) */
.word protection_exception_pte /* 15 - TLB permission violation (w) */
.word unhandled_exception /* 16 - MPU region violation */
trap_table :
.word handle_system_call /* 0 */
2015-04-16 10:19:01 +03:00
.word handle_trap_1 /* 1 */
.word handle_trap_2 /* 2 */
.word handle_trap_3 /* 3 */
.word handle_trap_reserved /* 4 */
.word handle_trap_reserved /* 5 */
.word handle_trap_reserved /* 6 */
.word handle_trap_reserved /* 7 */
.word handle_trap_reserved /* 8 */
.word handle_trap_reserved /* 9 */
.word handle_trap_reserved /* 10 */
.word handle_trap_reserved /* 11 */
.word handle_trap_reserved /* 12 */
.word handle_trap_reserved /* 13 */
.word handle_trap_reserved /* 14 */
.word handle_trap_reserved /* 15 */
.word handle_trap_reserved /* 16 */
.word handle_trap_reserved /* 17 */
.word handle_trap_reserved /* 18 */
.word handle_trap_reserved /* 19 */
.word handle_trap_reserved /* 20 */
.word handle_trap_reserved /* 21 */
.word handle_trap_reserved /* 22 */
.word handle_trap_reserved /* 23 */
.word handle_trap_reserved /* 24 */
.word handle_trap_reserved /* 25 */
.word handle_trap_reserved /* 26 */
.word handle_trap_reserved /* 27 */
.word handle_trap_reserved /* 28 */
.word handle_trap_reserved /* 29 */
2015-02-16 14:26:43 +03:00
# ifdef C O N F I G _ K G D B
.word handle_kgdb_breakpoint /* 30 KGDB breakpoint */
# else
.word instruction_trap /* 30 */
# endif
2014-11-06 10:19:38 +03:00
.word handle_breakpoint /* 31 */
.text
.set noat
.set nobreak
ENTRY( i n t h a n d l e r )
SAVE_ A L L
kuser_ c m p x c h g _ c h e c k
/ * Clear E H b i t b e f o r e w e g e t a n e w e x c p e t i o n i n t h e k e r n e l
* and a f t e r w e h a v e s a v e d i t t o t h e e x c e p t i o n f r a m e . T h i s i s d o n e
* whether i t ' s t r a p , t l b - m i s s o r i n t e r r u p t . I f w e d o n ' t d o t h i s
* estatus i s n o t u p d a t e d t h e n e x t e x c e p t i o n .
* /
rdctl r24 , s t a t u s
movi r9 , % l o ( ~ S T A T U S _ E H )
and r24 , r24 , r9
wrctl s t a t u s , r24
/* Read cause and vector and branch to the associated handler */
mov r4 , s p
rdctl r5 , e x c e p t i o n
movia r9 , e x c e p t i o n _ t a b l e
add r24 , r9 , r5
ldw r24 , 0 ( r24 )
jmp r24
/ * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
* Handle t r a p s
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
* /
ENTRY( h a n d l e _ t r a p )
2015-04-10 06:10:08 +03:00
ldwio r24 , - 4 ( e a ) / * i n s t r u c t i o n t h a t c a u s e d t h e e x c e p t i o n * /
2014-11-06 10:19:38 +03:00
srli r24 , r24 , 4
andi r24 , r24 , 0 x7 c
movia r9 ,t r a p _ t a b l e
add r24 , r24 , r9
ldw r24 , 0 ( r24 )
jmp r24
/ * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
* Handle s y s t e m c a l l s
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
* /
ENTRY( h a n d l e _ s y s t e m _ c a l l )
/* Enable interrupts */
rdctl r10 , s t a t u s
ori r10 , r10 , S T A T U S _ P I E
wrctl s t a t u s , r10
/* Reload registers destroyed by common code. */
ldw r4 , P T _ R 4 ( s p )
ldw r5 , P T _ R 5 ( s p )
local_restart :
/* Check that the requested system call is within limits */
movui r1 , _ _ N R _ s y s c a l l s
bgeu r2 , r1 , r e t _ i n v s y s c a l l
slli r1 , r2 , 2
movhi r11 , % h i a d j ( s y s _ c a l l _ t a b l e )
add r1 , r1 , r11
ldw r1 , % l o ( s y s _ c a l l _ t a b l e ) ( r1 )
beq r1 , r0 , r e t _ i n v s y s c a l l
/* Check if we are being traced */
GET_ T H R E A D _ I N F O r11
ldw r11 ,T I _ F L A G S ( r11 )
BTBNZ r11 ,r11 ,T I F _ S Y S C A L L _ T R A C E ,t r a c e d _ s y s t e m _ c a l l
/* Execute the system call */
callr r1
/ * If t h e s y s c a l l r e t u r n s a n e g a t i v e r e s u l t :
* Set r7 t o 1 t o i n d i c a t e e r r o r ,
* Negate r2 t o g e t a p o s i t i v e e r r o r c o d e
* If t h e s y s c a l l r e t u r n s z e r o o r a p o s i t i v e v a l u e :
* Set r7 t o 0 .
* The s i g r e t u r n s y s t e m c a l l s w i l l s k i p t h e c o d e b e l o w b y
* adding t o r e g i s t e r r a . T o a v o i d d e s t r o y i n g r e g i s t e r s
* /
translate_rc_and_ret :
movi r1 , 0
bge r2 , z e r o , 3 f
sub r2 , z e r o , r2
movi r1 , 1
3 :
stw r2 , P T _ R 2 ( s p )
stw r1 , P T _ R 7 ( s p )
end_translate_rc_and_ret :
ret_from_exception :
ldw r1 , P T _ E S T A T U S ( s p )
/* if so, skip resched, signals */
TSTBNZ r1 , r1 , E S T A T U S _ E U , L u s e r _ r e t u r n
restore_all :
rdctl r10 , s t a t u s / * d i s a b l e i n t r s * /
andi r10 , r10 , % l o ( ~ S T A T U S _ P I E )
wrctl s t a t u s , r10
RESTORE_ A L L
eret
/* If the syscall number was invalid return ENOSYS */
ret_invsyscall :
movi r2 , - E N O S Y S
br t r a n s l a t e _ r c _ a n d _ r e t
/ * This i m p l e m e n t s t h e s a m e a s a b o v e , e x c e p t i t c a l l s
* do_ s y s c a l l _ t r a c e _ e n t e r a n d d o _ s y s c a l l _ t r a c e _ e x i t b e f o r e a n d a f t e r t h e
* syscall i n o r d e r f o r u t i l i t i e s l i k e s t r a c e a n d g d b t o w o r k .
* /
traced_system_call :
SAVE_ S W I T C H _ S T A C K
call d o _ s y s c a l l _ t r a c e _ e n t e r
RESTORE_ S W I T C H _ S T A C K
/ * Create s y s t e m c a l l r e g i s t e r a r g u m e n t s . T h e 5 t h a n d 6 t h
arguments o n s t a c k a r e a l r e a d y i n p l a c e a t t h e b e g i n n i n g
of p t _ r e g s . * /
ldw r2 , P T _ R 2 ( s p )
ldw r4 , P T _ R 4 ( s p )
ldw r5 , P T _ R 5 ( s p )
ldw r6 , P T _ R 6 ( s p )
ldw r7 , P T _ R 7 ( s p )
/ * Fetch t h e s y s c a l l f u n c t i o n , w e d o n ' t n e e d t o c h e c k t h e b o u n d a r i e s
* since t h i s i s a l r e a d y d o n e .
* /
slli r1 , r2 , 2
movhi r11 ,% h i a d j ( s y s _ c a l l _ t a b l e )
add r1 , r1 , r11
ldw r1 , % l o ( s y s _ c a l l _ t a b l e ) ( r1 )
callr r1
/ * If t h e s y s c a l l r e t u r n s a n e g a t i v e r e s u l t :
* Set r7 t o 1 t o i n d i c a t e e r r o r ,
* Negate r2 t o g e t a p o s i t i v e e r r o r c o d e
* If t h e s y s c a l l r e t u r n s z e r o o r a p o s i t i v e v a l u e :
* Set r7 t o 0 .
* The s i g r e t u r n s y s t e m c a l l s w i l l s k i p t h e c o d e b e l o w b y
* adding t o r e g i s t e r r a . T o a v o i d d e s t r o y i n g r e g i s t e r s
* /
translate_rc_and_ret2 :
movi r1 , 0
bge r2 , z e r o , 4 f
sub r2 , z e r o , r2
movi r1 , 1
4 :
stw r2 , P T _ R 2 ( s p )
stw r1 , P T _ R 7 ( s p )
end_translate_rc_and_ret2 :
SAVE_ S W I T C H _ S T A C K
call d o _ s y s c a l l _ t r a c e _ e x i t
RESTORE_ S W I T C H _ S T A C K
br r e t _ f r o m _ e x c e p t i o n
Luser_return :
GET_ T H R E A D _ I N F O r11 / * g e t t h r e a d _ i n f o p o i n t e r * /
ldw r10 , T I _ F L A G S ( r11 ) / * g e t t h r e a d _ i n f o - > f l a g s * /
ANDI3 2 r11 , r10 , _ T I F _ W O R K _ M A S K
beq r11 , r0 , r e s t o r e _ a l l / * N o t h i n g t o d o * /
BTBZ r1 , r10 , T I F _ N E E D _ R E S C H E D , L s i g n a l _ r e t u r n
/* Reschedule work */
call s c h e d u l e
br r e t _ f r o m _ e x c e p t i o n
Lsignal_return :
ANDI3 2 r1 , r10 , _ T I F _ S I G P E N D I N G | _ T I F _ N O T I F Y _ R E S U M E
beq r1 , r0 , r e s t o r e _ a l l
mov r4 , s p / * p t _ r e g s * /
SAVE_ S W I T C H _ S T A C K
call d o _ n o t i f y _ r e s u m e
beq r2 , r0 , n o _ w o r k _ p e n d i n g
RESTORE_ S W I T C H _ S T A C K
/* prepare restart syscall here without leaving kernel */
ldw r2 , P T _ R 2 ( s p ) / * r e l o a d s y s c a l l n u m b e r i n r2 * /
ldw r4 , P T _ R 4 ( s p ) / * r e l o a d s y s c a l l a r g u m e n t s r4 - r9 * /
ldw r5 , P T _ R 5 ( s p )
ldw r6 , P T _ R 6 ( s p )
ldw r7 , P T _ R 7 ( s p )
ldw r8 , P T _ R 8 ( s p )
ldw r9 , P T _ R 9 ( s p )
br l o c a l _ r e s t a r t / * r e s t a r t s y s c a l l * /
no_work_pending :
RESTORE_ S W I T C H _ S T A C K
br r e t _ f r o m _ e x c e p t i o n
/ * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
* Handle e x t e r n a l i n t e r r u p t s .
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
* /
/ *
* This i s t h e g e n e r i c i n t e r r u p t h a n d l e r ( f o r a l l h a r d w a r e i n t e r r u p t
* sources) . I t f i g u r e s o u t t h e v e c t o r n u m b e r a n d c a l l s t h e a p p r o p r i a t e
* interrupt s e r v i c e r o u t i n e d i r e c t l y .
* /
external_interrupt :
rdctl r12 , i p e n d i n g
rdctl r9 , i e n a b l e
and r12 , r12 , r9
/* skip if no interrupt is pending */
beq r12 , r0 , r e t _ f r o m _ i n t e r r u p t
movi r24 , - 1
stw r24 , P T _ O R I G _ R 2 ( s p )
/ *
* Process a n e x t e r n a l h a r d w a r e i n t e r r u p t .
* /
addi e a , e a , - 4 / * r e - i s s u e t h e i n t e r r u p t e d i n s t r u c t i o n * /
stw e a , P T _ E A ( s p )
2 : movi r4 , % l o ( - 1 ) / * S t a r t f r o m b i t p o s i t i o n 0 ,
highest p r i o r i t y * /
/* This is the IRQ # for handler call */
1 : andi r10 , r12 , 1 / * I s o l a t e b i t w e a r e i n t e r e s t e d i n * /
srli r12 , r12 , 1 / * s h i f t c o u n t i s c o s t l y w i t h o u t h a r d w a r e
multiplier * /
addi r4 , r4 , 1
beq r10 , r0 , 1 b
mov r5 , s p / * S e t u p p t _ r e g s p o i n t e r f o r h a n d l e r c a l l * /
call d o _ I R Q
rdctl r12 , i p e n d i n g / * c h e c k a g a i n i f i r q s t i l l p e n d i n g * /
rdctl r9 , i e n a b l e / * I s o l a t e p o s s i b l e i n t e r r u p t s * /
and r12 , r12 , r9
bne r12 , r0 , 2 b
/* br ret_from_interrupt */ /* fall through to ret_from_interrupt */
ENTRY( r e t _ f r o m _ i n t e r r u p t )
ldw r1 , P T _ E S T A T U S ( s p ) / * c h e c k i f r e t u r n i n g t o k e r n e l * /
TSTBNZ r1 , r1 , E S T A T U S _ E U , L u s e r _ r e t u r n
# ifdef C O N F I G _ P R E E M P T
GET_ T H R E A D _ I N F O r1
ldw r4 , T I _ P R E E M P T _ C O U N T ( r1 )
bne r4 , r0 , r e s t o r e _ a l l
ldw r4 , T I _ F L A G S ( r1 ) / * ? N e e d r e s c h e d s e t * /
BTBZ r10 , r4 , T I F _ N E E D _ R E S C H E D , r e s t o r e _ a l l
ldw r4 , P T _ E S T A T U S ( s p ) / * ? I n t e r r u p t s o f f * /
andi r10 , r4 , E S T A T U S _ E P I E
beq r10 , r0 , r e s t o r e _ a l l
2014-12-31 05:53:11 +03:00
call p r e e m p t _ s c h e d u l e _ i r q
2014-11-06 10:19:38 +03:00
# endif
2014-12-31 05:53:11 +03:00
br r e s t o r e _ a l l
2014-11-06 10:19:38 +03:00
/ * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
* A f e w s y s c a l l w r a p p e r s
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
* /
/ *
* int c l o n e ( u n s i g n e d l o n g c l o n e _ f l a g s , u n s i g n e d l o n g n e w s p ,
* int _ _ u s e r * p a r e n t _ t i d p t r , i n t _ _ u s e r * c h i l d _ t i d p t r ,
* int t l s _ v a l )
* /
ENTRY( s y s _ c l o n e )
SAVE_ S W I T C H _ S T A C K
addi s p , s p , - 4
stw r7 , 0 ( s p ) / * P a s s 5 t h a r g t h r u s t a c k * /
mov r7 , r6 / * 4 t h a r g i s 3 r d o f c l o n e ( ) * /
mov r6 , z e r o / * 3 r d a r g a l w a y s 0 * /
call d o _ f o r k
addi s p , s p , 4
RESTORE_ S W I T C H _ S T A C K
ret
ENTRY( s y s _ r t _ s i g r e t u r n )
SAVE_ S W I T C H _ S T A C K
mov r4 , s p
call d o _ r t _ s i g r e t u r n
RESTORE_ S W I T C H _ S T A C K
addi r a , r a , ( e n d _ t r a n s l a t e _ r c _ a n d _ r e t - t r a n s l a t e _ r c _ a n d _ r e t )
ret
/ * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
* A f e w o t h e r w r a p p e r s a n d s t u b s
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
* /
protection_exception_pte :
rdctl r6 , p t e a d d r
slli r6 , r6 , 1 0
call d o _ p a g e _ f a u l t
br r e t _ f r o m _ e x c e p t i o n
protection_exception_ba :
rdctl r6 , b a d a d d r
call d o _ p a g e _ f a u l t
br r e t _ f r o m _ e x c e p t i o n
protection_exception_instr :
call h a n d l e _ s u p e r v i s o r _ i n s t r
br r e t _ f r o m _ e x c e p t i o n
handle_breakpoint :
call b r e a k p o i n t _ c
br r e t _ f r o m _ e x c e p t i o n
# ifdef C O N F I G _ N I O S 2 _ A L I G N M E N T _ T R A P
handle_unaligned :
SAVE_ S W I T C H _ S T A C K
call h a n d l e _ u n a l i g n e d _ c
RESTORE_ S W I T C H _ S T A C K
br r e t _ f r o m _ e x c e p t i o n
# else
handle_unaligned :
call h a n d l e _ u n a l i g n e d _ c
br r e t _ f r o m _ e x c e p t i o n
# endif
handle_illegal :
call h a n d l e _ i l l e g a l _ c
br r e t _ f r o m _ e x c e p t i o n
handle_diverror :
call h a n d l e _ d i v e r r o r _ c
br r e t _ f r o m _ e x c e p t i o n
2015-02-16 14:26:43 +03:00
# ifdef C O N F I G _ K G D B
handle_kgdb_breakpoint :
call k g d b _ b r e a k p o i n t _ c
br r e t _ f r o m _ e x c e p t i o n
# endif
2015-04-16 10:19:01 +03:00
handle_trap_1 :
call h a n d l e _ t r a p _ 1 _ c
br r e t _ f r o m _ e x c e p t i o n
handle_trap_2 :
call h a n d l e _ t r a p _ 2 _ c
br r e t _ f r o m _ e x c e p t i o n
handle_trap_3 :
handle_trap_reserved :
call h a n d l e _ t r a p _ 3 _ c
br r e t _ f r o m _ e x c e p t i o n
2014-11-06 10:19:38 +03:00
/ *
* Beware - w h e n e n t e r i n g r e s u m e , p r e v ( t h e c u r r e n t t a s k ) i s
* in r4 , n e x t ( t h e n e w t a s k ) i s i n r5 , d o n ' t c h a n g e t h e s e
* registers.
* /
ENTRY( r e s u m e )
rdctl r7 , s t a t u s / * s a v e t h r e a d s t a t u s r e g * /
stw r7 , T A S K _ T H R E A D + T H R E A D _ K P S R ( r4 )
andi r7 , r7 , % l o ( ~ S T A T U S _ P I E ) / * d i s a b l e i n t e r r u p t s * /
wrctl s t a t u s , r7
SAVE_ S W I T C H _ S T A C K
stw s p , T A S K _ T H R E A D + T H R E A D _ K S P ( r4 ) / * s a v e k e r n e l s t a c k p o i n t e r * /
ldw s p , T A S K _ T H R E A D + T H R E A D _ K S P ( r5 ) / * r e s t o r e n e w t h r e a d s t a c k * /
movia r24 , _ c u r r e n t _ t h r e a d / * s a v e t h r e a d * /
GET_ T H R E A D _ I N F O r1
stw r1 , 0 ( r24 )
RESTORE_ S W I T C H _ S T A C K
ldw r7 , T A S K _ T H R E A D + T H R E A D _ K P S R ( r5 ) / * r e s t o r e t h r e a d s t a t u s r e g * /
wrctl s t a t u s , r7
ret
ENTRY( r e t _ f r o m _ f o r k )
call s c h e d u l e _ t a i l
br r e t _ f r o m _ e x c e p t i o n
ENTRY( r e t _ f r o m _ k e r n e l _ t h r e a d )
call s c h e d u l e _ t a i l
mov r4 ,r17 / * a r g * /
callr r16 / * f u n c t i o n * /
br r e t _ f r o m _ e x c e p t i o n
/ *
* Kernel u s e r h e l p e r s .
*
* Each s e g m e n t i s 6 4 - b y t e a l i g n e d a n d w i l l b e m a p p e d t o t h e < U s e r s p a c e > .
* New s e g m e n t s ( i f e v e r n e e d e d ) m u s t b e a d d e d a f t e r t h e e x i s t i n g o n e s .
* This m e c h a n i s m s h o u l d b e u s e d o n l y f o r t h i n g s t h a t a r e r e a l l y s m a l l a n d
* justified, a n d n o t b e a b u s e d f r e e l y .
*
* /
/* Filling pads with undefined instructions. */
.macro kuser_pad sym s i z e
.if ( ( . - \ sym) & 3 )
.rept ( 4 - ( . - \ sym) & 3 )
.byte 0
.endr
.endif
.rept ( ( \ size - ( . - \ s y m ) ) / 4 )
.word 0xdeadbeef
.endr
.endm
.align 6
.globl __kuser_helper_start
__kuser_helper_start :
__kuser_helper_version : /* @ 0x1000 */
.word ( ( _ _ kuser_ h e l p e r _ e n d - _ _ k u s e r _ h e l p e r _ s t a r t ) > > 6 )
__kuser_cmpxchg : /* @ 0x1004 */
/ *
* r4 p o i n t e r t o e x c h a n g e v a r i a b l e
* r5 o l d v a l u e
* r6 n e w v a l u e
* /
cmpxchg_ldw :
ldw r2 , 0 ( r4 ) / * l o a d c u r r e n t v a l u e * /
sub r2 , r2 , r5 / * c o m p a r e w i t h o l d v a l u e * /
bne r2 , z e r o , c m p x c h g _ r e t
/* We had a match, store the new value */
cmpxchg_stw :
stw r6 , 0 ( r4 )
cmpxchg_ret :
ret
kuser_ p a d _ _ k u s e r _ c m p x c h g , 6 4
.globl __kuser_sigtramp
__kuser_sigtramp :
movi r2 , _ _ N R _ r t _ s i g r e t u r n
trap
kuser_ p a d _ _ k u s e r _ s i g t r a m p , 6 4
.globl __kuser_helper_end
__kuser_helper_end :