Skip to content

Commit df968ae

Browse files
committed
Remove extra catch handler for return
1 parent 92c841d commit df968ae

File tree

2 files changed

+7
-23
lines changed

2 files changed

+7
-23
lines changed

middle_end/flambda2.0/to_cmm/un_cps.ml

Lines changed: 3 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -932,8 +932,7 @@ and apply_cont env e =
932932
let args = Apply_cont_expr.args e in
933933
if Continuation.is_exn k then
934934
apply_cont_exn env e k args
935-
else if Continuation.equal (Env.return_cont env) k
936-
&& Apply_cont_expr.trap_action e = None then
935+
else if Continuation.equal (Env.return_cont env) k then
937936
apply_cont_ret env e k args
938937
else
939938
apply_cont_regular env e k args
@@ -1435,8 +1434,6 @@ let function_flags () =
14351434
let function_decl offsets used_closure_vars fun_name _ d =
14361435
Profile.record_call ~accumulate:true fun_name (fun () ->
14371436
let fun_dbg = Function_declaration.dbg d in
1438-
let result_arity = Function_declaration.result_arity d in
1439-
let ret_machtype = machtype_of_return_arity result_arity in
14401437
let p = Function_declaration.params_and_body d in
14411438
Function_params_and_body.pattern_match p
14421439
~f:(fun ~return_continuation:k k_exn vars ~body ~my_closure ->
@@ -1446,22 +1443,9 @@ let function_decl offsets used_closure_vars fun_name _ d =
14461443
(* Init the env and create a jump id for the ret closure
14471444
in case a trap action is attached to one of tis call *)
14481445
let env = Env.mk offsets k k_exn used_closure_vars in
1449-
let id, env = Env.add_jump_cont env [ret_machtype] k in
1450-
let fun_handle_var = Backend_var.create_local "*fun_res*" in
1451-
let fun_handler = C.var fun_handle_var in
1452-
let fun_handle_vars = [
1453-
Backend_var.With_provenance.create fun_handle_var,
1454-
ret_machtype
1455-
] in
1456-
(* translate the arg list and body, inserting a catch for the
1457-
return continuation. *)
1446+
(* translate the arg list and body *)
14581447
let env, fun_args = var_list env args in
1459-
let fun_body =
1460-
C.ccatch
1461-
~rec_flag:false
1462-
~body:(expr env body)
1463-
~handlers:[C.handler id fun_handle_vars fun_handler]
1464-
in
1448+
let fun_body = expr env body in
14651449
let fun_flags = function_flags () in
14661450
C.fundecl fun_name fun_args fun_body fun_flags fun_dbg
14671451
with Misc.Fatal_error ->

middle_end/flambda2.0/to_cmm/un_cps_env.ml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -74,7 +74,7 @@ type stage =
7474
(* Translation environment *)
7575

7676
type t = {
77-
k : Continuation.t;
77+
k_return : Continuation.t;
7878
(* The continuation of the current context
7979
(used to determine which calls are tail-calls) *)
8080
k_exn : Continuation.t;
@@ -101,8 +101,8 @@ type t = {
101101
(* archived stages, in reverse chronological order. *)
102102
}
103103

104-
let mk offsets k k_exn used_closure_vars = {
105-
k; k_exn; used_closure_vars; offsets;
104+
let mk offsets k_return k_exn used_closure_vars = {
105+
k_return; k_exn; used_closure_vars; offsets;
106106
stages = [];
107107
pures = Variable.Map.empty;
108108
vars = Variable.Map.empty;
@@ -117,7 +117,7 @@ let dummy offsets used_closure_vars =
117117
(Continuation.create ())
118118
used_closure_vars
119119

120-
let return_cont env = env.k
120+
let return_cont env = env.k_return
121121
let exn_cont env = env.k_exn
122122

123123
(* Variables *)

0 commit comments

Comments
 (0)