callback: bug dans l'interception des exceptions corrige.

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@596 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Xavier Leroy 1996-01-07 16:58:44 +00:00
parent 9c85a54888
commit c8ea6d04fd
7 changed files with 71 additions and 56 deletions

View File

@ -382,6 +382,12 @@ $107:
stt $f7, 104($sp)
stt $f8, 112($sp)
stt $f9, 120($sp)
/* Set up a callback link on the stack. */
lda $sp, -16($sp)
ldq $0, caml_bottom_of_stack
stq $0, 0($sp)
ldq $1, caml_last_return_address
stq $1, 8($sp)
/* Set up a trap frame to catch exceptions escaping the Caml code */
lda $sp, -16($sp)
ldq $15, caml_exception_pointer
@ -389,12 +395,6 @@ $107:
lda $0, $109
stq $0, 8($sp)
mov $sp, $15
/* Set up a callback link on the stack. */
lda $sp, -16($sp)
ldq $0, caml_bottom_of_stack
stq $0, 0($sp)
ldq $1, caml_last_return_address
stq $1, 8($sp)
/* Reload allocation pointers */
ldq $13, young_ptr
ldq $14, young_limit
@ -405,16 +405,16 @@ $108: jsr ($25)
/* Reload $gp */
bic $26, 1, $26 /* return address may have "scanned" bit set */
ldgp $gp, 4($26)
/* Pop the trap frame, restoring caml-exception_pointer */
ldq $15, 0($sp)
stq $15, caml_exception_pointer
lda $sp, 16($sp)
/* Restore the global variables used by caml_c_call */
ldq $24, 0($sp)
stq $24, caml_bottom_of_stack
ldq $25, 8($sp)
stq $25, caml_last_return_address
lda $sp, 16($sp)
/* Pop the trap frame, restoring caml-exception_pointer */
ldq $15, 0($sp)
stq $15, caml_exception_pointer
lda $sp, 16($sp)
/* Update allocation pointer */
stq $13, young_ptr
/* Reload callee-save registers */

View File

@ -400,6 +400,14 @@ L102:
fstds,ma %fr29, -8(%r1)
fstds,ma %fr30, -8(%r1)
fstds,ma %fr31, -8(%r1)
; Set up a callback link
ldo 8(%r30), %r30
ldil L`_caml_bottom_of_stack, %r1
ldw R`_caml_bottom_of_stack(%r1), %r1
stw %r1, -8(%r30)
ldil L`_caml_last_return_address, %r1
ldw R`_caml_last_return_address(%r1), %r1
stw %r1, -4(%r30)
; Set up a trap frame to catch exceptions escaping the Caml code
ldo 8(%r30), %r30
ldil L`_caml_exception_pointer, %r1
@ -409,14 +417,6 @@ L102:
ldo R`L103(%r1), %r1
stw %r1, -4(%r30)
copy %r30, %r5
; Set up a callback link
ldo 8(%r30), %r30
ldil L`_caml_bottom_of_stack, %r1
ldw R`_caml_bottom_of_stack(%r1), %r1
stw %r1, -8(%r30)
ldil L`_caml_last_return_address, %r1
ldw R`_caml_last_return_address(%r1), %r1
stw %r1, -4(%r30)
; Reload allocation pointers
ldil L`_young_ptr, %r1
ldw R`_young_ptr(%r1), %r3
@ -426,6 +426,11 @@ L102:
ble 0(4, %r22)
copy %r31, %r2
L104:
; Pop the trap frame
ldw -8(%r30), %r31
ldil L`_caml_exception_pointer, %r1
stw %r31, R`_caml_exception_pointer(%r1)
ldo -8(%r30), %r30
; Pop the callback link
ldw -8(%r30), %r31
ldil L`_caml_bottom_of_stack, %r1
@ -434,11 +439,6 @@ L104:
ldil L`_caml_last_return_address, %r1
stw %r31, R`_caml_last_return_address(%r1)
ldo -8(%r30), %r30
; Pop the trap frame
ldw -8(%r30), %r31
ldil L`_caml_exception_pointer, %r1
stw %r31, R`_caml_exception_pointer(%r1)
ldo -8(%r30), %r30
; Save allocation pointer
ldil L`_young_ptr, %r1
stw %r3, R`_young_ptr(%r1)

View File

@ -203,23 +203,23 @@ G(callback):
movl 24(%esp), %eax /* argument */
movl 0(%ebx), %esi /* code pointer */
L106:
/* Build a callback link */
pushl G(caml_last_return_address)
pushl G(caml_bottom_of_stack)
/* Build an exception handler */
pushl $L108
pushl G(caml_exception_pointer)
movl %esp, G(caml_exception_pointer)
/* Build a callback link */
pushl G(caml_last_return_address)
pushl G(caml_bottom_of_stack)
/* Call the Caml code */
call *%esi
L107:
/* Pop the exception handler */
popl G(caml_exception_pointer)
popl %esi /* dummy register */
/* Pop the callback link, restoring the global variables
used by caml_c_call */
popl G(caml_bottom_of_stack)
popl G(caml_last_return_address)
/* Pop the exception handler */
popl G(caml_exception_pointer)
popl %esi /* dummy register */
/* Restore callee-save registers.
In parallel, free the floating-point registers
that may have been used by Caml. */
@ -234,10 +234,13 @@ L107:
/* Return to caller. */
ret
L108:
/* Exception handler: re-raise the exception through mlraise,
so that local C roots are cleaned up correctly. */
/* Exception handler*/
/* Pop the callback link, restoring the global variables
used by caml_c_call */
popl G(caml_bottom_of_stack)
popl G(caml_last_return_address)
/* Re-raise the exception through mlraise,
so that local C roots are cleaned up correctly. */
pushl %eax /* exn bucket is the argument */
call G(mlraise) /* never returns */

View File

@ -302,6 +302,12 @@ $103:
s.d $f26, 60($sp)
s.d $f28, 68($sp)
s.d $f30, 76($sp)
/* Set up a callback link on the stack. */
subu $sp, $sp, 8
lw $2, caml_bottom_of_stack
sw $2, 0($sp)
lw $3, caml_last_return_address
sw $3, 4($sp)
/* Set up a trap frame to catch exceptions escaping the Caml code */
subu $sp, $sp, 8
lw $30, caml_exception_pointer
@ -309,12 +315,6 @@ $103:
la $2, $105
sw $2, 4($sp)
move $30, $sp
/* Set up a callback link on the stack. */
subu $sp, $sp, 8
lw $2, caml_bottom_of_stack
sw $2, 0($sp)
lw $3, caml_last_return_address
sw $3, 4($sp)
/* Reload allocation pointers */
lw $22, young_ptr
lw $23, young_limit
@ -322,6 +322,10 @@ $103:
sw $0, caml_last_return_address
/* Call the Caml code */
$104: jal $24
/* Pop the trap frame, restoring caml_exception_pointer */
lw $24, 0($sp)
sw $24, caml_exception_pointer
addu $sp, $sp, 8
/* Pop the callback link,
restoring the global variables used by caml_c_call */
lw $24, 0($sp)
@ -329,10 +333,6 @@ $104: jal $24
lw $25, 4($sp)
sw $25, caml_last_return_address
addu $sp, $sp, 8
/* Pop the trap frame, restoring caml_exception_pointer */
lw $24, 0($sp)
sw $24, caml_exception_pointer
addu $sp, $sp, 8
/* Update allocation pointer */
sw $22, young_ptr
/* Reload callee-save registers and return */

View File

@ -286,6 +286,14 @@ static void trap_handler(sig, info, context)
}
#endif
#if defined(TARGET_power)
static void trap_handler(sig)
int sig;
{
array_bound_error();
}
#endif
/* Initialization of signal stuff */
void init_signals()
@ -300,5 +308,8 @@ void init_signals()
act.sa_flags = SA_SIGINFO;
sigaction(SIGILL, &act, NULL);
#endif
#if defined(TARGET_power)
signal(SIGTRAP, trap_handler);
#endif
}

View File

@ -290,32 +290,32 @@ Callback:
mov %g1, %i1 /* environment */
ld [%g1], %l2 /* code pointer */
L108:
/* Set up a callback link on the stack. */
sub %sp, 8, %sp
Load(Caml_bottom_of_stack, %l0)
Load(Caml_last_return_address, %l1)
std %l0, [%sp + 96]
/* Set up a trap frame to catch exceptions escaping the Caml code */
sub %sp, 8, %sp
Load(Caml_exception_pointer, %g5)
Address(L110, %g4)
std %g4, [%sp + 96]
mov %sp, %g5
/* Set up a callback link on the stack. */
sub %sp, 8, %sp
Load(Caml_bottom_of_stack, %l0)
Load(Caml_last_return_address, %l1)
std %l0, [%sp + 96]
/* Reload allocation pointers */
Load(Young_ptr, %g6)
Address(Young_limit, %g7)
/* Call the Caml code */
L109: call %l2
nop
/* Restore the global variables used by caml_c_call */
ldd [%sp + 96], %l0
add %sp, 8, %sp
Store(%l0, Caml_bottom_of_stack)
Store(%l1, Caml_last_return_address)
/* Pop trap frame and restore caml_exception_pointer */
ld [%sp + 100], %g5
add %sp, 8, %sp
Store(%g5, Caml_exception_pointer)
/* Pop callback link, restoring the global variables used by caml_c_call */
ldd [%sp + 96], %l0
add %sp, 8, %sp
Store(%l0, Caml_bottom_of_stack)
Store(%l1, Caml_last_return_address)
/* Save allocation pointer */
Store(%g6, Young_ptr)
/* Move result where the C function expects it */

View File

@ -22,7 +22,7 @@
#define Already_scanned(sp, retaddr) (retaddr & 1)
#define Mark_scanned(sp, retaddr) (*((long *)(sp - 8)) = retaddr | 1)
#define Mask_already_scanned(retaddr) (retaddr & ~1)
#define Callback_link(sp) ((struct callback_link *)sp)
#define Callback_link(sp) ((struct callback_link *)(sp + 16))
#endif
#ifdef TARGET_sparc
@ -30,12 +30,12 @@
#define Already_scanned(sp, retaddr) (retaddr & 1)
#define Mark_scanned(sp, retaddr) (*((long *)(sp + 92)) = retaddr | 1)
#define Mask_already_scanned(retaddr) (retaddr & ~1)
#define Callback_link(sp) ((struct callback_link *)(sp + 96))
#define Callback_link(sp) ((struct callback_link *)(sp + 104))
#endif
#ifdef TARGET_i386
#define Saved_return_address(sp) *((long *)(sp - 4))
#define Callback_link(sp) ((struct callback_link *)sp)
#define Callback_link(sp) ((struct callback_link *)(sp + 8))
#endif
#ifdef TARGET_mips
@ -43,7 +43,7 @@
#define Already_scanned(sp, retaddr) (retaddr & 1)
#define Mark_scanned(sp, retaddr) (*((long *)(sp - 4)) = retaddr | 1)
#define Mask_already_scanned(retaddr) (retaddr & ~1)
#define Callback_link(sp) ((struct callback_link *)sp)
#define Callback_link(sp) ((struct callback_link *)(sp + 8))
#endif
#ifdef TARGET_hppa
@ -52,7 +52,7 @@
#define Already_scanned(sp, retaddr) (retaddr & 0x80000000)
#define Mark_scanned(sp, retaddr) (*((long *)sp) = retaddr | 0x80000000)
#define Mask_already_scanned(retaddr) (retaddr & ~0x80000000)
#define Callback_link(sp) ((struct callback_link *)(sp - 8))
#define Callback_link(sp) ((struct callback_link *)(sp - 16))
#endif
#ifdef TARGET_power
@ -63,4 +63,5 @@
#define Callback_link(sp) ((struct callback_link *)(sp + 24))
#endif
#endif /* _stack_ */