Skip to content

Commit

Permalink
correct comments
Browse files Browse the repository at this point in the history
  • Loading branch information
t6s committed Jul 28, 2021
1 parent c696d44 commit b67e424
Showing 1 changed file with 29 additions and 18 deletions.
47 changes: 29 additions & 18 deletions typing/types.mli
Original file line number Diff line number Diff line change
Expand Up @@ -98,7 +98,7 @@ type type_desc =
*)

| Tfield of string * field_kind * type_expr * type_expr
(** [Tfield ("foo", Fpublic, t, ts)] ==> [<...; foo : t; ts>] *)
(** [Tfield ("foo", field_public, t, ts)] ==> [<...; foo : t; ts>] *)

| Tnil
(** [Tnil] ==> [<...; >] *)
Expand Down Expand Up @@ -206,15 +206,15 @@ and abbrev_memo =
(** [commutable] is a flag appended to every arrow type.
When typing an application, if the type of the functional is
known, its type is instantiated with [Cok] arrows, otherwise as
[Clink (ref Cunknown)].
known, its type is instantiated with [commu_ok] arrows, otherwise as
[commu_var ()].
When the type is not known, the application will be used to infer
the actual type. This is fragile in presence of labels where
there is no principal type.
Two incompatible applications relying on [Cunknown] arrows will
trigger an error.
Two incompatible applications must rely on [is_commu_ok] arrows,
otherwise they will trigger an error.
let f g =
g ~a:() ~b:();
Expand All @@ -229,6 +229,26 @@ val is_commu_ok: commutable -> bool
val commu_ok: commutable
val commu_var: unit -> commutable

(** [field_kind] indicates the accessibility of a method.
An [Fprivate] field may become [Fpublic] or [Fabsent] during unification,
but not the other way round.
The same [field_kind] is kept shared when copying [Tfield] nodes
so that the copies of the self-type of a class share the same accessibility
(see also PR#10539).
*)

type field_kind_view =
Fprivate
| Fpublic
| Fabsent

val field_kind_repr: field_kind -> field_kind_view
val field_public: field_kind
val field_absent: field_kind
val field_private: unit -> field_kind

(** Getters for type_expr; calls repr before answering a value *)

val get_desc: type_expr -> type_desc
Expand Down Expand Up @@ -285,17 +305,6 @@ end
val eq_type: type_expr -> type_expr -> bool
val compare_type: type_expr -> type_expr -> int

(** Current contents of a field_kind *)
type field_kind_view =
Fprivate
| Fpublic
| Fabsent

val field_kind_repr: field_kind -> field_kind_view
val field_public: field_kind
val field_absent: field_kind
val field_private: unit -> field_kind

(* *)

module Uid : sig
Expand Down Expand Up @@ -650,7 +659,10 @@ val undo_compress: snapshot -> unit
not already backtracked to a previous snapshot.
Does not call [cleanup_abbrev] *)

(* Functions to use when modifying a type (only Ctype?) *)
(** Functions to use when modifying a type (only Ctype?).
The old values are logged and reverted on backtracking.
*)

val link_type: type_expr -> type_expr -> unit
(* Set the desc field of [t1] to [Tlink t2], logging the old
value if there is an active snapshot *)
Expand All @@ -666,4 +678,3 @@ val set_univar: type_expr option ref -> type_expr -> unit
val link_kind: inside:field_kind -> field_kind -> unit
val link_commu: inside:commutable -> commutable -> unit
val set_commu_ok: commutable -> unit
(* Set references, logging the old value *)

0 comments on commit b67e424

Please sign in to comment.