Skip to content

Commit

Permalink
fix: dune init project & root detection
Browse files Browse the repository at this point in the history
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
  • Loading branch information
rgrinberg committed Oct 26, 2021
1 parent a6b1dc3 commit 0229295
Show file tree
Hide file tree
Showing 5 changed files with 25 additions and 9 deletions.
13 changes: 10 additions & 3 deletions bin/common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -709,7 +709,7 @@ All available cache layers: %s.|}
in
value initial

let term =
let term ~default_root_is_cwd =
let docs = copts_sect in
let+ config_from_command_line = shared_with_config_file
and+ debug_dep_path =
Expand Down Expand Up @@ -947,7 +947,10 @@ let term =
deterministic order.")
in
let build_dir = Option.value ~default:default_build_dir build_dir in
let root = Workspace_root.create ~specified_by_user:root in
let root =
Workspace_root.create ~default_is_cwd:default_root_is_cwd
~specified_by_user:root
in
let rpc =
match watch with
| Yes _ -> Some (Dune_rpc_impl.Server.create ~root:root.dir)
Expand Down Expand Up @@ -1004,8 +1007,12 @@ let term =

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

let term_with_default_root_is_cwd =
let+ t, orig_args = Term.with_used_args (term ~default_root_is_cwd:true) in
{ t with orig_args }

let term =
let+ t, orig_args = Term.with_used_args term in
let+ t, orig_args = Term.with_used_args (term ~default_root_is_cwd:false) in
{ t with orig_args }

let config_from_config_file = Options_implied_by_dash_p.config_term
Expand Down
2 changes: 2 additions & 0 deletions bin/common.mli
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,8 @@ val footer : Cmdliner.Manpage.block

val term : t Cmdliner.Term.t

val term_with_default_root_is_cwd : t Cmdliner.Term.t

(** Set whether Dune should print the "Entering directory '<dir>'" message *)
val set_print_directory : t -> bool -> t

Expand Down
2 changes: 1 addition & 1 deletion bin/init.ml
Original file line number Diff line number Diff line change
Expand Up @@ -143,7 +143,7 @@ let man =
let info = Term.info "init" ~doc ~man

let term =
let+ common_term = Common.term
let+ common_term = Common.term_with_default_root_is_cwd
and+ kind =
(* TODO(shonfeder): Replace with nested subcommand once we have support for
that *)
Expand Down
15 changes: 11 additions & 4 deletions bin/workspace_root.ml
Original file line number Diff line number Diff line change
Expand Up @@ -62,15 +62,22 @@ let find () =
in
loop 0 ~to_cwd:[] cwd ~candidate:None

let create ~specified_by_user =
let create ~default_is_cwd ~specified_by_user =
match
match specified_by_user with
| Some dn -> Some { Candidate.kind = Explicit; dir = dn; to_cwd = [] }
| None ->
| None -> (
let cwd = { Candidate.kind = Cwd; dir = "."; to_cwd = [] } in
if Dune_util.Config.inside_dune then
Some { kind = Cwd; dir = "."; to_cwd = [] }
Some cwd
else
find ()
match find () with
| Some s -> Some s
| None ->
if default_is_cwd then
Some cwd
else
None)
with
| Some { Candidate.dir; to_cwd; kind } ->
{ kind
Expand Down
2 changes: 1 addition & 1 deletion bin/workspace_root.mli
Original file line number Diff line number Diff line change
Expand Up @@ -16,4 +16,4 @@ type t =
; kind : Kind.t
}

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

0 comments on commit 0229295

Please sign in to comment.