catch Nondep_cannot_erase exception

master
Thomas Refis 2020-08-26 15:04:47 +02:00
parent 6aad418899
commit 162df93916
2 changed files with 12 additions and 5 deletions

View File

@ -42,6 +42,10 @@ module Primitive(Linear_map : Linear_map) = struct
Linear_map.scale s x
end;;
[%%expect{|
Uncaught exception: Ctype.Nondep_cannot_erase(_)
Line 3, characters 21-22:
3 | Linear_map.scale s x
^
Error: This expression has type (module Scalar with type t = s)
but an expression was expected of type
(module Vector_space with type scalar = 'a and type t = 'b)
|}];;

View File

@ -2473,6 +2473,8 @@ let eq_package_path env p1 p2 =
let nondep_type' = ref (fun _ _ _ -> assert false)
let package_subtype = ref (fun _ _ _ _ _ _ _ -> assert false)
exception Nondep_cannot_erase of Ident.t
let rec concat_longident lid1 =
let open Longident in
function
@ -2514,7 +2516,10 @@ let complete_type_list ?(allow_absent=false) env nl1 lv2 mty2 nl2 tl2 =
match Env.find_type_by_name lid env' with
| (_, {type_arity = 0; type_kind = Type_abstract;
type_private = Public; type_manifest = Some t2}) ->
(n, nondep_instance env' lv2 id2 t2) :: complete nl ntl2
begin match nondep_instance env' lv2 id2 t2 with
| exception Nondep_cannot_erase _ -> raise Exit
| t -> (n, t) :: complete nl ntl2
end
| (_, {type_arity = 0; type_kind = Type_abstract;
type_private = Public; type_manifest = None})
when allow_absent ->
@ -4607,8 +4612,6 @@ let nondep_variants = TypeHash.create 17
let clear_hash () =
TypeHash.clear nondep_hash; TypeHash.clear nondep_variants
exception Nondep_cannot_erase of Ident.t
let rec nondep_type_rec ?(expand_private=false) env ids ty =
let expand_abbrev env t =
if expand_private then expand_abbrev_opt env t else expand_abbrev env t