Skip to content

Commit

Permalink
Address comments about comments, names, and type of bound_error_call
Browse files Browse the repository at this point in the history
  • Loading branch information
gretay-js committed Sep 13, 2019
1 parent e80d02e commit 3763294
Showing 1 changed file with 19 additions and 27 deletions.
46 changes: 19 additions & 27 deletions asmcomp/amd64/emit.mlp
Original file line number Diff line number Diff line change
Expand Up @@ -66,6 +66,7 @@ let emit_debug_info dbg =

let fp = Config.with_frame_pointers

(* Record calls to the GC -- we've moved them out of the way *)
type gc_call =
{ gc_size: int; (* Allocation size, in bytes *)
gc_lbl: label; (* Entry label *)
Expand All @@ -75,22 +76,24 @@ type gc_call =
(* Spacetime node hole pointer and index *)
}

(* Record calls to caml_ml_array_bound_error.
In -g mode, or when using Spacetime profiling, we maintain one call to
caml_ml_array_bound_error per bound check site. Without -g, we can share
a single call. *)
type bound_error_call =
{ bd_lbl: label; (* Entry label *)
bd_frame: label; (* Label of frame descriptor *)
bd_spacetime : (X86_ast.arg * int) option;
(* As for [gc_call]. *)
}

(* Environment *)
type env = {
(* Environment for emitting a function *)
type per_function_env = {
f : fundecl;
stack_offset : int;
call_gc_sites : gc_call list;
bound_error_sites : bound_error_call list;
bound_error_call : int;
symbols_defined : String.Set.t;
symbols_used : String.Set.t;
bound_error_call : label option;
}

let mk_env f =
Expand All @@ -99,13 +102,9 @@ let mk_env f =
stack_offset = 0;
call_gc_sites = [];
bound_error_sites = [];
bound_error_call = 0;
symbols_defined = String.Set.empty;
symbols_used = String.Set.empty;
bound_error_call = None;
}

(* Tradeoff between code size and code speed *)

let frame_size env = (* includes return address *)
if env.f.fun_frame_required then begin
let sz =
Expand Down Expand Up @@ -297,8 +296,6 @@ let spacetime_before_uninstrumented_call ~node_ptr ~index env =
assert (index >= 2);
I.add (int (index * 8)) (reg Proc.loc_spacetime_node_hole ~env)

(* Record calls to the GC -- we've moved them out of the way *)

let emit_call_gc gc ~env =
def_label gc.gc_lbl;
begin match gc.gc_spacetime with
Expand All @@ -317,12 +314,6 @@ let emit_call_gc gc ~env =
def_label gc.gc_frame;
I.jmp (label gc.gc_return_lbl)


(* Record calls to caml_ml_array_bound_error.
In -g mode, or when using Spacetime profiling, we maintain one call to
caml_ml_array_bound_error per bound check site. Without -g, we can share
a single call. *)

let bound_error_label ?label dbg ~spacetime env =
if !Clflags.debug || Config.spacetime then begin
let lbl_bound_error = new_label() in
Expand All @@ -333,12 +324,12 @@ let bound_error_label ?label dbg ~spacetime env =
bd_spacetime = spacetime; } :: env.bound_error_sites; } in
(lbl_bound_error, env)
end else begin
let env =
if env.bound_error_call = 0 then
{ env with bound_error_call = new_label() }
else env
in
(env.bound_error_call, env)
match env.bound_error_call with
| None ->
let lbl = new_label () in
let env = { env with bound_error_call = Some lbl } in
lbl, env
| Some lbl -> lbl, env
end

let emit_call_bound_error env bd =
Expand All @@ -353,10 +344,11 @@ let emit_call_bound_error env bd =

let emit_call_bound_errors env =
List.iter (emit_call_bound_error env) env.bound_error_sites;
if env.bound_error_call > 0 then begin
def_label env.bound_error_call;
match env.bound_error_call with
| Some lbl ->
def_label lbl;
emit_call "caml_ml_array_bound_error"
end
| None -> ()

(* Names for instructions *)

Expand Down

0 comments on commit 3763294

Please sign in to comment.