Do not keep data_size with integer constants.
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/abstract_intel_emit@15294 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
7e5a406a1c
commit
80e8e2c24f
|
@ -427,7 +427,7 @@ let add_float_constant cst =
|
|||
|
||||
let emit_float_constant f lbl =
|
||||
_label (emit_label lbl);
|
||||
_qword (Const (B64, f))
|
||||
_qword (Const f)
|
||||
|
||||
let emit_global_label s =
|
||||
let lbl = Compilenv.make_symbol (Some s) in
|
||||
|
@ -864,8 +864,8 @@ let emit_item = function
|
|||
| Cint16 n -> _word (const n)
|
||||
| Cint32 n -> _long (const_nat n)
|
||||
| Cint n -> _qword (const_nat n)
|
||||
| Csingle f -> _long (Const (B32, Int64.of_int32 (Int32.bits_of_float f)))
|
||||
| Cdouble f -> _qword (Const (B64, Int64.bits_of_float f))
|
||||
| Csingle f -> _long (Const (Int64.of_int32 (Int32.bits_of_float f)))
|
||||
| Cdouble f -> _qword (Const (Int64.bits_of_float f))
|
||||
| Csymbol_address s ->
|
||||
add_used_symbol s;
|
||||
_qword (ConstLabel (emit_symbol s))
|
||||
|
@ -907,12 +907,12 @@ let begin_assembly() =
|
|||
end;
|
||||
_align 16;
|
||||
_label (emit_symbol "caml_negf_mask");
|
||||
_qword (Const (B64, 0x8000000000000000L));
|
||||
_qword (Const (B64, 0L));
|
||||
_qword (Const 0x8000000000000000L);
|
||||
_qword (Const 0L);
|
||||
_align 16;
|
||||
_label (emit_symbol "caml_absf_mask");
|
||||
_qword (Const (B64, 0x7FFFFFFFFFFFFFFFL));
|
||||
_qword (Const (B64, 0xFFFFFFFFFFFFFFFFL));
|
||||
_qword (Const 0x7FFFFFFFFFFFFFFFL);
|
||||
_qword (Const 0xFFFFFFFFFFFFFFFFL);
|
||||
end;
|
||||
|
||||
_data ();
|
||||
|
@ -958,7 +958,7 @@ let end_assembly() =
|
|||
{ efa_label = (fun l -> _qword (ConstLabel (emit_label l)));
|
||||
efa_16 = (fun n -> _word (const n));
|
||||
efa_32 = (fun n -> _long (const_32 n));
|
||||
efa_word = (fun n -> _qword (Const (B64, Int64.of_int n)));
|
||||
efa_word = (fun n -> _qword (Const (Int64.of_int n)));
|
||||
efa_align = _align;
|
||||
efa_label_rel =
|
||||
if system = S_macosx then begin
|
||||
|
|
|
@ -468,8 +468,8 @@ let add_float_constant cst =
|
|||
let emit_float64_split_directive x =
|
||||
let lo = Int64.logand x 0xFFFF_FFFFL
|
||||
and hi = Int64.shift_right_logical x 32 in
|
||||
_long (Const (B32, if Arch.big_endian then hi else lo));
|
||||
_long (Const (B32, if Arch.big_endian then lo else hi));
|
||||
_long (Const (if Arch.big_endian then hi else lo));
|
||||
_long (Const (if Arch.big_endian then lo else hi));
|
||||
()
|
||||
|
||||
let emit_float_constant cst lbl =
|
||||
|
@ -1007,7 +1007,7 @@ let emit_item = function
|
|||
| Cint32 n -> _long (const_nat n)
|
||||
| Cint n -> _long (const_nat n)
|
||||
| Csingle f ->
|
||||
_long (Const (B32, Int64.of_int32 (Int32.bits_of_float f)))
|
||||
_long (Const (Int64.of_int32 (Int32.bits_of_float f)))
|
||||
| Cdouble f ->
|
||||
emit_float64_split_directive (Int64.bits_of_float f)
|
||||
| Csymbol_address s ->
|
||||
|
|
|
@ -45,7 +45,7 @@ type data_size =
|
|||
| B8 | B16 | B32 | B64
|
||||
|
||||
type constant =
|
||||
| Const of data_size * int64
|
||||
| Const of int64
|
||||
| ConstLabel of string
|
||||
| ConstAdd of constant * constant
|
||||
| ConstSub of constant * constant
|
||||
|
|
|
@ -60,26 +60,13 @@ module DSL = struct
|
|||
let sym s = Sym s
|
||||
|
||||
(* Override emitaux.ml *)
|
||||
let const_int n =
|
||||
if n >= -0x80L && n <= 0x7FL then
|
||||
Const (B8, n)
|
||||
else
|
||||
if n >= -0x8000L && n <= 0x7FFFL then
|
||||
Const (B16, n)
|
||||
else
|
||||
if n >= -0x8000_0000L && n <= 0x7FFF_FFFFL then
|
||||
Const (B32, n)
|
||||
else
|
||||
Const (B64, n)
|
||||
|
||||
|
||||
let emit_nat n = Imm (Int64.of_nativeint n)
|
||||
let int n = Imm (Int64.of_int n)
|
||||
|
||||
let const_64 n = const_int n
|
||||
let const_32 n = const_int (Int64.of_int32 n)
|
||||
let const_nat n = const_int (Int64.of_nativeint n)
|
||||
let const n = const_int (Int64.of_int n)
|
||||
let const_64 n = Const n
|
||||
let const_32 n = Const (Int64.of_int32 n)
|
||||
let const_nat n = Const (Int64.of_nativeint n)
|
||||
let const n = Const (Int64.of_int n)
|
||||
|
||||
let _cfi_startproc () = directive Cfi_startproc
|
||||
let _cfi_endproc () = directive Cfi_endproc
|
||||
|
|
|
@ -94,8 +94,8 @@ let rec string_of_constant = function
|
|||
|
||||
and string_of_simple_constant = function
|
||||
| ConstLabel l -> l
|
||||
| Const (B64, n) -> Printf.sprintf "0x%Lx" n
|
||||
| Const (_, n) -> Int64.to_string n
|
||||
| Const n when n <= 0x7FFF_FFFFL && n >= -0x8000_0000L -> Int64.to_string n
|
||||
| Const n -> Printf.sprintf "0x%Lx" n
|
||||
| ConstAdd (c1, c2) ->
|
||||
Printf.sprintf "(%s + %s)"
|
||||
(string_of_simple_constant c1) (string_of_simple_constant c2)
|
||||
|
@ -386,8 +386,6 @@ let bprint_instr_name b instr =
|
|||
Printf.bprintf b "\t.word\t%s" (string_of_constant n)
|
||||
| Constant (n, B32) ->
|
||||
Printf.bprintf b "\t.long\t%s" (string_of_constant n)
|
||||
| Constant (Const(_, n), B64) ->
|
||||
Printf.bprintf b "\t.quad\t%s" (string_of_constant (Const (B64,n)))
|
||||
| Constant (n, B64) ->
|
||||
Printf.bprintf b "\t.quad\t%s" (string_of_constant n)
|
||||
| Bytes s ->
|
||||
|
|
|
@ -97,8 +97,8 @@ let rec string_of_constant = function
|
|||
|
||||
and string_of_simple_constant = function
|
||||
| ConstLabel l -> if l = "." then "THIS BYTE" else l
|
||||
| Const ((B8|B16|B32), n) -> Int64.to_string n
|
||||
| Const (B64, n) -> Printf.sprintf "0%LxH" n
|
||||
| Const n when n <= 0x7FFF_FFFFL && n >= -0x8000_0000L -> Int64.to_string n
|
||||
| Const n -> Printf.sprintf "0%LxH" n
|
||||
| ConstAdd (c1, c2) ->
|
||||
Printf.sprintf "(%s + %s)"
|
||||
(string_of_simple_constant c1) (string_of_simple_constant c2)
|
||||
|
|
Loading…
Reference in New Issue