Skip to content

Commit

Permalink
Merge branch 'main' into doc-index-cards
Browse files Browse the repository at this point in the history
  • Loading branch information
emillon authored Mar 14, 2024
2 parents a2cde68 + 10fdc5d commit b42cd1e
Show file tree
Hide file tree
Showing 8 changed files with 34 additions and 16 deletions.
3 changes: 2 additions & 1 deletion bin/exec.ml
Original file line number Diff line number Diff line change
Expand Up @@ -82,7 +82,8 @@ module Command_to_exec = struct
let path = Path.to_string path in
let env = Env.to_unix env |> Spawn.Env.of_list in
let argv = path :: args in
Spawn.spawn ~prog:path ~env ~argv ()
let cwd = Spawn.Working_dir.Path Fpath.initial_cwd in
Spawn.spawn ~prog:path ~env ~cwd ~argv ()
in
Pid.of_int pid
;;
Expand Down
3 changes: 3 additions & 0 deletions doc/changes/10262.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
- Fix bug with `dune exec --watch` where the working directory would always be
set to the project root rather than the directory where the command was run
(#10262, @gridbugs)
12 changes: 0 additions & 12 deletions src/dune_lang/ordered_set_lang.ml
Original file line number Diff line number Diff line change
Expand Up @@ -340,18 +340,6 @@ module Unexpanded = struct
(Option.forall ~f:is_expanded)
;;

let has_special_forms t =
let rec loop (t : ast) =
let open Ast in
match t with
| Standard | Include _ -> true
| Element _ -> false
| Union l -> List.exists l ~f:loop
| Diff (l, r) -> loop l || loop r
in
loop t.ast
;;

let has_standard t =
let rec loop ast =
match ast with
Expand Down
1 change: 0 additions & 1 deletion src/dune_lang/ordered_set_lang.mli
Original file line number Diff line number Diff line change
Expand Up @@ -66,7 +66,6 @@ module Unexpanded : sig
-> string
-> t option Decoder.fields_parser

val has_special_forms : t -> bool
val has_standard : t -> bool

type position =
Expand Down
3 changes: 1 addition & 2 deletions src/dune_rules/expander.ml
Original file line number Diff line number Diff line change
Expand Up @@ -893,8 +893,7 @@ let expand_ordered_set_lang =

let expand_and_eval_set t set ~standard =
let+ standard =
(* This optimization builds [standard] if it's unused by the expander. *)
if Ordered_set_lang.Unexpanded.has_special_forms set
if Ordered_set_lang.Unexpanded.has_standard set
then standard
else Action_builder.return []
and+ set = expand_ordered_set_lang t set in
Expand Down
2 changes: 2 additions & 0 deletions test/blackbox-tests/test-cases/exec-watch/exec-pwd.t/bin/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
(executable
(name main))
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(lang dune 3.6)
25 changes: 25 additions & 0 deletions test/blackbox-tests/test-cases/exec-watch/exec-pwd.t/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,25 @@
$ export OUTPUT=output.txt

In normal (non-watching) mode, pwd is the folder from which dune is launched
$ cd bin
$ dune exec --root .. -- pwd > $OUTPUT
Entering directory '..'
Leaving directory '..'
$ cat $OUTPUT
$TESTCASE_ROOT/bin
$ rm -rf $OUTPUT
$ cd ..

In watch mode, pwd is also the folder from which dune is launched.
$ cd bin
$ dune exec --root .. -w -- pwd > $OUTPUT &
Entering directory '..'
Success, waiting for filesystem changes...
Leaving directory '..'
$ PID=$!
$ until test -s $OUTPUT; do sleep 0.1; done;
$ kill $PID
$ cat $OUTPUT
$TESTCASE_ROOT/bin
$ rm -rf $OUTPUT
$ cd ..

0 comments on commit b42cd1e

Please sign in to comment.