Skip to content

Commit 27f4009

Browse files
committed
Add comments; simplify Aliases API a bit
1 parent 54fbf27 commit 27f4009

File tree

3 files changed

+61
-27
lines changed

3 files changed

+61
-27
lines changed

middle_end/flambda/types/env/aliases.ml

+18-16
Original file line numberDiff line numberDiff line change
@@ -807,21 +807,20 @@ let choose_canonical_element_to_be_demoted t ~canonical_element1
807807
type add_result = {
808808
t : t;
809809
canonical_element : Simple.t;
810-
alias_of_demoted_element : Simple.t;
811-
coercion_from_alias_of_demoted_to_canonical : Coercion.t;
810+
demoted_alias : Simple.t;
812811
}
813812

814-
let invariant_add_result ~original_t { canonical_element; alias_of_demoted_element; t; coercion_from_alias_of_demoted_to_canonical = _; } =
813+
let invariant_add_result ~original_t { canonical_element; demoted_alias; t; } =
815814
if !Clflags.flambda_invariant_checks then begin
816815
invariant t;
817-
if not (Simple.equal canonical_element alias_of_demoted_element) then begin
816+
if not (Simple.equal canonical_element demoted_alias) then begin
818817
if not (defined_earlier t canonical_element
819-
~than:alias_of_demoted_element) then begin
818+
~than:demoted_alias) then begin
820819
Misc.fatal_errorf "Canonical element %a should be defined earlier \
821820
than %a after alias addition.@ Original alias tracker:@ %a@ \
822821
Resulting alias tracker:@ %a"
823822
Simple.print canonical_element
824-
Simple.print alias_of_demoted_element
823+
Simple.print demoted_alias
825824
print original_t
826825
print t
827826
end
@@ -833,9 +832,9 @@ let add_alias t ~element1 ~coercion_from_element2_to_element1 ~element2 =
833832
~coercion_from_element1_to_canonical_element1
834833
~coercion_from_element2_to_canonical_element2
835834
~coercion_from_canonical_element2_to_canonical_element1 =
836-
let canonical_element, to_be_demoted, alias_of_demoted_element,
837-
coercion_from_demoted_to_canonical,
838-
coercion_from_alias_of_demoted_to_demoted =
835+
let canonical_element, demoted_canonical, demoted_alias,
836+
coercion_from_demoted_canonical_to_canonical,
837+
coercion_from_demoted_alias_to_demoted_canonical =
839838
let which_element =
840839
choose_canonical_element_to_be_demoted t
841840
~canonical_element1 ~canonical_element2
@@ -858,19 +857,22 @@ let add_alias t ~element1 ~coercion_from_element2_to_element1 ~element2 =
858857
add_alias_between_canonical_elements
859858
t
860859
~canonical_element
861-
~coercion_to_canonical:coercion_from_demoted_to_canonical
862-
~to_be_demoted
860+
~coercion_to_canonical:coercion_from_demoted_canonical_to_canonical
861+
~to_be_demoted:demoted_canonical
863862
in
864-
let coercion_from_alias_of_demoted_to_canonical =
863+
let coercion_from_demoted_alias_to_canonical =
865864
Coercion.compose_exn
866-
coercion_from_alias_of_demoted_to_demoted
867-
~then_:coercion_from_demoted_to_canonical
865+
coercion_from_demoted_alias_to_demoted_canonical
866+
~then_:coercion_from_demoted_canonical_to_canonical
867+
in
868+
let demoted_alias =
869+
Simple.with_coercion demoted_alias
870+
coercion_from_demoted_alias_to_canonical
868871
in
869872
Or_bottom.map t ~f:(fun t ->
870873
{ t;
871874
canonical_element;
872-
alias_of_demoted_element;
873-
coercion_from_alias_of_demoted_to_canonical;
875+
demoted_alias;
874876
})
875877
in
876878
match canonical t element1, canonical t element2 with

middle_end/flambda/types/env/aliases.mli

+38-4
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,32 @@
1414

1515
(** Union-find-like structure for keeping track of equivalence classes,
1616
used for alias resolution in the typing environment, with support for
17-
associating orderings to aliases of canonical elements. *)
17+
associating orderings to aliases of canonical elements.
18+
19+
The concept of "alias" needs to be broadened where coercions are involved.
20+
A coercion is a sort of fudge factor---if [x] is equal to [(coerce y c)],
21+
then [x] and [y] are {i essentially} equal, close enough that we want to
22+
think of [y] as an alias of [x].
23+
24+
If the words "fudge factor" sound like we're being imprecise, happily we can
25+
be precise about our imprecision. Let [x ~ y] mean [x] and [y] are _equal up
26+
to coercion_, which is to say, there exists a coercion [c] such that [x =
27+
(coerce y c)]. Coercions form a _groupoid_, meaning they have just the
28+
right properties to let [~] be an equivalence relation:
29+
30+
+ There is an identity coercion, so [x = (coerce x id)], meaning [x ~ x].
31+
+ Coercions can be inverted, so if [x ~ y], meaning [x = (coerce y c)],
32+
then (writing [c^-1] for the inverse) we have [y = (coerce x c^-1)],
33+
meaning [y ~ x].
34+
+ Coercions can be composed, so if [x ~ y] and [y ~ z], meaning
35+
[x = (coerce y c_xy)] and [y = (coerce z c_yz)], then (using [>>] as
36+
the composition operator) we have [x = (coerce z (c_xy >> c_yz))] and
37+
[x ~ z].
38+
39+
Therefore we can safely redefine "alias" to mean [x ~ y] rather than [x =
40+
y], and the coercions keep track of the precise sense in which [x] and [y]
41+
are "equal enough." In particular, this module keeps track of aliases in
42+
this looser sense. *)
1843

1944
[@@@ocaml.warning "+a-4-30-40-41-42"]
2045

@@ -28,11 +53,20 @@ val invariant : t -> unit
2853

2954
val empty : t
3055

56+
(** The result of calling [add] to state that two [Simple.t]s are now
57+
aliases. *)
3158
type add_result = private {
3259
t : t;
33-
canonical_element : Simple.t; (* has no coercion *)
34-
alias_of_demoted_element : Simple.t; (* has no coercion *)
35-
coercion_from_alias_of_demoted_to_canonical : Coercion.t;
60+
(** The new state of the alias tracker. *)
61+
canonical_element : Simple.t;
62+
(** The canonical element of the combined equivalence class. In the type
63+
environment, this will be the name (if it is a name) that is assigned a
64+
concrete type. Does not carry a coercion. *)
65+
demoted_alias: Simple.t;
66+
(** Whichever argument to [add] had its equivalence class consumed and its
67+
canonical element demoted to an alias. It is this name that needs its type
68+
to change to record the new canonical element. Its coercion has been
69+
adjusted so that it is properly an alias of [canonical_element]. *)
3670
}
3771

3872
val add

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

+5-7
Original file line numberDiff line numberDiff line change
@@ -1034,13 +1034,11 @@ and add_equation t name ty =
10341034
let ty = Type_grammar.bottom_like ty in
10351035
aliases, lhs, t, ty
10361036
| Ok { canonical_element;
1037-
alias_of_demoted_element;
1038-
t = aliases;
1039-
coercion_from_alias_of_demoted_to_canonical; } ->
1040-
let lhs =
1041-
Simple.with_coercion alias_of_demoted_element
1042-
coercion_from_alias_of_demoted_to_canonical
1043-
in
1037+
demoted_alias;
1038+
t = aliases; } ->
1039+
(* We need to change the demoted alias's type to point to the new
1040+
canonical element. *)
1041+
let lhs = demoted_alias in
10441042
let ty =
10451043
Type_grammar.alias_type_of kind canonical_element
10461044
in

0 commit comments

Comments
 (0)