[ocamlbuild] Move tag_any and tag_file to Configuration but still export them in Ocamlbuild_plugin.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@8665 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
ae46dfee1c
commit
f835cca505
|
@ -61,3 +61,9 @@ let tags_of_filename x = fst (tags_and_flags_of_filename x)
|
|||
let flags_of_filename x = snd (tags_and_flags_of_filename x)
|
||||
|
||||
let has_tag tag = Tags.mem tag (tags_of_filename "")
|
||||
|
||||
let tag_file file tags =
|
||||
if tags <> [] then parse_string (Printf.sprintf "%S: %s" file (String.concat ", " tags));;
|
||||
|
||||
let tag_any tags =
|
||||
if tags <> [] then parse_string (Printf.sprintf "true: %s" (String.concat ", " tags));;
|
||||
|
|
|
@ -32,3 +32,9 @@ val tags_of_filename : string -> Tags.t
|
|||
val flags_of_filename : string -> Command.spec
|
||||
|
||||
val has_tag : string -> bool
|
||||
|
||||
(** [tag_file filename tag_list] Tag the given filename with all given tags. *)
|
||||
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
|
||||
|
|
|
@ -43,10 +43,8 @@ let string_list_of_file = Ocamlbuild_pack.Ocaml_utils.string_list_of_file
|
|||
let expand_module = Ocamlbuild_pack.Ocaml_utils.expand_module
|
||||
let tags_of_pathname = Ocamlbuild_pack.Tools.tags_of_pathname
|
||||
let hide_package_contents = Ocamlbuild_pack.Ocaml_compiler.hide_package_contents
|
||||
let tag_file file tags =
|
||||
Ocamlbuild_pack.Configuration.parse_string (Printf.sprintf "%S: %s" file (String.concat ", " tags));;
|
||||
let tag_any tags =
|
||||
Ocamlbuild_pack.Configuration.parse_string (Printf.sprintf "true: %s" (String.concat ", " tags));;
|
||||
let tag_file = Ocamlbuild_pack.Configuration.tag_file
|
||||
let tag_any = Ocamlbuild_pack.Configuration.tag_any
|
||||
type hook = Ocamlbuild_pack.Hooks.message =
|
||||
| Before_hygiene
|
||||
| After_hygiene
|
||||
|
|
|
@ -538,8 +538,10 @@ module type PLUGIN = sig
|
|||
this package even if it contains that module. *)
|
||||
val hide_package_contents : string -> unit
|
||||
|
||||
(** [tag_file filename tag_list] Tag the given filename with all given tags. *)
|
||||
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
|
||||
|
||||
val tags_of_pathname : Pathname.t -> Tags.t
|
||||
|
|
Loading…
Reference in New Issue