Skip to content

Commit ee10db5

Browse files
chambartGbury
authored andcommitted
Merge fix
1 parent bb8a90c commit ee10db5

File tree

1 file changed

+10
-11
lines changed

1 file changed

+10
-11
lines changed

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

Lines changed: 10 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -880,30 +880,29 @@ let add_definition t (name : Name_in_binding_pos.t) kind =
880880
end;
881881
add_symbol_definition t sym)
882882

883-
let invariant_for_alias aliases name ty =
883+
let invariant_for_alias (t:t) name ty =
884884
(* Check that no canonical element gets an [Equals] type *)
885885
if !Clflags.flambda_invariant_checks || true then begin
886886
match Type_grammar.get_alias_exn ty with
887887
| exception Not_found -> ()
888888
| alias ->
889889
assert (not (Simple.equal alias (Simple.name name)));
890890
let canonical =
891-
Aliases.get_canonical_ignoring_name_mode aliases name
891+
Aliases.get_canonical_ignoring_name_mode (aliases t) name
892892
in
893893
if Simple.equal canonical (Simple.name name) then
894894
Misc.fatal_errorf
895895
"There is about to be an [Equals] equation on canonical name %a@\nequation: %a@\n@."
896896
Name.print name Type_grammar.print ty
897897
end
898898

899-
let invariant_for_aliases t =
900-
let aliases = aliases t in
899+
let invariant_for_aliases (t:t) =
901900
Name.Map.iter (fun name (ty, _, _) ->
902-
invariant_for_alias aliases name ty
901+
invariant_for_alias t name ty
903902
) (names_to_types t)
904903

905-
let invariant_for_new_equation t aliases name ty =
906-
invariant_for_alias aliases name ty;
904+
let invariant_for_new_equation (t:t) name ty =
905+
invariant_for_alias t name ty;
907906
if !Clflags.flambda_invariant_checks then begin
908907
(* CR mshinwell: This should check that precision is not decreasing. *)
909908
let defined_names =
@@ -925,7 +924,7 @@ let invariant_for_new_equation t aliases name ty =
925924
end
926925
end
927926

928-
let rec add_equation0 t name ty =
927+
let rec add_equation0 (t:t) name ty =
929928
if !Clflags.Flambda.Debug.concrete_types_only_on_canonicals then begin
930929
let is_concrete =
931930
match Type_grammar.get_alias_exn ty with
@@ -934,7 +933,7 @@ let rec add_equation0 t name ty =
934933
in
935934
if is_concrete then begin
936935
let canonical =
937-
Aliases.get_canonical_ignoring_name_mode aliases name
936+
Aliases.get_canonical_ignoring_name_mode (aliases t) name
938937
|> Simple.without_coercion
939938
in
940939
if not (Simple.equal canonical (Simple.name name)) then begin
@@ -946,7 +945,7 @@ let rec add_equation0 t name ty =
946945
end
947946
end
948947
end;
949-
invariant_for_new_equation t aliases name ty;
948+
invariant_for_new_equation t name ty;
950949
let level =
951950
Typing_env_level.add_or_replace_equation
952951
(One_level.level t.current_level) name ty
@@ -1066,7 +1065,7 @@ and add_equation t name ty =
10661065
let ty =
10671066
Type_grammar.alias_type_of kind canonical_element
10681067
in
1069-
alias_of, t, ty
1068+
alias_of_demoted_element, t, ty
10701069
in
10711070
(* Beware: if we're about to add the equation on a name which is different
10721071
from the one that the caller passed in, then we need to make sure that the

0 commit comments

Comments
 (0)