ident: remove create_hidden

master
Thomas Refis 2018-09-13 10:24:21 +01:00
parent aad38c98c3
commit 582127f240
4 changed files with 7 additions and 15 deletions

View File

@ -428,7 +428,8 @@ module IdTbl =
| Some {root; using = _; next; components} ->
NameMap.iter
(fun s (x, pos) ->
f (Ident.create_hidden s (* ??? *))
let root_scope = Path.scope root in
f (Ident.create_scoped ~scope:root_scope s)
(Pdot (root, s, pos), x))
components;
iter f next

View File

@ -36,9 +36,6 @@ let create_local s =
incr currentstamp;
Local { name = s; stamp = !currentstamp }
let create_hidden s =
Local { name = s; stamp = -1 }
let create_predef s =
incr predefstamp;
Predef { name = s; stamp = !predefstamp }
@ -127,7 +124,6 @@ let print ppf = function
| Predef { name; stamp = n } ->
fprintf ppf "%s%s!" name
(if !Clflags.unique_ids then Printf.sprintf "/%i" n else "")
| Local { name; stamp = -1 } -> fprintf ppf "%s#" name
| Local { name; stamp = n } ->
fprintf ppf "%s%s" name
(if !Clflags.unique_ids then Printf.sprintf "/%i" n else "")

View File

@ -48,11 +48,6 @@ val same: t -> t -> bool
val compare: t -> t -> int
val create_hidden: string -> t
(** Same as [create_local] but stamp different from any stamp returned
by [create_*]. When put in a 'a tbl, this identifier can only be
looked up by name. *)
val global: t -> bool
val is_predef: t -> bool

View File

@ -1384,13 +1384,13 @@ let rec tree_of_class_type sch params =
let lab =
if !print_labels || is_optional l then string_of_label l else ""
in
let ty =
let tr =
if is_optional l then
match (repr ty).desc with
| Tconstr(path, [ty], _) when Path.same path Predef.path_option -> ty
| _ -> newconstr (Path.Pident(Ident.create_hidden "<hidden>")) []
else ty in
let tr = tree_of_typexp sch ty in
| Tconstr(path, [ty], _) when Path.same path Predef.path_option ->
tree_of_typexp sch ty
| _ -> Otyp_stuff "<hidden>"
else tree_of_typexp sch ty in
Octy_arrow (lab, tr, tree_of_class_type sch params cty)
let class_type ppf cty =