[ocamlbuild] Better understand and revamp .depends generation and usage.
.depends file was generated by an ugly rule that executed the ocamldep command instead of returning it for later execution. Moreover this execution was in order to read the output and store as a side effect. By doing this it was more complicated to work with this command. Now the rule just returns the command to execute as for other rules. And that's clients that wants dependencies of a file that trigger the reading of this file. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@8566 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
229bebc621
commit
5bc8725446
|
@ -275,7 +275,7 @@ let main () =
|
|||
This is likely to be a bug, please report this to the ocamlbuild\n\
|
||||
developers." s;
|
||||
exit rc_invalid_argument
|
||||
| Ocamldep.Error msg ->
|
||||
| Ocaml_utils.Ocamldep_error msg ->
|
||||
Log.eprintf "Ocamldep error: %s" msg;
|
||||
exit rc_ocamldep_error
|
||||
| Lexers.Error msg ->
|
||||
|
|
|
@ -100,7 +100,7 @@ let native_lib_linker_tags tags = tags++"ocaml"++"link"++"native"++"library"
|
|||
let prepare_compile build ml =
|
||||
let dir = Pathname.dirname ml in
|
||||
let include_dirs = Pathname.include_dirs_of dir in
|
||||
let modules = Ocamldep.module_dependencies_of ml in
|
||||
let modules = path_dependencies_of ml in
|
||||
let results =
|
||||
build (List.map (fun (_, x) -> expand_module include_dirs x ["cmi"]) modules) in
|
||||
List.iter2 begin fun (mandatory, name) res ->
|
||||
|
@ -129,9 +129,15 @@ let rec prepare_link tag cmx extensions build =
|
|||
let key = (tag, cmx, extensions) in
|
||||
let dir = Pathname.dirname cmx in
|
||||
let include_dirs = Pathname.include_dirs_of dir in
|
||||
if Hashtbl.mem cache_prepare_link key then () else
|
||||
let ml = Pathname.update_extensions "ml" cmx in
|
||||
let mli = Pathname.update_extensions "mli" cmx in
|
||||
let modules =
|
||||
List.union
|
||||
(if Pathname.exists (ml-.-"depends") then path_dependencies_of ml else [])
|
||||
(if Pathname.exists (mli-.-"depends") then path_dependencies_of mli else [])
|
||||
in
|
||||
if modules <> [] && not (Hashtbl.mem cache_prepare_link key) then
|
||||
let () = Hashtbl.add cache_prepare_link key true in
|
||||
let modules = Ocamldep.module_dependencies_of (Pathname.update_extensions "ml" cmx) in
|
||||
let modules' = List.map (fun (_, x) -> expand_module include_dirs x extensions) modules in
|
||||
List.iter2 begin fun (mandatory, _) result ->
|
||||
match mandatory, result with
|
||||
|
|
|
@ -223,13 +223,15 @@ rule "ocaml: cmx* & o* -> cmxa & a"
|
|||
~deps:["%.cmx"; x_o]
|
||||
(Ocaml_compiler.native_library_link "%.cmx" "%.cmxa");;
|
||||
|
||||
Ocamldep.depends "ocaml dependencies ml"
|
||||
rule "ocaml dependencies ml"
|
||||
~prod:"%.ml.depends"
|
||||
~dep:"%.ml" ();;
|
||||
~dep:"%.ml"
|
||||
(Ocaml_tools.ocamldep_command "%.ml" "%.ml.depends");;
|
||||
|
||||
Ocamldep.depends "ocaml dependencies mli"
|
||||
rule "ocaml dependencies mli"
|
||||
~prod:"%.mli.depends"
|
||||
~dep:"%.mli" ();;
|
||||
~dep:"%.mli"
|
||||
(Ocaml_tools.ocamldep_command "%.mli" "%.mli.depends");;
|
||||
|
||||
rule "ocamllex"
|
||||
~tags:["ocaml"] (* FIXME "lexer" *)
|
||||
|
@ -275,10 +277,10 @@ if !Options.use_menhir || Configuration.has_tag "use_menhir" then begin
|
|||
~deps:["%.mly"; "%.mly.depends"]
|
||||
(Ocaml_tools.menhir "%.mly");
|
||||
|
||||
Ocamldep.depends "ocaml: menhir dependencies"
|
||||
rule "ocaml: menhir dependencies"
|
||||
~prod:"%.mly.depends"
|
||||
~dep:"%.mly"
|
||||
~ocamldep_command:Ocamldep.menhir_ocamldep_command ();
|
||||
(Ocaml_tools.menhir_ocamldep_command "%.mly" "%.mly.depends");
|
||||
end else
|
||||
rule "ocamlyacc"
|
||||
~tags:["ocaml"] (* FIXME "parser" *)
|
||||
|
|
|
@ -18,6 +18,23 @@ open Tools
|
|||
open Command
|
||||
open Ocaml_utils
|
||||
|
||||
let ocamldep_command' arg =
|
||||
let tags = tags_of_pathname arg++"ocaml"++"ocamldep" in
|
||||
S [!Options.ocamldep; T tags; ocaml_ppflags tags;
|
||||
flags_of_pathname arg; A "-modules"]
|
||||
|
||||
let menhir_ocamldep_command arg out env _build =
|
||||
let arg = env arg and out = env out in
|
||||
let menhir = if !Options.ocamlyacc = N then V"MENHIR" else !Options.ocamlyacc in
|
||||
let tags = tags_of_pathname arg++"ocaml"++"menhir_ocamldep" in
|
||||
Cmd(S [menhir; T tags; A"--raw-depend";
|
||||
A"--ocamldep"; Quote (ocamldep_command' arg);
|
||||
P arg; Sh ">"; Px out])
|
||||
|
||||
let ocamldep_command arg out env _build =
|
||||
let arg = env arg and out = env out in
|
||||
Cmd(S[ocamldep_command' arg; P arg; Sh ">"; Px out])
|
||||
|
||||
let ocamlyacc mly env _build =
|
||||
let mly = env mly in
|
||||
let ocamlyacc = if !Options.ocamlyacc = N then V"OCAMLYACC" else !Options.ocamlyacc in
|
||||
|
|
|
@ -16,6 +16,8 @@ val ocamldoc_c : Tags.t -> string -> string -> Command.t
|
|||
val ocamldoc_l_dir : Tags.t -> string list -> string -> string -> Command.t
|
||||
val ocamldoc_l_file : Tags.t -> string list -> string -> string -> Command.t
|
||||
|
||||
val ocamldep_command : string -> string -> Rule.action
|
||||
val menhir_ocamldep_command : string -> string -> Rule.action
|
||||
val ocamlyacc : string -> Rule.action
|
||||
val ocamllex : string -> Rule.action
|
||||
val menhir : string -> Rule.action
|
||||
|
|
|
@ -41,12 +41,16 @@ let ignore_stdlib x =
|
|||
Pathname.exists x'
|
||||
|
||||
let non_dependencies = ref []
|
||||
let non_dependency m1 m2 = non_dependencies := (m1, m2) :: !non_dependencies
|
||||
let non_dependency m1 m2 =
|
||||
(* non_dependency was not supposed to accept pathnames without extension. *)
|
||||
if String.length (Pathname.get_extensions m1) = 0 then
|
||||
invalid_arg "non_dependency: no extension";
|
||||
non_dependencies := (m1, m2) :: !non_dependencies
|
||||
|
||||
let module_importance modpath x =
|
||||
if List.mem (modpath, x) !non_dependencies
|
||||
let path_importance path x =
|
||||
if List.mem (path, x) !non_dependencies
|
||||
|| (List.mem x !Options.ignore_list) then begin
|
||||
let () = dprintf 3 "This module (%s) is ignored by %s" x modpath in
|
||||
let () = dprintf 3 "This module (%s) is ignored by %s" x path in
|
||||
`ignored
|
||||
end
|
||||
else if ignore_stdlib x then `just_try else `mandatory
|
||||
|
@ -113,3 +117,38 @@ let ocaml_lib ?(extern=false) ?(byte=true) ?(native=true) ?dir ?tag_name libpath
|
|||
| Some dir -> flag ["ocaml"; tag_name; "compile"] (S[A"-I"; P dir])
|
||||
|
||||
let cmi_of = Pathname.update_extensions "cmi"
|
||||
|
||||
exception Ocamldep_error of string
|
||||
|
||||
let read_path_dependencies =
|
||||
let path_dependencies = Hashtbl.create 103 in
|
||||
let read path =
|
||||
let module_name = module_name_of_pathname path in
|
||||
let depends = path-.-"depends" in
|
||||
with_input_file depends begin fun ic ->
|
||||
let ocamldep_output =
|
||||
try Lexers.ocamldep_output (Lexing.from_channel ic)
|
||||
with Lexers.Error msg -> raise (Ocamldep_error(Printf.sprintf "Ocamldep.ocamldep: bad output (%s)" msg)) in
|
||||
let deps =
|
||||
List.fold_right begin fun (path, deps) acc ->
|
||||
let module_name' = module_name_of_pathname path in
|
||||
if module_name' = module_name
|
||||
then List.union deps acc
|
||||
else raise (Ocamldep_error(Printf.sprintf "Ocamldep.ocamldep: multiple files in ocamldep output (%s not expected)" path))
|
||||
end ocamldep_output [] in
|
||||
let deps =
|
||||
if !Options.nostdlib && not (Tags.mem "nopervasives" (tags_of_pathname path)) then
|
||||
"Pervasives" :: deps
|
||||
else deps in
|
||||
let deps' = List.fold_right begin fun dep acc ->
|
||||
match path_importance path dep with
|
||||
| `ignored -> acc
|
||||
| (`just_try | `mandatory) as importance -> (importance, dep) :: acc
|
||||
end deps [] in
|
||||
Hashtbl.replace path_dependencies path
|
||||
(List.union (try Hashtbl.find path_dependencies path with Not_found -> []) deps');
|
||||
deps'
|
||||
end
|
||||
in read
|
||||
|
||||
let path_dependencies_of = memo read_path_dependencies
|
||||
|
|
|
@ -25,7 +25,11 @@ val libraries_of : Pathname.t -> Pathname.t list
|
|||
val use_lib : Pathname.t -> Pathname.t -> unit
|
||||
val cmi_of : Pathname.t -> Pathname.t
|
||||
val ocaml_add_include_flag : string -> Command.spec list -> Command.spec list
|
||||
val module_importance : string -> string -> [ `ignored | `mandatory | `just_try ]
|
||||
|
||||
exception Ocamldep_error of string
|
||||
|
||||
(* Takes a path and returns a list of modules *)
|
||||
val path_dependencies_of : Pathname.t -> ([ `mandatory | `just_try ] * string) list
|
||||
|
||||
val info_libraries : (string, string * bool) Hashtbl.t
|
||||
|
||||
|
|
|
@ -34,5 +34,4 @@ Hooks
|
|||
Ocaml_utils
|
||||
Ocaml_tools
|
||||
Ocaml_compiler
|
||||
Ocamldep
|
||||
Ocaml_dependencies
|
||||
|
|
|
@ -1,83 +0,0 @@
|
|||
(***********************************************************************)
|
||||
(* ocamlbuild *)
|
||||
(* *)
|
||||
(* Nicolas Pouillard, Berke Durak, projet Gallium, INRIA Rocquencourt *)
|
||||
(* *)
|
||||
(* Copyright 2007 Institut National de Recherche en Informatique et *)
|
||||
(* en Automatique. All rights reserved. This file is distributed *)
|
||||
(* under the terms of the Q Public License version 1.0. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
(* $Id$ *)
|
||||
(* Original author: Nicolas Pouillard *)
|
||||
open My_std
|
||||
open Log
|
||||
open Command
|
||||
open Tags.Operators
|
||||
open Tools
|
||||
open Ocaml_utils
|
||||
open Pathname.Operators
|
||||
|
||||
exception Error of string
|
||||
|
||||
let ocamldep_command arg =
|
||||
let tags = tags_of_pathname arg++"ocaml"++"ocamldep" in
|
||||
S [!Options.ocamldep; T tags; ocaml_ppflags tags;
|
||||
flags_of_pathname arg; A "-modules"]
|
||||
|
||||
let menhir_ocamldep_command arg out =
|
||||
let menhir = if !Options.ocamlyacc = N then V"MENHIR" else !Options.ocamlyacc in
|
||||
let tags = tags_of_pathname arg++"ocaml"++"menhir_ocamldep" in
|
||||
S [menhir; T tags; A"--raw-depend";
|
||||
A"--ocamldep"; Quote (ocamldep_command arg);
|
||||
P arg; Sh ">"; Px out]
|
||||
|
||||
let ocamldep_command arg out =
|
||||
S[ocamldep_command arg; P arg; Sh ">"; Px out]
|
||||
|
||||
let module_dependencies = Hashtbl.create 103
|
||||
let module_dependencies_of module_path =
|
||||
try Hashtbl.find module_dependencies module_path with Not_found -> []
|
||||
let register_module_dependencies module_path deps =
|
||||
let deps' = List.fold_right begin fun dep acc ->
|
||||
match module_importance module_path dep with
|
||||
| `ignored -> acc
|
||||
| (`just_try | `mandatory) as importance -> (importance, dep) :: acc
|
||||
end deps [] in
|
||||
Hashtbl.replace module_dependencies module_path
|
||||
(List.union (module_dependencies_of module_path) deps')
|
||||
|
||||
let depends name ?tags ~prod ~dep ?insert ?(ocamldep_command=ocamldep_command) () =
|
||||
Rule.custom_rule name ?tags ~prod ~dep ?insert
|
||||
~cache: begin fun env build ->
|
||||
let cmd = ocamldep_command (env dep) (env prod) in
|
||||
let str, _, tags = Command.string_target_and_tags_of_command_spec cmd in
|
||||
let _ = Rule.build_deps_of_tags build (tags++"dont_link_with") in
|
||||
str
|
||||
end
|
||||
begin fun env ~cached ->
|
||||
let arg = env dep in
|
||||
let out = env prod in
|
||||
let cmd = Cmd (ocamldep_command arg out) in
|
||||
let () = dprintf 6 "ocamldep: %a %a" Pathname.print arg Command.print cmd in
|
||||
if not (Pathname.exists arg) then
|
||||
raise (Error(sbprintf "Ocamldep.ocamldep: no input file (%a)" Pathname.print arg))
|
||||
else begin
|
||||
Command.execute ~pretend:cached cmd;
|
||||
with_input_file out begin fun ic ->
|
||||
let ocamldep_output =
|
||||
try Lexers.ocamldep_output (Lexing.from_channel ic)
|
||||
with Lexers.Error msg -> raise (Error(Printf.sprintf "Ocamldep.ocamldep: bad output (%s)" msg)) in
|
||||
let ocamldep_output =
|
||||
List.fold_right begin fun (_, deps) acc ->
|
||||
List.union deps acc
|
||||
end ocamldep_output [] in
|
||||
let ocamldep_output =
|
||||
if !Options.nostdlib && not (Tags.mem "nopervasives" (tags_of_pathname arg)) then
|
||||
"Pervasives" :: ocamldep_output
|
||||
else ocamldep_output in
|
||||
register_module_dependencies arg ocamldep_output
|
||||
end
|
||||
end
|
||||
end
|
|
@ -1,26 +0,0 @@
|
|||
(***********************************************************************)
|
||||
(* ocamlbuild *)
|
||||
(* *)
|
||||
(* Nicolas Pouillard, Berke Durak, projet Gallium, INRIA Rocquencourt *)
|
||||
(* *)
|
||||
(* Copyright 2007 Institut National de Recherche en Informatique et *)
|
||||
(* en Automatique. All rights reserved. This file is distributed *)
|
||||
(* under the terms of the Q Public License version 1.0. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
(* $Id$ *)
|
||||
(* Original author: Nicolas Pouillard *)
|
||||
exception Error of string
|
||||
val ocamldep_command : Pathname.t -> Pathname.t -> Command.spec
|
||||
val menhir_ocamldep_command : Pathname.t -> Pathname.t -> Command.spec
|
||||
val module_dependencies_of : Pathname.t -> ([ `mandatory | `just_try ] * string) list
|
||||
val register_module_dependencies : Pathname.t -> string list -> unit
|
||||
val depends :
|
||||
string ->
|
||||
?tags:string list ->
|
||||
prod:string ->
|
||||
dep:string ->
|
||||
?insert:[`top | `before of string | `after of string | `bottom] ->
|
||||
?ocamldep_command:(Pathname.t -> Pathname.t -> Command.spec) ->
|
||||
unit -> unit
|
|
@ -35,7 +35,6 @@ ocamlc -c ocaml_tools.mli
|
|||
ocamlc -c ocaml_compiler.mli
|
||||
ocamlc -c ocaml_dependencies.mli
|
||||
ocamlc -c hooks.mli
|
||||
ocamlc -c ocamldep.mli
|
||||
ocamlc -c ocaml_specific.mli
|
||||
ocamlc -c configuration.mli
|
||||
ocamlc -c flags.mli
|
||||
|
@ -64,7 +63,6 @@ ocamlc -c slurp.ml
|
|||
ocamlc -c ocaml_utils.ml
|
||||
ocamlc -c ocaml_tools.ml
|
||||
ocamlc -c ocaml_compiler.ml
|
||||
ocamlc -c ocamldep.ml
|
||||
ocamlc -c hooks.ml
|
||||
ocamllex lexers.mll
|
||||
ocamlc -c lexers.ml
|
||||
|
@ -83,7 +81,7 @@ ocamlc -c rule.ml
|
|||
ocamlc -c report.ml
|
||||
ocamlc -c solver.ml
|
||||
ocamlc -c ocamlbuildlight.mli
|
||||
ocamlc -pack discard_printf.cmo my_std.cmo bool.cmo glob_ast.cmo glob_lexer.cmo glob.cmo lexers.cmo my_unix.cmo tags.cmo display.cmo log.cmo shell.cmo slurp.cmo ocamlbuild_where.cmo command.cmo options.cmo pathname.cmo resource.cmo rule.cmo flags.cmo solver.cmo report.cmo ocaml_arch.cmo hygiene.cmo configuration.cmo tools.cmo fda.cmo plugin.cmo ocaml_utils.cmo ocamldep.cmo ocaml_dependencies.cmo ocaml_compiler.cmo ocaml_tools.cmo hooks.cmo ocaml_specific.cmo main.cmo -o ocamlbuild_pack.cmo
|
||||
ocamlc -pack discard_printf.cmo my_std.cmo bool.cmo glob_ast.cmo glob_lexer.cmo glob.cmo lexers.cmo my_unix.cmo tags.cmo display.cmo log.cmo shell.cmo slurp.cmo ocamlbuild_where.cmo command.cmo options.cmo pathname.cmo resource.cmo rule.cmo flags.cmo solver.cmo report.cmo ocaml_arch.cmo hygiene.cmo configuration.cmo tools.cmo fda.cmo plugin.cmo ocaml_utils.cmo ocaml_dependencies.cmo ocaml_compiler.cmo ocaml_tools.cmo hooks.cmo ocaml_specific.cmo main.cmo -o ocamlbuild_pack.cmo
|
||||
ocamlc -c ocamlbuildlight.ml
|
||||
ocamlc ocamlbuild_pack.cmo ocamlbuildlight.cmo -o ../ocamlbuild.byte.start
|
||||
cd ..
|
||||
|
|
Loading…
Reference in New Issue