Skip to content

Commit

Permalink
error reporting
Browse files Browse the repository at this point in the history
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@10458 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
  • Loading branch information
Jacques Garrigue committed May 24, 2010
1 parent 9209d55 commit bcb5a6b
Show file tree
Hide file tree
Showing 4 changed files with 5 additions and 5 deletions.
4 changes: 2 additions & 2 deletions testsuite/tests/typing-private/private.ml.reference
Original file line number Diff line number Diff line change
Expand Up @@ -78,8 +78,8 @@
type t = M.t = T of int
val mk : int -> t
end = M;;
Error: The variant or record definition does not match that of type
M.t
Error: 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' :
Expand Down
2 changes: 1 addition & 1 deletion typing/includecore.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion typing/includemod.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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"
Expand Down
2 changes: 1 addition & 1 deletion typing/typedecl.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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")
Expand Down

0 comments on commit bcb5a6b

Please sign in to comment.