Skip to content

Commit

Permalink
typing: fix a try_expand_once forgotten from ocaml#10170
Browse files Browse the repository at this point in the history
On OCaml versions 5.1 and older, this caused a Ctype.Escape(_)
uncaught exception on the included test case.

Reported-by: Neven Villani <vanille@crans.org>
  • Loading branch information
gasche committed Feb 12, 2024
1 parent ef62c57 commit 652b0dd
Show file tree
Hide file tree
Showing 3 changed files with 37 additions and 1 deletion.
9 changes: 9 additions & 0 deletions testsuite/tests/typing-misc-bugs/pr12971.compilers.reference
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
type 'a t = T of 'a
module Seq :
sig
type 'a t = unit -> 'a node
and 'a node
val empty : 'a t
val cons : 'a -> 'a t -> 'a t
end
val to_seq : ('a Seq.t as 'a) Seq.t t -> 'a Seq.t Seq.t
27 changes: 27 additions & 0 deletions testsuite/tests/typing-misc-bugs/pr12971.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,27 @@
(* TEST_BELOW *)
type 'a t = T of 'a

module Seq : sig
type 'a t = unit -> 'a node
and 'a node

val empty : 'a t
val cons : 'a -> 'a t -> 'a t
end = struct
type 'a t = unit -> 'a node
and 'a node = unit

let empty () = ()
let cons x xs () = ()
end

let to_seq (xt : 'a t) : 'a Seq.t =
let T x = xt in
Seq.cons Seq.empty x

(* TEST
ocamlc_flags = "-i";
setup-ocamlc.byte-build-env;
ocamlc.byte;
check-ocamlc.byte-output;
*)
2 changes: 1 addition & 1 deletion typing/ctype.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1841,7 +1841,7 @@ let rec occur_rec env allow_recursive visited ty0 ty =
let visited = TypeSet.add ty visited in
iter_type_expr (occur_rec env allow_recursive visited ty0) ty
with Occur -> try
let ty' = try_expand_head try_expand_once env ty in
let ty' = try_expand_head try_expand_safe env ty in
(* This call used to be inlined, but there seems no reason for it.
Message was referring to change in rev. 1.58 of the CVS repo. *)
occur_rec env allow_recursive visited ty0 ty'
Expand Down

0 comments on commit 652b0dd

Please sign in to comment.