@@ -43,16 +43,16 @@ module Cached : sig
4343 -> Type_grammar. t
4444 -> Binding_time. t
4545 -> Name_mode. t
46- -> new_aliases:Aliases. t
4746 -> t
4847
4948 val replace_variable_binding
5049 : t
5150 -> Variable. t
5251 -> Type_grammar. t
53- -> new_aliases:Aliases. t
5452 -> t
5553
54+ val with_aliases : t -> aliases :Aliases .t -> t
55+
5656 val add_symbol_projection : t -> Variable .t -> Symbol_projection .t -> t
5757
5858 val find_symbol_projection : t -> Variable .t -> Symbol_projection .t option
@@ -131,27 +131,30 @@ end = struct
131131 (used to be add-or-replace), the [names_to_types] map addition was a
132132 major source of allocation. *)
133133
134- let add_or_replace_binding t (name : Name.t ) ty binding_time name_mode ~ new_aliases =
134+ let add_or_replace_binding t (name : Name.t ) ty binding_time name_mode =
135135 let names_to_types =
136136 Name.Map. add name (ty, binding_time, name_mode) t.names_to_types
137137 in
138138 { names_to_types;
139- aliases = new_aliases ;
139+ aliases = t.aliases ;
140140 symbol_projections = t.symbol_projections;
141141 }
142142
143- let replace_variable_binding t var ty ~ new_aliases =
143+ let replace_variable_binding t var ty =
144144 let names_to_types =
145145 Name.Map. replace (Name. var var)
146146 (function (_old_ty , binding_time , name_mode ) ->
147147 ty, binding_time, name_mode)
148148 t.names_to_types
149149 in
150150 { names_to_types;
151- aliases = new_aliases ;
151+ aliases = t.aliases ;
152152 symbol_projections = t.symbol_projections;
153153 }
154154
155+ let with_aliases t ~aliases =
156+ { t with aliases; }
157+
155158 let add_symbol_projection t var proj =
156159 let symbol_projections = Variable.Map. add var proj t.symbol_projections in
157160 { t with symbol_projections; }
@@ -260,6 +263,12 @@ module One_level = struct
260263 let level t = t.level
261264 let just_after_level t = t.just_after_level
262265
266+ let with_aliases t ~aliases =
267+ let just_after_level =
268+ Cached. with_aliases t.just_after_level ~aliases
269+ in
270+ { t with just_after_level; }
271+
263272 let is_empty t = Typing_env_level. is_empty t.level
264273
265274(*
@@ -781,6 +790,12 @@ let with_current_level_and_next_binding_time t ~current_level
781790 invariant t;
782791 t
783792
793+ let with_aliases t ~aliases =
794+ let current_level =
795+ One_level. with_aliases t.current_level ~aliases
796+ in
797+ with_current_level t ~current_level
798+
784799let cached t = One_level. just_after_level t.current_level
785800
786801let add_variable_definition t var kind name_mode =
@@ -810,7 +825,6 @@ let add_variable_definition t var kind name_mode =
810825 Cached. add_or_replace_binding (cached t)
811826 name (Type_grammar. unknown kind)
812827 t.next_binding_time name_mode
813- ~new_aliases: (aliases t)
814828 in
815829 let current_level =
816830 One_level. create (current_scope t) level ~just_after_level
@@ -911,7 +925,7 @@ let invariant_for_new_equation t aliases name ty =
911925 end
912926 end
913927
914- let rec add_equation0 t aliases name ty =
928+ let rec add_equation0 t name ty =
915929 if ! Clflags.Flambda.Debug. concrete_types_only_on_canonicals then begin
916930 let is_concrete =
917931 match Type_grammar. get_alias_exn ty with
@@ -946,20 +960,18 @@ let rec add_equation0 t aliases name ty =
946960 then
947961 Cached. replace_variable_binding
948962 (One_level. just_after_level t.current_level)
949- var ty ~new_aliases: aliases
963+ var ty
950964 else
951965 Cached. add_or_replace_binding
952966 (One_level. just_after_level t.current_level)
953967 name ty Binding_time. imported_variables Name_mode. in_types
954- ~new_aliases: aliases
955968 in
956969 just_after_level)
957970 ~symbol: (fun _ ->
958971 let just_after_level =
959972 Cached. add_or_replace_binding
960973 (One_level. just_after_level t.current_level)
961974 name ty Binding_time. symbols Name_mode. normal
962- ~new_aliases: aliases
963975 in
964976 just_after_level)
965977 in
@@ -1014,15 +1026,15 @@ and add_equation t name ty =
10141026 end )
10151027 ~const: (fun _ -> () )
10161028 end ;
1017- let aliases, simple, t, ty =
1029+ let simple, t, ty =
10181030 let aliases = aliases t in
10191031 match Type_grammar. get_alias_exn ty with
10201032 | exception Not_found ->
10211033 (* Equations giving concrete types may only be added to the canonical
10221034 element as known by the alias tracker (the actual canonical, ignoring
10231035 any name modes). *)
10241036 let canonical = Aliases. get_canonical_ignoring_name_mode aliases name in
1025- aliases, canonical, t, ty
1037+ canonical, t, ty
10261038 | alias_of ->
10271039 let alias_of = Simple. without_coercion alias_of in
10281040 (* Forget where [name] and [alias_of] came from---our job is now to
@@ -1048,12 +1060,13 @@ and add_equation t name ty =
10481060 ~element2: alias_of
10491061 ~binding_time_and_mode2: binding_time_and_mode_alias_of
10501062 in
1063+ let t = with_aliases t ~aliases in
10511064 (* We need to change the demoted alias's type to point to the new
10521065 canonical element. *)
10531066 let ty =
10541067 Type_grammar. alias_type_of kind canonical_element
10551068 in
1056- aliases, alias_of_demoted_element , t, ty
1069+ alias_of , t, ty
10571070 in
10581071 (* Beware: if we're about to add the equation on a name which is different
10591072 from the one that the caller passed in, then we need to make sure that the
0 commit comments