summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorNicolas Pouillard <np@nicolaspouillard.fr>2007-12-18 08:58:32 +0000
committerNicolas Pouillard <np@nicolaspouillard.fr>2007-12-18 08:58:32 +0000
commit653f2273b8cd03d5d7d05519e64a1ef9f3922d97 (patch)
tree5404196875c3cf06179cb392b3724221c068402c
parentc0b37df251b286234522123d356d089da68ce8af (diff)
ocamlbuild: normalize pathname and authorize absolute pathnames as dependencies.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@8717 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--ocamlbuild/main.ml1
-rw-r--r--ocamlbuild/ocamlbuild.odocl1
-rw-r--r--ocamlbuild/resource.ml15
-rw-r--r--ocamlbuild/resource.mli1
-rw-r--r--ocamlbuild/rule.ml6
-rw-r--r--ocamlbuild/solver.ml8
6 files changed, 28 insertions, 4 deletions
diff --git a/ocamlbuild/main.ml b/ocamlbuild/main.ml
index fbccc1c3c..dbeb879c1 100644
--- a/ocamlbuild/main.ml
+++ b/ocamlbuild/main.ml
@@ -156,6 +156,7 @@ let proceed () =
let targets =
List.map begin fun starget ->
+ let starget = Resource.import starget in
let target = path_and_context_of_string starget in
let ext = Pathname.get_extension starget in
(target, starget, ext)
diff --git a/ocamlbuild/ocamlbuild.odocl b/ocamlbuild/ocamlbuild.odocl
index d4374386a..09c34475c 100644
--- a/ocamlbuild/ocamlbuild.odocl
+++ b/ocamlbuild/ocamlbuild.odocl
@@ -36,3 +36,4 @@ Ocaml_tools
Ocaml_compiler
Ocamldep
Ocaml_dependencies
+Ocamlbuild_plugin
diff --git a/ocamlbuild/resource.ml b/ocamlbuild/resource.ml
index 7b8d51e31..408ccdf44 100644
--- a/ocamlbuild/resource.ml
+++ b/ocamlbuild/resource.ml
@@ -138,6 +138,18 @@ module Cache = struct
dprintf 10 "resource_changed:@ %a" print r;
(get r).changed <- Yes
+ let external_is_up_to_date absolute_path =
+ let key = "Resource: " ^ absolute_path in
+ let digest = Digest.file absolute_path in
+ let is_up_to_date =
+ try
+ let digest' = Digest_cache.get key in
+ digest = digest'
+ with Not_found ->
+ false
+ in
+ is_up_to_date || (Digest_cache.put key digest; false)
+
let source_is_up_to_date r_in_source_dir r_in_build_dir =
Pathname.exists r_in_build_dir && Digest.file r_in_build_dir = Digest.file r_in_source_dir
@@ -264,7 +276,8 @@ let rec subst percent r =
let print_env = pp_print_string
*)
-let import x = x
+(* Should normalize *)
+let import x = Pathname.normalize x
module MetaPath : sig
diff --git a/ocamlbuild/resource.mli b/ocamlbuild/resource.mli
index d34623bef..bd22cae8b 100644
--- a/ocamlbuild/resource.mli
+++ b/ocamlbuild/resource.mli
@@ -44,6 +44,7 @@ module Cache :
val clear_resource_failed : t -> unit
val add_dependency : t -> t -> unit
val fold_dependencies : (string -> string -> 'a -> 'a) -> 'a -> 'a
+ val external_is_up_to_date : t -> bool
(* These are not currently used by others modules. *)
val dependencies : t -> Resources.t
diff --git a/ocamlbuild/rule.ml b/ocamlbuild/rule.ml
index ee6afb28b..b65863d88 100644
--- a/ocamlbuild/rule.ml
+++ b/ocamlbuild/rule.ml
@@ -28,7 +28,7 @@ type digest_command = { digest : string; command : Command.t }
type 'a gen_rule =
{ name : string;
tags : Tags.t;
- deps : Pathname.t list;
+ deps : Pathname.t list; (* These pathnames must be normalized *)
prods : 'a list; (* Note that prods also contains stamp *)
stamp : 'a option;
code : env -> builder -> digest_command }
@@ -67,7 +67,7 @@ let subst env rule =
let prods = subst_resource_patterns rule.prods in
{ (rule) with name = sbprintf "%s (%a)" rule.name Resource.print_env env;
prods = prods;
- deps = subst_resources rule.deps;
+ deps = subst_resources rule.deps; (* The substition should preserve normalization of pathnames *)
stamp = stamp;
code = (fun env -> rule.code (finder env)) }
@@ -298,7 +298,7 @@ let rule name ?(tags=[]) ?(prods=[]) ?(deps=[]) ?prod ?dep ?stamp ?(insert = `bo
add_rule insert
{ name = name;
tags = List.fold_right Tags.add tags Tags.empty;
- deps = res_add Resource.import deps dep;
+ deps = res_add Resource.import (* should normalize *) deps dep;
stamp = stamp;
prods = prods;
code = code }
diff --git a/ocamlbuild/solver.ml b/ocamlbuild/solver.ml
index 6e63d4499..84b3dadf0 100644
--- a/ocamlbuild/solver.ml
+++ b/ocamlbuild/solver.ml
@@ -31,6 +31,10 @@ let failed target backtrace =
let rec pp_repeat f (n, s) =
if n > 0 then (pp_print_string f s; pp_repeat f (n - 1, s))
+(* Targets must be normalized pathnames.
+ * Recursive calls are either on input targets
+ * or dependencies of these targets (returned by Rule.deps_of_rule).
+ *)
let rec self depth on_the_go_orig target =
let rules = Rule.get_rules () in
let on_the_go = target :: on_the_go_orig in
@@ -46,6 +50,10 @@ let rec self depth on_the_go_orig target =
(dprintf 5 "%a was suspended -> resuming" Resource.print target;
Resource.Cache.resume_suspension s)
| Resource.Cache.Bnot_built_yet ->
+ if not (Pathname.is_relative target) && Pathname.exists target then
+ if Resource.Cache.external_is_up_to_date target then ()
+ else (* perhaps the error can be refined *) failed target (Leaf target)
+ else
if Resource.exists_in_source_dir target then
Resource.Cache.import_in_build_dir target
else