master
Florian Angeletti 2020-01-29 09:53:49 +01:00
parent 9f696f0a8e
commit 62699c1ce3
4 changed files with 12 additions and 21 deletions

View File

@ -175,9 +175,9 @@ Working version
- #9097: Do not emit references to dead labels introduced by #2321 (spacetime).
(Greta Yorsh, review by Mark Shinwell)
- #9218, ???: avoid a rare wrong module name error with "-annot" and
- #9218, #9269: avoid a rare wrong module name error with "-annot" and
inline records.
(Florian Angeletti, review by ???, report by Kate Deplaix)
(Florian Angeletti, review by Gabriel Scherer, report by Kate Deplaix)
- #9225: Do not drop bytecode debug info after C calls.
(Stephen Dolan, review by Gabriel Scherer and Jacques-Henri Jourdan)

View File

@ -1097,11 +1097,6 @@ let normalize_path_prefix oloc env path =
| Papply _ ->
assert false
let is_uident s =
match s.[0] with
| 'A'..'Z' -> true
| _ -> false
let normalize_type_path oloc env path =
(* Inlined version of Path.is_constructor_typath:
constructor type paths (i.e. path pointing to an inline
@ -1112,7 +1107,7 @@ let normalize_type_path oloc env path =
path
| Pdot(p, s) ->
let p2 =
if is_uident s && not (is_uident (Path.last p)) then
if Path.is_uident s && not (Path.is_uident (Path.last p)) then
(* Cstr M.t.C *)
normalize_path_prefix oloc env p
else

View File

@ -37,6 +37,8 @@ val heads: t -> Ident.t list
val last: t -> string
val is_uident: string -> bool
type typath =
| Regular of t
| Ext of t * string

View File

@ -389,25 +389,19 @@ let rewrite_double_underscore_paths env p =
else
rewrite_double_underscore_paths env p
let rec regular_tree_of_path namespace = function
let rec tree_of_path namespace = function
| Pident id ->
Oide_ident (ident_name namespace id)
| Pdot(_, s) as path when non_shadowed_pervasive path ->
Oide_ident (Naming_context.pervasives_name namespace s)
| Pdot(Pident t, s)
when namespace=Type && not (Path.is_uident (Ident.name t)) ->
(* [t.A]: inline record of the constructor [A] from type [t] *)
Oide_dot (Oide_ident (ident_name Type t), s)
| Pdot(p, s) ->
Oide_dot (regular_tree_of_path Module p, s)
Oide_dot (tree_of_path Module p, s)
| Papply(p1, p2) ->
Oide_apply (regular_tree_of_path Module p1,
regular_tree_of_path Module p2)
let tree_of_path namespace p = match namespace with
| Module | Module_type | Class | Class_type | Other->
regular_tree_of_path namespace p
| Type ->
match Path.constructor_typath p with
| Regular _ | Ext _ | LocalExt _ -> regular_tree_of_path namespace p
| Cstr (p, s) -> (* t.A *)
Oide_dot (regular_tree_of_path Type p, s)
Oide_apply (tree_of_path Module p1, tree_of_path Module p2)
let tree_of_path namespace p =
tree_of_path namespace (rewrite_double_underscore_paths !printing_env p)