diff options
author | Xavier Leroy <xavier.leroy@inria.fr> | 2012-02-17 10:12:09 +0000 |
---|---|---|
committer | Xavier Leroy <xavier.leroy@inria.fr> | 2012-02-17 10:12:09 +0000 |
commit | 339bcbb2c603c22b99cf07daf5f8296d5ea8e940 (patch) | |
tree | 33cb94c04a8463fa83dd81cd2d5f073003b9252a | |
parent | d6029c574f0914e5bc3fb608bdedb2c3f2c186ab (diff) |
PR#5064, PR#5485: try to ensure that 4K words of stack are available
before calling into C functions, raising a Stack_overflow exception
otherwise. This reduces (but does not eliminate) the risk of
segmentation faults due to stack overflow in C code.
Implemented for i386, amd64 and power, under Linux and MacOSX.
Plus: remove some more stuff related to obsoleted platforms (IA64, SunOS 4).
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@12159 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r-- | Changes | 4 | ||||
-rw-r--r-- | asmrun/amd64.S | 20 | ||||
-rw-r--r-- | asmrun/arm.S | 6 | ||||
-rw-r--r-- | asmrun/i386.S | 22 | ||||
-rw-r--r-- | asmrun/ia64.S | 524 | ||||
-rw-r--r-- | asmrun/power-elf.S | 22 | ||||
-rw-r--r-- | asmrun/power-rhapsody.S | 16 | ||||
-rw-r--r-- | asmrun/signals_asm.c | 5 | ||||
-rw-r--r-- | asmrun/sparc.S | 207 | ||||
-rw-r--r-- | asmrun/stack.h | 31 | ||||
-rwxr-xr-x | configure | 3 |
11 files changed, 171 insertions, 689 deletions
@@ -51,6 +51,10 @@ Bug Fixes: - PR#4549: Filename.dirname is not handling multiple / on Unix - PR#4869: rare collisions between assembly labels for code and data - PR#4880: "assert" constructs now show up in the exception stack backtrace +- PR#5064, PR#5485: try to ensure that 4K words of stack are available + before calling into C functions, raising a Stack_overflow exception + otherwise. This reduces (but does not eliminate) the risk of + segmentation faults due to stack overflow in C code - PR#5313: ocamlopt -g misses optimizations - PR#5322: type abbreviations expanding to a universal type variable - PR#5325: (Windows) blocked Unix.recv in one thread blocks Unix.send in diff --git a/asmrun/amd64.S b/asmrun/amd64.S index 5208fa83f..40716e019 100644 --- a/asmrun/amd64.S +++ b/asmrun/amd64.S @@ -220,11 +220,21 @@ .text + .globl G(caml_system__code_begin) +G(caml_system__code_begin): + /* Allocation */ FUNCTION(G(caml_call_gc)) RECORD_STACK_FRAME(0) LBL(caml_call_gc): +#ifndef SYS_mingw64 + /* Touch the stack to trigger a recoverable segfault + if insufficient space remains */ + subq $32768, %rsp + movq %rax, 0(%rsp) + addq $32768, %rsp +#endif /* Build array of registers, save it into caml_gc_regs */ pushq %r13 pushq %r12 @@ -363,6 +373,13 @@ LBL(caml_c_call): popq %r12 STORE_VAR(%r12, caml_last_return_address) STORE_VAR(%rsp, caml_bottom_of_stack) +#ifndef SYS_mingw64 + /* Touch the stack to trigger a recoverable segfault + if insufficient space remains */ + subq $32768, %rsp + movq %rax, 0(%rsp) + addq $32768, %rsp +#endif /* Make the exception handler and alloc ptr available to the C code */ STORE_VAR(%r15, caml_young_ptr) STORE_VAR(%r14, caml_exception_pointer) @@ -518,6 +535,9 @@ FUNCTION(G(caml_ml_array_bound_error)) leaq GCALL(caml_array_bound_error)(%rip), %rax jmp LBL(caml_c_call) + .globl G(caml_system__code_end) +G(caml_system__code_end): + .data .globl G(caml_system__frametable) .align EIGHT_ALIGN diff --git a/asmrun/arm.S b/asmrun/arm.S index ce32a40f1..6fa7eb16d 100644 --- a/asmrun/arm.S +++ b/asmrun/arm.S @@ -58,6 +58,9 @@ alloc_limit .req r11 /* Allocation functions and GC interface */ + .globl caml_system__code_begin +caml_system__code_begin: + .align 2 .globl caml_call_gc caml_call_gc: @@ -415,6 +418,9 @@ caml_ml_array_bound_error: .type caml_ml_array_bound_error, %function .size caml_ml_array_bound_error, .-caml_ml_array_bound_error + .globl caml_system__code_end +caml_system__code_end: + /* GC roots for callback */ .data diff --git a/asmrun/i386.S b/asmrun/i386.S index 663d61753..6c86de05a 100644 --- a/asmrun/i386.S +++ b/asmrun/i386.S @@ -81,6 +81,9 @@ /* Allocation */ .text + .globl G(caml_system__code_begin) +G(caml_system__code_begin): + .globl G(caml_call_gc) .globl G(caml_alloc1) .globl G(caml_alloc2) @@ -95,8 +98,15 @@ G(caml_call_gc): movl %eax, G(caml_last_return_address) leal 4(%esp), %eax movl %eax, G(caml_bottom_of_stack) - /* Build array of registers, save it into caml_gc_regs */ LBL(105): +#if !defined(SYS_mingw) && !defined(SYS_cygwin) + /* Touch the stack to trigger a recoverable segfault + if insufficient space remains */ + subl $16384, %esp + movl %eax, 0(%esp) + addl $16384, %esp +#endif + /* Build array of registers, save it into caml_gc_regs */ pushl %ebp pushl %edi pushl %esi @@ -211,6 +221,13 @@ G(caml_c_call): movl %edx, G(caml_last_return_address) leal 4(%esp), %edx movl %edx, G(caml_bottom_of_stack) +#if !defined(SYS_mingw) && !defined(SYS_cygwin) + /* Touch the stack to trigger a recoverable segfault + if insufficient space remains */ + subl $16384, %esp + movl %eax, 0(%esp) + addl $16384, %esp +#endif /* Call the function (address in %eax) */ jmp *%eax @@ -396,6 +413,9 @@ G(caml_ml_array_bound_error): /* Branch to [caml_array_bound_error] (never returns) */ call G(caml_array_bound_error) + .globl G(caml_system__code_end) +G(caml_system__code_end): + .data .globl G(caml_system__frametable) G(caml_system__frametable): diff --git a/asmrun/ia64.S b/asmrun/ia64.S deleted file mode 100644 index f7bd90c5f..000000000 --- a/asmrun/ia64.S +++ /dev/null @@ -1,524 +0,0 @@ -/***********************************************************************/ -/* */ -/* OCaml */ -/* */ -/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */ -/* */ -/* Copyright 1996 Institut National de Recherche en Informatique et */ -/* en Automatique. All rights reserved. This file is distributed */ -/* under the terms of the GNU Library General Public License, with */ -/* the special exception on linking described in file ../LICENSE. */ -/* */ -/***********************************************************************/ - -/* $Id$ */ - -/* Asm part of the runtime system, IA64 processor */ - -#undef BROKEN_POSTINCREMENT - -#define ADDRGLOBAL(reg,symb) \ - add reg = @ltoff(symb), gp;; ld8 reg = [reg] -#define LOADGLOBAL(reg,symb) \ - add r3 = @ltoff(symb), gp;; ld8 r3 = [r3];; ld8 reg = [r3] -#define STOREGLOBAL(reg,symb) \ - add r3 = @ltoff(symb), gp;; ld8 r3 = [r3];; st8 [r3] = reg - -#define ST8OFF(a,b,d) st8 [a] = b, d -#define LD8OFF(a,b,d) ld8 a = [b], d -#define STFDOFF(a,b,d) stfd [a] = b, d -#define LDFDOFF(a,b,d) ldfd a = [b], d -#define STFSPILLOFF(a,b,d) stf.spill [a] = b, d -#define LDFFILLOFF(a,b,d) ldf.fill a = [b], d - -#define SAVE2(a,b) ST8OFF(r2, a, 16); ST8OFF(r3, b, 16) -#define SAVE4(a,b,c,d) SAVE2(a,b);; SAVE2(c,d) -#define SAVE8(a,b,c,d,e,f,g,h) SAVE4(a,b,c,d);; SAVE4(e,f,g,h) - -#define LOAD2(a,b) LD8OFF(a, r2, 16); LD8OFF(b, r3, 16) -#define LOAD4(a,b,c,d) LOAD2(a,b);; LOAD2(c,d) -#define LOAD8(a,b,c,d,e,f,g,h) LOAD4(a,b,c,d);; LOAD4(e,f,g,h) - -#define FSAVE2(a,b) STFDOFF(r2, a, 16); STFDOFF(r3, b, 16) -#define FSAVE4(a,b,c,d) FSAVE2(a,b);; FSAVE2(c,d) -#define FSAVE8(a,b,c,d,e,f,g,h) FSAVE4(a,b,c,d);; FSAVE4(e,f,g,h) - -#define FLOAD2(a,b) LDFDOFF(a, r2, 16); LDFDOFF(b, r3, 16) -#define FLOAD4(a,b,c,d) FLOAD2(a,b);; FLOAD2(c,d) -#define FLOAD8(a,b,c,d,e,f,g,h) FLOAD4(a,b,c,d);; FLOAD4(e,f,g,h) - -#define FSPILL2(a,b) STFSPILLOFF(r2, a, 32); STFSPILLOFF(r3, b, 32) -#define FSPILL4(a,b,c,d) FSPILL2(a,b);; FSPILL2(c,d) -#define FSPILL8(a,b,c,d,e,f,g,h) FSPILL4(a,b,c,d);; FSPILL4(e,f,g,h) - -#define FFILL2(a,b) LDFFILLOFF(a, r2, 32); LDFFILLOFF(b, r3, 32) -#define FFILL4(a,b,c,d) FFILL2(a,b);; FFILL2(c,d) -#define FFILL8(a,b,c,d,e,f,g,h) FFILL4(a,b,c,d);; FFILL4(e,f,g,h) - -/* Allocation */ - .text - - .global caml_allocN# - .proc caml_allocN# - .align 16 - -/* caml_allocN: all code generator registers preserved, - gp preserved, r2 = requested size */ - -caml_allocN: - sub r4 = r4, r2 ;; - cmp.ltu p0, p6 = r4, r5 - (p6) br.ret.sptk b0 ;; - /* Fall through caml_call_gc */ - br.sptk.many caml_call_gc# - - .endp caml_allocN# - -/* caml_call_gc: all code generator registers preserved, - gp preserved, r2 = requested size */ - - .global caml_call_gc# - .proc caml_call_gc# - .align 16 -caml_call_gc: - /* Allocate stack frame */ - add sp = -(16 + 16 + 80*8 + 42*8), sp ;; - - /* Save requested size and GP on stack */ - add r3 = 16, sp ;; - ST8OFF(r3, r2, 8) ;; - st8 [r3] = gp - - /* Record lowest stack address, return address, GC regs */ - mov r2 = b0 ;; - STOREGLOBAL(r2, caml_last_return_address#) - add r2 = (16 + 16 + 80*8 + 42*8), sp ;; - STOREGLOBAL(r2, caml_bottom_of_stack#) - add r2 = (16 + 16), sp ;; - STOREGLOBAL(r2, caml_gc_regs#) - - /* Save all integer regs used by the code generator in the context */ -.L100: add r3 = 8, r2 ;; - SAVE4(r8,r9,r10,r11) ;; - SAVE8(r16,r17,r18,r19,r20,r21,r22,r23) ;; - SAVE8(r24,r25,r26,r27,r28,r29,r30,r31) ;; - SAVE8(r32,r33,r34,r35,r36,r37,r38,r39) ;; - SAVE8(r40,r41,r42,r43,r44,r45,r46,r47) ;; - SAVE8(r48,r49,r50,r51,r52,r53,r54,r55) ;; - SAVE8(r56,r57,r58,r59,r60,r61,r62,r63) ;; - SAVE8(r64,r65,r66,r67,r68,r69,r70,r71) ;; - SAVE8(r72,r73,r74,r75,r76,r77,r78,r79) ;; - SAVE8(r80,r81,r82,r83,r84,r85,r86,r87) ;; - SAVE4(r88,r89,r90,r91) ;; - - /* Save all floating-point registers not preserved by C */ - FSAVE2(f6,f7) ;; - FSAVE8(f8,f9,f10,f11,f12,f13,f14,f15) ;; - FSAVE8(f32,f33,f34,f35,f36,f37,f38,f39) ;; - FSAVE8(f40,f41,f42,f43,f44,f45,f46,f47) ;; - FSAVE8(f48,f49,f50,f51,f52,f53,f54,f55) ;; - FSAVE8(f56,f57,f58,f59,f60,f61,f62,f63) ;; - - /* Save current allocation pointer for debugging purposes */ - STOREGLOBAL(r4, caml_young_ptr#) - - /* Save trap pointer in case an exception is raised */ - STOREGLOBAL(r6, caml_exception_pointer#) - - /* Call the garbage collector */ - br.call.sptk b0 = caml_garbage_collection# ;; - - /* Restore gp */ - add r3 = 24, sp ;; - ld8 gp = [r3] - - /* Restore all integer regs from GC context */ - add r2 = (16 + 16), sp ;; - add r3 = 8, r2 ;; - LOAD4(r8,r9,r10,r11) ;; - LOAD8(r16,r17,r18,r19,r20,r21,r22,r23) ;; - LOAD8(r24,r25,r26,r27,r28,r29,r30,r31) ;; - LOAD8(r32,r33,r34,r35,r36,r37,r38,r39) ;; - LOAD8(r40,r41,r42,r43,r44,r45,r46,r47) ;; - LOAD8(r48,r49,r50,r51,r52,r53,r54,r55) ;; - LOAD8(r56,r57,r58,r59,r60,r61,r62,r63) ;; - LOAD8(r64,r65,r66,r67,r68,r69,r70,r71) ;; - LOAD8(r72,r73,r74,r75,r76,r77,r78,r79) ;; - LOAD8(r80,r81,r82,r83,r84,r85,r86,r87) ;; - LOAD4(r88,r89,r90,r91) ;; - - /* Restore all floating-point registers not preserved by C */ - FLOAD2(f6,f7) ;; - FLOAD8(f8,f9,f10,f11,f12,f13,f14,f15) ;; - FLOAD8(f32,f33,f34,f35,f36,f37,f38,f39) ;; - FLOAD8(f40,f41,f42,f43,f44,f45,f46,f47) ;; - FLOAD8(f48,f49,f50,f51,f52,f53,f54,f55) ;; - FLOAD8(f56,f57,f58,f59,f60,f61,f62,f63) ;; - - /* Reload new allocation pointer and allocation limit */ - LOADGLOBAL(r4, caml_young_ptr#) - LOADGLOBAL(r5, caml_young_limit#) - - /* Allocate space for the block */ - add r3 = 16, sp ;; - ld8 r2 = [r3] ;; - sub r4 = r4, r2 ;; - cmp.ltu p6, p0 = r4, r5 /* enough space? */ - (p6) br.cond.spnt .L100 ;; /* no: call GC again */ - - /* Reload return address and say that we are back into OCaml code */ - ADDRGLOBAL(r3, caml_last_return_address#) ;; - ld8 r2 = [r3] - st8 [r3] = r0 ;; - - /* Return to caller */ - mov b0 = r2 - add sp = (16 + 16 + 80*8 + 42*8), sp ;; - br.ret.sptk b0 - - .endp caml_call_gc# - -/* Call a C function from OCaml */ -/* Function to call is in r2 */ - - .global caml_c_call# - .proc caml_c_call# - .align 16 - -caml_c_call: - /* The OCaml code that called us does not expect any - code-generator registers to be preserved */ - - /* Recover entry point from the function pointer in r2 */ - LD8OFF(r3, r2, 8) ;; - mov b6 = r3 - - /* Preserve gp in r7 */ - mov r7 = gp - - /* Record lowest stack address and return address */ - mov r14 = b0 - STOREGLOBAL(sp, caml_bottom_of_stack#) ;; - STOREGLOBAL(r14, caml_last_return_address#) - - /* Make the exception handler and alloc ptr available to the C code */ - STOREGLOBAL(r4, caml_young_ptr#) - STOREGLOBAL(r6, caml_exception_pointer#) - - /* Recover gp from the function pointer in r2 */ - ld8 gp = [r2] - - /* Call the function */ - br.call.sptk b0 = b6 ;; - - /* Restore gp */ - mov gp = r7 ;; - - /* Reload alloc ptr and alloc limit */ - LOADGLOBAL(r4, caml_young_ptr#) - LOADGLOBAL(r5, caml_young_limit#) - - /* Reload return address and say that we are back into OCaml code */ - ADDRGLOBAL(r3, caml_last_return_address#) ;; - ld8 r2 = [r3] - st8 [r3] = r0 ;; - - /* Return to caller */ - mov b0 = r2 ;; - br.ret.sptk b0 - - .endp caml_c_call# - -/* Start the OCaml program */ - - .global caml_start_program# - .proc caml_start_program# - .align 16 - -caml_start_program: - ADDRGLOBAL(r2, caml_program#) ;; - mov b6 = r2 - - /* Code shared with caml_callback* */ -.L103: - /* Allocate 64 "out" registers (for the OCaml code) and no locals */ - alloc r3 = ar.pfs, 0, 0, 64, 0 - add sp = -(56 * 8), sp ;; - - /* Save all callee-save registers on stack */ - add r2 = 16, sp ;; - ST8OFF(r2, r3, 8) /* 0 : ar.pfs */ - mov r3 = b0 ;; - ST8OFF(r2, r3, 8) ;; /* 1 : return address */ - ST8OFF(r2, gp, 8) /* 2 : gp */ - mov r3 = pr ;; - ST8OFF(r2, r3, 8) /* 3 : predicates */ - mov r3 = ar.fpsr ;; - ST8OFF(r2, r3, 8) /* 4 : ar.fpsr */ - mov r3 = ar.unat ;; - ST8OFF(r2, r3, 8) /* 5 : ar.unat */ - mov r3 = ar.lc ;; - ST8OFF(r2, r3, 8) /* 6 : ar.lc */ - mov r3 = b1 ;; - ST8OFF(r2, r3, 8) /* 7 - 11 : b1 - b5 */ - mov r3 = b2 ;; - ST8OFF(r2, r3, 8) - mov r3 = b3 ;; - ST8OFF(r2, r3, 8) - mov r3 = b4 ;; - ST8OFF(r2, r3, 8) - mov r3 = b5 ;; - ST8OFF(r2, r3, 8) ;; - - add r3 = 8, r2 ;; - SAVE4(r4,r5,r6,r7) ;; /* 12 - 15 : r4 - r7 */ - - add r3 = 16, r2 ;; /* 16 - 55 : f2 - f5, f16 - f31 */ - FSPILL4(f2,f3,f4,f5) ;; - FSPILL8(f16,f17,f18,f19,f20,f21,f22,f23) ;; - FSPILL8(f24,f25,f26,f27,f28,f29,f30,f31) ;; - - /* Set up a callback link on the stack. In addition to - the normal callback link contents (saved values of - caml_bottom_of_stack, caml_last_return_address and - caml_gc_regs), we also save there caml_saved_bsp - and caml_saved_rnat */ - add sp = -48, sp - LOADGLOBAL(r3, caml_bottom_of_stack#) - add r2 = 16, sp ;; - ST8OFF(r2, r3, 8) - LOADGLOBAL(r3, caml_last_return_address#) ;; - ST8OFF(r2, r3, 8) - LOADGLOBAL(r3, caml_gc_regs#) ;; - ST8OFF(r2, r3, 8) - LOADGLOBAL(r3, caml_saved_bsp#) ;; - ST8OFF(r2, r3, 8) - LOADGLOBAL(r3, caml_saved_rnat#) ;; - ST8OFF(r2, r3, 8) - - /* Set up a trap frame to catch exceptions escaping the OCaml code */ - mov r6 = sp - add sp = -16, sp ;; - LOADGLOBAL(r3, caml_exception_pointer#) - add r2 = 16, sp ;; - ST8OFF(r2, r3, 8) -.L110: mov r3 = ip ;; - add r3 = .L101 - .L110, r3 ;; - ST8OFF(r2, r3, 8) ;; - - /* Save ar.bsp, flush register window, and save ar.rnat */ - mov r2 = ar.bsp ;; - STOREGLOBAL(r2, caml_saved_bsp#) ;; - mov r14 = ar.rsc ;; - and r2 = ~0x3, r14;; /* set rsc.mode = 0 */ - mov ar.rsc = r2 ;; /* RSE is in enforced lazy mode */ - flushrs ;; /* must be first instr in group */ - mov r2 = ar.rnat ;; - STOREGLOBAL(r2, caml_saved_rnat#) - mov ar.rsc = r14 /* restore original RSE mode */ - - /* Reload allocation pointers */ - LOADGLOBAL(r4, caml_young_ptr#) - LOADGLOBAL(r5, caml_young_limit#) - - /* We are back into OCaml code */ - STOREGLOBAL(r0, caml_last_return_address#) - - /* Call the OCaml code */ - br.call.sptk b0 = b6 ;; -.L102: - - /* Pop the trap frame, restoring caml_exception_pointer */ - add sp = 16, sp ;; - ld8 r2 = [sp] ;; - STOREGLOBAL(r2, caml_exception_pointer#) - -.L104: - /* Pop the callback link, restoring the global variables */ - add r14 = 16, sp ;; - LD8OFF(r2, r14, 8) ;; - STOREGLOBAL(r2, caml_bottom_of_stack#) - LD8OFF(r2, r14, 8) ;; - STOREGLOBAL(r2, caml_last_return_address#) - LD8OFF(r2, r14, 8) ;; - STOREGLOBAL(r2, caml_gc_regs#) - LD8OFF(r2, r14, 8) ;; - STOREGLOBAL(r2, caml_saved_bsp#) - LD8OFF(r2, r14, 8) ;; - STOREGLOBAL(r2, caml_saved_rnat#) - add sp = 48, sp - - /* Update allocation pointer */ - STOREGLOBAL(r4, caml_young_ptr#) - - /* Restore all callee-save registers from stack */ - add r2 = 16, sp ;; - LD8OFF(r3, r2, 8) ;; /* 0 : ar.pfs */ - mov ar.pfs = r3 - LD8OFF(r3, r2, 8) ;; /* 1 : return address */ - mov b0 = r3 - LD8OFF(gp, r2, 8) ;; /* 2 : gp */ - LD8OFF(r3, r2, 8) ;; /* 3 : predicates */ - mov pr = r3, -1 - LD8OFF(r3, r2, 8) ;; /* 4 : ar.fpsr */ - mov ar.fpsr = r3 - LD8OFF(r3, r2, 8) ;; /* 5 : ar.unat */ - mov ar.unat = r3 - LD8OFF(r3, r2, 8) ;; /* 6 : ar.lc */ - mov ar.lc = r3 - LD8OFF(r3, r2, 8) ;; /* 7 - 11 : b1 - b5 */ - mov b1 = r3 - LD8OFF(r3, r2, 8) ;; - mov b2 = r3 - LD8OFF(r3, r2, 8) ;; - mov b3 = r3 - LD8OFF(r3, r2, 8) ;; - mov b4 = r3 - LD8OFF(r3, r2, 8) ;; - mov b5 = r3 - - add r3 = 8, r2 ;; - LOAD4(r4,r5,r6,r7) ;; /* 12 - 15 : r4 - r7 */ - - add r3 = 16, r2 ;; /* 16 - 55 : f2 - f5, f16 - f31 */ - FFILL4(f2,f3,f4,f5) ;; - FFILL8(f16,f17,f18,f19,f20,f21,f22,f23) ;; - FFILL8(f24,f25,f26,f27,f28,f29,f30,f31) ;; - - /* Pop stack frame and return */ - add sp = (56 * 8), sp - br.ret.sptk.many b0 ;; - - /* The trap handler */ -.L101: - /* Save exception pointer */ - STOREGLOBAL(r6, caml_exception_pointer#) - - /* Encode exception bucket as exception result */ - or r8 = 2, r8 - - /* Return it */ - br.sptk .L104 ;; - - .endp caml_start_program# - -/* Raise an exception from C */ - - .global caml_raise_exception# - .proc caml_raise_exception# - .align 16 -caml_raise_exception: - /* Allocate 64 "out" registers (for the OCaml code) and no locals */ - /* Since we don't return, don't bother saving the PFS */ - alloc r2 = ar.pfs, 0, 0, 64, 0 - - /* Move exn bucket where OCaml expects it */ - mov r8 = r32 ;; - - /* Perform "context switch" as per the Software Conventions Guide, - chapter 10 */ - flushrs ;; /* flush dirty registers to stack */ - mov r14 = ar.rsc ;; - and r2 = ~0x3, r14;; /* set rsc.mode = 0 */ - dep r2 = r0, r2, 16, 4 ;; /* clear rsc.loadrs */ - mov ar.rsc = r2 ;; /* RSE is in enforced lazy mode */ - invala ;; /* Invalidate ALAT */ - LOADGLOBAL(r2, caml_saved_bsp#) ;; - mov ar.bspstore = r2 /* Restore ar.bspstore */ - LOADGLOBAL(r2, caml_saved_rnat#) ;; - mov ar.rnat = r2 /* Restore ar.rnat */ - mov ar.rsc = r14 ;; /* Restore original RSE mode */ - - /* Reload allocation pointers and exception pointer */ - LOADGLOBAL(r4, caml_young_ptr#) - LOADGLOBAL(r5, caml_young_limit#) - LOADGLOBAL(r6, caml_exception_pointer#) - - /* Say that we're back into OCaml */ - STOREGLOBAL(r0, caml_last_return_address#) - - /* Raise the exception proper */ - mov sp = r6 - add r2 = 8, r6 ;; - ld8 r6 = [r6] - ld8 r2 = [r2] ;; - mov b6 = r2 ;; - - /* Branch to handler. Must use a call so as to set up the - CFM and PFS correctly. */ - br.call.sptk.many b0 = b6 - - .endp caml_raise_exception - -/* Callbacks from C to OCaml */ - - .global caml_callback_exn# - .proc caml_callback_exn# - .align 16 -caml_callback_exn: - /* Initial shuffling of arguments */ - ld8 r3 = [r32] /* code pointer */ - mov r2 = r32 - mov r32 = r33 ;; /* first arg */ - mov r33 = r2 /* environment */ - mov b6 = r3 - br.sptk .L103 ;; - - .endp caml_callback_exn# - - .global caml_callback2_exn# - .proc caml_callback2_exn# - .align 16 -caml_callback2_exn: - /* Initial shuffling of arguments */ - ADDRGLOBAL(r3, caml_apply2) /* code pointer */ - mov r2 = r32 - mov r32 = r33 /* first arg */ - mov r33 = r34 ;; /* second arg */ - mov r34 = r2 /* environment */ - mov b6 = r3 - br.sptk .L103 ;; - - .endp caml_callback2_exn# - - .global caml_callback3_exn# - .proc caml_callback3_exn# - .align 16 -caml_callback3_exn: - /* Initial shuffling of arguments */ - ADDRGLOBAL(r3, caml_apply3) /* code pointer */ - mov r2 = r32 - mov r32 = r33 /* first arg */ - mov r33 = r34 /* second arg */ - mov r34 = r35 ;; /* third arg */ - mov r35 = r2 /* environment */ - mov b6 = r3 - br.sptk .L103 ;; - - .endp caml_callback3_exn# - -/* Glue code to call [caml_array_bound_error] */ - - .global caml_ml_array_bound_error# - .proc caml_ml_array_bound_error# - .align 16 -caml_ml_array_bound_error: - ADDRGLOBAL(r2, @fptr(caml_array_bound_error#)) - br.sptk caml_c_call /* never returns */ - - .rodata - - .global caml_system__frametable# - .type caml_system__frametable#, @object - .size caml_system__frametable#, 8 -caml_system__frametable: - data8 1 /* one descriptor */ - data8 .L102 /* return address into callback */ - data2 -1 /* negative frame size => use callback link */ - data2 0 /* no roots here */ - .align 8 - -/* Global variables used by caml_raise_exception */ - - .common caml_saved_bsp#, 8, 8 - .common caml_saved_rnat#, 8, 8 diff --git a/asmrun/power-elf.S b/asmrun/power-elf.S index 0b3493688..338afbed9 100644 --- a/asmrun/power-elf.S +++ b/asmrun/power-elf.S @@ -27,6 +27,9 @@ /* Invoke the garbage collector. */ + .globl caml_system__code_begin +caml_system__code_begin: + .globl caml_call_gc .type caml_call_gc, @function caml_call_gc: @@ -39,6 +42,11 @@ caml_call_gc: /* Record lowest stack address */ addi 0, 1, 0x1A0 Storeglobal(0, caml_bottom_of_stack, 11) + /* Touch the stack to trigger a recoverable segfault + if insufficient space remains */ + addi 1, 1, -16384 + stw 0, 0(1) + addi 1, 1, 16384 /* Record pointer to register array */ addi 0, 1, 8*32 + 32 Storeglobal(0, caml_gc_regs, 11) @@ -185,15 +193,20 @@ caml_c_call: /* Save return address */ mflr 25 /* Get ready to call C function (address in 11) */ - mtlr 11 + mtctr 11 /* Record lowest stack address and return address */ Storeglobal(1, caml_bottom_of_stack, 12) Storeglobal(25, caml_last_return_address, 12) + /* Touch the stack to trigger a recoverable segfault + if insufficient space remains */ + addi 1, 1, -16384 + stw 0, 0(1) + addi 1, 1, 16384 /* Make the exception handler and alloc ptr available to the C code */ Storeglobal(31, caml_young_ptr, 11) Storeglobal(29, caml_exception_pointer, 11) - /* Call the function (address in link register) */ - blrl + /* Call the function (address in CTR register) */ + bctrl /* Restore return address (in 25, preserved by the C function) */ mtlr 25 /* Reload allocation pointer and allocation limit*/ @@ -408,6 +421,9 @@ caml_callback3_exn: Addrglobal(12, caml_apply3) b .L102 + .globl caml_system__code_end +caml_system__code_end: + /* Frame table */ .section ".data" diff --git a/asmrun/power-rhapsody.S b/asmrun/power-rhapsody.S index 334d6a31a..843e056af 100644 --- a/asmrun/power-rhapsody.S +++ b/asmrun/power-rhapsody.S @@ -41,6 +41,9 @@ .text + .globl _caml_system__code_begin +_caml_system__code_begin: + /* Invoke the garbage collector. */ .globl _caml_call_gc @@ -54,6 +57,11 @@ _caml_call_gc: /* Record lowest stack address */ addi r0, r1, FRAMESIZE Storeglobal r0, _caml_bottom_of_stack, r11 + /* Touch the stack to trigger a recoverable segfault + if insufficient space remains */ + addi r1, r1, -4096*WORD + stg r0, 0(r1) + addi r1, r1, 4096*WORD /* Record pointer to register array */ addi r0, r1, 8*32 + 32 Storeglobal r0, _caml_gc_regs, r11 @@ -204,6 +212,11 @@ _caml_c_call: /* Record lowest stack address and return address */ Storeglobal r1, _caml_bottom_of_stack, r12 Storeglobal r25, _caml_last_return_address, r12 + /* Touch the stack to trigger a recoverable segfault + if insufficient space remains */ + addi r1, r1, -4096*WORD + stg r0, 0(r1) + addi r1, r1, 4096*WORD /* Make the exception handler and alloc ptr available to the C code */ Storeglobal r31, _caml_young_ptr, r11 Storeglobal r29, _caml_exception_pointer, r11 @@ -462,6 +475,9 @@ _caml_callback3_exn: Addrglobal r12, _caml_apply3 b L102 + .globl _caml_system__code_end +_caml_system__code_end: + /* Frame table */ .const diff --git a/asmrun/signals_asm.c b/asmrun/signals_asm.c index 09bc8abc1..9d42718b8 100644 --- a/asmrun/signals_asm.c +++ b/asmrun/signals_asm.c @@ -46,11 +46,14 @@ extern void caml_win32_overflow_detection(); #endif extern char * caml_code_area_start, * caml_code_area_end; +extern char caml_system__code_begin, caml_system__code_end; #define Is_in_code_area(pc) \ ( ((char *)(pc) >= caml_code_area_start && \ (char *)(pc) <= caml_code_area_end) \ - || (Classify_addr(pc) & In_code_area) ) +|| ((char *)(pc) >= &caml_system__code_begin && \ + (char *)(pc) <= &caml_system__code_end) \ +|| (Classify_addr(pc) & In_code_area) ) /* This routine is the common entry point for garbage collection and signal handling. It can trigger a callback to OCaml code. diff --git a/asmrun/sparc.S b/asmrun/sparc.S index ed4e34987..261743159 100644 --- a/asmrun/sparc.S +++ b/asmrun/sparc.S @@ -16,60 +16,6 @@ /* Asm part of the runtime system for the Sparc processor. */ /* Must be preprocessed by cpp */ -/* SunOS 4 prefixes identifiers with _ */ - -#if defined(SYS_sunos) - -#define Caml_young_limit _caml_young_limit -#define Caml_young_ptr _caml_young_ptr -#define Caml_bottom_of_stack _caml_bottom_of_stack -#define Caml_last_return_address _caml_last_return_address -#define Caml_gc_regs _caml_gc_regs -#define Caml_exception_pointer _caml_exception_pointer -#define Caml_allocN _caml_allocN -#define Caml_call_gc _caml_call_gc -#define Caml_garbage_collection _caml_garbage_collection -#define Caml_c_call _caml_c_call -#define Caml_start_program _caml_start_program -#define Caml_program _caml_program -#define Caml_raise_exception _caml_raise_exception -#define Caml_callback_exn _caml_callback_exn -#define Caml_callback2_exn _caml_callback2_exn -#define Caml_callback3_exn _caml_callback3_exn -#define Caml_apply2 _caml_apply2 -#define Caml_apply3 _caml_apply3 -#define Caml_raise _caml_raise -#define Caml_system__frametable _caml_system__frametable -#define Caml_ml_array_bound_error _caml_ml_array_bound_error -#define Caml_array_bound_error _caml_array_bound_error - -#else - -#define Caml_young_limit caml_young_limit -#define Caml_young_ptr caml_young_ptr -#define Caml_bottom_of_stack caml_bottom_of_stack -#define Caml_last_return_address caml_last_return_address -#define Caml_gc_regs caml_gc_regs -#define Caml_exception_pointer caml_exception_pointer -#define Caml_allocN caml_allocN -#define Caml_call_gc caml_call_gc -#define Caml_garbage_collection caml_garbage_collection -#define Caml_c_call caml_c_call -#define Caml_start_program caml_start_program -#define Caml_program caml_program -#define Caml_raise_exception caml_raise_exception -#define Caml_callback_exn caml_callback_exn -#define Caml_callback2_exn caml_callback2_exn -#define Caml_callback3_exn caml_callback3_exn -#define Caml_apply2 caml_apply2 -#define Caml_apply3 caml_apply3 -#define Caml_raise caml_raise -#define Caml_system__frametable caml_system__frametable -#define Caml_ml_array_bound_error caml_ml_array_bound_error -#define Caml_array_bound_error caml_array_bound_error - -#endif - #ifndef SYS_solaris #define INDIRECT_LIMIT #endif @@ -85,11 +31,15 @@ /* Allocation functions */ .text - .global Caml_allocN - .global Caml_call_gc + + .global caml_system__code_begin +caml_system__code_begin: + + .global caml_allocN + .global caml_call_gc /* Required size in %g2 */ -Caml_allocN: +caml_allocN: #ifdef INDIRECT_LIMIT ld [Alloc_limit], %g1 sub Alloc_ptr, %g2, Alloc_ptr @@ -98,22 +48,22 @@ Caml_allocN: sub Alloc_ptr, %g2, Alloc_ptr cmp Alloc_ptr, Alloc_limit #endif - /*blu,pt %icc, Caml_call_gc*/ - blu Caml_call_gc + /*blu,pt %icc, caml_call_gc*/ + blu caml_call_gc nop retl nop /* Required size in %g2 */ -Caml_call_gc: +caml_call_gc: /* Save exception pointer if GC raises */ - Store(Exn_ptr, Caml_exception_pointer) + Store(Exn_ptr, caml_exception_pointer) /* Save current allocation pointer for debugging purposes */ - Store(Alloc_ptr, Caml_young_ptr) + Store(Alloc_ptr, caml_young_ptr) /* Record lowest stack address */ - Store(%sp, Caml_bottom_of_stack) + Store(%sp, caml_bottom_of_stack) /* Record last return address */ - Store(%o7, Caml_last_return_address) + Store(%o7, caml_last_return_address) /* Allocate space on stack for caml_context structure and float regs */ sub %sp, 20*4 + 15*8, %sp /* Save int regs on stack and save it into caml_gc_regs */ @@ -139,7 +89,7 @@ L100: add %sp, 96 + 15*8, %g1 st %g4, [%g1 + 0x48] st %g2, [%g1 + 0x4C] /* Save required size */ mov %g1, %g2 - Store(%g2, Caml_gc_regs) + Store(%g2, caml_gc_regs) /* Save the floating-point registers */ add %sp, 96, %g1 std %f0, [%g1] @@ -158,7 +108,7 @@ L100: add %sp, 96 + 15*8, %g1 std %f26, [%g1 + 0x68] std %f28, [%g1 + 0x70] /* Call the garbage collector */ - call Caml_garbage_collection + call caml_garbage_collection nop /* Restore all regs used by the code generator */ add %sp, 96 + 15*8, %g1 @@ -199,116 +149,116 @@ L100: add %sp, 96 + 15*8, %g1 ldd [%g1 + 0x68], %f26 ldd [%g1 + 0x70], %f28 /* Reload alloc ptr */ - Load(Caml_young_ptr, Alloc_ptr) + Load(caml_young_ptr, Alloc_ptr) /* Allocate space for block */ #ifdef INDIRECT_LIMIT ld [Alloc_limit], %g1 sub Alloc_ptr, %g2, Alloc_ptr cmp Alloc_ptr, %g1 /* Check that we have enough free space */ #else - Load(Caml_young_limit,Alloc_limit) + Load(caml_young_limit,Alloc_limit) sub Alloc_ptr, %g2, Alloc_ptr cmp Alloc_ptr, Alloc_limit #endif blu L100 /* If not, call GC again */ nop /* Return to caller */ - Load(Caml_last_return_address, %o7) + Load(caml_last_return_address, %o7) retl add %sp, 20*4 + 15*8, %sp /* in delay slot */ -/* Call a C function from OCaml */ +/* Call a C function from Ocaml */ - .global Caml_c_call + .global caml_c_call /* Function to call is in %g2 */ -Caml_c_call: +caml_c_call: /* Record lowest stack address and return address */ - Store(%sp, Caml_bottom_of_stack) - Store(%o7, Caml_last_return_address) + Store(%sp, caml_bottom_of_stack) + Store(%o7, caml_last_return_address) /* Save the exception handler and alloc pointer */ - Store(Exn_ptr, Caml_exception_pointer) - sethi %hi(Caml_young_ptr), %g1 + Store(Exn_ptr, caml_exception_pointer) + sethi %hi(caml_young_ptr), %g1 /* Call the C function */ call %g2 - st Alloc_ptr, [%g1 + %lo(Caml_young_ptr)] /* in delay slot */ + st Alloc_ptr, [%g1 + %lo(caml_young_ptr)] /* in delay slot */ /* Reload return address */ - Load(Caml_last_return_address, %o7) + Load(caml_last_return_address, %o7) /* Reload alloc pointer */ - sethi %hi(Caml_young_ptr), %g1 + sethi %hi(caml_young_ptr), %g1 /* Return to caller */ retl - ld [%g1 + %lo(Caml_young_ptr)], Alloc_ptr /* in delay slot */ + ld [%g1 + %lo(caml_young_ptr)], Alloc_ptr /* in delay slot */ -/* Start the OCaml program */ +/* Start the Ocaml program */ - .global Caml_start_program -Caml_start_program: + .global caml_start_program +caml_start_program: /* Save all callee-save registers */ save %sp, -96, %sp /* Address of code to call */ - Address(Caml_program, %l2) + Address(caml_program, %l2) /* Code shared with caml_callback* */ L108: /* Set up a callback link on the stack. */ sub %sp, 16, %sp - Load(Caml_bottom_of_stack, %l0) - Load(Caml_last_return_address, %l1) - Load(Caml_gc_regs, %l3) + Load(caml_bottom_of_stack, %l0) + Load(caml_last_return_address, %l1) + Load(caml_gc_regs, %l3) st %l0, [%sp + 96] st %l1, [%sp + 100] - /* Set up a trap frame to catch exceptions escaping the OCaml code */ + /* Set up a trap frame to catch exceptions escaping the Ocaml code */ call L111 st %l3, [%sp + 104] b L110 nop L111: sub %sp, 8, %sp - Load(Caml_exception_pointer, Exn_ptr) + Load(caml_exception_pointer, Exn_ptr) st %o7, [%sp + 96] st Exn_ptr, [%sp + 100] mov %sp, Exn_ptr /* Reload allocation pointers */ - Load(Caml_young_ptr, Alloc_ptr) + Load(caml_young_ptr, Alloc_ptr) #ifdef INDIRECT_LIMIT - Address(Caml_young_limit, Alloc_limit) + Address(caml_young_limit, Alloc_limit) #else - Load(Caml_young_limit, Alloc_limit) + Load(caml_young_limit, Alloc_limit) #endif - /* Call the OCaml code */ + /* Call the Ocaml code */ L109: call %l2 nop /* Pop trap frame and restore caml_exception_pointer */ ld [%sp + 100], Exn_ptr add %sp, 8, %sp - Store(Exn_ptr, Caml_exception_pointer) + Store(Exn_ptr, caml_exception_pointer) /* Pop callback link, restoring the global variables */ L112: ld [%sp + 96], %l0 ld [%sp + 100], %l1 ld [%sp + 104], %l2 - Store(%l0, Caml_bottom_of_stack) - Store(%l1, Caml_last_return_address) - Store(%l2, Caml_gc_regs) + Store(%l0, caml_bottom_of_stack) + Store(%l1, caml_last_return_address) + Store(%l2, caml_gc_regs) add %sp, 16, %sp /* Save allocation pointer */ - Store(Alloc_ptr, Caml_young_ptr) + Store(Alloc_ptr, caml_young_ptr) /* Reload callee-save registers and return */ ret restore %o0, 0, %o0 /* copy %o0 in this window to caller's %o0 */ L110: /* The trap handler */ - Store(Exn_ptr, Caml_exception_pointer) + Store(Exn_ptr, caml_exception_pointer) /* Encode exception bucket as an exception result */ b L112 or %o0, 2, %o0 /* Raise an exception from C */ - .global Caml_raise_exception -Caml_raise_exception: + .global caml_raise_exception +caml_raise_exception: /* Save exception bucket in a register outside the reg windows */ mov %o0, %g2 /* Load exception pointer in a register outside the reg windows */ - Load(Caml_exception_pointer, %g3) + Load(caml_exception_pointer, %g3) /* Pop some frames until the trap pointer is in the current frame. */ cmp %g3, %fp blt L107 /* if Exn_ptr < %fp, over */ @@ -319,11 +269,11 @@ L106: restore nop L107: /* Reload allocation registers */ - Load(Caml_young_ptr, Alloc_ptr) + Load(caml_young_ptr, Alloc_ptr) #ifdef INDIRECT_LIMIT - Address(Caml_young_limit, Alloc_limit) + Address(caml_young_limit, Alloc_limit) #else - Load(Caml_young_limit, Alloc_limit) + Load(caml_young_limit, Alloc_limit) #endif /* Branch to exception handler */ mov %g3, %sp @@ -336,8 +286,8 @@ L107: /* Callbacks C -> ML */ - .global Caml_callback_exn -Caml_callback_exn: + .global caml_callback_exn +caml_callback_exn: /* Save callee-save registers and return address */ save %sp, -96, %sp /* Initial shuffling of arguments */ @@ -347,8 +297,8 @@ Caml_callback_exn: b L108 ld [%g1], %l2 /* code pointer */ - .global Caml_callback2_exn -Caml_callback2_exn: + .global caml_callback2_exn +caml_callback2_exn: /* Save callee-save registers and return address */ save %sp, -104, %sp /* Initial shuffling of arguments */ @@ -356,12 +306,12 @@ Caml_callback2_exn: mov %i1, %i0 /* first arg */ mov %i2, %i1 /* second arg */ mov %g1, %i2 /* environment */ - sethi %hi(Caml_apply2), %l2 + sethi %hi(caml_apply2), %l2 b L108 - or %l2, %lo(Caml_apply2), %l2 + or %l2, %lo(caml_apply2), %l2 - .global Caml_callback3_exn -Caml_callback3_exn: + .global caml_callback3_exn +caml_callback3_exn: /* Save callee-save registers and return address */ save %sp, -104, %sp /* Initial shuffling of arguments */ @@ -370,38 +320,41 @@ Caml_callback3_exn: mov %i2, %i1 /* second arg */ mov %i3, %i2 /* third arg */ mov %g1, %i3 /* environment */ - sethi %hi(Caml_apply3), %l2 + sethi %hi(caml_apply3), %l2 b L108 - or %l2, %lo(Caml_apply3), %l2 + or %l2, %lo(caml_apply3), %l2 #ifndef SYS_solaris /* Glue code to call [caml_array_bound_error] */ - .global Caml_ml_array_bound_error -Caml_ml_array_bound_error: - Address(Caml_array_bound_error, %g2) - b Caml_c_call + .global caml_ml_array_bound_error +caml_ml_array_bound_error: + Address(caml_array_bound_error, %g2) + b caml_c_call nop #endif + .global caml_system__code_end +caml_system__code_end: + #ifdef SYS_solaris .section ".rodata" #else .data #endif - .global Caml_system__frametable + .global caml_system__frametable .align 4 /* required for gas? */ -Caml_system__frametable: +caml_system__frametable: .word 1 /* one descriptor */ .word L109 /* return address into callback */ .half -1 /* negative frame size => use callback link */ .half 0 /* no roots */ #ifdef SYS_solaris - .type Caml_allocN, #function - .type Caml_call_gc, #function - .type Caml_c_call, #function - .type Caml_start_program, #function - .type Caml_raise_exception, #function - .type Caml_system__frametable, #object + .type caml_allocN, #function + .type caml_call_gc, #function + .type caml_c_call, #function + .type caml_start_program, #function + .type caml_raise_exception, #function + .type caml_system__frametable, #object #endif diff --git a/asmrun/stack.h b/asmrun/stack.h index 907d51c79..9b575cb70 100644 --- a/asmrun/stack.h +++ b/asmrun/stack.h @@ -19,13 +19,6 @@ #define CAML_STACK_H /* Macros to access the stack frame */ -#ifdef TARGET_alpha -#define Saved_return_address(sp) *((intnat *)((sp) - 8)) -#define Already_scanned(sp, retaddr) ((retaddr) & 1L) -#define Mark_scanned(sp, retaddr) (*((intnat *)((sp) - 8)) = (retaddr) | 1L) -#define Mask_already_scanned(retaddr) ((retaddr) & ~1L) -#define Callback_link(sp) ((struct caml_context *)((sp) + 16)) -#endif #ifdef TARGET_sparc #define Saved_return_address(sp) *((intnat *)((sp) + 92)) @@ -41,17 +34,6 @@ #endif #endif -#ifdef TARGET_mips -#define Saved_return_address(sp) *((intnat *)((sp) - 4)) -#define Callback_link(sp) ((struct caml_context *)((sp) + 16)) -#endif - -#ifdef TARGET_hppa -#define Stack_grows_upwards -#define Saved_return_address(sp) *((intnat *)(sp)) -#define Callback_link(sp) ((struct caml_context *)((sp) - 24)) -#endif - #ifdef TARGET_power #define Saved_return_address(sp) *((intnat *)((sp) - SIZEOF_PTR)) #define Already_scanned(sp, retaddr) ((retaddr) & 1) @@ -65,24 +47,11 @@ #define Callback_link(sp) ((struct caml_context *)((sp) + Trap_frame_size)) #endif -#ifdef TARGET_m68k -#define Saved_return_address(sp) *((intnat *)((sp) - 4)) -#define Callback_link(sp) ((struct caml_context *)((sp) + 8)) -#endif - #ifdef TARGET_arm #define Saved_return_address(sp) *((intnat *)((sp) - 4)) #define Callback_link(sp) ((struct caml_context *)((sp) + 8)) #endif -#ifdef TARGET_ia64 -#define Saved_return_address(sp) *((intnat *)((sp) + 8)) -#define Already_scanned(sp, retaddr) ((retaddr) & 1L) -#define Mark_scanned(sp, retaddr) (*((intnat *)((sp) + 8)) = (retaddr) | 1L) -#define Mask_already_scanned(retaddr) ((retaddr) & ~1L) -#define Callback_link(sp) ((struct caml_context *)((sp) + 32)) -#endif - #ifdef TARGET_amd64 #define Saved_return_address(sp) *((intnat *)((sp) - 8)) #define Callback_link(sp) ((struct caml_context *)((sp) + 16)) @@ -663,7 +663,6 @@ model=default system=unknown case "$host" in - sparc*-*-sunos4.*) arch=sparc; system=sunos;; sparc*-*-solaris2.*) arch=sparc; system=solaris;; sparc*-*-*bsd*) arch=sparc; system=bsd;; sparc*-*-linux*) arch=sparc; system=linux;; @@ -1149,7 +1148,7 @@ fi # Determine if system stack overflows can be detected case "$arch,$system" in - i386,linux_elf|amd64,linux|power,rhapsody|amd64,macosx|i386,macosx|amd64,macosx) + i386,linux_elf|amd64,linux|power,elf|power,rhapsody|amd64,macosx|i386,macosx) echo "System stack overflow can be detected." echo "#define HAS_STACK_OVERFLOW_DETECTION" >> s.h;; *) |