diff options
-rw-r--r-- | Changes | 1 | ||||
-rw-r--r-- | asmcomp/sparc/arch.ml | 1 | ||||
-rw-r--r-- | asmcomp/sparc/emit.mlp | 1 | ||||
-rw-r--r-- | asmcomp/sparc/selection.ml | 1 | ||||
-rw-r--r-- | asmrun/backtrace.c | 133 | ||||
-rw-r--r-- | asmrun/signals_asm.c | 2 | ||||
-rw-r--r-- | byterun/backtrace.c | 1 | ||||
-rw-r--r-- | byterun/backtrace.h | 14 |
8 files changed, 11 insertions, 143 deletions
@@ -9,7 +9,6 @@ Bug fixes: third arguments - PR#5551: Avoid repeated lookups for missing cmi files - PR#5662: typo in md5.c -- PR#5695: remove warnings on sparc code emitter Internals: - Moved debugger/envaux.ml to typing/envaux.ml to publish env_of_only_summary diff --git a/asmcomp/sparc/arch.ml b/asmcomp/sparc/arch.ml index ce2c0e157..beaf33a91 100644 --- a/asmcomp/sparc/arch.ml +++ b/asmcomp/sparc/arch.ml @@ -14,6 +14,7 @@ (* Specific operations for the Sparc processor *) +open Misc open Format (* SPARC V8 adds multiply and divide. diff --git a/asmcomp/sparc/emit.mlp b/asmcomp/sparc/emit.mlp index 95bb29421..ef3fb9a8e 100644 --- a/asmcomp/sparc/emit.mlp +++ b/asmcomp/sparc/emit.mlp @@ -14,6 +14,7 @@ (* Emission of Sparc assembly code *) +open Location open Misc open Cmm open Arch diff --git a/asmcomp/sparc/selection.ml b/asmcomp/sparc/selection.ml index 31d6e7020..e82cc670a 100644 --- a/asmcomp/sparc/selection.ml +++ b/asmcomp/sparc/selection.ml @@ -14,6 +14,7 @@ (* Instruction selection for the Sparc processor *) +open Misc open Cmm open Reg open Arch diff --git a/asmrun/backtrace.c b/asmrun/backtrace.c index cd10be603..7b47c0bfc 100644 --- a/asmrun/backtrace.c +++ b/asmrun/backtrace.c @@ -23,10 +23,9 @@ #include "mlvalues.h" #include "stack.h" -CAMLexport code_t * caml_after_stackoverflow = NULL; int caml_backtrace_active = 0; int caml_backtrace_pos = 0; -backtrace_item_t * caml_backtrace_buffer = NULL; +code_t * caml_backtrace_buffer = NULL; value caml_backtrace_last_exn = Val_unit; #define BACKTRACE_BUFFER_SIZE 1024 @@ -55,25 +54,6 @@ CAMLprim value caml_backtrace_status(value vunit) return Val_bool(caml_backtrace_active); } -void store_backtrace_descr(frame_descr* d) -{ - if( caml_backtrace_pos == 0 ){ - backtrace_item_t *p = &caml_backtrace_buffer[caml_backtrace_pos++]; - p -> backtrace_descriptor = d; - p -> backtrace_count = 0x10; - } else { - backtrace_item_t *prev = &caml_backtrace_buffer[caml_backtrace_pos-1]; - if ( prev->backtrace_descriptor == d && (prev->backtrace_count & 0xf) == 0 ){ - prev->backtrace_count += 0x10; - } else { - backtrace_item_t *p = &caml_backtrace_buffer[caml_backtrace_pos++]; - p -> backtrace_descriptor = d; - p -> backtrace_count = 0x10; - } - } -} - - /* Store the return addresses contained in the given stack fragment into the backtrace array */ @@ -82,110 +62,16 @@ void caml_stash_backtrace(value exn, uintnat pc, char * sp, char * trapsp) frame_descr * d; uintnat h; - /* - { - code_t* stack_ptr = caml_bottom_of_stack; -#ifdef Stack_grows_upwards - stack_ptr += sizeof(code_t*); -#else - stack_ptr -= sizeof(code_t*); -#endif - - } - */ - - /* fprintf(stderr, "caml_bottom_of_stack = %ld\n", caml_bottom_of_stack); */ - if (exn != caml_backtrace_last_exn) { caml_backtrace_pos = 0; caml_backtrace_last_exn = exn; } if (caml_backtrace_buffer == NULL) { - caml_backtrace_buffer = malloc(BACKTRACE_BUFFER_SIZE * sizeof(backtrace_item_t)); + caml_backtrace_buffer = malloc(BACKTRACE_BUFFER_SIZE * sizeof(code_t)); if (caml_backtrace_buffer == NULL) return; } if (caml_frame_descriptors == NULL) caml_init_frame_descriptors(); - if( caml_after_stackoverflow != NULL ){ - char *fault_addr = caml_after_stackoverflow; -#ifndef Stack_grows_upwards - int sp_move = sizeof(code_t*); -#else - int sp_move = - sizeof(code_t*); -#endif - int attempts = 32768; - - caml_after_stackoverflow = NULL; - -#ifndef Stack_grows_upwards - fault_addr += 32768; -#else - fault_addr -= 32768; -#endif - sp = fault_addr; - pc = *((uintnat *)sp); - sp += sp_move; - - /* fprintf(stderr, "stack overflow at raise %ld - sp=%ld - trapsp=%ld = %ld\n", fault_addr, sp, trapsp, trapsp-sp); */ - while (1) { - /* Find the descriptor corresponding to the return address */ - h = Hash_retaddr(pc); - while(1) { - /* fprintf(stderr, "trying hash\n"); */ - d = caml_frame_descriptors[h]; - if (d == 0){ - /* fprintf(stderr, "failed :-( \n"); */ -#ifndef Stack_grows_upwards - if (sp > trapsp) return; -#else - if (sp < trapsp) return; -#endif - pc = *((uintnat *)sp); - sp += sp_move; - /* fprintf(stderr, "trying now pc = %ld at sp = %ld\n", pc, sp); */ - break; - } - if (d->retaddr == pc) { - attempts = 0; - break; - } - h = (h+1) & caml_frame_descriptors_mask; - } - if( d == 0 ) continue; - /* fprintf(stderr, "found frame !\n"); */ - /* Skip to next frame */ - if (d->frame_size != 0xFFFF) { - /* Regular frame, store its descriptor in the backtrace buffer */ - if (caml_backtrace_pos >= BACKTRACE_BUFFER_SIZE) return; - store_backtrace_descr(d); -#ifndef Stack_grows_upwards - sp += (d->frame_size & 0xFFFC); -#else - sp -= (d->frame_size & 0xFFFC); -#endif - pc = Saved_return_address(sp); -#ifdef Mask_already_scanned - pc = Mask_already_scanned(pc); -#endif - } else { - /* Special frame marking the top of a stack chunk for an ML callback. - Skip C portion of stack and continue with next ML stack chunk. */ - struct caml_context * next_context = Callback_link(sp); - sp = next_context->bottom_of_stack; - pc = next_context->last_retaddr; - /* A null sp means no more ML stack chunks; stop here. */ - if (sp == NULL) return; - } - /* Stop when we reach the current exception handler */ -#ifndef Stack_grows_upwards - if (sp > trapsp) return; -#else - if (sp < trapsp) return; -#endif - } - } else { - - fprintf(stderr, "stack at raise %ld - %ld = %ld\n", sp, trapsp, trapsp-sp); while (1) { /* Find the descriptor corresponding to the return address */ h = Hash_retaddr(pc); @@ -199,7 +85,7 @@ void caml_stash_backtrace(value exn, uintnat pc, char * sp, char * trapsp) if (d->frame_size != 0xFFFF) { /* Regular frame, store its descriptor in the backtrace buffer */ if (caml_backtrace_pos >= BACKTRACE_BUFFER_SIZE) return; - store_backtrace_descr(d); + caml_backtrace_buffer[caml_backtrace_pos++] = (code_t) d; #ifndef Stack_grows_upwards sp += (d->frame_size & 0xFFFC); #else @@ -225,8 +111,6 @@ void caml_stash_backtrace(value exn, uintnat pc, char * sp, char * trapsp) if (sp < trapsp) return; #endif } - - } } /* Extract location information for the given frame descriptor */ @@ -278,7 +162,7 @@ static void extract_location_info(frame_descr * d, li->loc_endchr = ((info2 & 0xF) << 6) | (info1 >> 26); } -static void print_location(struct loc_info * li, int index, int count) +static void print_location(struct loc_info * li, int index) { char * info; @@ -294,9 +178,6 @@ static void print_location(struct loc_info * li, int index, int count) fprintf (stderr, "%s file \"%s\", line %d, characters %d-%d\n", info, li->loc_filename, li->loc_lnum, li->loc_startchr, li->loc_endchr); - if( count != 1 << 4 ){ - fprintf(stderr, "\t(called %d times)\n", count >> 4); - } } /* Print a backtrace */ @@ -307,8 +188,8 @@ void caml_print_exception_backtrace(void) struct loc_info li; for (i = 0; i < caml_backtrace_pos; i++) { - extract_location_info(caml_backtrace_buffer[i].backtrace_descriptor, &li); - print_location(&li, i, caml_backtrace_buffer[i].backtrace_count); + extract_location_info((frame_descr *) (caml_backtrace_buffer[i]), &li); + print_location(&li, i); } } @@ -323,7 +204,7 @@ CAMLprim value caml_get_exception_backtrace(value unit) arr = caml_alloc(caml_backtrace_pos, 0); for (i = 0; i < caml_backtrace_pos; i++) { - extract_location_info(caml_backtrace_buffer[i].backtrace_descriptor, &li); + extract_location_info((frame_descr *) (caml_backtrace_buffer[i]), &li); if (li.loc_valid) { fname = caml_copy_string(li.loc_filename); p = caml_alloc_small(5, 0); diff --git a/asmrun/signals_asm.c b/asmrun/signals_asm.c index e045bc5b5..9d42718b8 100644 --- a/asmrun/signals_asm.c +++ b/asmrun/signals_asm.c @@ -187,7 +187,6 @@ static char sig_alt_stack[SIGSTKSZ]; #define EXTRA_STACK 0x2000 #endif -extern void* caml_after_stackoverflow; DECLARE_SIGNAL_HANDLER(segv_handler) { struct rlimit limit; @@ -212,7 +211,6 @@ DECLARE_SIGNAL_HANDLER(segv_handler) caml_exception_pointer = (char *) CONTEXT_EXCEPTION_POINTER; caml_young_ptr = (char *) CONTEXT_YOUNG_PTR; #endif - caml_after_stackoverflow = fault_addr; caml_raise_stack_overflow(); } /* Otherwise, deactivate our exception handler and return, diff --git a/byterun/backtrace.c b/byterun/backtrace.c index 39f85dab5..b5efdc3db 100644 --- a/byterun/backtrace.c +++ b/byterun/backtrace.c @@ -108,7 +108,6 @@ void caml_stash_backtrace(value exn, code_t pc, value * sp) if (pc >= caml_start_code && pc < end_code){ caml_backtrace_buffer[caml_backtrace_pos++] = pc; } - fprintf(stderr, "sp=%lx - caml_trapsp = %lx\n", sp, caml_trapsp); for (/*nothing*/; sp < caml_trapsp; sp++) { code_t p = (code_t) *sp; if (p >= caml_start_code && p < end_code) { diff --git a/byterun/backtrace.h b/byterun/backtrace.h index 56ce167a2..23c72e6c9 100644 --- a/byterun/backtrace.h +++ b/byterun/backtrace.h @@ -18,21 +18,9 @@ #include "mlvalues.h" -#ifdef NATIVE_CODE -#include "../asmrun/stack.h" - -typedef struct backtrace_item { - frame_descr* backtrace_descriptor; - uintnat backtrace_count; -} backtrace_item_t; -CAMLextern backtrace_item_t * caml_backtrace_buffer; - -#else -CAMLextern code_t * caml_backtrace_buffer; -#endif - CAMLextern int caml_backtrace_active; CAMLextern int caml_backtrace_pos; +CAMLextern code_t * caml_backtrace_buffer; CAMLextern value caml_backtrace_last_exn; CAMLextern char * caml_cds_file; |