Skip to content

Commit

Permalink
ocaml#10780: missing cmi can hide type declaration
Browse files Browse the repository at this point in the history
  • Loading branch information
Octachron committed Dec 1, 2021
1 parent 3fa2cfc commit ae134cf
Show file tree
Hide file tree
Showing 5 changed files with 40 additions and 11 deletions.
3 changes: 2 additions & 1 deletion Changes
Original file line number Diff line number Diff line change
Expand Up @@ -231,7 +231,8 @@ OCaml 4.14.0

### Compiler user-interface and warnings:

- #10328: Give more precise error when disambiguation could not possibly work.
- #10328, #10780: Give more precise error when disambiguation could not
possibly work.
(Leo White, review by Gabriel Scherer and Florian Angeletti)

- #10361: Improve error messages for mismatched record and variant
Expand Down
7 changes: 7 additions & 0 deletions testsuite/tests/typing-missing-cmi-3/middle.ml
Original file line number Diff line number Diff line change
Expand Up @@ -6,3 +6,10 @@ let g: (module Original.T) -> unit = fun _ -> ()
type pack1 = (module Original.T with type t = int)
module type T = sig module M : Original.T end
type pack2 = (module T with type M.t = int)

(* Check the detection of type kind in type-directed disambiguation. *)
type r = Original.r = { x:unit }
let r = Original.r

type s = Original.s = S
let s = Original.s
6 changes: 6 additions & 0 deletions testsuite/tests/typing-missing-cmi-3/original.ml
Original file line number Diff line number Diff line change
@@ -1,2 +1,8 @@
type 'a t = T
module type T = sig type t end

type r = { x:unit }
let r = { x = () }

type s = S
let s = S
12 changes: 12 additions & 0 deletions testsuite/tests/typing-missing-cmi-3/user.ml
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@ script = "rm -f original.cmi"


#directory "ocamlc.byte";;
#load "original.cmo"
#load "middle.cmo"

let x:'a. 'a Middle.t =
Expand Down Expand Up @@ -87,3 +88,14 @@ Line 2, characters 12-45:
Error: Type Middle.pack2 = (module Middle.T with type M.t = int)
is not a subtype of (module T2)
|}]

(* Check the detection of type kind in type-directed disambiguation . *)
let t = Middle.r.Middle.x
[%%expect {|
val t : unit = ()
|}]

let k = match Middle.s with Middle.S -> ()
[%%expect {|
val k : unit = ()
|}]
23 changes: 13 additions & 10 deletions typing/ctype.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1616,16 +1616,19 @@ type typedecl_extraction_result =
let rec extract_concrete_typedecl env ty =
match get_desc ty with
Tconstr (p, _, _) ->
let decl = Env.find_type p env in
if decl.type_kind <> Type_abstract then Typedecl(p, p, decl)
else begin
match try_expand_safe env ty with
| exception Cannot_expand -> May_have_typedecl
| ty ->
match extract_concrete_typedecl env ty with
| Typedecl(_, p', decl) -> Typedecl(p, p', decl)
| Has_no_typedecl -> Has_no_typedecl
| May_have_typedecl -> May_have_typedecl
begin match Env.find_type p env with
| exception Not_found -> May_have_typedecl
| decl ->
if decl.type_kind <> Type_abstract then Typedecl(p, p, decl)
else begin
match try_expand_safe env ty with
| exception Cannot_expand -> May_have_typedecl
| ty ->
match extract_concrete_typedecl env ty with
| Typedecl(_, p', decl) -> Typedecl(p, p', decl)
| Has_no_typedecl -> Has_no_typedecl
| May_have_typedecl -> May_have_typedecl
end
end
| Tpoly(ty, _) -> extract_concrete_typedecl env ty
| Tarrow _ | Ttuple _ | Tobject _ | Tfield _ | Tnil
Expand Down

0 comments on commit ae134cf

Please sign in to comment.