diff options
-rw-r--r-- | asmcomp/emit_mips.mlp | 195 | ||||
-rw-r--r-- | asmcomp/proc_mips.ml | 8 | ||||
-rw-r--r-- | asmrun/mips.S | 123 | ||||
-rw-r--r-- | config/auto-aux/endian.c | 2 | ||||
-rwxr-xr-x | configure | 41 | ||||
-rw-r--r-- | testasmcomp/mips.S | 2 |
6 files changed, 254 insertions, 117 deletions
diff --git a/asmcomp/emit_mips.mlp b/asmcomp/emit_mips.mlp index ab149f003..252f1ce7e 100644 --- a/asmcomp/emit_mips.mlp +++ b/asmcomp/emit_mips.mlp @@ -22,6 +22,15 @@ open Mach open Linearize open Emitaux +(* Determine whether we're emitting PIC code (IRIX -32 model) + or absolute code *) + +let pic = + match Config.system with + "ultrix" -> false + | "irix" -> true + | _ -> fatal_error "Emit_mips.pic" + (* Tradeoff between code size and code speed *) let fastcode_flag = ref true @@ -55,6 +64,10 @@ let emit_twin_reg = function { loc = Reg r; typ = Float } -> emit_string (float_reg_twin_name.(r - 100)) | _ -> fatal_error "Emit_mips.emit_twin_reg" +(* Record if $gp is needed (in PIC mode) *) + +let uses_gp = ref false + (* Layout of the stack frame *) let stack_offset = ref 0 @@ -63,7 +76,7 @@ let frame_size () = let size = !stack_offset + 4 * num_stack_slots.(0) + 8 * num_stack_slots.(1) + - (if !contains_calls then 4 else 0) in + (if !contains_calls then if !uses_gp then 8 else 4 else 0) in Misc.align size 8 let slot_offset loc cl = @@ -95,7 +108,6 @@ let emit_addressing addr r n = `{emit_symbol s} + {emit_int ofs}` (* Communicate live registers at call points to the assembler *) -(* Not supported by older versions of the assembler ... *) let int_reg_number = [| 2; 3; 4; 5; 6; 7; 8; 9; 10; 11; 12; 13; 14; 15; 16; 17; 18; 19; 20; 21 @@ -105,25 +117,27 @@ let float_reg_number = [| 0; 2; 4; 6; 8; 12; 14; 16; 18; 20; 22; 24; 26; 28; 30 |] -let liveregs instr extra_msk = () -(* - * (* $22, $23, $30 always live *) - * let int_mask = ref(0x00000302 lor extra_msk) - * and float_mask = ref 0 in - * let add_register = function - * {loc = Reg r; typ = (Int | Addr)} -> - * int_mask := - * !int_mask lor (1 lsl (31 - int_reg_number.(r))) - * | {loc = Reg r; typ = Float} -> - * float_mask := - * !float_mask lor (3 lsl (31 - float_reg_number.(r - 100))) - * | _ -> () in - * Reg.Set.iter add_register instr.live; - * Array.iter add_register instr.arg; - * emit_printf " .livereg 0x%08x, 0x%08x\n" !int_mask !float_mask ***) +let liveregs instr extra_msk = + (* The .livereg directive is not supported by old Ultrix versions of + the MIPS assembler... *) + if pic then begin + (* $22, $23, $30 always live *) + let int_mask = ref(0x00000302 lor extra_msk) + and float_mask = ref 0 in + let add_register = function + {loc = Reg r; typ = (Int | Addr)} -> + int_mask := + !int_mask lor (1 lsl (31 - int_reg_number.(r))) + | {loc = Reg r; typ = Float} -> + float_mask := + !float_mask lor (3 lsl (31 - float_reg_number.(r - 100))) + | _ -> () in + Reg.Set.iter add_register instr.live; + Array.iter add_register instr.arg; + emit_printf " .livereg 0x%08x, 0x%08x\n" !int_mask !float_mask + end let live_24 = 1 lsl (31 - 24) -let live_25 = 1 lsl (31 - 25) (* Record live pointers at call points *) @@ -161,6 +175,36 @@ let emit_frame fd = fd.fd_live_offset; ` .align 2\n` +(* In PIC mode, determine if $gp is used in the function *) + +let rec instr_uses_gp i = + match i.desc with + Lend -> false + | Lop(Iconst_symbol s) -> true + | Lop(Icall_imm s) -> true + | Lop(Itailcall_imm s) -> true + | Lop(Iconst_symbol s) -> true + | Lop(Iextcall(_, _)) -> true + | Lop(Iload(_, Ibased(_, _))) -> true + | Lop(Istore(_, Ibased(_, _))) -> true + | Lswitch jumptbl -> true + | _ -> instr_uses_gp i.next + +(* Emit code to reload $gp after a jal *) + +let reload_gp () = + if !uses_gp then + ` lw $gp, {emit_int(frame_size() - 8)}($sp)\n` + +(* Initialize $gp ``out of nowhere'' in rarely-executed code *) + +let reinit_gp () = + let lbl = new_label() in + ` bal {emit_label lbl}, $25\n`; + `{emit_label lbl}: .set noreorder\n`; + ` .cpload $25\n`; + ` .set reorder\n` + (* Names of various instructions *) let name_for_comparison = function @@ -181,12 +225,12 @@ let name_for_int_operation = function | Imul -> "mul" | Idiv -> "div" | Imod -> "rem" - | Iand -> "and" - | Ior -> "or" - | Ixor -> "xor" - | Ilsl -> "sll" - | Ilsr -> "srl" - | Iasr -> "sra" + | Iand -> "and" + | Ior -> "or" + | Ixor -> "xor" + | Ilsl -> "sll" + | Ilsr -> "srl" + | Iasr -> "sra" | Icomp cmp -> "s" ^ name_for_comparison cmp | _ -> Misc.fatal_error "Emit.name_for_int_operation" @@ -244,10 +288,14 @@ let emit_instr i = ` la {emit_reg i.res.(0)}, {emit_symbol s}\n` | Lop(Icall_ind) -> liveregs i 0; - `{record_frame i.live} jal {emit_reg i.arg.(0)}\n` + if pic then + ` move $25, {emit_reg i.arg.(0)}\n`; + `{record_frame i.live} jal {emit_reg i.arg.(0)}\n`; + reload_gp() | Lop(Icall_imm s) -> liveregs i 0; - `{record_frame i.live} jal {emit_symbol s}\n` + `{record_frame i.live} jal {emit_symbol s}\n`; + reload_gp() | Lop(Itailcall_ind) -> let n = frame_size() in if !contains_calls then @@ -255,6 +303,8 @@ let emit_instr i = if n > 0 then ` addu $sp, $sp, {emit_int n}\n`; liveregs i 0; + if pic then + ` mov $25, {emit_reg i.arg.(0)}\n`; ` j {emit_reg i.arg.(0)}\n` | Lop(Itailcall_imm s) -> if s = !function_name then begin @@ -266,17 +316,22 @@ let emit_instr i = if n > 0 then ` addu $sp, $sp, {emit_int n}\n`; liveregs i 0; - ` j {emit_symbol s}\n` + if pic then begin + ` la $25, {emit_symbol s}\n`; + ` j $25\n` + end else + ` j {emit_symbol s}\n` end | Lop(Iextcall(s, alloc)) -> if alloc then begin - ` la $25, {emit_symbol s}\n`; - liveregs i live_25; + ` la $24, {emit_symbol s}\n`; + liveregs i live_24; `{record_frame i.live} jal caml_c_call\n` end else begin ` jal {emit_symbol s}\n` - end - | Lop(Istackoffset n) -> + end; + reload_gp() + | Lop(Istackoffset n) -> if n >= 0 then ` subu $sp, $sp, {emit_int n}\n` else @@ -313,25 +368,24 @@ let emit_instr i = ` swc1 {emit_twin_reg i.arg.(0)}, {emit_addressing (offset_addressing addr 4) i.arg 1}\n` end | Lop(Ialloc n) -> - if !fastcode_flag then begin + if pic or !fastcode_flag then begin if !call_gc_label = 0 then call_gc_label := new_label(); - ` subu $22, $22, {emit_int n}\n`; - ` subu $25, $22, $23\n`; ` .set noreorder\n`; - `{record_frame i.live} bltzal $25, {emit_label !call_gc_label}\n`; - ` li $25, {emit_int n}\n`; - ` .set reorder\n`; - ` addu {emit_reg i.res.(0)}, $22, 4\n` + ` subu $22, $22, {emit_int n}\n`; + ` subu $24, $22, $23\n`; + `{record_frame i.live} bltzal $24, {emit_label !call_gc_label}\n`; + ` addu {emit_reg i.res.(0)}, $22, 4\n`; + ` .set reorder\n` end else begin begin match n with - 8 -> liveregs i 0; + 8 -> liveregs i 0; `{record_frame i.live} jal caml_alloc1\n` | 12 -> liveregs i 0; `{record_frame i.live} jal caml_alloc2\n` | 16 -> liveregs i 0; `{record_frame i.live} jal caml_alloc3\n` - | _ -> ` li $25, {emit_int n}\n`; - liveregs i live_25; + | _ -> ` li $24, {emit_int n}\n`; + liveregs i live_24; `{record_frame i.live} jal caml_alloc\n` end; ` addu {emit_reg i.res.(0)}, $22, 4\n` @@ -358,7 +412,7 @@ let emit_instr i = ` mtc1 {emit_reg i.arg.(0)}, {emit_reg i.res.(0)}\n`; ` cvt.d.w {emit_reg i.res.(0)}, {emit_reg i.res.(0)}\n` | Lop(Iintoffloat) -> - ` trunc.w.d $f10, {emit_reg i.arg.(0)}, $25\n`; + ` trunc.w.d $f10, {emit_reg i.arg.(0)}, $24\n`; ` mfc1 {emit_reg i.res.(0)}, $f10\n` | Lop(Ispecific sop) -> fatal_error "Emit_mips: Ispecific" @@ -394,41 +448,46 @@ let emit_instr i = then ` bc1f {emit_label lbl}\n` else ` bc1t {emit_label lbl}\n` | Ioddtest -> - ` and $25, {emit_reg i.arg.(0)}, 1\n`; - ` bne $25, $0, {emit_label lbl}\n` + ` and $24, {emit_reg i.arg.(0)}, 1\n`; + ` bne $24, $0, {emit_label lbl}\n` | Ieventest -> - ` and $25, {emit_reg i.arg.(0)}, 1\n`; - ` beq $25, $0, {emit_label lbl}\n` + ` and $24, {emit_reg i.arg.(0)}, 1\n`; + ` beq $24, $0, {emit_label lbl}\n` end | Lcondbranch3(lbl0, lbl1, lbl2) -> - ` subu $25, {emit_reg i.arg.(0)}, 1\n`; + ` subu $24, {emit_reg i.arg.(0)}, 1\n`; begin match lbl0 with None -> () | Some lbl -> ` beq {emit_reg i.arg.(0)}, $0, {emit_label lbl}\n` end; begin match lbl1 with None -> () - | Some lbl -> ` beq $25, $0, {emit_label lbl}\n` + | Some lbl -> ` beq $24, $0, {emit_label lbl}\n` end; begin match lbl2 with None -> () - | Some lbl -> ` bgtz $25, {emit_label lbl}\n` + | Some lbl -> ` bgtz $24, {emit_label lbl}\n` end | Lswitch jumptbl -> let lbl_jumptbl = new_label() in - ` sll $25, {emit_reg i.arg.(0)}, 2\n`; - ` lw $25, {emit_label lbl_jumptbl}($25)\n`; - liveregs i live_25; - ` j $25\n`; + ` sll $24, {emit_reg i.arg.(0)}, 2\n`; + ` lw $24, {emit_label lbl_jumptbl}($24)\n`; + if pic then + ` .cpadd $24\n`; + liveregs i live_24; + ` j $24\n`; ` .rdata\n`; `{emit_label lbl_jumptbl}:\n`; for i = 0 to Array.length jumptbl - 1 do - ` .word {emit_label jumptbl.(i)}\n` + if pic + then ` .gpword {emit_label jumptbl.(i)}\n` + else ` .word {emit_label jumptbl.(i)}\n` done; ` .text\n` | Lsetuptrap lbl -> ` subu $sp, $sp, 8\n`; - ` bal {emit_label lbl}\n` + ` bal {emit_label lbl}\n`; + reload_gp() | Lpushtrap -> stack_offset := !stack_offset + 8; ` sw $30, 0($sp)\n`; @@ -439,8 +498,8 @@ let emit_instr i = ` addu $sp, $sp, 8\n`; stack_offset := !stack_offset - 8 | Lraise -> + ` lw $25, 4($30)\n`; ` move $sp, $30\n`; - ` lw $25, 4($sp)\n`; ` lw $30, 0($sp)\n`; ` addu $sp, $sp, 8\n`; liveregs i 0; @@ -454,6 +513,7 @@ let rec emit_all i = let fundecl fundecl = function_name := fundecl.fun_name; fastcode_flag := fundecl.fun_fast; + uses_gp := pic && instr_uses_gp fundecl.fun_body; tailrec_entry_point := new_label(); stack_offset := 0; call_gc_label := 0; @@ -463,17 +523,30 @@ let fundecl fundecl = ` .globl {emit_symbol fundecl.fun_name}\n`; ` .ent {emit_symbol fundecl.fun_name}\n`; `{emit_symbol fundecl.fun_name}:\n`; + if !uses_gp then begin + ` .set noreorder\n`; + ` .cpload $25\n`; + ` .set reorder\n` + end; let n = frame_size() in if n > 0 then ` subu $sp, $sp, {emit_int n}\n`; if !contains_calls then ` sw $31, {emit_int(n - 4)}($sp)\n`; + if !uses_gp && !contains_calls then + ` sw $gp, {emit_int(n - 8)}($sp)\n`; `{emit_label !tailrec_entry_point}:\n`; emit_all fundecl.fun_body; - if !call_gc_label > 0 then - `{emit_label !call_gc_label}: j caml_call_gc\n`; - if !range_check_trap > 0 then - `{emit_label !range_check_trap}: j array_bound_error\n`; + if !call_gc_label > 0 then begin + `{emit_label !call_gc_label}:\n`; + if pic && not !uses_gp then reinit_gp(); + ` j caml_call_gc\n` + end; + if !range_check_trap > 0 then begin + `{emit_label !range_check_trap}:\n`; + if pic && not !uses_gp then reinit_gp(); + ` j array_bound_error\n` + end; ` .end {emit_symbol fundecl.fun_name}\n` (* Emission of data *) diff --git a/asmcomp/proc_mips.ml b/asmcomp/proc_mips.ml index 33c4cb29b..c89389ef6 100644 --- a/asmcomp/proc_mips.ml +++ b/asmcomp/proc_mips.ml @@ -234,6 +234,12 @@ let contains_calls = ref false (* Calling the assembler *) +let asm_command = + match Config.system with + "ultrix" -> "as -O2 -nocpp -o " + | "irix" -> "as -32 -O2 -nocpp -o " + | _ -> fatal_error "Proc_mips.asm_command" + let assemble_file infile outfile = - Sys.command ("as -O2 -nocpp -o " ^ outfile ^ " " ^ infile) + Sys.command (asm_command ^ outfile ^ " " ^ infile) diff --git a/asmrun/mips.S b/asmrun/mips.S index 97fdb6f63..ff999978d 100644 --- a/asmrun/mips.S +++ b/asmrun/mips.S @@ -38,7 +38,21 @@ .globl caml_alloc3 .globl caml_alloc .globl caml_call_gc - .ent caml_alloc1 + .ent caml_call_gc + +caml_call_gc: +#ifdef _PIC + .set noreorder + .cpload $25 + .set reorder +#endif + /* Record return address and adjust it to point back to + the beginning of the allocation sequence */ + sw $31, caml_last_return_address + subu $31, $31, 32 + /* Don't request any allocation, will be redone at return */ + li $24, 0 + b $110 /* caml_alloc* : all code generator registers preserved. */ @@ -46,36 +60,43 @@ caml_alloc1: subu $22, $22, 8 bltu $22, $23, $100 j $31 -$100: li $25, 8 - b caml_call_gc +$100: li $24, 8 + b caml_call_gc_internal caml_alloc2: subu $22, $22, 12 bltu $22, $23, $101 j $31 -$101: li $25, 12 - b caml_call_gc +$101: li $24, 12 + b caml_call_gc_internal caml_alloc3: subu $22, $22, 16 bltu $22, $23, $102 j $31 -$102: li $25, 16 - b caml_call_gc +$102: li $24, 16 + b caml_call_gc_internal caml_alloc: - subu $22, $22, $25 - bltu $22, $23, caml_call_gc + subu $22, $22, $24 + bltu $22, $23, caml_call_gc_internal j $31 -caml_call_gc: - /* Record lowest stack address and return address */ +caml_call_gc_internal: + /* Record return address */ sw $31, caml_last_return_address + +$110: + /* Record lowest stack address */ sw $sp, caml_bottom_of_stack - /* Save requested size. Also reserve some stack space for the call. */ - subu $sp, $sp, 24 - sw $31, 20($sp) - sw $25, 16($sp) + /* Save actual return address, $gp, requested size. + Also reserve some stack space for the call. */ + subu $sp, $sp, 32 + sw $31, 28($sp) +#ifdef _PIC + .cprestore 24 +#endif + sw $24, 16($sp) /* Save current allocation pointer for debugging purposes */ sw $22, young_ptr /* Save the exception handler (if e.g. a sighandler raises) */ @@ -159,16 +180,16 @@ caml_call_gc: lw $22, young_ptr lw $23, young_limit /* Allocate space for the block */ - lw $25, 16($sp) - subu $22, $22, $25 + lw $24, 16($sp) + subu $22, $22, $24 /* Say that we are back into Caml code */ sw $0, caml_last_return_address /* Return to caller */ - lw $31, 20($sp) - addu $sp, $sp, 24 + lw $31, 28($sp) + addu $sp, $sp, 32 j $31 - .end caml_alloc1 + .end caml_call_gc /* Call a C function from Caml */ @@ -176,7 +197,12 @@ caml_call_gc: .ent caml_c_call caml_c_call: - /* Function to call is in $25 */ + /* Function to call is in $24 */ +#ifdef _PIC + .set noreorder + .cpload $25 + .set reorder +#endif /* Record lowest stack address and return address */ sw $31, caml_last_return_address sw $sp, caml_bottom_of_stack @@ -184,7 +210,16 @@ caml_c_call: sw $22, young_ptr sw $30, caml_exception_pointer /* Call the function */ - jal $25 +#ifdef _PIC + move $25, $24 +#endif + jal $24 +#ifdef _PIC + /* Reload $gp based on return address */ + .set noreorder + .cpload $31 + .set reorder +#endif /* Reload alloc ptr and alloc limit */ lw $22, young_ptr lw $23, young_limit @@ -203,6 +238,11 @@ caml_c_call: .globl stray_exn_handler .ent caml_start_program caml_start_program: +#ifdef _PIC + .set noreorder + .cpload $25 + .set reorder +#endif subu $sp, $sp, 88 sw $31, 84($sp) /* Save all callee-save registers */ @@ -264,14 +304,19 @@ stray_exn_handler: .globl raise_caml_exception .ent raise_caml_exception raise_caml_exception: +#ifdef _PIC + .set noreorder + .cpload $25 + .set reorder +#endif move $2, $4 lw $22, young_ptr lw $23, young_limit lw $sp, caml_exception_pointer lw $30, 0($sp) - lw $25, 4($sp) + lw $24, 4($sp) addu $sp, $sp, 8 - j $25 + j $24 .end raise_caml_exception @@ -280,6 +325,11 @@ raise_caml_exception: .globl callback .ent callback callback: +#ifdef _PIC + .set noreorder + .cpload $25 + .set reorder +#endif /* Initial shuffling of arguments */ move $9, $4 /* closure */ move $8, $5 /* argument */ @@ -323,7 +373,16 @@ $103: /* Say that we are back into Caml code */ sw $0, caml_last_return_address /* Call the Caml code */ +#ifdef _PIC + move $25, $24 +#endif $104: jal $24 +#ifdef _PIC + /* Reload $gp based on return address */ + .set noreorder + .cpload $31 + .set reorder +#endif /* Pop the trap frame, restoring caml_exception_pointer */ lw $24, 0($sp) sw $24, caml_exception_pointer @@ -360,6 +419,12 @@ $104: jal $24 /* The trap handler: re-raise the exception through mlraise, so that local C roots are cleaned up correctly. */ $105: +#ifdef _PIC + /* Reload $gp based on trap address (still in $25) */ + .set noreorder + .cpload $25 + .set reorder +#endif sw $22, young_ptr sw $30, caml_exception_pointer lw $24, 0($sp) @@ -374,6 +439,11 @@ $105: .globl callback2 .ent callback2 callback2: +#ifdef _PIC + .set noreorder + .cpload $25 + .set reorder +#endif /* Initial shuffling of arguments */ move $10, $4 /* closure */ move $8, $5 /* first argument */ @@ -386,6 +456,11 @@ callback2: .globl callback3 .ent callback3 callback3: +#ifdef _PIC + .set noreorder + .cpload $25 + .set reorder +#endif /* Initial shuffling of arguments */ move $11, $4 /* closure */ move $8, $5 /* first argument */ diff --git a/config/auto-aux/endian.c b/config/auto-aux/endian.c index 0f3306d0e..7f1da82d3 100644 --- a/config/auto-aux/endian.c +++ b/config/auto-aux/endian.c @@ -13,7 +13,7 @@ #include "m.h" -#ifndef SIXTYFOUR +#ifndef ARCH_SIXTYFOUR long intval = 0x41424344L; char * bigendian = "ABCD"; char * littleendian = "DCBA"; @@ -189,7 +189,8 @@ case "$host" in i[3456]86-*-*bsd*) arch=i386; system=bsd;; i[3456]86-*-nextstep*) arch=i386; system=nextstep;; i[3456]86-*-solaris*) arch=i386; system=solaris;; - mips-*-ultrix*) arch=mips;; + mips-*-irix*) arch=mips; system=irix;; + mips-*-ultrix*) arch=mips; system=ultrix;; hppa1.1-*-hpux*) arch=hppa; system=hpux;; hppa1.1-*-nextstep*) arch=hppa; system=nextstep;; rs6000-*-aix*) arch=power; model=rs6000; system=aix;; @@ -204,11 +205,12 @@ case "$arch" in esac case "$arch,$nativecc,$system" in - alpha,cc,*) nativecccompopts=-std1;; - mips,cc,*) nativecccompopts=-std;; - *,*,nextstep) nativecccompopts="-Wall -D_POSIX_SOURCE";; - *,gcc,*) nativecccompopts=-Wall;; - *) nativecccompopts='';; + alpha,cc,*) nativecccompopts=-std1;; + mips,cc,irix) nativecccompopts="-32 -std";; + mips,cc,ultrix) nativecccompopts=-std;; + *,*,nextstep) nativecccompopts="-Wall -D_POSIX_SOURCE";; + *,gcc,*) nativecccompopts=-Wall;; + *) nativecccompopts='';; esac nativecclinkopts='' @@ -219,7 +221,8 @@ asppflags='' case "$arch,$model,$system" in alpha,*,*) asflags='-O2'; asppflags="$asflags";; - mips,*,*) asflags='-O2'; asppflags="$asflags";; + mips,*,irix) asflags='-32 -O2'; asppflags="$asflags";; + mips,*,ultrix) asflags='-O2'; asppflags="$asflags";; sparc,*,bsd) aspp='gcc'; asppflags='-c -DSYS_$(SYSTEM)';; sparc,*,*) asppflags='-P -DSYS_$(SYSTEM)';; i386,*,solaris) asppflags='-P -DSYS_$(SYSTEM)';; @@ -240,26 +243,6 @@ echo "ASFLAGS=$asflags" >> Makefile echo "ASPP=$aspp" >> Makefile echo "ASPPFLAGS=$asppflags" >> Makefile -# Checking how to invoke cpp -# We don't need cpp anymore -#if sh ./searchpath cpp; then -# cpp="cpp -P" -#elif test -f /lib/cpp; then -# cpp="/lib/cpp -P" -#elif test -f /usr/ccs/lib/cpp; then -# cpp="/usr/ccs/lib/cpp -P" -#else -# cpp="not found" -#fi -# -#echo "CPP=$cpp" >> Makefile -# -#echo "How to invoke the C preprocessor: $cpp" -# -#if test "$cpp" = "not found"; then -# echo "(Please edit the generated config/Makefile to set CPP correctly)" -#fi - # Where is ranlib? if sh ./searchpath ranlib; then @@ -459,7 +442,7 @@ fi # Async I/O under OSF1 3.x are so buggy that the test program hangs... testasyncio=true if test -f /usr/bin/uname; then - case "`uname -s -r`" in + case "`/usr/bin/uname -s -r`" in "OSF1 V3."*) testasyncio=false;; esac fi @@ -498,7 +481,7 @@ fi # Determine the target architecture for the "num" library case "$host" in - mips*) bignum_arch=mips;; + mips-*-ultrix*) bignum_arch=mips;; alpha*) bignum_arch=alpha;; i960*) bignum_arch=i960;; sparc-*-sunos*) bignum_arch=supersparc;; diff --git a/testasmcomp/mips.S b/testasmcomp/mips.S index 82f2e23f8..ca5ab0088 100644 --- a/testasmcomp/mips.S +++ b/testasmcomp/mips.S @@ -64,5 +64,5 @@ call_gen_code: .globl caml_c_call .ent caml_c_call caml_c_call: - j $25 + j $24 .end caml_c_call
\ No newline at end of file |