Issues with Iconst_int of a constant that exceeds 32 bits signed
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@7401 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
e120ba1de7
commit
b34288b2a1
|
@ -310,22 +310,18 @@ let emit_instr fallthrough i =
|
|||
` mov {emit_reg dst}, {emit_reg src}\n`
|
||||
end
|
||||
| Lop(Iconst_int n) ->
|
||||
(**
|
||||
`; const_int {emit_nativeint n}\n`;
|
||||
`; n <= 0x7FFFFFFFn {emit_string (if n <= 0x7FFFFFFFn then "true" else "false")}\n`;
|
||||
`; n >= -0x80000000n {emit_string (if n >= -0x80000000n then "true" else "false")}\n`;
|
||||
**)
|
||||
if n = 0n then begin
|
||||
match i.res.(0).loc with
|
||||
Reg n -> ` xor {emit_reg i.res.(0)}, {emit_reg i.res.(0)}\n`
|
||||
| _ -> ` mov {emit_reg i.res.(0)}, 0\n`
|
||||
(* end else if n <= 0x7FFFFFFFn && n >= -0x80000000n then
|
||||
end else if n >= -0x80000000n && n <= 0x7FFFFFFFn then
|
||||
` mov {emit_reg i.res.(0)}, {emit_nativeint n}\n`
|
||||
else if n >= 0x80000000n && n <= 0xFFFFFFFFn then
|
||||
(* work around bug in ml64 *)
|
||||
` mov {emit_reg32 i.res.(0)}, {emit_nativeint n}\n`
|
||||
else
|
||||
` movabs {emit_reg i.res.(0)}, {emit_nativeint n}\n`
|
||||
*)
|
||||
end else
|
||||
` mov {emit_reg i.res.(0)}, {emit_nativeint n}\n`
|
||||
(* force ml64 to use mov reg, imm64 instruction *)
|
||||
` mov {emit_reg i.res.(0)}, {emit_printf "0%nxH" n}\n`
|
||||
| Lop(Iconst_float s) ->
|
||||
begin match Int64.bits_of_float (float_of_string s) with
|
||||
| 0x0000_0000_0000_0000L -> (* +0.0 *)
|
||||
|
@ -386,7 +382,8 @@ let emit_instr fallthrough i =
|
|||
` movzx {emit_reg dest}, WORD PTR {emit_addressing addr i.arg 0}\n`
|
||||
| Sixteen_signed ->
|
||||
` movsx {emit_reg dest}, WORD PTR {emit_addressing addr i.arg 0}\n`
|
||||
| Thirtytwo_unsigned -> (* TO CHECK *)
|
||||
| Thirtytwo_unsigned ->
|
||||
(* load to low 32 bits sets high 32 bits to 0 *)
|
||||
` mov {emit_reg32 dest}, DWORD PTR {emit_addressing addr i.arg 0}\n`
|
||||
| Thirtytwo_signed ->
|
||||
` movsxd {emit_reg dest}, DWORD PTR {emit_addressing addr i.arg 0}\n`
|
||||
|
|
|
@ -24,7 +24,7 @@ open Mach
|
|||
Operation Res Arg1 Arg2
|
||||
Imove R S
|
||||
or S R
|
||||
Iconst_int S
|
||||
Iconst_int S if 32-bit signed, R otherwise
|
||||
Iconst_float R
|
||||
Iconst_symbol (not PIC) S
|
||||
Iconst_symbol (PIC) R
|
||||
|
@ -77,7 +77,8 @@ method reload_operation op arg res =
|
|||
if !pic_code
|
||||
then super#reload_operation op arg res
|
||||
else (arg, res)
|
||||
| Iconst_int _
|
||||
| Iconst_int n when n >= -0x80000000n && n <= 0x7FFFFFFFn ->
|
||||
(arg, res)
|
||||
| Iintop(Idiv | Imod | Ilsl | Ilsr | Iasr)
|
||||
| Iintop_imm(_, _) ->
|
||||
(* The argument(s) and results can be either in register or on stack *)
|
||||
|
|
Loading…
Reference in New Issue