Original bug ID: 7519 Reporter:@mmottl Assigned to:@garrigue Status: resolved (set by @garrigue on 2017-08-29T07:34:22Z) Resolution: fixed Priority: normal Severity: minor Version: 4.04.1 Fixed in version: 4.06.0 +dev/beta1/beta2/rc1 Category: typing Monitored by:@gasche@yallop@mmottl
Bug description
The following program is rejected by the compiler:
module Gen_spec = struct type 't extra = unit end
module type S = sig
module Spec : sig type 't extra = unit end
type t
val make : unit -> t Spec.extra
end (* S *)
module Make () : S with module Spec := Gen_spec = struct
type t = int
let make () = ()
end (* Make *)
let () =
let module M = Make () in
M.make ()
(* (M.make () : unit) *)
The error is:
File "./foo.ml", line 17, characters 2-11:
Error: This expression has type M.t Gen_spec.extra = unit
but an expression was expected of type unit
The type constructor M.t would escape its scope
The error shows that the compiler already knows that M.t Gen_spec.extra is equivalent to the unit type. Therefore, there should not be any type escaping the scope of the local module. Using the commented out last line instead of the preceding one also shows that the compiler will happily unify the type with "unit" and then accept the program.
I suppose that there is a missing conversion somewhere in the type checker that should attempt to eliminate all local types before complaining about scope violations.
The text was updated successfully, but these errors were encountered:
The interesting phenomenon here is that one needs to expand extra, not t, to avoid the escape.
This is nowhere in the logic of the compiler at this point.
This can be done, but the runtime cost could be significant (should check).
Original bug ID: 7519
Reporter: @mmottl
Assigned to: @garrigue
Status: resolved (set by @garrigue on 2017-08-29T07:34:22Z)
Resolution: fixed
Priority: normal
Severity: minor
Version: 4.04.1
Fixed in version: 4.06.0 +dev/beta1/beta2/rc1
Category: typing
Monitored by: @gasche @yallop @mmottl
Bug description
The following program is rejected by the compiler:
module Gen_spec = struct type 't extra = unit end
module type S = sig
module Spec : sig type 't extra = unit end
type t
val make : unit -> t Spec.extra
end (* S *)
module Make () : S with module Spec := Gen_spec = struct
type t = int
let make () = ()
end (* Make *)
let () =
let module M = Make () in
M.make ()
(* (M.make () : unit) *)
The error is:
File "./foo.ml", line 17, characters 2-11:
Error: This expression has type M.t Gen_spec.extra = unit
but an expression was expected of type unit
The type constructor M.t would escape its scope
The error shows that the compiler already knows that M.t Gen_spec.extra is equivalent to the unit type. Therefore, there should not be any type escaping the scope of the local module. Using the commented out last line instead of the preceding one also shows that the compiler will happily unify the type with "unit" and then accept the program.
I suppose that there is a missing conversion somewhere in the type checker that should attempt to eliminate all local types before complaining about scope violations.
The text was updated successfully, but these errors were encountered: