# * * * # type 'a t = { t : 'a; } # type 'a fold = { fold : 'b. f:('b -> 'a -> 'b) -> init:'b -> 'b; } # val f : 'a list -> 'a fold = # - : int = 6 # class ['b] ilist : 'b list -> object ('c) val l : 'b list method add : 'b -> 'c method fold : f:('a -> 'b -> 'a) -> init:'a -> 'a end # class virtual ['a] vlist : object ('c) method virtual add : 'a -> 'c method virtual fold : f:('b -> 'a -> 'b) -> init:'b -> 'b end # class ilist2 : int list -> object ('a) val l : int list method add : int -> 'a method fold : f:('b -> int -> 'b) -> init:'b -> 'b end # val ilist2 : 'a list -> 'a vlist = # class ['a] ilist3 : 'a list -> object ('c) val l : 'a list method add : 'a -> 'c method fold : f:('b -> 'a -> 'b) -> init:'b -> 'b end # class ['a] ilist4 : 'a list -> object ('c) val l : 'a list method add : 'a -> 'c method fold : f:('b -> 'a -> 'b) -> init:'b -> 'b end # class ['a] ilist5 : 'a list -> object ('c) val l : 'a list method add : 'a -> 'c method fold : f:('b -> 'a -> 'b) -> init:'b -> 'b method fold2 : f:('b -> 'a -> 'b) -> init:'b -> 'b end # class ['a] ilist6 : 'a list -> object ('c) val l : 'a list method add : 'a -> 'c method fold : f:('b -> 'a -> 'b) -> init:'b -> 'b method fold2 : f:('b -> 'a -> 'b) -> init:'b -> 'b end # class virtual ['a] olist : object method virtual fold : f:('a -> 'c -> 'c) -> init:'c -> 'c end # class ['a] onil : object method fold : f:('a -> 'c -> 'c) -> init:'c -> 'c end # class ['a] ocons : hd:'a -> tl:'a olist -> object val hd : 'a val tl : 'a olist method fold : f:('a -> 'c -> 'c) -> init:'c -> 'c end # class ['a] ostream : hd:'a -> tl:'a ostream -> object val hd : 'a val tl : < empty : bool; fold : 'c. f:('a -> 'c -> 'c) -> init:'c -> 'c > method empty : bool method fold : f:('a -> 'c -> 'c) -> init:'c -> 'c end # class ['a] ostream1 : hd:'a -> tl:'b -> object ('b) val hd : 'a val tl : 'b method fold : f:('a -> 'c -> 'c) -> init:'c -> 'c method hd : 'a method tl : 'b end # class vari : object method m : [< `A | `B | `C ] -> int end # class vari : object method m : [< `A | `B | `C ] -> int end # module V : sig type v = [ `A | `B | `C ] val m : [< v ] -> int end # class varj : object method m : [< V.v ] -> int end # module type T = sig class vari : object method m : [< `A | `B | `C ] -> int end end # module M0 : sig class vari : object method m : [< `A | `B | `C ] -> int end end # module M : T # val v : M.vari = # - : int = 1 # class point : x:int -> y:int -> object val x : int val y : int method x : int method y : int end # class color_point : x:int -> y:int -> color:string -> object val color : string val x : int val y : int method color : string method x : int method y : int end # class circle : #point -> r:int -> object val p : point val r : int method distance : #point -> float end # val p0 : point = val p1 : point = val cp : color_point = val c : circle = val d : float = 11. # val f : < m : 'a. 'a -> 'a > -> < m : 'b. 'b -> 'b > = # Characters 41-42: let f (x : < m : 'a. 'a -> 'a list >) = (x : < m : 'b. 'b -> 'c >) ^ Error: This expression has type < m : 'b. 'b -> 'b list > but an expression was expected of type < m : 'b. 'b -> 'c > The universal variable 'b would escape its scope # class id : object method id : 'a -> 'a end # class type id_spec = object method id : 'a -> 'a end # class id_impl : object method id : 'a -> 'a end # class a : object method m : bool end and b : object method id : 'a -> 'a end # Characters 72-77: method id x = x ^^^^^ Error: This method has type 'a -> 'a which is less general than 'b. 'b -> 'a # Characters 75-80: method id x = x ^^^^^ Error: This method has type 'a -> 'a which is less general than 'b. 'b -> 'a # Characters 80-85: method id _ = x ^^^^^ Error: This method has type 'b -> 'b which is less general than 'a. 'a -> 'a # Characters 92-159: ............x = match r with None -> r <- Some x; x | Some y -> y Error: This method has type 'b -> 'b which is less general than 'a. 'a -> 'a # class c : object method m : 'a -> 'b -> 'a end # val f1 : id -> int * bool = # val f2 : id -> int * bool = # Characters 24-28: let f3 f = f#id 1, f#id true ^^^^ Error: This expression has type bool but an expression was expected of type int # val f4 : id -> int * bool = # class c : object method m : #id -> int * bool end # class id2 : object method id : 'a -> 'a method mono : int -> int end # val app : int * bool = (1, true) # Characters 4-25: type 'a foo = 'a foo list ^^^^^^^^^^^^^^^^^^^^^ Error: The type abbreviation foo is cyclic # class ['a] bar : 'a -> object end # type 'a foo = 'a foo bar # - : (< m : 'a. 'a * 'b > as 'b) -> 'c * 'b = # - : (< m : 'a. 'b * 'a list > as 'b) -> 'b * 'c list = # val f : (< m : 'b. 'a * (< n : 'b; .. > as 'b) > as 'a) -> 'a * (< n : 'c; .. > as 'c) = # - : (< p : 'b. < m : 'b; n : 'a; .. > as 'b > as 'a) -> (< m : 'c; n : 'a; .. > as 'c) = # - : (< m : 'a. 'a * < p : 'b. 'b * 'd * 'c > as 'd > as 'c) -> ('f * < p : 'b. 'b * 'e * 'c > as 'e) = # - : < m : 'a. < p : 'a; .. > as 'b > -> 'b = # type sum = T of < id : 'a. 'a -> 'a > # - : sum -> 'a -> 'a = # type record = { r : < id : 'a. 'a -> 'a >; } # - : record -> 'a -> 'a = # - : record -> 'a -> 'a = # class myself : object ('b) method self : 'a -> 'b end # class number : object ('b) val num : int method num : int method prev : 'b method succ : 'b method switch : zero:(unit -> 'a) -> prev:('b -> 'a) -> 'a end # val id : 'a -> 'a = # class c : object method id : 'a -> 'a end # class c' : object method id : 'a -> 'a end # class d : object val mutable count : int method count : int method id : 'a -> 'a method old : 'a -> 'a end # class ['a] olist : 'a list -> object ('c) val l : 'a list method cons : 'a -> 'c method fold : f:('a -> 'b -> 'b) -> init:'b -> 'b end # val sum : int #olist -> int = # val count : 'a #olist -> int = # val append : 'a #olist -> ('a #olist as 'b) -> 'b = # type 'a t = unit # class o : object method x : [> `A ] t -> unit end # class c : object method m : d end and d : ?x:int -> unit -> object end # class d : ?x:int -> unit -> object end and c : object method m : d end # class type numeral = object method fold : ('a -> 'a) -> 'a -> 'a end class zero : object method fold : ('a -> 'a) -> 'a -> 'a end class next : #numeral -> object method fold : ('a -> 'a) -> 'a -> 'a end # class type node_type = object method as_variant : [> `Node of node_type ] end # class node : node_type # class node : object method as_variant : [> `Node of node_type ] end # type bad = { bad : 'a. 'a option ref; } # Characters 17-25: let bad = {bad = ref None};; ^^^^^^^^ Error: This field value has type 'b option ref which is less general than 'a. 'a option ref # type bad2 = { mutable bad2 : 'a. 'a option ref option; } # val bad2 : bad2 = {bad2 = None} # Characters 13-28: bad2.bad2 <- Some (ref None);; ^^^^^^^^^^^^^^^ Error: This field value has type 'b option ref option which is less general than 'a. 'a option ref option # val f : < m : 'a. < p : 'a * 'c > as 'c > -> 'b -> unit = # val f : < m : 'a. 'a * (< p : int * 'b > as 'b) > -> 'b -> unit = # type 'a t = [ `A of 'a ] # class c : object method m : ([> 'a t ] as 'a) -> unit end # class c : object method m : ([> 'a t ] as 'a) -> unit end # class c : object method m : ([> 'a t ] as 'a) -> 'a end # class c : object method m : ([> `A ] as 'a) option -> 'a end # Characters 145-166: object method virtual visit : 'a.('a visitor -> 'a) end;; ^^^^^^^^^^^^^^^^^^^^^ Error: The universal type variable 'a cannot be generalized: it escapes its scope. # type ('a, 'b) list_visitor = < caseCons : 'b -> 'b list -> 'a; caseNil : 'a > type 'b alist = < visit : 'a. ('a, 'b) list_visitor -> 'a > class type ct = object ('a) method fold : ('b -> 'a -> 'b) -> 'b -> 'b end type t = { f : 'a 'b. ('b -> (#ct as 'a) -> 'b) -> 'b; } # Characters 20-25: type t = u and u = t;; ^^^^^ Error: The type abbreviation t is cyclic # class ['a] a : object constraint 'a = [> `A of 'a a ] end type t = [ `A of t a ] # Characters 71-80: type ('a,'b) t constraint 'a = 'b and ('a,'b) u = ('a,'b) t;; ^^^^^^^^^ Error: Constraints are not satisfied in this type. Type ('a, 'b) t should be an instance of ('c, 'c) t # type 'a t = 'a and u = int t # type 'a t constraint 'a = int # Characters 26-32: type 'a u = 'a and 'a v = 'a u t;; ^^^^^^ Error: Constraints are not satisfied in this type. Type 'a u t should be an instance of int t # type 'a u = 'a constraint 'a = int and 'a v = 'a u t constraint 'a = int # type g = int # type 'a t = unit constraint 'a = g # Characters 26-32: type 'a u = 'a and 'a v = 'a u t;; ^^^^^^ Error: Constraints are not satisfied in this type. Type 'a u t should be an instance of g t # type 'a u = 'a constraint 'a = g and 'a v = 'a u t constraint 'a = g # Characters 38-58: type 'a u = < m : 'a v > and 'a v = 'a list u;; ^^^^^^^^^^^^^^^^^^^^ Error: In the definition of v, type 'a list u should be 'a u # type 'a t = 'a type 'a u = A of 'a t # type 'a t = < a : 'a > # - : ('a t as 'a) -> 'a t = # type u = 'a t as 'a # type t = A | B # - : [> `A ] * t -> int = # - : [> `A ] * t -> int = # - : [> `A ] option * t -> int = # - : [> `A ] option * t -> int = # - : t * [< `A | `B ] -> int = # - : [< `A | `B ] * t -> int = # Characters 0-41: function (`A|`B), _ -> 0 | _,(`A|`B) -> 1;; ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Warning 8: this pattern-matching is not exhaustive. Here is an example of a value that is not matched: (`AnyExtraTag, `AnyExtraTag) - : [> `A | `B ] * [> `A | `B ] -> int = # Characters 0-29: function `B,1 -> 1 | _,1 -> 2;; ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Warning 8: this pattern-matching is not exhaustive. Here is an example of a value that is not matched: (_, 0) Characters 21-24: function `B,1 -> 1 | _,1 -> 2;; ^^^ Warning 11: this match case is unused. - : [< `B ] * int -> int = # Characters 0-29: function 1,`B -> 1 | 1,_ -> 2;; ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Warning 8: this pattern-matching is not exhaustive. Here is an example of a value that is not matched: (0, _) Characters 21-24: function 1,`B -> 1 | 1,_ -> 2;; ^^^ Warning 11: this match case is unused. - : int * [< `B ] -> int = # Characters 69-135: type ('a, 'b) a = 'a -> unit constraint 'a = [> `B of ('a, 'b) b as 'b] ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Error: Constraints are not satisfied in this type. Type ([> `B of 'a ], 'a) b as 'a should be an instance of (('b, [> `A of 'b ] as 'c) a as 'b, 'c) b # * class type ['a, 'b] a = object constraint 'a = < as_a : ('a, 'b) a as 'c; b : 'b; .. > constraint 'b = < a : 'a; as_b : ('a, 'b) b; .. > method as_a : 'c method b : 'b end and ['a, 'b] b = object constraint 'a = < as_a : ('a, 'b) a; b : 'b; .. > constraint 'b = < a : 'a; as_b : ('a, 'b) b; .. > method a : 'a method as_b : ('a, 'b) b end class type ['a] ca = object ('b) constraint 'a = < a : 'b; as_b : ('b, 'a) b; .. > method as_a : ('b, 'a) a method b : 'a end class type ['a] cb = object ('b) constraint 'a = < as_a : ('a, 'b) a; b : 'b; .. > method a : 'a method as_b : ('a, 'b) b end type bt = 'a ca cb as 'a # class c : object method m : int end # val f : unit -> c = # val f : unit -> c = # Characters 11-60: let f () = object method private n = 1 method m = {<>}#n end;; ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Warning 15: the following private methods were made public implicitly: n. val f : unit -> < m : int; n : int > = # Characters 11-56: let f () = object (self:c) method n = 1 method m = 2 end;; ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Error: This object is expected to have type c but actually has type < m : int; n : 'a > The first object type has no method n # Characters 11-69: let f () = object (_:'s) constraint 's = < n : int > method m = 1 end;; ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Error: This object is expected to have type < n : int > but actually has type < m : 'a > The second object type has no method n # Characters 66-124: object (self: 's) method x = 3 method private m = self end ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Error: This object is expected to have type < x : int; .. > but actually has type < x : int > Self type cannot be unified with a closed object type # val o : < x : int > = # Characters 76-77: (x : > as 'bar) >);; ^ Error: This expression has type < m : 'a. 'a * < m : 'a * 'b > > as 'b but an expression was expected of type < m : 'a. 'a * (< m : 'a * < m : 'c. 'c * 'd > > as 'd) > Types for method m are incompatible # Characters 176-177: let f (x : foo') = (x : bar');; ^ Error: This expression has type foo' = < m : 'a. 'a * 'a foo > but an expression was expected of type bar' = < m : 'a. 'a * 'a bar > Type 'a foo = < m : 'a * 'a foo > is not compatible with type 'a bar = < m : 'a * < m : 'c. 'c * 'a bar > > Type 'a foo = < m : 'a * 'a foo > is not compatible with type < m : 'c. 'c * 'a bar > Types for method m are incompatible # Characters 67-68: (x : )> as 'bar);; ^ Error: This expression has type < m : 'b. 'b * ('b * < m : 'c. 'c * 'a > as 'a) > but an expression was expected of type < m : 'b. 'b * ('b * < m : 'c. 'c * ('c * 'd) >) > as 'd Types for method m are incompatible # Characters 66-67: (x : )> as 'bar);; ^ Error: This expression has type < m : 'b. 'b * ('b * < m : 'c. 'c * 'a > as 'a) > but an expression was expected of type < m : 'b. 'b * ('b * < m : 'c. 'c * ('b * 'd) >) > as 'd Types for method m are incompatible # Characters 51-52: (x : as 'bar)>);; ^ Error: This expression has type < m : 'b. 'b * ('b * 'a) > as 'a but an expression was expected of type < m : 'b. 'b * ('b * < m : 'c. 'c * 'd > as 'd) > Types for method m are incompatible # Characters 14-115: ....(x : ('a * 'bar> as 'bar)> :> ('a * 'foo)> as 'foo).. Error: Type < m : 'a. 'a -> ('a * (< m : 'c. 'c -> 'b as 'e > as 'd) as 'b) > is not a subtype of < m : 'a. 'a -> ('a * 'f as 'h) as 'g > as 'f Type 'c. 'e is not a subtype of 'a. 'g # Characters 88-150: = struct let f (x : as 'foo) = () end;; ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Error: Signature mismatch: ... Values do not match: val f : (< m : 'a. 'a * ('a * 'b) > as 'b) -> unit is not included in val f : < m : 'b. 'b * ('b * < m : 'c. 'c * 'a > as 'a) > -> unit # Characters 78-132: = struct type t = as 'foo end;; ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Error: Signature mismatch: Modules do not match: sig type t = < m : 'a. 'a * ('a * 'b) > as 'b end is not included in sig type t = < m : 'b. 'b * ('b * < m : 'c. 'c * 'a > as 'a) > end Type declarations do not match: type t = < m : 'a. 'a * ('a * 'b) > as 'b is not included in type t = < m : 'b. 'b * ('b * < m : 'c. 'c * 'a > as 'a) > # module M : sig type 'a t type u = < m : 'a. 'a t > end # module M : sig type 'a t val f : < m : 'a. 'a t > -> int end # module M : sig type 'a t val f : < m : 'a. 'a t > -> int end # val f : (< m : 'a. 'a -> (< m : 'a. 'a -> 'c * < > > as 'c) * < .. >; .. > as 'b) -> 'b -> bool = # type t = [ `A | `B ] # type v = private [> t ] # - : t -> v = # type u = private [< t ] # - : u -> v = # Characters 9-21: fun x -> (x : v :> u);; ^^^^^^^^^^^^ Error: Type v = [> `A | `B ] is not a subtype of u = [< `A | `B ] # type v = private [< t ] # Characters 9-21: fun x -> (x : u :> v);; ^^^^^^^^^^^^ Error: Type u = [< `A | `B ] is not a subtype of v = [< `A | `B ] # type p = < x : p > # type q = private < x : p; .. > # - : q -> p = # Characters 9-21: fun x -> (x : p :> q);; ^^^^^^^^^^^^ Error: Type p = < x : p > is not a subtype of q = < x : p; .. > # Characters 14-100: ..(x : as 'a) -> int> :> as 'b) -> int>).. Error: Type < m : 'a. (< p : int; .. > as 'a) -> int > is not a subtype of < m : 'b. (< p : int; q : int; .. > as 'b) -> int > Type < p : int; q : int; .. > as 'c is not a subtype of < p : int; .. > as 'd # val f2 : < m : 'a. (< p : < a : int >; .. > as 'a) -> int > -> < m : 'b. (< p : < a : int; b : int >; .. > as 'b) -> int > = # Characters 13-107: ..(x : ;..> as 'a) -> int> :> ;..> as 'b) -> int>).. Error: Type < m : 'a. (< p : < a : int; b : int >; .. > as 'a) -> int > is not a subtype of < m : 'b. (< p : < a : int >; .. > as 'b) -> int > Type < a : int > is not a subtype of < a : int; b : int > # Characters 11-55: let f4 x = (x : ;..> :> ;..>);; ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Error: Type < p : < a : int; b : int >; .. > is not a subtype of < p : < a : int >; .. > The second object type has no method b # val f5 : < m : 'a. [< `A of < p : int > ] as 'a > -> < m : 'b. [< `A of < > ] as 'b > = # Characters 13-83: (x : ] as 'a> :> ] as 'a>);; ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Error: Type < m : 'a. [< `A of < > ] as 'a > is not a subtype of < m : 'b. [< `A of < p : int > ] as 'b > Type < > is not a subtype of < p : int > # val f : < m : 'a. 'a -> 'a > -> < m : 'a. 'a -> 'a > = # - : < m : 'a. 'a -> 'a > -> 'b -> 'b = # val f : < m : 'a. 'a -> 'a > * 'b -> < m : 'a. 'a -> 'a > = # - : < m : 'a. 'a -> 'a > -> 'b -> 'b = # val f : < m : 'a. 'a -> 'a > -> < m : 'a. 'a -> 'a > array = # - : < m : 'a. 'a -> 'a > -> 'b -> 'b = # class c : object method id : 'a -> 'a end # type u = c option # val just : 'a option -> 'a = # val f : c -> 'a -> 'a = # val g : c -> 'a -> 'a = # val h : < id : 'a; .. > -> 'a = # type 'a u = c option # val just : 'a option -> 'a = # val f : c -> 'a -> 'a = # val f : 'a -> int = val g : 'a -> int = # type 'a t = Leaf of 'a | Node of ('a * 'a) t # val depth : 'a t -> int = # Characters 34-74: function Leaf _ -> 1 | Node x -> 1 + d x ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Error: This definition has type 'a t -> int which is less general than 'a0. 'a0 t -> int # Characters 34-78: function Leaf x -> x | Node x -> 1 + depth x;; (* fails *) ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Error: This definition has type int t -> int which is less general than 'a. 'a t -> int # Characters 34-74: function Leaf x -> x | Node x -> depth x;; (* fails *) ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Error: This definition has type 'a t -> 'a which is less general than 'a0. 'a0 t -> 'a # Characters 38-78: function Leaf x -> x | Node x -> depth x;; (* fails *) ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Error: This definition has type 'b. 'b t -> 'b which is less general than 'a 'b. 'a t -> 'b # val r : 'a list * '_b list ref = ([], {contents = []}) val q : unit -> 'a list * '_b list ref = # val f : 'a -> 'a = # val zero : [> `B of 'a | `Int of int ] as 'a = `Int 0 # Characters 39-45: let zero : 'a. [< `Int of int] as 'a = `Int 0;; (* fails *) ^^^^^^ Error: This expression has type [> `Int of int ] but an expression was expected of type [< `Int of int ] Types for tag `Int are incompatible # type t = { f : 'a. [> `B of 'a | `Int of int ] as 'a; } val zero : t = {f = `Int 0} # Characters 56-62: let zero = {f = `Int 0} ;; (* fails *) ^^^^^^ Error: This expression has type [> `Int of int ] but an expression was expected of type [< `Int of int ] Types for tag `Int are incompatible # val id : 'a -> 'a = val neg : int -> bool -> int * bool = # type t = A of int | B of (int * t) list | C of (string * t) list val transf : (int -> t) -> t -> t = val transf_alist : (int -> t) -> ('a * t) list -> ('a * t) list = # type t = { f : 'a. ('a list -> int) Lazy.t; } val l : t = {f = } # type t = { f : 'a. 'a -> unit; } # - : t = {f = } # Characters 19-20: let f ?x y = y in {f};; (* fail *) ^ Error: This field value has type unit -> unit which is less general than 'a. 'a -> unit # module Polux : sig type 'par t = 'par val ident : 'a -> 'a class alias : object method alias : 'a t -> 'a end val f : < m : 'a. 'a t > -> < m : 'a. 'a > end # Exception: Pervasives.Exit. # Exception: Pervasives.Exit. # Exception: Pervasives.Exit. # Characters 20-44: type 'x t = < f : 'y. 'y t >;; ^^^^^^^^^^^^^^^^^^^^^^^^ Error: In the definition of t, type 'y t should be 'x t # val using_match : bool -> int * ('a -> 'a) = # - : ('a -> 'a) * ('b -> 'b) = (, ) # - : ('a -> 'a) * ('b -> 'b) = (, ) # val n : < m : 'x 'a. ([< `Foo of 'x ] as 'a) -> 'x > = # val n : < m : 'x. [< `Foo of 'x ] -> 'x > = # Characters 60-130: object method m : 'x. [< `Foo of 'x] -> 'x = fun x -> assert false end;; ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Error: This expression has type < m : 'x. [< `Foo of 'x ] -> 'x > but an expression was expected of type < m : 'a. [< `Foo of int ] -> 'a > The universal variable 'x would escape its scope # Characters 83-153: object method m : 'x. [< `Foo of 'x] -> 'x = fun x -> assert false end;; ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Error: This expression has type < m : 'x. [< `Foo of 'x ] -> 'x > but an expression was expected of type < m : 'a. [< `Foo of int ] -> 'a > The universal variable 'x would escape its scope # Characters 95-98: if b then x else M.A;; ^^^ Error: This expression has type M.t but an expression was expected of type 'x The type constructor M.t would escape its scope #