ocamlbuild: polish the interaction between Param_tags.init() and plugin execution

Before this path, [Param_tags.init()] was run before
[Plugin.execute_plugin_if_needed()]. It had the downside of making
plugin compilation warn about any unknown parametrized tag present in
a _tags file, even those that would be defined by the plugin
itself. The fix is to [really_acknowledge] only the tags used for the
plugin compilation, and delay the full [Param_tags.init()] call to
after plugin execution.

This was discussed in detail in PR#5680, comment 0010186.

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14015 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Gabriel Scherer 2013-08-19 07:42:36 +00:00
parent 58d23575b7
commit 6929678509
6 changed files with 57 additions and 15 deletions

View File

@ -62,7 +62,8 @@ let tags_of_filename s =
let () = Hashtbl.replace cache s res in
res
let has_tag tag = Tags.mem tag (tags_of_filename "")
let global_tags () = tags_of_filename ""
let has_tag tag = Tags.mem tag (global_tags ())
let tag_file file tags =
if tags <> [] then parse_string (Printf.sprintf "%S: %s" file (String.concat ", " tags));;

View File

@ -34,3 +34,6 @@ val tag_file : Pathname.t -> Tags.elt list -> unit
(** [tag_any tag_list] Tag anything with all given tags. *)
val tag_any : Tags.elt list -> unit
(** the tags that apply to any file *)
val global_tags : unit -> Tags.t

View File

@ -169,11 +169,17 @@ let proceed () =
Ocaml_specific.init ();
Hooks.call_hook Hooks.After_rules;
Param_tags.init ();
Sys.chdir options_wd;
Plugin.execute_plugin_if_needed ();
(* [Param_tags.init ()] is called *after* the plugin is executed, as
some of the parametrized tags present in the _tags files parsed
will be declared by the plugin, and would therefore result in
"tag X does not expect a parameter" warnings if initialized
before. Note that [Plugin.rebuild_plugin_if_needed] is careful to
partially initialize the tags that it uses for plugin compilation. *)
Param_tags.init ();
Sys.chdir newpwd;
(*let () = dprintf 0 "source_dir_path_set:@ %a" StringSet.print source_dir_path_set*)

View File

@ -32,22 +32,26 @@ let only_once f =
let declare name action =
Hashtbl.add declared_tags name (only_once action)
let parse tag = Lexers.tag_gen (Lexing.from_string tag)
let acknowledge tag =
let tag = Lexers.tag_gen (Lexing.from_string tag) in
acknowledged_tags := tag :: !acknowledged_tags
acknowledged_tags := parse tag :: !acknowledged_tags
let really_acknowledge (name, param) =
let really_acknowledge ?(quiet=false) (name, param) =
match param with
| None ->
if Hashtbl.mem declared_tags name then
if Hashtbl.mem declared_tags name && not quiet then
Log.eprintf "Warning: tag %S expects a parameter" name
| Some param ->
let actions = List.rev (Hashtbl.find_all declared_tags name) in
if actions = [] then
Log.eprintf "Warning: tag %S does not expect a parameter, but is used with parameter %S" name param;
if actions = [] && not quiet then
Log.eprintf "Warning: tag %S does not expect a parameter, \
but is used with parameter %S" name param;
List.iter (fun f -> f param) actions
let partial_init ?quiet tags =
Tags.iter (fun tag -> really_acknowledge ?quiet (parse tag)) tags
let init () =
List.iter really_acknowledge (My_std.List.ordered_unique !acknowledged_tags)

View File

@ -33,9 +33,16 @@ acknowledged parameter. *)
val init: unit -> unit
(** Initialize parameterized tags.
Call this function once all tags have been [declare]d and [acknowledge]d.
If you [declare] or [acknowledge] a tag after having called [init], this will
have no effect. [init] should only be called once. *)
This will make effective all instantiations [foo(bar)] such that the
parametrized tag [foo] has been [declare]d and [foo(bar)] has been
[acknowledge]d after the last [init] call. *)
val partial_init: ?quiet:bool -> Tags.t -> unit
(** Initialize a list of tags
This will make effective the instances [foo(bar)] appearing
in the given tag list, instead of those that have been
[acknowledged] previously. This is for system use only. *)
val make: Tags.elt -> string -> Tags.elt
(** Make a parameterized tag instance.

View File

@ -87,11 +87,32 @@ module Make(U:sig end) =
if not (sys_file_exists (dir/ocamlbuildlib)) then
failwith (sprintf "Cannot find %S in ocamlbuild -where directory" ocamlbuildlib);
let dir = if Pathname.is_implicit dir then Pathname.pwd/dir else dir in
let tags =
let plugin_tags =
tags_of_pathname plugin_file
++"ocaml"++"program"++"link"++byte_or_native in
(* The plugin is compiled before [Param_tags.init()] is called
globally, which means that parametrized tags have not been
made effective yet. The [partial_init] calls below initializes
precisely those that will be used during the compilation of
the plugin, and no more.
Among the tags that apply to the plugin, we make a special
case for the global tags that come from (true: ...)
lines. They will be used for plugin compilation, but users
may still use parametrized tags that are defined by the
plugin there. So we initialize them "quietly", with no
warning in case of unknown tag.
*)
let global_tags = Configuration.global_tags () in
let not_global tag = not (Tags.mem tag global_tags) in
Param_tags.partial_init ~quiet:true global_tags;
Param_tags.partial_init ~quiet:false
(Tags.filter not_global plugin_tags);
let cmd =
Cmd(S[compiler; A"-I"; P dir; libs; T tags;
Cmd(S[compiler; A"-I"; P dir; libs; T plugin_tags;
P(dir/ocamlbuildlib); plugin_config; P plugin_file;
P(dir/ocamlbuild); A"-o"; Px (plugin^(!Options.exe))])
in