Skip to content

Commit

Permalink
testsuite example from Florian
Browse files Browse the repository at this point in the history
  • Loading branch information
gasche committed Dec 12, 2024
1 parent 933c422 commit 93692f9
Showing 1 changed file with 27 additions and 0 deletions.
27 changes: 27 additions & 0 deletions testsuite/tests/tool-toplevel/constructor_printing.ml
Original file line number Diff line number Diff line change
Expand Up @@ -72,3 +72,30 @@ let it = Q.Sub.A
[%%expect {|
val it : Q.Sub.t = Q.Sub.A
|}]

(* A "hellish example" from Florian Angeletti. *)
module M = struct
module N = struct
module A = struct
module B = struct
type t = X
end
end
module F(X:sig type t end) = struct type t = A of X.t end
end
end
open M open N open A open B
[%%expect {|
module M :
sig
module N :
sig
module A : sig module B : sig type t = X end end
module F : (X : sig type t end) -> sig type t = A of X.t end
end
end
|}]
let x = let module FB = F(B) in FB.A X
[%%expect {|
val x : M.N.F(M.N.A.B).t = M.N.F(M.N.A.B).A X
|}]

0 comments on commit 93692f9

Please sign in to comment.