Skip to content

Commit

Permalink
In dune init proj set workspace root to proj dir
Browse files Browse the repository at this point in the history
Signed-off-by: Stephen Sherratt <stephen@sherra.tt>
  • Loading branch information
gridbugs committed Dec 19, 2022
1 parent 5ed445a commit 1e18a5e
Show file tree
Hide file tree
Showing 8 changed files with 115 additions and 14 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -53,6 +53,9 @@ Unreleased
- Fix inline tests with js_of_ocaml and whole program compilation mode enabled
(#6645, @hhugo)

- Remove spurious build dir created when running `dune init proj ...` (#6707,
fixes #5429, @gridbugs)

3.6.1 (2022-11-24)
------------------

Expand Down
4 changes: 4 additions & 0 deletions bin/common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -777,6 +777,8 @@ module Builder = struct
; react_to_insignificant_changes : bool
}

let set_root t root = { t with root = Some root }

let term =
let docs = copts_sect in
let+ config_from_command_line = shared_with_config_file
Expand Down Expand Up @@ -1220,6 +1222,8 @@ let term_with_default_root_is_cwd = term ~default_root_is_cwd:true

let term = term ~default_root_is_cwd:false

let build = build ~default_root_is_cwd:false

let envs =
Cmd.Env.
[ info
Expand Down
10 changes: 10 additions & 0 deletions bin/common.mli
Original file line number Diff line number Diff line change
Expand Up @@ -86,3 +86,13 @@ module Let_syntax : sig
val ( and+ ) :
'a Cmdliner.Term.t -> 'b Cmdliner.Term.t -> ('a * 'b) Cmdliner.Term.t
end

module Builder : sig
type t

val set_root : t -> string -> t

val term : t Cmdliner.Term.t
end

val build : Builder.t -> t
7 changes: 2 additions & 5 deletions bin/dune_init.ml
Original file line number Diff line number Diff line change
Expand Up @@ -457,12 +457,9 @@ module Component = struct
in
lib_target @ test_target

let proj
({ context; common; options } as opts : Options.Project.t Options.t) =
let proj ({ common; options; _ } as opts : Options.Project.t Options.t) =
let ({ template; pkg; _ } : Options.Project.t) = options in
let dir =
Path.relative context.dir (Dune_lang.Atom.to_string common.name)
in
let dir = Path.root in
let name =
Package.Name.parse_string_exn
(Loc.none, Dune_lang.Atom.to_string common.name)
Expand Down
34 changes: 25 additions & 9 deletions bin/init.ml
Original file line number Diff line number Diff line change
Expand Up @@ -80,12 +80,13 @@ let common : Component.Options.Common.t Term.t =
in
{ Component.Options.Common.name; libraries; pps }

let context : Init_context.t Term.t =
let path =
let docv = "PATH" in
Arg.(value & pos 1 (some string) None & info [] ~docv)

let context_cwd : Init_context.t Term.t =
let+ common_term = Common.term_with_default_root_is_cwd
and+ path =
let docv = "PATH" in
Arg.(value & pos 1 (some string) None & info [] ~docv)
in
and+ path = path in
let config = Common.init common_term in
Scheduler.go ~common:common_term ~config (fun () ->
Memo.run (Init_context.make path))
Expand Down Expand Up @@ -116,7 +117,7 @@ let executable =
let man = [] in
let kind = "executable" in
Cmd.v (Cmd.info kind ~doc ~man)
@@ let+ context = context
@@ let+ context = context_cwd
and+ common = common
and+ public = public in
Component.init (Executable { context; common; options = { public } });
Expand All @@ -127,7 +128,7 @@ let library =
let man = [] in
let kind = "library" in
Cmd.v (Cmd.info kind ~doc ~man)
@@ let+ context = context
@@ let+ context = context_cwd
and+ common = common
and+ public = public
and+ inline_tests = inline_tests in
Expand All @@ -143,12 +144,13 @@ let test =
let man = [] in
let kind = "test" in
Cmd.v (Cmd.info kind ~doc ~man)
@@ let+ context = context
@@ let+ context = context_cwd
and+ common = common in
Component.init (Test { context; common; options = () });
print_completion kind common.name

let project =
let module C = Common in
let open Component.Options in
let doc =
"A project is a predefined composition of components arranged in a \
Expand All @@ -159,7 +161,8 @@ let project =
in
let man = [] in
Cmd.v (Cmd.info "project" ~doc ~man)
@@ let+ context = context
@@ let+ common_builder = C.Builder.term
and+ path = path
and+ common = common
and+ inline_tests = inline_tests
and+ template =
Expand Down Expand Up @@ -187,6 +190,19 @@ let project =
& opt (some (enum Project.Pkg.commands)) None
& info [ "pkg" ] ~docv ~doc)
in
let context =
let init_context = Init_context.make path in
let name = Dune_lang.Atom.to_string common.name in
let root =
match path with
| Some path -> Filename.concat path name
| None -> name
in
let common = C.Builder.set_root common_builder root |> C.build in
let _ = Fpath.mkdir_p root in
let config = C.init common in
Scheduler.go ~common ~config (fun () -> Memo.run init_context)
in
Component.init
(Project { context; common; options = { template; inline_tests; pkg } });
print_completion "project" common.name
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -53,7 +53,9 @@ fields:
> EOF
$ dune init project foo
Entering directory 'foo'
Success: initialized project component named foo
Leaving directory 'foo'
But if we do the build we do get an error:
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,54 @@
Ensure that running `dune init proj ...` doesn't create a spurious _build
directory in the current directory.
$ dune init proj foo
Entering directory 'foo'
Success: initialized project component named foo
Leaving directory 'foo'
$ ls
foo
$ ls foo
_build
bin
dune-project
foo.opam
lib
test
$ dune init proj foo bar
Entering directory 'bar/foo'
Success: initialized project component named foo
Leaving directory 'bar/foo'
$ ls
bar
foo
$ ls bar
foo
$ ls bar/foo
_build
bar
bin
dune-project
foo.opam
lib
test
$ mkdir baz
$ dune init proj foo baz
Entering directory 'baz/foo'
Success: initialized project component named foo
Leaving directory 'baz/foo'
$ ls
bar
baz
foo
$ ls baz
foo
$ ls baz/foo
_build
baz
bin
dune-project
foo.opam
lib
test
15 changes: 15 additions & 0 deletions test/blackbox-tests/test-cases/dune-init.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -293,14 +293,19 @@ Initializing executable projects
We can init a new executable project:
$ dune init proj test_exec_proj
Entering directory 'test_exec_proj'
Success: initialized project component named test_exec_proj
Leaving directory 'test_exec_proj'
The generated project contains all expected sub-components:
$ ls test_exec_proj/**
test_exec_proj/dune-project
test_exec_proj/test_exec_proj.opam
test_exec_proj/_build:
log
test_exec_proj/bin:
dune
main.ml
Expand Down Expand Up @@ -402,14 +407,19 @@ Initializing library projects
We can init a new library project:
$ dune init proj test_lib_proj --kind lib
Entering directory 'test_lib_proj'
Success: initialized project component named test_lib_proj
Leaving directory 'test_lib_proj'
The generated project contains all expected sub-components:
$ ls test_lib_proj/**
test_lib_proj/dune-project
test_lib_proj/test_lib_proj.opam
test_lib_proj/_build:
log
test_lib_proj/lib:
dune
Expand Down Expand Up @@ -504,14 +514,19 @@ Initializing projects using Esy
We can init a project using Esy:
$ dune init proj test_esy_proj --pkg esy
Entering directory 'test_esy_proj'
Success: initialized project component named test_esy_proj
Leaving directory 'test_esy_proj'
The esy project contains all expected sub-components:
$ ls test_esy_proj/**
test_esy_proj/dune-project
test_esy_proj/package.json
test_esy_proj/_build:
log
test_esy_proj/bin:
dune
main.ml
Expand Down

0 comments on commit 1e18a5e

Please sign in to comment.