Skip to content

Commit

Permalink
Merge pull request #1965 from rgrinberg/fix-external-glob
Browse files Browse the repository at this point in the history
Fix glob dependencies on external directories
  • Loading branch information
rgrinberg authored Mar 21, 2019
2 parents dbd2408 + 4231c9d commit 5d690c5
Show file tree
Hide file tree
Showing 4 changed files with 32 additions and 29 deletions.
2 changes: 2 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,8 @@ unreleased
- Watch mode: display "Success" in green and "Had errors" in red (#1956,
@emillon)

- Fix glob dependencies on installed directories (#1965, @rgrinberg)

1.8.2 (10/03/2019)
------------------

Expand Down
43 changes: 22 additions & 21 deletions src/build_system.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1087,7 +1087,7 @@ and get_file_spec t path =
Errors.fail_opt loc
"File unavailable: %s" (Path.to_string_maybe_quoted path)

let stamp_file_for_files_of ~dir ~ext =
let stamp_files_for_files_of ~dir ~exts =
let t = t () in
let files_of_dir =
Path.Table.find_or_add t.files_of dir ~f:(fun dir ->
Expand All @@ -1102,26 +1102,27 @@ let stamp_file_for_files_of ~dir ~ext =
; stamps = String.Map.empty
})
in
match String.Map.find files_of_dir.stamps ext with
| Some fn -> fn
| None ->
let stamp_file = Path.relative misc_dir (files_of_dir.dir_hash ^ ext) in
let files =
Option.value
(String.Map.find files_of_dir.files_by_ext ext)
~default:[]
in
compile_rule t
(let open Build.O in
Pre_rule.make
~env:None
~context:None
(Build.paths files >>>
Build.action ~targets:[stamp_file]
(Action.with_stdout_to stamp_file
(Action.digest_files files))));
files_of_dir.stamps <- String.Map.add files_of_dir.stamps ext stamp_file;
stamp_file
List.map exts ~f:(fun ext ->
match String.Map.find files_of_dir.stamps ext with
| Some fn -> fn
| None ->
let stamp_file = Path.relative misc_dir (files_of_dir.dir_hash ^ ext) in
let files =
Option.value
(String.Map.find files_of_dir.files_by_ext ext)
~default:[]
in
compile_rule t
(let open Build.O in
Pre_rule.make
~env:None
~context:None
(Build.paths files >>>
Build.action ~targets:[stamp_file]
(Action.with_stdout_to stamp_file
(Action.digest_files files))));
files_of_dir.stamps <- String.Map.add files_of_dir.stamps ext stamp_file;
stamp_file)

let all_targets () =
let t = t () in
Expand Down
4 changes: 2 additions & 2 deletions src/build_system.mli
Original file line number Diff line number Diff line change
Expand Up @@ -74,8 +74,8 @@ val targets_of : dir:Path.t -> Path.Set.t
(** Load the rules for this directory. *)
val load_dir : dir:Path.t -> unit

(** Stamp file that depends on all files of [dir] with extension [ext]. *)
val stamp_file_for_files_of : dir:Path.t -> ext:string -> Path.t
(** Stamp files that depends on all files of [dir] with extensions [exts]. *)
val stamp_files_for_files_of : dir:Path.t -> exts:string list -> Path.t list

(** Sets the package this file is part of *)
val set_package : Path.t -> Package.Name.t -> unit
Expand Down
12 changes: 6 additions & 6 deletions src/lib_file_deps.ml
Original file line number Diff line number Diff line change
Expand Up @@ -64,16 +64,16 @@ let setup_file_deps =

let file_deps_of_lib (lib : Lib.t) ~groups =
if Lib.is_local lib then
Alias.stamp_file
(Group.L.alias groups ~dir:(Lib.src_dir lib) ~name:(Lib.name lib))
[Alias.stamp_file
(Group.L.alias groups ~dir:(Lib.src_dir lib) ~name:(Lib.name lib))]
else
(* suppose that all the files of an external lib are at the same place *)
Build_system.stamp_file_for_files_of
Build_system.stamp_files_for_files_of
~dir:(Obj_dir.public_cmi_dir (Lib.obj_dir lib))
~ext:(Group.L.to_string groups)
~exts:(List.map ~f:Group.to_string groups)

let file_deps_with_exts =
List.rev_map ~f:(fun (lib, groups) -> file_deps_of_lib lib ~groups)
List.concat_map ~f:(fun (lib, groups) -> file_deps_of_lib lib ~groups)

let file_deps libs ~groups =
List.rev_map libs ~f:(file_deps_of_lib ~groups)
List.concat_map libs ~f:(file_deps_of_lib ~groups)

0 comments on commit 5d690c5

Please sign in to comment.