1 http://caml.inria.fr/mantis/view.php?id=4849
3 diff -bur ocaml-3.11.1/asmcomp/mips/arch.ml my_ocaml/asmcomp/mips/arch.ml
4 --- asmcomp/mips/arch.ml 2002-11-29 16:03:36.000000000 +0100
5 +++ asmcomp/mips/arch.ml 2009-08-09 23:18:31.000000000 +0200
9 match Config.system with
11 + "ultrix" | "gnu" -> false
13 | _ -> fatal_error "Arch_mips.big_endian"
15 diff -bur ocaml-3.11.1/asmcomp/mips/emit.mlp my_ocaml/asmcomp/mips/emit.mlp
16 --- asmcomp/mips/emit.mlp 2004-01-05 21:25:56.000000000 +0100
17 +++ asmcomp/mips/emit.mlp 2009-08-23 12:11:58.000000000 +0200
20 4 * num_stack_slots.(0) + 8 * num_stack_slots.(1) +
21 (if !contains_calls then if !uses_gp then 8 else 4 else 0) in
23 + Misc.align size 16 (* n32 require quadword alignment *)
25 let slot_offset loc cl =
29 ` move $25, {emit_reg i.arg.(0)}\n`;
31 - ` jal {emit_reg i.arg.(0)}\n`;
32 + ` jal $25\n`; (* {emit_reg i.arg.(0)}\n; Equivalent but avoids "Warning: MIPS PIC call to register other than $25" on GNU as *)
33 `{record_frame i.live}\n`
38 ` move $25, {emit_reg i.arg.(0)}\n`;
40 - ` j {emit_reg i.arg.(0)}\n`
42 | Lop(Itailcall_imm s) ->
43 if s = !function_name then begin
44 ` b {emit_label !tailrec_entry_point}\n`
46 let n = frame_size() in
47 if !contains_calls then
48 ` lw $31, {emit_int(n - 4)}($sp)\n`;
49 + ` la $25, {emit_symbol s}\n`; (* Rxd: put before gp restore *)
51 ` lw $gp, {emit_int(n - 8)}($sp)\n`;
53 ` addu $sp, $sp, {emit_int n}\n`;
54 - ` la $25, {emit_symbol s}\n`;
59 begin match chunk with
61 (* Destination is not 8-aligned, hence cannot use l.d *)
62 + if big_endian then begin
63 ` ldl $24, {emit_addressing addr i.arg 0}\n`;
64 - ` ldr $24, {emit_addressing (offset_addressing addr 7) i.arg 0}\n`;
65 + ` ldr $24, {emit_addressing (offset_addressing addr 7) i.arg 0}\n`
67 + ` ldl $24, {emit_addressing (offset_addressing addr 7) i.arg 0}\n`;
68 + ` ldr $24, {emit_addressing addr i.arg 0}\n`
70 ` dmtc1 $24, {emit_reg dest}\n`
72 ` l.s {emit_reg dest}, {emit_addressing addr i.arg 0}\n`;
75 (* Destination is not 8-aligned, hence cannot use l.d *)
76 ` dmfc1 $24, {emit_reg src}\n`;
77 + if big_endian then begin
78 ` sdl $24, {emit_addressing addr i.arg 1}\n`;
79 ` sdr $24, {emit_addressing (offset_addressing addr 7) i.arg 1}\n`
81 + ` sdl $24, {emit_addressing (offset_addressing addr 7) i.arg 1}\n`;
82 + ` sdr $24, {emit_addressing addr i.arg 1}\n`
85 ` cvt.s.d $f31, {emit_reg src}\n`;
86 ` s.s $f31, {emit_addressing addr i.arg 1}\n`
88 (* There are really two groups of registers:
89 $sp and $30 always point to stack locations
90 $2 - $21 never point to stack locations. *)
91 + if Config.system = "irix" then begin
92 ` .noalias $2,$sp; .noalias $2,$30; .noalias $3,$sp; .noalias $3,$30\n`;
93 ` .noalias $4,$sp; .noalias $4,$30; .noalias $5,$sp; .noalias $5,$30\n`;
94 ` .noalias $6,$sp; .noalias $6,$30; .noalias $7,$sp; .noalias $7,$30\n`;
96 ` .noalias $14,$sp; .noalias $14,$30; .noalias $15,$sp; .noalias $15,$30\n`;
97 ` .noalias $16,$sp; .noalias $16,$30; .noalias $17,$sp; .noalias $17,$30\n`;
98 ` .noalias $18,$sp; .noalias $18,$30; .noalias $19,$sp; .noalias $19,$30\n`;
99 - ` .noalias $20,$sp; .noalias $20,$30; .noalias $21,$sp; .noalias $21,$30\n\n`;
100 + ` .noalias $20,$sp; .noalias $20,$30; .noalias $21,$sp; .noalias $21,$30\n\n`
102 let lbl_begin = Compilenv.make_symbol (Some "data_begin") in
104 ` .globl {emit_symbol lbl_begin}\n`;
105 diff -bur ocaml-3.11.1/asmrun/mips.s my_ocaml/asmrun/mips.s
106 --- asmrun/mips.s 2004-07-13 14:18:53.000000000 +0200
107 +++ asmrun/mips.s 2009-08-20 09:34:36.000000000 +0200
109 sw $30, caml_exception_pointer
110 /* Call C function */
113 + jal $25 /* Rxd: $24 replaced by $25 to avoid this "Warning: MIPS PIC call to register other than $25" ? */
114 /* Reload return address, alloc ptr, alloc limit */
115 lw $31, 0($16) /* caml_last_return_address */
116 lw $22, 0($17) /* caml_young_ptr */
118 sw $0, caml_last_return_address
119 /* Call the Caml code */
122 + jal $25 /* Rxd: 24 replaced by 25 */
124 /* Pop the trap frame, restoring caml_exception_pointer */
127 .word $104 /* return address into callback */
128 .half -1 /* negative frame size => use callback link */
129 .half 0 /* no roots here */
131 +#if defined(SYS_linux)
132 + /* Mark stack as non-executable, PR#4564 */
133 + .section .note.GNU-stack,"",%progbits
135 diff -bur ocaml-3.11.1/configure my_ocaml/configure
136 --- configure 2009-05-20 17:33:09.000000000 +0200
137 +++ configure 2009-08-23 10:55:44.000000000 +0200
142 -gcc_warnings="-Wall"
143 +gcc_warnings="-W -Wall"
146 # Try to turn internationalization off, can cause config.guess to malfunction!
148 # (For those who want to force "cc -64")
149 # Turn off warning "unused library"
150 bytecclinkopts="-Wl,-woff,84";;
153 + bytecclinkopts="-fno-defer-pop $gcc_warnings -Wl,-O1 -Wl,--as-needed";;
156 bytecccompopts="-DUMK";;
158 echo "64-bit integers must be doubleword-aligned."
159 echo "#define ARCH_ALIGN_INT64" >> m.h
162 + echo "#define ARCH_ALIGN_INT64" >> m.h;;
164 sh ./runtest int64align.c
168 i[3456]86-*-gnu*) arch=i386; system=gnu;;
169 mips-*-irix6*) arch=mips; system=irix;;
170 + mips*-gnu*) arch=mips; system=gnu;;
171 hppa1.1-*-hpux*) arch=hppa; system=hpux;;
172 hppa2.0*-*-hpux*) arch=hppa; system=hpux;;
173 hppa*-*-linux*) arch=hppa; system=linux;;
175 if test -z "$ccoption"; then
176 case "$arch,$system,$cc" in
177 alpha,digital,gcc*) nativecc=cc;;
178 - mips,*,gcc*) nativecc=cc;;
179 + mips,irix,gcc*) nativecc=cc;;
180 *) nativecc="$bytecc";;
184 alpha,cc*,digital,*) nativecccompopts=-std1;;
185 mips,cc*,irix,*) nativecccompopts=-n32
186 nativecclinkopts="-n32 -Wl,-woff,84";;
187 + mips,gcc*,gnu,mips64el-*)
188 + nativecccompopts="$gcc_warnings -fPIC"
189 + nativecclinkopts="--as-needed";;
190 *,*,nextstep,*) nativecccompopts="$gcc_warnings -U__GNUC__ -posix"
191 nativecclinkopts="-posix";;
192 *,*,rhapsody,*darwin[1-5].*)
194 aspp='gcc -c -Wa,-xexplicit';;
195 mips,*,irix) as='as -n32 -O2 -nocpp -g0'
197 + mips,*,gnu) as='as -KPIC'
198 + aspp='gcc -c -fPIC';; # got bus error without fPIC ?
199 power,*,elf) as='as -u -m ppc'
203 case "$nativecc" in gcc*) ;; *) cc_profile='-xpg';; esac;;
204 amd64,*,linux) profiling='prof';;
205 amd64,*,gnu) profiling='prof';;
206 + mips,*,gnu) profiling='prof';;
207 *) profiling='noprof';;
210 diff -bur ocaml-3.11.1/asmcomp/mips/proc.ml my_ocaml/asmcomp/mips/proc.ml
211 --- asmcomp/mips/proc.ml 2007-10-30 13:37:16.000000000 +0100
212 +++ asmcomp/mips/proc.ml 2010-03-18 08:08:06.000000000 +0100
216 loc.(i) <- stack_slot (make_stack !ofs) ty;
217 - ofs := !ofs + size_int
221 if !float <= last_float then begin
223 or float regs $f12...$f19. Each argument "consumes" both one slot
224 in the int register file and one slot in the float register file.
225 Extra arguments are passed on stack, in a 64-bits slot, right-justified
226 - (i.e. at +4 from natural address). *)
227 + (i.e. at +4 from natural address for big endians). *)
229 let loc_external_arguments arg =
230 let loc = Array.create (Array.length arg) Reg.dummy in
233 begin match arg.(i).typ with
234 Float -> loc.(i) <- stack_slot (Outgoing !ofs) Float
235 - | ty -> loc.(i) <- stack_slot (Outgoing (!ofs + 4)) ty
236 + | ty -> loc.(i) <- stack_slot (Outgoing (!ofs + (if big_endian then 4 else 0))) ty