Represent the current location explicitly, not through gas encoding (special dot symbol).

git-svn-id: http://caml.inria.fr/svn/ocaml/branches/abstract_intel_emit@15296 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Alain Frisch 2014-09-22 14:56:33 +00:00
parent fe2e3ae271
commit 237406042b
5 changed files with 10 additions and 7 deletions

View File

@ -848,7 +848,7 @@ let fundecl fundecl =
_type (emit_symbol fundecl.fun_name) "@function";
_size (emit_symbol fundecl.fun_name)
(ConstSub (
ConstLabel ".",
ConstThis,
ConstLabel (emit_symbol fundecl.fun_name)))
end
@ -977,7 +977,7 @@ let end_assembly() =
_long (ConstAdd (
ConstSub(
ConstLabel(emit_label lbl),
ConstLabel "."),
ConstThis),
const_32 ofs))
end;
efa_def_label = (fun l -> _label (emit_label l));

View File

@ -988,7 +988,7 @@ let fundecl fundecl =
_type (emit_symbol fundecl.fun_name) "@function";
_size (emit_symbol fundecl.fun_name)
(ConstSub (
ConstLabel ".",
ConstThis,
ConstLabel (emit_symbol fundecl.fun_name)))
| _ -> ()
end
@ -1090,7 +1090,7 @@ let end_assembly() =
efa_label_rel = (fun lbl ofs ->
_long (ConstAdd (
ConstSub(ConstLabel(emit_label lbl),
ConstLabel "."),
ConstThis),
const_32 ofs)));
efa_def_label = (fun l -> _label (emit_label l));
efa_string = (fun s ->

View File

@ -38,6 +38,7 @@ type rounding =
type constant =
| Const of int64
| ConstThis
| ConstLabel of string
| ConstAdd of constant * constant
| ConstSub of constant * constant

View File

@ -86,13 +86,14 @@ let bprint_arg b = function
| Mem64 addr -> bprint_arg_mem b string_of_register64 addr
let rec string_of_constant = function
| ConstLabel _ | Const _ as c -> string_of_simple_constant c
| ConstLabel _ | Const _ | ConstThis as c -> string_of_simple_constant c
| ConstAdd (c1, c2) ->
(string_of_simple_constant c1) ^ " + " ^ (string_of_simple_constant c2)
| ConstSub (c1, c2) ->
(string_of_simple_constant c1) ^ " - " ^ (string_of_simple_constant c2)
and string_of_simple_constant = function
| ConstThis -> "."
| ConstLabel l -> l
| Const n when n <= 0x7FFF_FFFFL && n >= -0x8000_0000L -> Int64.to_string n
| Const n -> Printf.sprintf "0x%Lx" n

View File

@ -83,14 +83,15 @@ let bprint_arg b arg =
let rec string_of_constant = function
| ConstLabel _ | Const _ as c -> string_of_simple_constant c
| ConstLabel _ | Const _ | ConstThis as c -> string_of_simple_constant c
| ConstAdd (c1, c2) ->
(string_of_simple_constant c1) ^ " + " ^ (string_of_simple_constant c2)
| ConstSub (c1, c2) ->
(string_of_simple_constant c1) ^ " - " ^ (string_of_simple_constant c2)
and string_of_simple_constant = function
| ConstLabel l -> if l = "." then "THIS BYTE" else l
| ConstThis -> "THIS BYTE"
| ConstLabel l -> l
| Const n when n <= 0x7FFF_FFFFL && n >= -0x8000_0000L -> Int64.to_string n
| Const n -> Printf.sprintf "0%LxH" n
| ConstAdd (c1, c2) ->