Skip to content

Commit 1ae7614

Browse files
lthlschambart
authored andcommitted
Do not track rec info in Typing_env
1 parent c5fd825 commit 1ae7614

File tree

1 file changed

+23
-86
lines changed

1 file changed

+23
-86
lines changed

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

Lines changed: 23 additions & 86 deletions
Original file line numberDiff line numberDiff line change
@@ -443,6 +443,9 @@ let is_empty t =
443443
&& Scope.Map.is_empty t.prev_levels
444444
&& Symbol.Set.is_empty t.defined_symbols
445445

446+
let aliases t =
447+
Cached.aliases (One_level.just_after_level t.current_level)
448+
446449
(* CR mshinwell: Should print name occurrence kinds *)
447450
(* CR mshinwell: Add option to print [aliases] *)
448451
let print_with_cache ~cache ppf
@@ -465,12 +468,14 @@ let print_with_cache ~cache ppf
465468
"@[<hov 1>(\
466469
@[<hov 1>(defined_symbols@ %a)@]@ \
467470
@[<hov 1>(code_age_relation@ %a)@]@ \
468-
@[<hov 1>(levels@ %a)@]\
471+
@[<hov 1>(levels@ %a)@]@ \
472+
@[<hov 1>(aliases@ %a)@]\
469473
)@]"
470474
Symbol.Set.print defined_symbols
471475
Code_age_relation.print code_age_relation
472476
(Scope.Map.print (One_level.print_with_cache ~min_binding_time ~cache))
473-
levels)
477+
levels
478+
Aliases.print (aliases t))
474479

475480
let print ppf t =
476481
print_with_cache ~cache:(Printing_cache.create ()) ppf t
@@ -523,9 +528,6 @@ let current_scope t = One_level.scope t.current_level
523528
let names_to_types t =
524529
Cached.names_to_types (One_level.just_after_level t.current_level)
525530

526-
let aliases t =
527-
Cached.aliases (One_level.just_after_level t.current_level)
528-
529531
let aliases_with_min_binding_time t =
530532
aliases t, t.min_binding_time
531533

@@ -984,20 +986,20 @@ and add_equation t name ty =
984986
end)
985987
~const:(fun _ -> ())
986988
end;
987-
let aliases, simple, rec_info, t, ty =
989+
let aliases, simple, t, ty =
988990
let aliases = aliases t in
989991
match Type_grammar.get_alias_exn ty with
990992
| exception Not_found ->
991993
(* Equations giving concrete types may only be added to the canonical
992994
element as known by the alias tracker (the actual canonical, ignoring
993995
any name modes). *)
994996
let canonical = Aliases.get_canonical_ignoring_name_mode aliases name in
995-
aliases, canonical, None, t, ty
997+
aliases, canonical, t, ty
996998
| alias_of ->
999+
let alias_of = Simple.without_rec_info alias_of in
9971000
let alias = Simple.name name in
9981001
let kind = Type_grammar.kind ty in
9991002
let binding_time_and_mode_alias = binding_time_and_mode t name in
1000-
let rec_info = Simple.rec_info alias_of in
10011003
let binding_time_and_mode_alias_of =
10021004
binding_time_and_mode_of_simple t alias_of
10031005
in
@@ -1008,7 +1010,7 @@ and add_equation t name ty =
10081010
let ty =
10091011
Type_grammar.alias_type_of kind canonical_element
10101012
in
1011-
aliases, alias_of, rec_info, t, ty
1013+
aliases, alias_of, t, ty
10121014
in
10131015
(* Beware: if we're about to add the equation on a name which is different
10141016
from the one that the caller passed in, then we need to make sure that the
@@ -1036,14 +1038,6 @@ and add_equation t name ty =
10361038
in
10371039
Simple.pattern_match simple ~name ~const:(fun _ -> ty, t)
10381040
in
1039-
let ty =
1040-
match rec_info with
1041-
| None -> ty
1042-
| Some rec_info ->
1043-
match Type_grammar.apply_rec_info ty rec_info with
1044-
| Bottom -> Type_grammar.bottom (Type_grammar.kind ty)
1045-
| Ok ty -> ty
1046-
in
10471041
let [@inline always] name name = add_equation0 t aliases name ty in
10481042
Simple.pattern_match simple ~name ~const:(fun _ -> t)
10491043

@@ -1203,22 +1197,6 @@ let type_simple_in_term_exn t ?min_name_mode simple =
12031197
Simple.pattern_match simple ~const ~name
12041198
in
12051199
let kind = Type_grammar.kind ty in
1206-
let newer_rec_info =
1207-
let newer_rec_info = Simple.rec_info simple in
1208-
match newer_rec_info with
1209-
| None -> None
1210-
| Some newer_rec_info ->
1211-
Simple.pattern_match simple
1212-
~const:(fun _ -> Some newer_rec_info)
1213-
~name:(fun _ ->
1214-
match Type_grammar.get_alias_exn ty with
1215-
| exception Not_found -> Some newer_rec_info
1216-
| simple ->
1217-
match Simple.rec_info simple with
1218-
| None -> Some newer_rec_info
1219-
| Some rec_info ->
1220-
Some (Rec_info.merge rec_info ~newer:newer_rec_info))
1221-
in
12221200
let aliases_for_simple, min_binding_time =
12231201
if Aliases.mem (aliases t) simple then aliases_with_min_binding_time t
12241202
else
@@ -1259,34 +1237,10 @@ let type_simple_in_term_exn t ?min_name_mode simple =
12591237
print t
12601238
end;
12611239
raise Misc.Fatal_error
1262-
| alias ->
1263-
match newer_rec_info with
1264-
| None -> Type_grammar.alias_type_of kind alias
1265-
| Some _ ->
1266-
match Simple.merge_rec_info alias ~newer_rec_info with
1267-
| None -> raise Not_found
1268-
| Some simple -> Type_grammar.alias_type_of kind simple
1240+
| alias -> Type_grammar.alias_type_of kind alias
12691241

12701242
let get_canonical_simple_exn t ?min_name_mode ?name_mode_of_existing_simple
12711243
simple =
1272-
let newer_rec_info =
1273-
let newer_rec_info = Simple.rec_info simple in
1274-
match newer_rec_info with
1275-
| None -> None
1276-
| Some newer_rec_info ->
1277-
Simple.pattern_match simple
1278-
~const:(fun _ -> Some newer_rec_info)
1279-
~name:(fun name ->
1280-
if variable_is_from_missing_cmx_file t name then Some newer_rec_info
1281-
else
1282-
match Type_grammar.get_alias_exn (find t name None) with
1283-
| exception Not_found -> Some newer_rec_info
1284-
| simple ->
1285-
match Simple.rec_info simple with
1286-
| None -> Some newer_rec_info
1287-
| Some rec_info ->
1288-
Some (Rec_info.merge rec_info ~newer:newer_rec_info))
1289-
in
12901244
let aliases_for_simple, min_binding_time =
12911245
if Aliases.mem (aliases t) simple then aliases_with_min_binding_time t
12921246
else
@@ -1365,42 +1319,25 @@ let get_canonical_simple_exn t ?min_name_mode ?name_mode_of_existing_simple
13651319
print t
13661320
end;
13671321
raise Misc.Fatal_error
1368-
| alias ->
1369-
match newer_rec_info with
1370-
| None -> alias
1371-
| Some _ ->
1372-
match Simple.merge_rec_info alias ~newer_rec_info with
1373-
| None -> raise Not_found
1374-
| Some simple -> simple
1322+
| alias -> alias
13751323

13761324
let get_alias_then_canonical_simple_exn t ?min_name_mode
13771325
?name_mode_of_existing_simple typ =
13781326
let simple = Type_grammar.get_alias_exn typ in
1327+
let simple = Simple.without_rec_info simple in
13791328
get_canonical_simple_exn t ?min_name_mode ?name_mode_of_existing_simple
13801329
simple
13811330

13821331
let aliases_of_simple t ~min_name_mode simple =
1383-
let aliases =
1384-
Aliases.get_aliases (aliases t) simple
1385-
|> Simple.Set.filter (fun alias ->
1386-
let name_mode =
1387-
Binding_time.With_name_mode.name_mode
1388-
(binding_time_and_mode_of_simple t alias)
1389-
in
1390-
match Name_mode.compare_partial_order name_mode min_name_mode with
1391-
| None -> false
1392-
| Some c -> c >= 0)
1393-
in
1394-
let newer_rec_info = Simple.rec_info simple in
1395-
match newer_rec_info with
1396-
| None -> aliases
1397-
| Some _ ->
1398-
Simple.Set.fold (fun simple simples ->
1399-
match Simple.merge_rec_info simple ~newer_rec_info with
1400-
| None -> simples
1401-
| Some simple -> Simple.Set.add simple simples)
1402-
aliases
1403-
Simple.Set.empty
1332+
Aliases.get_aliases (aliases t) simple
1333+
|> Simple.Set.filter (fun alias ->
1334+
let name_mode =
1335+
Binding_time.With_name_mode.name_mode
1336+
(binding_time_and_mode_of_simple t alias)
1337+
in
1338+
match Name_mode.compare_partial_order name_mode min_name_mode with
1339+
| None -> false
1340+
| Some c -> c >= 0)
14041341

14051342
let aliases_of_simple_allowable_in_types t simple =
14061343
aliases_of_simple t ~min_name_mode:Name_mode.in_types simple

0 commit comments

Comments
 (0)