error reporting
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@10458 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
9209d550c5
commit
bcb5a6b669
|
@ -78,8 +78,8 @@
|
|||
type [4mt = M.t = T of int[m
|
||||
val mk : int -> t
|
||||
end = M;;
|
||||
[mError: The variant or record definition does not match that of type
|
||||
M.t
|
||||
[mError: This variant or record definition does not match that of type M.t
|
||||
A private type would be revealed.
|
||||
# module M5 : sig type t = M.t = private T of int val mk : int -> t end
|
||||
# module M6 : sig type t = private T of int val mk : int -> t end
|
||||
# module M' :
|
||||
|
|
|
@ -158,7 +158,7 @@ let report_type_mismatch first second decl ppf =
|
|||
List.iter
|
||||
(fun err ->
|
||||
if err = Manifest then () else
|
||||
Format.fprintf ppf "%a." (report_type_mismatch0 first second decl) err)
|
||||
Format.fprintf ppf "@ %a." (report_type_mismatch0 first second decl) err)
|
||||
|
||||
let rec compare_variants env decl1 decl2 n cstrs1 cstrs2 =
|
||||
match cstrs1, cstrs2 with
|
||||
|
|
|
@ -337,7 +337,7 @@ let include_err ppf = function
|
|||
%a@;<1 -2>is not included in@ %a@]"
|
||||
(value_description id) d1 (value_description id) d2
|
||||
| Type_declarations(id, d1, d2, errs) ->
|
||||
fprintf ppf "@[@[<hv>%s:@;<1 2>%a@ %s@;<1 2>%a@]@ %a@]"
|
||||
fprintf ppf "@[@[<hv>%s:@;<1 2>%a@ %s@;<1 2>%a@]%a@]"
|
||||
"Type declarations do not match"
|
||||
(type_declaration id) d1
|
||||
"is not included in"
|
||||
|
|
|
@ -902,7 +902,7 @@ let report_error ppf = function
|
|||
fprintf ppf "The type abbreviation %s is cyclic" s
|
||||
| Definition_mismatch (ty, errs) ->
|
||||
Printtyp.reset_and_mark_loops ty;
|
||||
fprintf ppf "@[<v>@[<hov>%s@ %s@;<1 2>%a@]@ %a@]"
|
||||
fprintf ppf "@[<v>@[<hov>%s@ %s@;<1 2>%a@]%a@]"
|
||||
"This variant or record definition" "does not match that of type"
|
||||
Printtyp.type_expr ty
|
||||
(Includecore.report_type_mismatch "the original" "this" "definition")
|
||||
|
|
Loading…
Reference in New Issue