Skip to content

Commit 0229295

Browse files
committed
fix: dune init project & root detection
dune init project should assume the root is cwd if it's not set. Signed-off-by: Rudi Grinberg <[email protected]> ps-id: CF09BF37-DB27-43B9-9ED8-0DC40739106F
1 parent a6b1dc3 commit 0229295

File tree

5 files changed

+25
-9
lines changed

5 files changed

+25
-9
lines changed

bin/common.ml

Lines changed: 10 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -709,7 +709,7 @@ All available cache layers: %s.|}
709709
in
710710
value initial
711711

712-
let term =
712+
let term ~default_root_is_cwd =
713713
let docs = copts_sect in
714714
let+ config_from_command_line = shared_with_config_file
715715
and+ debug_dep_path =
@@ -947,7 +947,10 @@ let term =
947947
deterministic order.")
948948
in
949949
let build_dir = Option.value ~default:default_build_dir build_dir in
950-
let root = Workspace_root.create ~specified_by_user:root in
950+
let root =
951+
Workspace_root.create ~default_is_cwd:default_root_is_cwd
952+
~specified_by_user:root
953+
in
951954
let rpc =
952955
match watch with
953956
| Yes _ -> Some (Dune_rpc_impl.Server.create ~root:root.dir)
@@ -1004,8 +1007,12 @@ let term =
10041007

10051008
let set_rpc t rpc = { t with rpc = Some rpc }
10061009

1010+
let term_with_default_root_is_cwd =
1011+
let+ t, orig_args = Term.with_used_args (term ~default_root_is_cwd:true) in
1012+
{ t with orig_args }
1013+
10071014
let term =
1008-
let+ t, orig_args = Term.with_used_args term in
1015+
let+ t, orig_args = Term.with_used_args (term ~default_root_is_cwd:false) in
10091016
{ t with orig_args }
10101017

10111018
let config_from_config_file = Options_implied_by_dash_p.config_term

bin/common.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,8 @@ val footer : Cmdliner.Manpage.block
4242

4343
val term : t Cmdliner.Term.t
4444

45+
val term_with_default_root_is_cwd : t Cmdliner.Term.t
46+
4547
(** Set whether Dune should print the "Entering directory '<dir>'" message *)
4648
val set_print_directory : t -> bool -> t
4749

bin/init.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -143,7 +143,7 @@ let man =
143143
let info = Term.info "init" ~doc ~man
144144

145145
let term =
146-
let+ common_term = Common.term
146+
let+ common_term = Common.term_with_default_root_is_cwd
147147
and+ kind =
148148
(* TODO(shonfeder): Replace with nested subcommand once we have support for
149149
that *)

bin/workspace_root.ml

Lines changed: 11 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -62,15 +62,22 @@ let find () =
6262
in
6363
loop 0 ~to_cwd:[] cwd ~candidate:None
6464

65-
let create ~specified_by_user =
65+
let create ~default_is_cwd ~specified_by_user =
6666
match
6767
match specified_by_user with
6868
| Some dn -> Some { Candidate.kind = Explicit; dir = dn; to_cwd = [] }
69-
| None ->
69+
| None -> (
70+
let cwd = { Candidate.kind = Cwd; dir = "."; to_cwd = [] } in
7071
if Dune_util.Config.inside_dune then
71-
Some { kind = Cwd; dir = "."; to_cwd = [] }
72+
Some cwd
7273
else
73-
find ()
74+
match find () with
75+
| Some s -> Some s
76+
| None ->
77+
if default_is_cwd then
78+
Some cwd
79+
else
80+
None)
7481
with
7582
| Some { Candidate.dir; to_cwd; kind } ->
7683
{ kind

bin/workspace_root.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -16,4 +16,4 @@ type t =
1616
; kind : Kind.t
1717
}
1818

19-
val create : specified_by_user:string option -> t
19+
val create : default_is_cwd:bool -> specified_by_user:string option -> t

0 commit comments

Comments
 (0)