Skip to content

Commit 2afe765

Browse files
committed
Review comments
1 parent ec58e8a commit 2afe765

File tree

1 file changed

+27
-24
lines changed

1 file changed

+27
-24
lines changed

middle_end/flambda/types/env/typing_env_level.rec.ml

Lines changed: 27 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -286,28 +286,28 @@ let join_types ~env_at_fork envs_with_levels =
286286
consistency of binding time order in the branches and the result.
287287
In addition, this also aggregates the code age relations of the branches.
288288
*)
289-
let env_at_fork =
290-
List.fold_left (fun env_at_fork (env_at_use, _, _, level) ->
291-
let env_with_variables =
292-
Binding_time.Map.fold (fun _ vars env ->
293-
Variable.Set.fold (fun var env ->
294-
if Typing_env.mem env (Name.var var) then env
289+
let base_env =
290+
List.fold_left (fun base_env (env_at_use, _, _, level) ->
291+
let base_env =
292+
Binding_time.Map.fold (fun _ vars base_env ->
293+
Variable.Set.fold (fun var base_env ->
294+
if Typing_env.mem base_env (Name.var var) then base_env
295295
else
296296
let kind = Variable.Map.find var level.defined_vars in
297-
Typing_env.add_definition env
297+
Typing_env.add_definition base_env
298298
(Name_in_binding_pos.var
299299
(Var_in_binding_pos.create var Name_mode.in_types))
300300
kind)
301301
vars
302-
env)
302+
base_env)
303303
level.binding_times
304-
env_at_fork
304+
base_env
305305
in
306306
let code_age_relation =
307-
Code_age_relation.union (Typing_env.code_age_relation env_at_fork)
307+
Code_age_relation.union (Typing_env.code_age_relation base_env)
308308
(Typing_env.code_age_relation env_at_use)
309309
in
310-
Typing_env.with_code_age_relation env_with_variables code_age_relation)
310+
Typing_env.with_code_age_relation base_env code_age_relation)
311311
env_at_fork
312312
envs_with_levels
313313
in
@@ -316,7 +316,10 @@ let join_types ~env_at_fork envs_with_levels =
316316
~init:(Name.Map.empty, true)
317317
~f:(fun (joined_types, is_first_join) (env_at_use, _, _, t) ->
318318
let left_env =
319-
Typing_env.add_env_extension env_at_fork
319+
(* CR vlaviron: This is very likely quadratic (number of uses times
320+
number of variables in all uses).
321+
However it's hard to know how we could do better. *)
322+
Typing_env.add_env_extension base_env
320323
(Typing_env_extension.from_map joined_types)
321324
in
322325
let join_types name joined_ty use_ty =
@@ -327,17 +330,17 @@ let join_types ~env_at_fork envs_with_levels =
327330
Compilation_unit.equal (Name.compilation_unit name)
328331
(Compilation_unit.get_current_exn ())
329332
in
330-
if same_unit && not (Typing_env.mem env_at_fork name) then begin
331-
Misc.fatal_errorf "Name %a not defined in [env_at_fork]:@ %a"
333+
if same_unit && not (Typing_env.mem base_env name) then begin
334+
Misc.fatal_errorf "Name %a not defined in [base_env]:@ %a"
332335
Name.print name
333-
Typing_env.print env_at_fork
336+
Typing_env.print base_env
334337
end;
335338
(* If [name] is that of a lifted constant symbol generated during one
336339
of the levels, then ignore it. [Simplify_expr] will already have
337-
made its type suitable for [env_at_fork] and inserted it into that
340+
made its type suitable for [base_env] and inserted it into that
338341
environment.
339342
If [name] is a symbol that is not a lifted constant, then it was
340-
defined before the fork and already has an equation in env_at_fork.
343+
defined before the fork and already has an equation in base_env.
341344
While it is possible that its type could be refined by all of the
342345
branches, it is unlikely. *)
343346
if Name.is_symbol name then None
@@ -363,11 +366,11 @@ let join_types ~env_at_fork envs_with_levels =
363366
to case split. *)
364367
else
365368
let expected_kind = Some (Type_grammar.kind use_ty) in
366-
Typing_env.find env_at_fork name expected_kind
369+
Typing_env.find base_env name expected_kind
367370
in
368371
(* Recall: the order of environments matters for [join]. *)
369372
let join_env =
370-
Join_env.create env_at_fork
373+
Join_env.create base_env
371374
~left_env
372375
~right_env:env_at_use
373376
in
@@ -378,14 +381,14 @@ let join_types ~env_at_fork envs_with_levels =
378381
the current level for [name]. However we have seen an
379382
equation for [name] on a previous level. We need to get the
380383
best type we can for [name] on the current level, from
381-
[env_at_fork], similarly to the previous case. *)
384+
[base_env], similarly to the previous case. *)
382385
assert (not is_first_join);
383386
let expected_kind = Some (Type_grammar.kind joined_ty) in
384-
let right_ty = Typing_env.find env_at_fork name expected_kind in
387+
let right_ty = Typing_env.find base_env name expected_kind in
385388
let join_env =
386-
Join_env.create env_at_fork
389+
Join_env.create base_env
387390
~left_env
388-
~right_env:env_at_fork
391+
~right_env:base_env
389392
in
390393
Type_grammar.join ~bound_name:name
391394
join_env joined_ty right_ty
@@ -395,7 +398,7 @@ let join_types ~env_at_fork envs_with_levels =
395398
equation for [name] on the current level. *)
396399
assert (not is_first_join);
397400
let join_env =
398-
Join_env.create env_at_fork
401+
Join_env.create base_env
399402
~left_env
400403
~right_env:env_at_use
401404
in

0 commit comments

Comments
 (0)