Merge pull request #8910 from gasche/better-printing-of-module-types

Better printing of empty signatures
master
Gabriel Scherer 2019-09-03 14:42:22 +02:00 committed by GitHub
commit 5526a31364
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
35 changed files with 176 additions and 178 deletions

View File

@ -77,7 +77,7 @@ Line 3, characters 7-20:
3 | open M(struct end)
^^^^^^^^^^^^^
Error: This module is not a structure; it has type
functor (X : sig end) -> sig end
functor (X : sig end) -> sig end
|}]
open struct
@ -298,7 +298,7 @@ module N = struct
assert(y = 1)
end
[%%expect{|
module N : sig end
module N : sig end
|}]
module M = struct
@ -314,7 +314,7 @@ module M = struct
end
end
[%%expect{|
module M : sig end
module M : sig end
|}]
(* It was decided to not allow this anymore *)
@ -385,5 +385,5 @@ Line 1, characters 20-53:
1 | let f () = let open functor(X: sig end) -> struct end in ();;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Error: This module is not a structure; it has type
functor (X : sig end) -> sig end
functor (X : sig end) -> sig end
|}]

View File

@ -134,7 +134,7 @@ val bind_map : int list = [8; 9; 10; 9; 10; 11; 10; 11; 12]
module Let_unbound = struct
end;;
[%%expect{|
module Let_unbound : sig end
module Let_unbound : sig end
|}];;
let let_unbound =

View File

@ -72,7 +72,7 @@ let rec x = (module (val y : T) : T)
and y = let module M = struct let x = x end in (module M : T)
;;
[%%expect{|
module type T = sig end
module type T = sig end
Line 2, characters 12-36:
2 | let rec x = (module (val y : T) : T)
^^^^^^^^^^^^^^^^^^^^^^^^

View File

@ -516,7 +516,7 @@ module M = struct (** foo *) end;;
[%%expect {|
module M = struct [@@@ocaml.text " foo "] end;;
module M : sig end
module M : sig end
|}]
module M = struct (** foo *)
@ -525,7 +525,7 @@ end;;
[%%expect {|
module M = struct [@@@ocaml.text " foo "] end;;
module M : sig end
module M : sig end
|}]
module M = struct
@ -534,7 +534,7 @@ module M = struct
[%%expect {|
module M = struct [@@@ocaml.text " foo "] end;;
module M : sig end
module M : sig end
|}]
module M = struct
@ -543,7 +543,7 @@ end;;
[%%expect {|
module M = struct [@@@ocaml.text " foo "] end;;
module M : sig end
module M : sig end
|}]
module M = struct
@ -553,7 +553,7 @@ end;;
[%%expect {|
module M = struct [@@@ocaml.text " foo "] end;;
module M : sig end
module M : sig end
|}]
module M = struct
@ -563,7 +563,7 @@ end;;
[%%expect {|
module M = struct [@@@ocaml.text " foo "] end;;
module M : sig end
module M : sig end
|}]
module M = struct
@ -574,7 +574,7 @@ end;;
[%%expect {|
module M = struct [@@@ocaml.text " foo "] end;;
module M : sig end
module M : sig end
|}]
module M = struct
@ -588,7 +588,7 @@ end;;
module M = struct [@@@ocaml.text " foo "]
[@@@ocaml.text " bar "] end;;
module M : sig end
module M : sig end
|}]
module M = struct
@ -600,7 +600,7 @@ end;;
module M = struct [@@@ocaml.text " foo "]
[@@@ocaml.text " bar "] end;;
module M : sig end
module M : sig end
|}]

View File

@ -282,8 +282,8 @@ module N :
type t
val unit : unit
external e : unit -> unit = "%identity"
module M : sig end
module type T = sig end
module M : sig end
module type T = sig end
exception E
type ext = ..
type ext += C
@ -304,7 +304,7 @@ module NN :
val unit : unit
external e : unit -> unit = "%identity"
module M = N.M
module type T = sig end
module type T = sig end
exception E
type ext = N.ext = ..
type ext += C
@ -329,7 +329,7 @@ module Type :
val unit : unit
external e : unit -> unit = "%identity"
module M = N.M
module type T = sig end
module type T = sig end
exception E
type ext = N.ext = ..
type ext += C
@ -352,7 +352,7 @@ module Module :
val unit : unit
external e : unit -> unit = "%identity"
module M = N.M
module type T = sig end
module type T = sig end
exception E
type ext = N.ext = ..
type ext += C
@ -370,12 +370,12 @@ end
[%%expect{|
module Module_type :
sig
module type U = sig end
module type U = sig end
type t = N.t
val unit : unit
external e : unit -> unit = "%identity"
module M = N.M
module type T = sig end
module type T = sig end
exception E
type ext = N.ext = ..
type ext += C
@ -398,7 +398,7 @@ module Exception :
val unit : unit
external e : unit -> unit = "%identity"
module M = N.M
module type T = sig end
module type T = sig end
exception E
type ext = N.ext = ..
type ext += C
@ -421,7 +421,7 @@ module Extension :
val unit : unit
external e : unit -> unit = "%identity"
module M = N.M
module type T = sig end
module type T = sig end
exception E
type ext = N.ext = ..
type ext += C
@ -444,7 +444,7 @@ module Class :
val unit : unit
external e : unit -> unit = "%identity"
module M = N.M
module type T = sig end
module type T = sig end
exception E
type ext = N.ext = ..
type ext += C
@ -467,7 +467,7 @@ module Class_type :
val unit : unit
external e : unit -> unit = "%identity"
module M = N.M
module type T = sig end
module type T = sig end
exception E
type ext = N.ext = ..
type ext += C

View File

@ -7,7 +7,7 @@ Module Inline_records
Module
.BI "Inline_records"
:
.B sig end
.B sig end
.sp
This test focuses on the printing of documentation for inline record

View File

@ -1,19 +1,19 @@
#
# module T01:
# Odoc_info.string_of_module_type:
<[sig end]>
<[sig end]>
# Odoc_info.string_of_module_type ~complete: true :
<[sig end]>
<[sig end]>
#
# module T01.M:
# Odoc_info.string_of_module_type:
<[sig end]>
<[sig end]>
# Odoc_info.string_of_module_type ~complete: true :
<[sig val y : int end]>
#
# module type T01.MT:
# Odoc_info.string_of_module_type:
<[sig end]>
<[sig end]>
# Odoc_info.string_of_module_type ~complete: true :
<[sig
type t =

View File

@ -1,13 +1,13 @@
#
# module T04:
# Odoc_info.string_of_module_type:
<[sig end]>
<[sig end]>
# Odoc_info.string_of_module_type ~complete: true :
<[sig end]>
<[sig end]>
#
# module T04.A:
# Odoc_info.string_of_module_type:
<[sig end]>
<[sig end]>
# Odoc_info.string_of_module_type ~complete: true :
<[sig type a = A of { lbl : int; } end]>
# type T04.A.a:
@ -16,12 +16,12 @@
#
# module type T04.E:
# Odoc_info.string_of_module_type:
<[sig end]>
<[sig end]>
# Odoc_info.string_of_module_type ~complete: true :
<[sig exception E of { lbl : int; } end]>
#
# module T04.E_bis:
# Odoc_info.string_of_module_type:
<[sig end]>
<[sig end]>
# Odoc_info.string_of_module_type ~complete: true :
<[sig exception E of { lbl : int; } end]>

View File

@ -20,8 +20,8 @@
&nbsp;&nbsp;<span class="keyword">type</span>&nbsp;s&nbsp;=&nbsp;..<br>
&nbsp;&nbsp;<span class="keyword">type</span>&nbsp;s&nbsp;+=&nbsp;<span class="constructor">B</span><br>
&nbsp;&nbsp;<span class="keyword">val</span>&nbsp;x&nbsp;:&nbsp;<span class="constructor">Linebreaks</span>.a<br>
&nbsp;&nbsp;<span class="keyword">module</span>&nbsp;<span class="constructor">S</span>&nbsp;:&nbsp;<span class="keyword">sig</span>&nbsp;<span class="keyword">module</span>&nbsp;<span class="constructor">I</span>&nbsp;:&nbsp;<span class="keyword">sig</span>&nbsp;&nbsp;<span class="keyword">end</span>&nbsp;<span class="keyword">end</span><br>
&nbsp;&nbsp;<span class="keyword">module</span>&nbsp;<span class="keyword">type</span>&nbsp;s&nbsp;=&nbsp;<span class="keyword">sig</span>&nbsp;&nbsp;<span class="keyword">end</span><br>
&nbsp;&nbsp;<span class="keyword">module</span>&nbsp;<span class="constructor">S</span>&nbsp;:&nbsp;<span class="keyword">sig</span>&nbsp;<span class="keyword">module</span>&nbsp;<span class="constructor">I</span>&nbsp;:&nbsp;<span class="keyword">sig</span>&nbsp;<span class="keyword">end</span>&nbsp;<span class="keyword">end</span><br>
&nbsp;&nbsp;<span class="keyword">module</span>&nbsp;<span class="keyword">type</span>&nbsp;s&nbsp;=&nbsp;<span class="keyword">sig</span>&nbsp;<span class="keyword">end</span><br>
&nbsp;&nbsp;<span class="keyword">class</span>&nbsp;<span class="keyword">type</span>&nbsp;d&nbsp;=&nbsp;<span class="keyword">object</span>&nbsp;&nbsp;<span class="keyword">end</span><br>
&nbsp;&nbsp;<span class="keyword">exception</span>&nbsp;<span class="constructor">E</span>&nbsp;<span class="keyword">of</span>&nbsp;{&nbsp;inline&nbsp;:&nbsp;int;&nbsp;}<br>
<span class="keyword">end</span></code></body></html>

View File

@ -1,11 +1,11 @@
module Empty : sig end
module Empty : sig end
type u = A
type v = B
module type S = sig end
module type S = sig end
val m : (module S) = <module>
module M : sig type 'a t = X of 'a end
val x : (u * v * (module S)) M.t = M.X (A, B, <module>)
module type S = sig end
module type S = sig end
val m : (module S) = <module>
type u = A
type v = B

View File

@ -384,7 +384,7 @@ module D = struct end[@@ocaml.deprecated]
open D
;;
[%%expect{|
module D : sig end
module D : sig end
Line 3, characters 5-6:
3 | open D
^
@ -575,7 +575,7 @@ Line 8, characters 22-36:
8 | [@@@ocaml.ppwarning "Pp warning2!"]
^^^^^^^^^^^^^^
Warning 22: Pp warning2!
module X : sig end
module X : sig end
|}]
let x =

View File

@ -30,7 +30,7 @@ A
module M :
functor (A : sig module type T end) (B : sig module type T end) ->
sig val f : ((module A.T), (module B.T)) t -> string end
module A : sig module type T = sig end end
module A : sig module type T = sig end end
module N : sig val f : ((module A.T), (module A.T)) t -> string end
Exception: Match_failure ("", 8, 52).
|}];;

View File

@ -78,14 +78,14 @@ Lines 4-7, characters 4-7:
7 | end
Error: Signature mismatch:
Modules do not match:
sig module type s module A : functor (X : s) -> sig end end
sig module type s module A : functor (X : s) -> sig end end
is not included in
sig module A : functor (X : s) -> sig end end
sig module A : functor (X : s) -> sig end end
In module A:
Modules do not match:
functor (X : s/1) -> sig end
functor (X : s/1) -> sig end
is not included in
functor (X : s/2) -> sig end
functor (X : s/2) -> sig end
At position module A(X : <here>) : ...
Modules do not match: s/2 is not included in s/1
Line 5, characters 6-19:
@ -403,7 +403,7 @@ let add_extra_info arg = arg.Foo.info.doc
[%%expect{|
module Bar : sig type info = { doc : unit; } end
module Foo : sig type t = { info : Bar.info; } end
module Bar : sig end
module Bar : sig end
Line 8, characters 38-41:
8 | let add_extra_info arg = arg.Foo.info.doc
^^^

View File

@ -224,7 +224,7 @@ module type empty = sig end
let f (x:int) = ()
let x = f (module struct end)
[%%expect {|
module type empty = sig end
module type empty = sig end
val f : int -> unit = <fun>
Line 3, characters 10-29:
3 | let x = f (module struct end)

View File

@ -14,8 +14,8 @@ module type S' = sig type s = int end
module type S = sig module rec M : sig end and N : sig end end;;
module type S' = S with module M := String;;
[%%expect{|
module type S = sig module rec M : sig end and N : sig end end
module type S' = sig module rec N : sig end end
module type S = sig module rec M : sig end and N : sig end end
module type S' = sig module rec N : sig end end
|}];;
(* with module type *)
@ -119,7 +119,7 @@ Error: Multiple definition of the extension constructor name Foo.
module F(X : sig end) = struct let x = 3 end;;
F.x;; (* fail *)
[%%expect{|
module F : functor (X : sig end) -> sig val x : int end
module F : functor (X : sig end) -> sig val x : int end
Line 2, characters 0-3:
2 | F.x;; (* fail *)
^^^

View File

@ -57,7 +57,7 @@ module C4 = F(struct end);;
C4.chr 66;;
[%%expect{|
module F :
functor (X : sig end) ->
functor (X : sig end) ->
sig
external code : char -> int = "%identity"
val chr : int -> char
@ -91,8 +91,8 @@ module C4 :
module G(X:sig end) = struct module M = X end;; (* does not alias X *)
module M = G(struct end);;
[%%expect{|
module G : functor (X : sig end) -> sig module M : sig end end
module M : sig module M : sig end end
module G : functor (X : sig end) -> sig module M : sig end end
module M : sig module M : sig end end
|}];;
module M' = struct
@ -141,9 +141,9 @@ module M5 = G(struct end);;
M5.N'.x;;
[%%expect{|
module F :
functor (X : sig end) ->
functor (X : sig end) ->
sig module N : sig val x : int end module N' = N end
module G : functor (X : sig end) -> sig module N' : sig val x : int end end
module G : functor (X : sig end) -> sig module N' : sig val x : int end end
module M5 : sig module N' : sig val x : int end end
- : int = 1
|}];;
@ -377,8 +377,8 @@ end;;
include T;;
let f (x : t) : T.t = x ;;
[%%expect{|
module F : functor (M : sig end) -> sig type t end
module T : sig module M : sig end type t = F(M).t end
module F : functor (M : sig end) -> sig type t end
module T : sig module M : sig end type t = F(M).t end
module M = T.M
type t = F(M).t
val f : t -> T.t = <fun>
@ -462,16 +462,11 @@ module G = F (M.Y);;
(*module N = G (M);;
module N = F (M.Y) (M);;*)
[%%expect{|
module FF : functor (X : sig end) -> sig type t end
module FF : functor (X : sig end) -> sig type t end
module M :
sig
module X : sig end
module Y : sig type t = FF(X).t end
type t = Y.t
end
module F :
functor (Y : sig type t end) (M : sig type t = Y.t end) -> sig end
module G : functor (M : sig type t = M.Y.t end) -> sig end
sig module X : sig end module Y : sig type t = FF(X).t end type t = Y.t end
module F : functor (Y : sig type t end) (M : sig type t = Y.t end) -> sig end
module G : functor (M : sig type t = M.Y.t end) -> sig end
|}];;
(* PR#6307 *)
@ -486,13 +481,13 @@ module F (L : (module type of L1 [@remove_aliases])) = struct end;;
module F1 = F(L1);; (* ok *)
module F2 = F(L2);; (* should succeed too *)
[%%expect{|
module A1 : sig end
module A2 : sig end
module A1 : sig end
module A2 : sig end
module L1 : sig module X = A1 end
module L2 : sig module X = A2 end
module F : functor (L : sig module X : sig end end) -> sig end
module F1 : sig end
module F2 : sig end
module F : functor (L : sig module X : sig end end) -> sig end
module F1 : sig end
module F2 : sig end
|}];;
(* Counter example: why we need to be careful with PR#6307 *)
@ -663,8 +658,8 @@ module F (X : sig end) = struct type t end;;
module type A = Alias with module N := F(List);;
module rec Bad : A = Bad;;
[%%expect{|
module type Alias = sig module N : sig end module M = N end
module F : functor (X : sig end) -> sig type t end
module type Alias = sig module N : sig end module M = N end
module F : functor (X : sig end) -> sig type t end
Line 1:
Error: Module type declarations do not match:
module type A = sig module M = F(List) end
@ -716,7 +711,7 @@ module type S = sig
module Q = M
end;;
[%%expect{|
module type S = sig module M : sig module P : sig end end module Q = M end
module type S = sig module M : sig module P : sig end end module Q = M end
|}];;
module type S = sig
module M : sig module N : sig end module P : sig end end
@ -730,12 +725,12 @@ module R' : S = R;;
[%%expect{|
module type S =
sig
module M : sig module N : sig end module P : sig end end
module M : sig module N : sig end module P : sig end end
module Q : sig module N = M.N module P = M.P end
end
module R :
sig
module M : sig module N : sig end module P : sig end end
module M : sig module N : sig end module P : sig end end
module Q = M
end
module R' : S
@ -756,9 +751,9 @@ end = struct
type a = Foo.b
end;;
[%%expect{|
module F : functor (X : sig end) -> sig type t end
module F : functor (X : sig end) -> sig type t end
module M :
sig type a module Foo : sig module Bar : sig end type b = a end end
sig type a module Foo : sig module Bar : sig end type b = a end end
|}];;
(* PR#6578 *)
@ -796,7 +791,7 @@ end = struct
module type S = module type of struct include X end
end;;
[%%expect{|
module X : sig module N : sig end end
module X : sig module N : sig end end
module Y : sig module type S = sig module N = X.N end end
|}];;
@ -819,7 +814,7 @@ let s : string = Bar.N.x
[%%expect {|
module type S =
sig
module M : sig module A : sig end module B : sig end end
module M : sig module A : sig end module B : sig end end
module N = M.A
end
module Foo :

View File

@ -14,8 +14,8 @@ module H (X : sig end) = (val v);; (* ok *)
module type S = sig val x : int end
val v : (module S) = <module>
module F : functor () -> S
module G : functor (X : sig end) -> S
module H : functor (X : sig end) -> S
module G : functor (X : sig end) -> S
module H : functor (X : sig end) -> S
|}];;
(* With type *)
@ -44,7 +44,7 @@ module H : functor () -> S
module U = struct end;;
module M = F(struct end);; (* ok *)
[%%expect{|
module U : sig end
module U : sig end
module M : S
|}];;
module M = F(U);; (* fail *)
@ -59,28 +59,28 @@ Error: This is a generative functor. It can only be applied to ()
module F1 (X : sig end) = struct end;;
module F2 : functor () -> sig end = F1;; (* fail *)
[%%expect{|
module F1 : functor (X : sig end) -> sig end
module F1 : functor (X : sig end) -> sig end
Line 2, characters 36-38:
2 | module F2 : functor () -> sig end = F1;; (* fail *)
^^
Error: Signature mismatch:
Modules do not match:
functor (X : sig end) -> sig end
functor (X : sig end) -> sig end
is not included in
functor () -> sig end
functor () -> sig end
|}];;
module F3 () = struct end;;
module F4 : functor (X : sig end) -> sig end = F3;; (* fail *)
[%%expect{|
module F3 : functor () -> sig end
module F3 : functor () -> sig end
Line 2, characters 47-49:
2 | module F4 : functor (X : sig end) -> sig end = F3;; (* fail *)
^^
Error: Signature mismatch:
Modules do not match:
functor () -> sig end
functor () -> sig end
is not included in
functor (X : sig end) -> sig end
functor (X : sig end) -> sig end
|}];;
(* tests for shortened functor notation () *)
@ -91,8 +91,8 @@ module Z = functor (_: sig end) (_:sig end) (_: sig end) -> struct end;;
module GZ : functor (X: sig end) () (Z: sig end) -> sig end
= functor (X: sig end) () (Z: sig end) -> struct end;;
[%%expect{|
module X : functor (X : sig end) (Y : sig end) (Z : sig end) -> sig end
module Y : functor (X : sig end) (Y : sig end) (Z : sig end) -> sig end
module Z : sig end -> sig end -> sig end -> sig end
module GZ : functor (X : sig end) () (Z : sig end) -> sig end
module X : functor (X : sig end) (Y : sig end) (Z : sig end) -> sig end
module Y : functor (X : sig end) (Y : sig end) (Z : sig end) -> sig end
module Z : sig end -> sig end -> sig end -> sig end
module GZ : functor (X : sig end) () (Z : sig end) -> sig end
|}];;

View File

@ -503,23 +503,23 @@ Error: Signature mismatch:
module B :
sig
module C :
functor (X : sig end) (Y : sig end)
functor (X : sig end) (Y : sig end)
(Z : sig
module D :
sig
module E :
sig
module F :
functor (X : sig end)
functor (X : sig end)
(Arg : sig
val two : int
val one : int
end)
-> sig end
-> sig end
end
end
end)
-> sig end
-> sig end
end
end
end
@ -533,23 +533,23 @@ Error: Signature mismatch:
module B :
sig
module C :
functor (X : sig end) (Y : sig end)
functor (X : sig end) (Y : sig end)
(Z : sig
module D :
sig
module E :
sig
module F :
functor (X : sig end)
functor (X : sig end)
(Arg : sig
val one : int
val two : int
end)
-> sig end
-> sig end
end
end
end)
-> sig end
-> sig end
end
end
end
@ -562,23 +562,23 @@ Error: Signature mismatch:
module B :
sig
module C :
functor (X : sig end) (Y : sig end)
functor (X : sig end) (Y : sig end)
(Z : sig
module D :
sig
module E :
sig
module F :
functor (X : sig end)
functor (X : sig end)
(Arg : sig
val two : int
val one : int
end)
-> sig end
-> sig end
end
end
end)
-> sig end
-> sig end
end
end
end
@ -590,23 +590,23 @@ Error: Signature mismatch:
module B :
sig
module C :
functor (X : sig end) (Y : sig end)
functor (X : sig end) (Y : sig end)
(Z : sig
module D :
sig
module E :
sig
module F :
functor (X : sig end)
functor (X : sig end)
(Arg : sig
val one : int
val two : int
end)
-> sig end
-> sig end
end
end
end)
-> sig end
-> sig end
end
end
end

View File

@ -8,7 +8,7 @@ end = struct
type t = int
end;;
[%%expect{|
module F : sig end -> sig type t = private int end
module F : sig end -> sig type t = private int end
|}]
module Direct = F(struct end);;
@ -20,7 +20,7 @@ module G(X : sig end) : sig
type t = F(X).t
end = F(X);;
[%%expect{|
module G : functor (X : sig end) -> sig type t = F(X).t end
module G : functor (X : sig end) -> sig type t = F(X).t end
|}]
module Indirect = G(struct end);;
@ -34,14 +34,14 @@ module Pub(_ : sig end) = struct
type t = [ `Foo of t ]
end;;
[%%expect{|
module Pub : sig end -> sig type t = [ `Foo of t ] end
module Pub : sig end -> sig type t = [ `Foo of t ] end
|}]
module Priv(_ : sig end) = struct
type t = private [ `Foo of t ]
end;;
[%%expect{|
module Priv : sig end -> sig type t = private [ `Foo of t ] end
module Priv : sig end -> sig type t = private [ `Foo of t ] end
|}]
module DirectPub = Pub(struct end);;
@ -58,14 +58,14 @@ module H(X : sig end) : sig
type t = Pub(X).t
end = Pub(X);;
[%%expect{|
module H : functor (X : sig end) -> sig type t = Pub(X).t end
module H : functor (X : sig end) -> sig type t = Pub(X).t end
|}]
module I(X : sig end) : sig
type t = Priv(X).t
end = Priv(X);;
[%%expect{|
module I : functor (X : sig end) -> sig type t = Priv(X).t end
module I : functor (X : sig end) -> sig type t = Priv(X).t end
|}]
module IndirectPub = H(struct end);;
@ -121,14 +121,14 @@ module Priv(_ : sig end) = struct
end;;
[%%expect{|
module Priv :
sig end -> sig type t = private [ `Bar of int | `Foo of t -> int ] end
sig end -> sig type t = private [ `Bar of int | `Foo of t -> int ] end
|}]
module I(X : sig end) : sig
type t = Priv(X).t
end = Priv(X);;
[%%expect{|
module I : functor (X : sig end) -> sig type t = Priv(X).t end
module I : functor (X : sig end) -> sig type t = Priv(X).t end
|}]
module IndirectPriv = I(struct end);;

View File

@ -12,7 +12,7 @@ module Good (X : S with type t := unit) = struct
end;;
[%%expect{|
module type S = sig type t val x : t end
module Good : functor (X : sig val x : unit end) -> sig end
module Good : functor (X : sig val x : unit end) -> sig end
|}];;
module type T = sig module M : S end;;
@ -23,6 +23,5 @@ end;;
[%%expect{|
module type T = sig module M : S end
module Bad :
functor (X : sig module M : sig type t = unit val x : t end end) ->
sig end
functor (X : sig module M : sig type t = unit val x : t end end) -> sig end
|}];;

View File

@ -5,7 +5,7 @@
module F (X : sig end) = struct type t = int end;;
type t = F(Does_not_exist).t;;
[%%expect{|
module F : functor (X : sig end) -> sig type t = int end
module F : functor (X : sig end) -> sig type t = int end
Line 2, characters 9-28:
2 | type t = F(Does_not_exist).t;;
^^^^^^^^^^^^^^^^^^^

View File

@ -37,5 +37,5 @@ module A : sig end = struct
let _ = (N.x = M.x)
end;;
[%%expect{|
module A : sig end
module A : sig end
|}]

View File

@ -122,7 +122,7 @@ module M = struct end;;
type t = F(M).t;;
[%%expect{|
module F : functor () -> sig type t end
module M : sig end
module M : sig end
Line 3, characters 9-15:
3 | type t = F(M).t;;
^^^^^^
@ -139,7 +139,7 @@ module Fix2 :
functor (F : T -> T) ->
sig
module rec Fixed : sig type t = F(Fixed).t end
module R : functor (X : sig end) -> sig type t = Fixed.t end
module R : functor (X : sig end) -> sig type t = Fixed.t end
end
Line 5, characters 11-26:
5 | let f (x : Fix2(Id).R(M).t) = x;;

View File

@ -19,7 +19,7 @@ end;;
[%%expect{|
module Termsig :
sig
module Term0 : sig module type S = sig module Id : sig end end end
module Term0 : sig module type S = sig module Id : sig end end end
module Term :
sig module type S = sig module Term0 : Term0.S module T = Term0 end end
end
@ -36,9 +36,9 @@ module Make1 :
functor
(T' : sig
module Term0 : Termsig.Term0.S
module T : sig module Id : sig end end
module T : sig module Id : sig end end
end)
-> sig module T : sig module Id : sig end val u : int end end
-> sig module T : sig module Id : sig end val u : int end end
|}]
module Make2 (T' : Termsig.Term.S) = struct
@ -53,11 +53,11 @@ module Make2 :
functor
(T' : sig
module Term0 : Termsig.Term0.S
module T : sig module Id : sig end end
module T : sig module Id : sig end end
end)
->
sig
module T : sig module Id : sig end module Id2 = Id val u : int end
module T : sig module Id : sig end module Id2 = Id val u : int end
end
|}]
@ -74,11 +74,11 @@ module Make3 :
functor
(T' : sig
module Term0 : Termsig.Term0.S
module T : sig module Id : sig end end
module T : sig module Id : sig end end
end)
->
sig
module T : sig module Id : sig end module Id2 = Id val u : int end
module T : sig module Id : sig end module Id2 = Id val u : int end
end
|}]
@ -94,14 +94,14 @@ module Make1 (T' : S) = struct
end;;
[%%expect{|
module type S =
sig module Term0 : sig module Id : sig end end module T = Term0 end
sig module Term0 : sig module Id : sig end end module T = Term0 end
module Make1 :
functor
(T' : sig
module Term0 : sig module Id : sig end end
module T : sig module Id : sig end end
module Term0 : sig module Id : sig end end
module T : sig module Id : sig end end
end)
-> sig module Id : sig end module Id2 = Id end
-> sig module Id : sig end module Id2 = Id end
|}]
module Make2 (T' : S) : sig module Id : sig end module Id2 = Id end
@ -117,7 +117,7 @@ Lines 2-5, characters 57-3:
5 | end..
Error: Signature mismatch:
Modules do not match:
sig module Id : sig end module Id2 = Id end
sig module Id : sig end module Id2 = Id end
is not included in
sig module Id2 = T'.Term0.Id end
In module Id2:
@ -136,12 +136,12 @@ end;;
module Make3 :
functor
(T' : sig
module Term0 : sig module Id : sig end end
module T : sig module Id : sig end end
module Term0 : sig module Id : sig end end
module T : sig module Id : sig end end
end)
->
sig
module T : sig module Id : sig end module Id2 = Id val u : int end
module T : sig module Id : sig end module Id2 = Id val u : int end
end
|}]
@ -150,7 +150,7 @@ module M = Make1 (struct module Term0 =
struct module Id = struct let x = "a" end end module T = Term0 end);;
M.Id.x;;
[%%expect{|
module M : sig module Id : sig end module Id2 = Id end
module M : sig module Id : sig end module Id2 = Id end
Line 3, characters 0-6:
3 | M.Id.x;;
^^^^^^
@ -180,28 +180,28 @@ end;;
module M = Make1(IS);;
[%%expect{|
module MkT : functor (X : sig end) -> sig type t end
module MkT : functor (X : sig end) -> sig type t end
module type S =
sig
module Term0 : sig module Id : sig end end
module Term0 : sig module Id : sig end end
module T = Term0
type t = MkT(T).t
end
module Make1 :
functor
(T' : sig
module Term0 : sig module Id : sig end end
module T : sig module Id : sig end end
module Term0 : sig module Id : sig end end
module T : sig module Id : sig end end
type t = MkT(T).t
end)
-> sig module Id : sig end module Id2 = Id type t = T'.t end
-> sig module Id : sig end module Id2 = Id type t = T'.t end
module IS :
sig
module Term0 : sig module Id : sig val x : string end end
module T = Term0
type t = MkT(T).t
end
module M : sig module Id : sig end module Id2 = Id type t = IS.t end
module M : sig module Id : sig end module Id2 = Id type t = IS.t end
|}]

View File

@ -44,5 +44,5 @@ module type C
module type D
module type E
module type F
module Test : functor (X : (A -> (B -> C) -> D) -> E -> F) -> sig end
module Test : functor (X : (A -> (B -> C) -> D) -> E -> F) -> sig end
|}]

View File

@ -48,7 +48,7 @@ end = struct
end;;
[%%expect{|
module F :
functor (X : sig end) ->
functor (X : sig end) ->
sig
type s = private [ `Bar of 'a | `Foo ] as 'a
val from : M.t -> s

View File

@ -728,7 +728,7 @@ val x : '_weak2 list ref = {contents = []}
module F(X : sig end) =
struct type t = int let _ = (x : < m : t> list ref) end;;
[%%expect{|
module F : functor (X : sig end) -> sig type t = int end
module F : functor (X : sig end) -> sig type t = int end
|}];;
x;;
[%%expect{|

View File

@ -4,7 +4,7 @@
module type S = sig module M : sig end module N = M end;;
[%%expect{|
module type S = sig module M : sig end module N = M end
module type S = sig module M : sig end module N = M end
|}];;
module rec M : S with module M := M = M;;

View File

@ -88,7 +88,7 @@ module type AcceptAnd = sig
and u := int * int
end;;
[%%expect{|
module type AcceptAnd = sig end
module type AcceptAnd = sig end
|}]
module type RejectAnd = sig

View File

@ -122,7 +122,7 @@ module type S' = sig val f : M.exp -> M.arg end
module type S = sig type 'a t end with type 'a t := unit
[%%expect {|
module type S = sig end
module type S = sig end
|}]
module type S = sig
@ -336,7 +336,7 @@ Lines 2-5, characters 17-25:
5 | end with type M2.t := int
Error: This `with' constraint on M2.t makes the applicative functor
type Id(M2).t ill-typed in the constrained signature:
Modules do not match: sig end is not included in sig type t end
Modules do not match: sig end is not included in sig type t end
The type `t' is required but not provided
|}]
@ -356,7 +356,7 @@ module type S = sig
end with module M.N := A
[%%expect {|
module A : sig module P : sig type t val x : int end end
module type S = sig module M : sig end type t = A.P.t end
module type S = sig module M : sig end type t = A.P.t end
|}]
(* Same as for types, not all substitutions are accepted *)

View File

@ -15,7 +15,7 @@ Line 3, characters 2-8:
3 | open M (* unused open *)
^^^^^^
Warning 33: unused open M.
module T1 : sig end
module T1 : sig end
|}]
@ -47,7 +47,7 @@ Line 2, characters 12-13:
2 | type t0 = A (* unused type and constructor *)
^
Warning 37: unused constructor A.
module T3 : sig end
module T3 : sig end
|}]
module T4 : sig end = struct
@ -69,7 +69,7 @@ Line 4, characters 2-8:
4 | open M (* unused open; no shadowing (A below refers to the one in t0) *)
^^^^^^
Warning 33: unused open M.
module T4 : sig end
module T4 : sig end
|}]
module T5 : sig end = struct
@ -91,7 +91,7 @@ Line 2, characters 12-13:
2 | type t0 = A (* unused type and constructor *)
^
Warning 37: unused constructor A.
module T5 : sig end
module T5 : sig end
|}]
@ -108,7 +108,7 @@ Line 3, characters 2-9:
3 | open! M (* unused open *)
^^^^^^^
Warning 66: unused open! M.
module T1_bis : sig end
module T1_bis : sig end
|}]
module T2_bis : sig type s end = struct
@ -135,7 +135,7 @@ Line 2, characters 12-13:
2 | type t0 = A (* unused type and constructor *)
^
Warning 37: unused constructor A.
module T3_bis : sig end
module T3_bis : sig end
|}]
module T4_bis : sig end = struct
@ -157,7 +157,7 @@ Line 4, characters 2-9:
4 | open! M (* unused open; no shadowing (A below refers to the one in t0) *)
^^^^^^^
Warning 66: unused open! M.
module T4_bis : sig end
module T4_bis : sig end
|}]
module T5_bis : sig end = struct
@ -175,5 +175,5 @@ Line 2, characters 12-13:
2 | type t0 = A (* unused type and constructor *)
^
Warning 37: unused constructor A.
module T5_bis : sig end
module T5_bis : sig end
|}]

View File

@ -17,7 +17,7 @@ Line 2, characters 10-11:
2 | let _f ~x (* x unused argument *) = function
^
Warning 27: unused variable x.
module X1 : sig end
module X1 : sig end
|}]
module X2 : sig end = struct
@ -30,7 +30,7 @@ Line 2, characters 6-7:
2 | let x = 42 (* unused value *)
^
Warning 32: unused value x.
module X2 : sig end
module X2 : sig end
|}]
module X3 : sig end = struct
@ -49,5 +49,5 @@ Line 3, characters 2-8:
3 | open O (* unused open *)
^^^^^^
Warning 33: unused open O.
module X3 : sig end
module X3 : sig end
|}]

View File

@ -24,7 +24,7 @@ Line 2, characters 2-8:
2 | open A
^^^^^^
Warning 33: unused open A.
module rec C : sig end
module rec C : sig end
|}]
module rec D : sig
@ -46,5 +46,5 @@ Line 4, characters 6-12:
4 | open A
^^^^^^
Warning 33: unused open A.
module rec D : sig module M : sig module X : sig end end end
module rec D : sig module M : sig module X : sig end end end
|}]

View File

@ -13,7 +13,7 @@ Line 3, characters 2-19:
3 | type unused = int
^^^^^^^^^^^^^^^^^
Warning 34: unused type unused.
module Unused : sig end
module Unused : sig end
|}]
module Unused_nonrec : sig
@ -27,7 +27,7 @@ Line 4, characters 2-27:
4 | type nonrec unused = used
^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 34: unused type unused.
module Unused_nonrec : sig end
module Unused_nonrec : sig end
|}]
module Unused_rec : sig
@ -44,7 +44,7 @@ Line 3, characters 16-27:
3 | type unused = A of unused
^^^^^^^^^^^
Warning 37: unused constructor A.
module Unused_rec : sig end
module Unused_rec : sig end
|}]
module Used_constructor : sig
@ -178,7 +178,7 @@ Line 3, characters 2-26:
3 | exception Nobody_uses_me
^^^^^^^^^^^^^^^^^^^^^^^^
Warning 38: unused exception Nobody_uses_me
module Unused_exception : sig end
module Unused_exception : sig end
|}]
module Unused_extension_constructor : sig
@ -319,7 +319,7 @@ end = struct
sig type t = private [> `Foo | `Bar] include S with type t := t end
end;;
[%%expect {|
module Pr7438 : sig end
module Pr7438 : sig end
|}]
module Unused_type_disable_warning : sig
@ -331,7 +331,7 @@ Line 3, characters 11-12:
3 | type t = A [@@warning "-34"]
^
Warning 37: unused constructor A.
module Unused_type_disable_warning : sig end
module Unused_type_disable_warning : sig end
|}]
module Unused_constructor_disable_warning : sig
@ -343,5 +343,5 @@ Line 3, characters 2-30:
3 | type t = A [@@warning "-37"]
^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 34: unused type t.
module Unused_constructor_disable_warning : sig end
module Unused_constructor_disable_warning : sig end
|}]

View File

@ -493,7 +493,11 @@ and print_simple_out_module_type ppf =
| Omty_functor _ as t -> fprintf ppf "(%a)" print_out_module_type t
| Omty_ident id -> fprintf ppf "%a" print_ident id
| Omty_signature sg ->
fprintf ppf "@[<hv 2>sig@ %a@;<1 -2>end@]" !out_signature sg
begin match sg with
| [] -> fprintf ppf "sig end"
| sg ->
fprintf ppf "@[<hv 2>sig@ %a@;<1 -2>end@]" print_out_signature sg
end
| Omty_alias id -> fprintf ppf "(module %a)" print_ident id
and print_out_signature ppf =
function