Skip to content

Commit 022d397

Browse files
chambartbasimkhajwal
authored andcommitted
Dominator symbols (was ocaml-flambda/ocaml#556) (oxcaml#143)
1 parent e7327b3 commit 022d397

31 files changed

+1420
-1205
lines changed

middle_end/flambda2/compare/compare.ml

Lines changed: 3 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -364,9 +364,9 @@ and subst_static_consts env (g : Static_const.Group.t) =
364364
Static_const.Group.map g ~f:(subst_static_const env)
365365
and subst_bindable_let_bound env (blb : Bindable_let_bound.t) =
366366
match blb with
367-
| Symbols { bound_symbols; scoping_rule } ->
367+
| Symbols { bound_symbols } ->
368368
let bound_symbols = subst_bound_symbols env bound_symbols in
369-
Bindable_let_bound.symbols bound_symbols scoping_rule
369+
Bindable_let_bound.symbols bound_symbols
370370
| _ ->
371371
blb
372372
and subst_bound_symbols env bound_symbols =
@@ -1220,14 +1220,6 @@ and let_symbol_exprs env
12201220
((bound_symbols2 : Bindable_let_bound.symbols), static_consts2, body2)
12211221
: Expr.t Comparison.t =
12221222
let ok = ref true in
1223-
let scoping_rule1 = bound_symbols1.scoping_rule in
1224-
let scoping_rule2 = bound_symbols2.scoping_rule in
1225-
begin
1226-
match scoping_rule1, scoping_rule2 with
1227-
| Syntactic, Syntactic
1228-
| Dominator, Dominator -> ()
1229-
| _, _ -> ok := false
1230-
end;
12311223
let bound_symbols1 = bound_symbols1.bound_symbols in
12321224
let bound_symbols2 = bound_symbols2.bound_symbols in
12331225
let bound_symbols1' : Bound_symbols.t =
@@ -1251,7 +1243,7 @@ and let_symbol_exprs env
12511243
else
12521244
let approximant =
12531245
Let.create
1254-
(Bindable_let_bound.symbols bound_symbols1' scoping_rule1)
1246+
(Bindable_let_bound.symbols bound_symbols1')
12551247
(Named.create_static_consts static_consts1')
12561248
~body:body1'
12571249
~free_names_of_body:Unknown

middle_end/flambda2/from_lambda/closure_conversion.ml

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1111,7 +1111,7 @@ let close_program ~backend ~module_ident ~module_block_size_in_words
11111111
(Static_const.Group.create [static_const])
11121112
in
11131113
Let_with_acc.create acc
1114-
(Bindable_let_bound.symbols bound_symbols Syntactic)
1114+
(Bindable_let_bound.symbols bound_symbols)
11151115
named
11161116
~body:return
11171117
~free_names_of_body:Unknown
@@ -1178,7 +1178,7 @@ let close_program ~backend ~module_ident ~module_block_size_in_words
11781178
|> Named.create_static_consts
11791179
in
11801180
Let_with_acc.create acc
1181-
(Bindable_let_bound.symbols bound_symbols Syntactic)
1181+
(Bindable_let_bound.symbols bound_symbols)
11821182
defining_expr ~body ~free_names_of_body:Unknown
11831183
|> Expr_with_acc.create_let)
11841184
(Acc.code acc)
@@ -1209,7 +1209,7 @@ let close_program ~backend ~module_ident ~module_block_size_in_words
12091209
|> Named.create_static_consts
12101210
in
12111211
Let_with_acc.create acc
1212-
(Bindable_let_bound.symbols bound_symbols Syntactic)
1212+
(Bindable_let_bound.symbols bound_symbols)
12131213
defining_expr ~body ~free_names_of_body:Unknown
12141214
|> Expr_with_acc.create_let)
12151215
(acc, body)

middle_end/flambda2/inlining/call_site_inlining_decision.ml

Lines changed: 12 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -214,8 +214,18 @@ let speculative_inlining dacc ~apply ~function_decl ~simplify_expr
214214
| Never_returns -> Continuation.create ()
215215
| Return cont -> cont
216216
in
217-
let { required_variables; } : Data_flow.result =
217+
(* When doing the speculative analysis, in order to not blow up,
218+
the data_flow analysis is only done on the speculatively inlined
219+
body; however the reachable code_ids part of the data flow analysis
220+
is only correct at toplevel when all information about the
221+
code_age relation and used_closure vars is available (for the whole
222+
compilation unit). Thus we here provide empty/dummy values
223+
for the used_closure_vars and code_age_relation, and ignore the
224+
reachable_code_id part of the data_flow analysis. *)
225+
let { required_names; reachable_code_ids = _; } : Data_flow.result =
218226
Data_flow.analyze data_flow
227+
~code_age_relation:Code_age_relation.empty
228+
~used_closure_vars:Unknown
219229
~return_continuation:function_return_cont
220230
~exn_continuation:(Exn_continuation.exn_handler exn_continuation)
221231
in
@@ -227,7 +237,7 @@ let speculative_inlining dacc ~apply ~function_decl ~simplify_expr
227237
UE.add_return_continuation uenv return_continuation scope
228238
return_arity
229239
in
230-
let uacc = UA.create ~required_variables uenv dacc in
240+
let uacc = UA.create ~required_names ~reachable_code_ids:Unknown uenv dacc in
231241
rebuild uacc ~after_rebuild:(fun expr uacc -> expr, uacc)
232242
)
233243
in

middle_end/flambda2/naming/bindable_let_bound.ml

Lines changed: 8 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,6 @@
1616

1717
type symbols = {
1818
bound_symbols : Bound_symbols.t;
19-
scoping_rule : Symbol_scoping_rule.t;
2019
}
2120

2221
type t =
@@ -40,13 +39,11 @@ include Container_types.Make (struct
4039
(Format.pp_print_list ~pp_sep:Format.pp_print_space
4140
Var_in_binding_pos.print)
4241
closure_vars
43-
| Symbols { bound_symbols; scoping_rule; } ->
42+
| Symbols { bound_symbols } ->
4443
Format.fprintf ppf "@[<hov 1>\
45-
@[(bound_symbols@ %a)@]@ \
46-
@[(scoping_rule@ %a)@]\
44+
@[(bound_symbols@ %a)@]\
4745
)@]"
4846
Bound_symbols.print bound_symbols
49-
Symbol_scoping_rule.print scoping_rule
5047

5148
(* The following would only be required if using
5249
[Name_abstraction.Make_map], which we don't with this module. *)
@@ -78,7 +75,7 @@ let free_names t =
7875
Name_mode.normal)
7976
Name_occurrences.empty
8077
closure_vars
81-
| Symbols { bound_symbols; scoping_rule = _; } ->
78+
| Symbols { bound_symbols; } ->
8279
Bound_symbols.free_names bound_symbols
8380

8481
let rec map_sharing f l0 =
@@ -103,12 +100,12 @@ let apply_renaming t perm =
103100
in
104101
if closure_vars == closure_vars' then t
105102
else Set_of_closures { name_mode; closure_vars = closure_vars'; }
106-
| Symbols { bound_symbols; scoping_rule; } ->
103+
| Symbols { bound_symbols; } ->
107104
let bound_symbols' =
108105
Bound_symbols.apply_renaming bound_symbols perm
109106
in
110107
if bound_symbols == bound_symbols' then t
111-
else Symbols { scoping_rule; bound_symbols = bound_symbols'; }
108+
else Symbols { bound_symbols = bound_symbols'; }
112109

113110
let all_ids_for_export t =
114111
match t with
@@ -120,7 +117,7 @@ let all_ids_for_export t =
120117
Ids_for_export.add_variable ids (Var_in_binding_pos.var var))
121118
Ids_for_export.empty
122119
closure_vars
123-
| Symbols { bound_symbols; scoping_rule = _; } ->
120+
| Symbols { bound_symbols; } ->
124121
Bound_symbols.all_ids_for_export bound_symbols
125122

126123
let rename t =
@@ -194,8 +191,8 @@ let set_of_closures ~closure_vars =
194191
Var_in_binding_pos.print)
195192
closure_vars
196193

197-
let symbols bound_symbols scoping_rule =
198-
Symbols { bound_symbols; scoping_rule; }
194+
let symbols bound_symbols =
195+
Symbols { bound_symbols; }
199196

200197
let name_mode t =
201198
match t with
@@ -260,8 +257,3 @@ let all_bound_vars' t =
260257
| Set_of_closures { closure_vars; _ } ->
261258
Variable.Set.of_list (List.map Var_in_binding_pos.var closure_vars)
262259
| Symbols _ -> Variable.Set.empty
263-
264-
let let_symbol_scoping_rule t =
265-
match t with
266-
| Singleton _ | Set_of_closures _ -> None
267-
| Symbols { scoping_rule; _ } -> Some scoping_rule

middle_end/flambda2/naming/bindable_let_bound.mli

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,6 @@
1818

1919
type symbols = private {
2020
bound_symbols : Bound_symbols.t;
21-
scoping_rule : Symbol_scoping_rule.t;
2221
}
2322

2423
type t = private
@@ -43,7 +42,7 @@ val singleton : Var_in_binding_pos.t -> t
4342

4443
val set_of_closures : closure_vars:Var_in_binding_pos.t list -> t
4544

46-
val symbols : Bound_symbols.t -> Symbol_scoping_rule.t -> t
45+
val symbols : Bound_symbols.t -> t
4746

4847
val must_be_singleton : t -> Var_in_binding_pos.t
4948

@@ -71,5 +70,3 @@ val fold_all_bound_vars
7170
val all_bound_vars : t -> Var_in_binding_pos.Set.t
7271

7372
val all_bound_vars' : t -> Variable.Set.t
74-
75-
val let_symbol_scoping_rule : t -> Symbol_scoping_rule.t option

middle_end/flambda2/parser/fexpr.ml

Lines changed: 0 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -347,10 +347,6 @@ type apply_cont = {
347347
args : simple list;
348348
}
349349

350-
type symbol_scoping_rule = Symbol_scoping_rule.t =
351-
| Syntactic
352-
| Dominator
353-
354350
type expr =
355351
| Let of let_
356352
| Let_cont of let_cont
@@ -409,7 +405,6 @@ and let_symbol = {
409405
bindings : symbol_binding list;
410406
(* Only used if there's no [Set_of_closures] in the list *)
411407
closure_elements : closure_elements option;
412-
scoping_rule : symbol_scoping_rule option;
413408
body : expr;
414409
}
415410

middle_end/flambda2/parser/fexpr_to_flambda.ml

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -656,7 +656,7 @@ let rec expr env (e : Fexpr.expr) : Flambda.Expr.t =
656656
~scrutinee:(simple env scrutinee)
657657
~arms)
658658

659-
| Let_symbol { bindings; closure_elements; scoping_rule; body } ->
659+
| Let_symbol { bindings; closure_elements; body } ->
660660
(* Desugar the abbreviated form for a single set of closures *)
661661
let found_explicit_set = ref false in
662662
let closures_in_implicit_set =
@@ -866,9 +866,8 @@ let rec expr env (e : Fexpr.expr) : Flambda.Expr.t =
866866
List.map (static_const env) bindings
867867
|> Flambda.Static_const.Group.create
868868
in
869-
let scoping_rule = scoping_rule |> Option.value ~default:Fexpr.Syntactic in
870869
let body = expr env body in
871-
Flambda.Let.create (Bindable_let_bound.symbols bound_symbols scoping_rule)
870+
Flambda.Let.create (Bindable_let_bound.symbols bound_symbols)
872871
(Flambda.Named.create_static_consts static_consts)
873872
~body
874873
~free_names_of_body:Unknown

0 commit comments

Comments
 (0)