Skip to content

Commit

Permalink
Allow for (chdir foo/bar)
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg committed Mar 18, 2020
1 parent 3cb5143 commit 72d054c
Show file tree
Hide file tree
Showing 2 changed files with 47 additions and 10 deletions.
34 changes: 27 additions & 7 deletions src/dune/sub_dirs.ml
Original file line number Diff line number Diff line change
Expand Up @@ -143,12 +143,26 @@ module Dir_map = struct
; nodes : t String.Map.t
}

let empty_per_dir =
{ sexps = []; subdir_status = Status.Map.init (fun _ -> None) }

let empty = { data = empty_per_dir; nodes = String.Map.empty }

let root t = t.data

let descend t (p : string) = String.Map.find t.nodes p

let sub_dirs t = String.Map.keys t.nodes

let rec make_at_path path data =
match path with
| [] -> data
| x :: xs ->
let nodes = String.Map.singleton x (make_at_path xs data) in
{ empty with nodes }

let singleton data = { empty with data }

let merge_data d1 d2 =
{ sexps = d1.sexps @ d2.sexps
; subdir_status =
Expand All @@ -170,8 +184,14 @@ module Dir_map = struct
String.Map.union t1.nodes t2.nodes ~f:(fun _ l r -> Some (merge l r))
in
{ data; nodes }

let merge_all = List.fold_left ~f:merge ~init:empty
end

let descedant_path =
Dune_lang.Decoder.plain_string (fun ~loc fn ->
Path.Local.parse_string_exn ~loc fn |> Path.Local.explode)

let strict_subdir field_name =
let open Dune_lang.Decoder in
plain_string (fun ~loc dn ->
Expand Down Expand Up @@ -243,9 +263,9 @@ let decode =
in
let rec chdir () =
let* () = Dune_lang.Syntax.since Stanza.syntax (2, 5) in
let* _, chdir = strict_subdir "chdir" in
let* chdir = descedant_path in
let+ node = fields (decode ~allow_ignored_subdirs:false) in
(chdir, node)
Dir_map.make_at_path chdir node
and decode ~allow_ignored_subdirs =
let+ dirs = field_o "dirs" dirs
and+ data_only = field_o "data_only_dirs" data_only_dirs
Expand Down Expand Up @@ -277,10 +297,10 @@ let decode =
dune file. "
]
| _ ->
let nodes = String.Map.of_list_exn chdirs in
let subdir_status =
make ~dirs ~data_only ~ignored_sub_dirs ~vendored_dirs
in
{ Dir_map.nodes; data = { sexps = rest; subdir_status } }
Dir_map.merge_all
(let subdir_status =
make ~dirs ~data_only ~ignored_sub_dirs ~vendored_dirs
in
Dir_map.singleton { Dir_map.sexps = rest; subdir_status } :: chdirs)
in
enter (fields (decode ~allow_ignored_subdirs:true))
23 changes: 20 additions & 3 deletions test/blackbox-tests/test-cases/chdir-stanza/run.t
Original file line number Diff line number Diff line change
@@ -1,10 +1,8 @@
$ echo "(lang dune 2.5)" > dune-project
$ cat >dune <<EOF
> (rule (with-stdout-to foo.txt (echo "bar")))
> (chdir
> bar
> (chdir bar
> (rule (with-stdout-to foo.txt (echo "bar"))))
> EOF
$ dune build ./foo.txt ./bar/foo.txt
Warning: Unable to read directory bar. Ignoring.
Remove this message by ignoring by adding:
Expand All @@ -13,3 +11,22 @@
Reason: No such file or directory
$ cat _build/default/foo.txt
bar

$ cat >dune <<EOF
> (rule (with-stdout-to foo.txt (echo "bar")))
> (chdir bar/baz
> (rule (with-stdout-to foo.txt (echo "bar"))))
> EOF
$ dune build bar/baz/foo.txt
Warning: Unable to read directory bar. Ignoring.
Remove this message by ignoring by adding:
(dirs \ bar)
to the dune file: dune
Reason: No such file or directory
Warning: Unable to read directory bar/baz. Ignoring.
Remove this message by ignoring by adding:
(dirs \ baz)
to the dune file: bar/dune
Reason: No such file or directory
$ cat _build/default/bar/baz/foo.txt
bar

0 comments on commit 72d054c

Please sign in to comment.