Skip to content

Commit

Permalink
Merge pull request #10096 from gasche/fix-oo-caching-problem
Browse files Browse the repository at this point in the history
fix a caching problem in OO code causing a 4.11 performance regression

(cherry picked from commit 9f53c6b)
  • Loading branch information
gasche committed Dec 26, 2020
1 parent c418bc6 commit fc5061c
Show file tree
Hide file tree
Showing 2 changed files with 30 additions and 17 deletions.
15 changes: 12 additions & 3 deletions Changes
Original file line number Diff line number Diff line change
Expand Up @@ -680,8 +680,17 @@ OCaml 4.12.0
- #10048: Fix bug with generalized local opens.
(Leo White, review by Thomas Refis)

OCaml 4.11.1
------------
OCaml 4.11 maintenance branch
-----------------------------

### Bug fixes:

- #9096, #10096: fix a 4.11.0 performance regression in classes/objects
declared within a function
(Gabriel Scherer, review by Leo White, report by Sacha Ayoun)

OCaml 4.11.1 (31 August 2020)
-----------------------------

### Bug fixes:

Expand All @@ -694,7 +703,7 @@ OCaml 4.11.1
(Florian Angeletti, review by Thomas Refis)

OCaml 4.11.0 (19 August 2020)
---------------------------
-----------------------------

(Changes that can break existing programs are marked with a "*")

Expand Down
32 changes: 18 additions & 14 deletions lambda/translcore.ml
Original file line number Diff line number Diff line change
Expand Up @@ -219,17 +219,25 @@ let transl_ident loc env ty path desc =
| _ -> fatal_error "Translcore.transl_exp: bad Texp_ident"

let rec transl_exp ~scopes e =
transl_exp1 ~scopes ~in_new_scope:false e

(* ~in_new_scope tracks whether we just opened a new scope.
We go to some trouble to avoid introducing many new anonymous function
scopes, as `let f a b = ...` is desugared to several Pexp_fun.
*)
and transl_exp1 ~scopes ~in_new_scope e =
List.iter (Translattribute.check_attribute e) e.exp_attributes;
let eval_once =
(* Whether classes for immediate objects must be cached *)
match e.exp_desc with
Texp_function _ | Texp_for _ | Texp_while _ -> false
| _ -> true
in
if eval_once then transl_exp0 ~scopes e else
Translobj.oo_wrap e.exp_env true (transl_exp0 ~scopes) e
if eval_once then transl_exp0 ~scopes ~in_new_scope e else
Translobj.oo_wrap e.exp_env true (transl_exp0 ~scopes ~in_new_scope) e

and transl_exp0 ~scopes e =
and transl_exp0 ~in_new_scope ~scopes e =
match e.exp_desc with
| Texp_ident(path, _, desc) ->
transl_ident (of_location ~scopes e.exp_loc)
Expand All @@ -240,7 +248,10 @@ and transl_exp0 ~scopes e =
transl_let ~scopes rec_flag pat_expr_list
(event_before ~scopes body (transl_exp ~scopes body))
| Texp_function { arg_label = _; param; cases; partial; } ->
let scopes = enter_anonymous_function ~scopes in
let scopes =
if in_new_scope then scopes
else enter_anonymous_function ~scopes
in
transl_function ~scopes e param cases partial
| Texp_apply({ exp_desc = Texp_ident(path, _, {val_kind = Val_prim p});
exp_type = prim_type } as funct, oargs)
Expand Down Expand Up @@ -850,18 +861,11 @@ and transl_function ~scopes e param cases partial =
let lam = Lfunction{kind; params; return; body; attr; loc} in
Translattribute.add_function_attributes lam e.exp_loc e.exp_attributes

(* Like transl_exp, but used when introducing a new scope.
Goes to some trouble to avoid introducing many new anonymous function
scopes, as `let f a b = ...` is desugared to several Pexp_fun *)
(* Like transl_exp, but used when a new scope was just introduced. *)
and transl_scoped_exp ~scopes expr =
match expr.exp_desc with
| Texp_function { arg_label = _; param; cases; partial } ->
transl_function ~scopes expr param cases partial
| _ ->
transl_exp ~scopes expr
transl_exp1 ~scopes ~in_new_scope:true expr

(* Calls transl_scoped_exp or transl_exp, according to whether a pattern
binding should introduce a new scope *)
(* Decides whether a pattern binding should introduce a new scope. *)
and transl_bound_exp ~scopes ~in_structure pat expr =
let should_introduce_scope =
match expr.exp_desc with
Expand Down

0 comments on commit fc5061c

Please sign in to comment.