Skip to content

Commit 34869b4

Browse files
lthlschambart
authored andcommitted
Typing_env_level.join_types: use correct typing env
1 parent 8fc9a1a commit 34869b4

File tree

3 files changed

+41
-36
lines changed

3 files changed

+41
-36
lines changed

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

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -51,6 +51,9 @@ let empty () = { equations = Name.Map.empty; }
5151

5252
let is_empty { equations } = Name.Map.is_empty equations
5353

54+
let from_map equations =
55+
{ equations; }
56+
5457
let one_equation name ty =
5558
Type_grammar.check_equation name ty;
5659
{ equations = Name.Map.singleton name ty; }

middle_end/flambda/types/env/typing_env_extension.rec.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,8 @@ val is_empty : t -> bool
4141

4242
val one_equation : Name.t -> Type_grammar.t -> t
4343

44+
val from_map : Type_grammar.t Name.Map.t -> t
45+
4446
val add_or_replace_equation : t -> Name.t -> Type_grammar.t -> t
4547

4648
val meet : Meet_env.t -> t -> t -> t Or_bottom.t

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

Lines changed: 36 additions & 36 deletions
Original file line numberDiff line numberDiff line change
@@ -192,35 +192,42 @@ let join_types ~env_at_fork envs_with_levels ~extra_lifted_consts_in_use_envs =
192192
Any such variable will be given type [Unknown] on a branch where it
193193
was not originally present.
194194
Iterating on [level.binding_times] instead of [level.defined_vars] ensures
195-
consistency of binding time order in the branches and the result. *)
195+
consistency of binding time order in the branches and the result.
196+
In addition, this also aggregates the code age relations of the branches.
197+
*)
196198
let env_at_fork =
197-
List.fold_left (fun env_at_fork (_, _, _, level) ->
198-
Binding_time.Map.fold (fun _ vars env ->
199-
Variable.Set.fold (fun var env ->
200-
if Typing_env.mem env (Name.var var) then env
201-
else
202-
let kind = Variable.Map.find var level.defined_vars in
203-
Typing_env.add_definition env
204-
(Name_in_binding_pos.var
205-
(Var_in_binding_pos.create var Name_mode.in_types))
206-
kind)
207-
vars
208-
env)
209-
level.binding_times
210-
env_at_fork)
199+
List.fold_left (fun env_at_fork (env_at_use, _, _, level) ->
200+
let env_with_variables =
201+
Binding_time.Map.fold (fun _ vars env ->
202+
Variable.Set.fold (fun var env ->
203+
if Typing_env.mem env (Name.var var) then env
204+
else
205+
let kind = Variable.Map.find var level.defined_vars in
206+
Typing_env.add_definition env
207+
(Name_in_binding_pos.var
208+
(Var_in_binding_pos.create var Name_mode.in_types))
209+
kind)
210+
vars
211+
env)
212+
level.binding_times
213+
env_at_fork
214+
in
215+
let code_age_relation =
216+
Code_age_relation.union (Typing_env.code_age_relation env_at_fork)
217+
(Typing_env.code_age_relation env_at_use)
218+
in
219+
Typing_env.with_code_age_relation env_with_variables code_age_relation)
211220
env_at_fork
212221
envs_with_levels
213222
in
214223
(* Now fold over the levels doing the actual join operation on equations. *)
215224
ListLabels.fold_left envs_with_levels
216-
~init:(env_at_fork, Name.Map.empty, true)
217-
~f:(fun (join_env, joined_types, is_first_join) (env_at_use, _, _, t) ->
218-
let join_env =
219-
Code_age_relation.union (Typing_env.code_age_relation join_env)
220-
(Typing_env.code_age_relation env_at_use)
221-
|> Typing_env.with_code_age_relation join_env
225+
~init:(Name.Map.empty, true)
226+
~f:(fun (joined_types, is_first_join) (env_at_use, _, _, t) ->
227+
let left_env =
228+
Typing_env.add_env_extension env_at_fork
229+
(Typing_env_extension.from_map joined_types)
222230
in
223-
let next_join_env = ref join_env in
224231
let join_types name joined_ty use_ty =
225232
(* CR mshinwell for vlaviron: Looks like [Typing_env.mem] needs
226233
fixing with respect to names from other units with their
@@ -269,16 +276,11 @@ let join_types ~env_at_fork envs_with_levels ~extra_lifted_consts_in_use_envs =
269276
let expected_kind = Some (Type_grammar.kind use_ty) in
270277
Typing_env.find env_at_fork name expected_kind
271278
in
272-
(* Recall: the order of environments matters for [join].
273-
Also note that we use [env_at_fork] not [env_at_use] for
274-
the right-hand environment. This is done because there may
275-
be names in types in [env_at_fork] that are not defined in
276-
[env_at_use] -- see the comment in [check_join_inputs]
277-
below. *)
279+
(* Recall: the order of environments matters for [join]. *)
278280
let join_env =
279281
Join_env.create env_at_fork
280-
~left_env:join_env
281-
~right_env:env_at_fork
282+
~left_env
283+
~right_env:env_at_use
282284
in
283285
Type_grammar.join ~bound_name:name
284286
join_env left_ty use_ty
@@ -293,7 +295,7 @@ let join_types ~env_at_fork envs_with_levels ~extra_lifted_consts_in_use_envs =
293295
let right_ty = Typing_env.find env_at_fork name expected_kind in
294296
let join_env =
295297
Join_env.create env_at_fork
296-
~left_env:join_env
298+
~left_env
297299
~right_env:env_at_fork
298300
in
299301
Type_grammar.join ~bound_name:name
@@ -305,7 +307,7 @@ let join_types ~env_at_fork envs_with_levels ~extra_lifted_consts_in_use_envs =
305307
assert (not is_first_join);
306308
let join_env =
307309
Join_env.create env_at_fork
308-
~left_env:join_env
310+
~left_env
309311
~right_env:env_at_use
310312
in
311313
Type_grammar.join ~bound_name:name
@@ -314,15 +316,13 @@ let join_types ~env_at_fork envs_with_levels ~extra_lifted_consts_in_use_envs =
314316
in
315317
begin match joined_ty with
316318
| Known joined_ty ->
317-
next_join_env :=
318-
Typing_env.add_equation !next_join_env name joined_ty;
319319
Some joined_ty
320320
| Unknown -> None
321321
end
322322
in
323323
let joined_types = Name.Map.merge join_types joined_types t.equations in
324-
!next_join_env, joined_types, false)
325-
|> fun (_, joined_types, _) ->
324+
joined_types, false)
325+
|> fun (joined_types, _) ->
326326
joined_types
327327

328328
let construct_joined_level envs_with_levels ~env_at_fork ~allowed

0 commit comments

Comments
 (0)