Skip to content

Commit bfccd68

Browse files
committed
Protocol to allow ppx processors to report warnings to the compiler (reported as warning 22).
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14762 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
1 parent bdeeab6 commit bfccd68

File tree

9 files changed

+59
-8
lines changed

9 files changed

+59
-8
lines changed

parsing/ast_mapper.ml

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -618,6 +618,10 @@ let rec extension_of_error {loc; msg; if_highlight; sub} =
618618
Str.eval (Exp.constant (Asttypes.Const_string (if_highlight, None)))] @
619619
(List.map (fun ext -> Str.extension (extension_of_error ext)) sub))
620620

621+
let attribute_of_warning loc s =
622+
{ loc; txt = "ocaml.ppwarning" },
623+
PStr ([Str.eval ~loc (Exp.constant (Asttypes.Const_string (s, None)))])
624+
621625
let apply ~source ~target mapper =
622626
let ic = open_in_bin source in
623627
let magic =

parsing/ast_mapper.mli

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -115,3 +115,8 @@ val extension_of_error: Location.error -> extension
115115
(** Encode an error into an 'ocaml.error' extension node which can be
116116
inserted in a generated Parsetree. The compiler will be
117117
responsible for reporting the error. *)
118+
119+
val attribute_of_warning: Location.t -> string -> attribute
120+
(** Encode a warning message into an 'ocaml.ppwarning' attribute which can be
121+
inserted in a generated Parsetree. The compiler will be
122+
responsible for reporting the warning. *)

parsing/location.ml

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -367,3 +367,13 @@ let report_exception ppf exn =
367367
match error_of_exn exn with
368368
| Some err -> fprintf ppf "@[%a@]@." report_error err
369369
| None -> raise exn
370+
371+
372+
exception Error of error
373+
374+
let () =
375+
register_error_of_exn
376+
(function
377+
| Error e -> Some e
378+
| _ -> None
379+
)

parsing/location.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -89,6 +89,8 @@ type error =
8989
if_highlight: string; (* alternative message if locations are highlighted *)
9090
}
9191

92+
exception Error of error
93+
9294
val error: ?loc:t -> ?sub:error list -> ?if_highlight:string -> string -> error
9395

9496
val errorf: ?loc:t -> ?sub:error list -> ?if_highlight:string

typing/typemod.ml

Lines changed: 12 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1551,13 +1551,19 @@ let () =
15511551
Typecore.type_package := type_package;
15521552
type_module_type_of_fwd := type_module_type_of
15531553

1554+
15541555
(* Typecheck an implementation file *)
15551556

15561557
let type_implementation sourcefile outputprefix modulename initial_env ast =
15571558
Cmt_format.clear ();
15581559
try
15591560
Typecore.reset_delayed_checks ();
15601561
Env.reset_required_globals ();
1562+
begin
1563+
let map = Typetexp.emit_external_warnings in
1564+
ignore (map.Ast_mapper.structure map ast)
1565+
end;
1566+
15611567
let (str, sg, finalenv) =
15621568
type_structure initial_env ast (Location.in_file sourcefile) in
15631569
let simple_sg = simplify_signature sg in
@@ -1618,8 +1624,12 @@ let save_signature modname tsg outputprefix source_file initial_env cmi =
16181624
Cmt_format.save_cmt (outputprefix ^ ".cmti") modname
16191625
(Cmt_format.Interface tsg) (Some source_file) initial_env (Some cmi)
16201626

1621-
let type_interface env sg =
1622-
transl_signature env sg
1627+
let type_interface env ast =
1628+
begin
1629+
let map = Typetexp.emit_external_warnings in
1630+
ignore (map.Ast_mapper.signature map ast)
1631+
end;
1632+
transl_signature env ast
16231633

16241634
(* "Packaging" of several compilation units into one unit
16251635
having them as sub-modules. *)

typing/typetexp.ml

Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -99,6 +99,24 @@ let check_deprecated loc attrs s =
9999
| _ -> ())
100100
attrs
101101

102+
let emit_external_warnings =
103+
let open Ast_mapper in
104+
{
105+
default_mapper with
106+
attribute = (fun _ a ->
107+
begin match a with
108+
| {txt="ocaml.ppwarning"|"ppwarning"},
109+
PStr[{pstr_desc=Pstr_eval({pexp_desc=Pexp_constant
110+
(Const_string (s, _))},_);
111+
pstr_loc}] ->
112+
Location.prerr_warning pstr_loc (Warnings.Preprocessor s)
113+
| _ -> ()
114+
end;
115+
a
116+
)
117+
}
118+
119+
102120
let warning_scope = ref []
103121

104122
let warning_enter_scope () =

typing/typetexp.mli

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -116,4 +116,6 @@ val warning_enter_scope: unit -> unit
116116
val warning_leave_scope: unit -> unit
117117
val warning_attribute: Parsetree.attributes -> unit
118118

119-
val error_of_extension : Parsetree.extension -> Location.error
119+
val error_of_extension: Parsetree.extension -> Location.error
120+
121+
val emit_external_warnings: Ast_mapper.mapper

utils/warnings.ml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -39,7 +39,7 @@ type t =
3939
| Without_principality of string (* 19 *)
4040
| Unused_argument (* 20 *)
4141
| Nonreturning_statement (* 21 *)
42-
| Camlp4 of string (* 22 *)
42+
| Preprocessor of string (* 22 *)
4343
| Useless_record_with (* 23 *)
4444
| Bad_module_name of string (* 24 *)
4545
| All_clauses_guarded (* 25 *)
@@ -97,7 +97,7 @@ let number = function
9797
| Without_principality _ -> 19
9898
| Unused_argument -> 20
9999
| Nonreturning_statement -> 21
100-
| Camlp4 _ -> 22
100+
| Preprocessor _ -> 22
101101
| Useless_record_with -> 23
102102
| Bad_module_name _ -> 24
103103
| All_clauses_guarded -> 25
@@ -288,7 +288,7 @@ let message = function
288288
| Unused_argument -> "this argument will not be used by the function."
289289
| Nonreturning_statement ->
290290
"this statement never returns (or has an unsound type.)"
291-
| Camlp4 s -> s
291+
| Preprocessor s -> s
292292
| Useless_record_with ->
293293
"all the fields are explicitly listed in this record:\n\
294294
the 'with' clause is useless."
@@ -433,7 +433,7 @@ let descriptions =
433433
19, "Type without principality.";
434434
20, "Unused function argument.";
435435
21, "Non-returning statement.";
436-
22, "Camlp4 warning.";
436+
22, "Proprocessor warning.";
437437
23, "Useless record \"with\" clause.";
438438
24, "Bad module name: the source file name is not a valid OCaml module \
439439
name.";

utils/warnings.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,7 @@ type t =
3434
| Without_principality of string (* 19 *)
3535
| Unused_argument (* 20 *)
3636
| Nonreturning_statement (* 21 *)
37-
| Camlp4 of string (* 22 *)
37+
| Preprocessor of string (* 22 *)
3838
| Useless_record_with (* 23 *)
3939
| Bad_module_name of string (* 24 *)
4040
| All_clauses_guarded (* 25 *)

0 commit comments

Comments
 (0)