Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
41 changes: 32 additions & 9 deletions src/dune_rules/pkg_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -439,6 +439,8 @@ module Pkg = struct
; build_command : Build_command.t option
; install_command : Dune_lang.Action.t option
; depends : t list
; depends_on_dune : bool
(* whether the package declares a dependency on Dune, even if Dune is stripped from [depends] *)
; depexts : Depexts.t list
; info : Pkg_info.t
; paths : Path.t Paths.t
Expand Down Expand Up @@ -1202,6 +1204,7 @@ module DB = struct
type entry =
{ pkg : Pkg.t
; deps : dep list
; has_dune_dep : bool
; pkg_digest : Pkg_digest.t
}

Expand Down Expand Up @@ -1231,24 +1234,30 @@ module DB = struct
Package.Name.Table.find_or_add cache pkg.info.name ~f:(fun name ->
let seen_set = Package.Name.Set.add seen_set name in
let seen_list = pkg :: seen_list in
let deps =
let system_deps, deps =
Dune_pkg.Lock_dir.Conditional_choice.choose_for_platform pkg.depends ~platform
|> Option.value ~default:[]
|> List.filter_map
|> List.partition_map
~f:(fun { Dune_pkg.Lock_dir.Dependency.name; loc = dep_loc } ->
if Package.Name.Set.mem system_provided name
then None
then Left name
else (
let dep_pkg = Package.Name.Map.find_exn pkgs_by_name name in
let dep_entry = compute_entry dep_pkg ~seen_set ~seen_list in
Some { dep_pkg; dep_loc; dep_pkg_digest = dep_entry.pkg_digest }))
Right { dep_pkg; dep_loc; dep_pkg_digest = dep_entry.pkg_digest }))
in
let has_dune_dep =
List.mem
~equal:Dune_lang.Package_name.equal
system_deps
Dune_pkg.Dune_dep.name
in
let pkg_digest =
Pkg_digest.create
pkg
(List.map deps ~f:(fun { dep_pkg_digest; _ } -> dep_pkg_digest))
in
{ pkg; deps; pkg_digest })
{ pkg; deps; has_dune_dep; pkg_digest })
in
Package.Name.Map.map
pkgs_by_name
Expand All @@ -1271,8 +1280,8 @@ module DB = struct
dependencies are identical as a sanity check. *)
let union_check
pkg_digest
({ pkg = pkg_a; deps = deps_a; pkg_digest = _ } as entry)
{ pkg = pkg_b; deps = deps_b; pkg_digest = _ }
({ pkg = pkg_a; deps = deps_a; has_dune_dep = _; pkg_digest = _ } as entry)
{ pkg = pkg_b; deps = deps_b; has_dune_dep = _; pkg_digest = _ }
=
if not (Pkg.equal (Pkg.remove_locs pkg_a) (Pkg.remove_locs pkg_b))
then
Expand Down Expand Up @@ -1475,6 +1484,7 @@ end = struct
; enabled_on_platforms = _
} as pkg
; deps
; has_dune_dep
; pkg_digest = _
} ->
assert (Package.Name.equal pkg_digest.name info.name);
Expand Down Expand Up @@ -1589,6 +1599,7 @@ end = struct
; build_command
; install_command
; depends
; depends_on_dune = has_dune_dep
; depexts
; paths
; write_paths
Expand Down Expand Up @@ -2234,9 +2245,21 @@ let build_rule context_name ~source_deps (pkg : Pkg.t) =
|> Action_builder.progn
in
let deps = Dep.Set.union source_deps (Pkg.package_deps pkg) in
let depend_on_dune =
match pkg.depends_on_dune with
| false -> Action_builder.return ()
| true ->
Sys.executable_name
|> Path.External.of_string
|> Path.external_
|> Action_builder.path
in
let open Action_builder.O in
let action_builder =
Action_builder.deps deps >>> depend_on_dune |> Action_builder.with_no_targets
in
let open Action_builder.With_targets.O in
Action_builder.deps deps
|> Action_builder.with_no_targets
action_builder
(* TODO should we add env deps on these? *)
>>> add_env (Pkg.exported_env pkg) build_action
|> Action_builder.With_targets.add_directories
Expand Down
18 changes: 14 additions & 4 deletions src/dune_rules/run_with_path.ml
Original file line number Diff line number Diff line change
Expand Up @@ -141,11 +141,21 @@ module Spec = struct
|> String.concat ~sep:"")
in
let metadata = Process.create_metadata ~purpose:ectx.metadata.purpose () in
let dune_folder =
let bin_folder = Temp.create Dir ~prefix:"dune" ~suffix:"self-in-path" in
let src = Path.of_string Sys.executable_name in
let dst = Path.relative bin_folder "dune" in
Io.portable_symlink ~src ~dst;
Path.to_string bin_folder
in
let env =
Env.add
eenv.env
~var:"OCAMLFIND_DESTDIR"
~value:(Path.to_absolute_filename ocamlfind_destdir)
eenv.env
|> Env.add
~var:"OCAMLFIND_DESTDIR"
~value:(Path.to_absolute_filename ocamlfind_destdir)
|> Env.update ~var:"PATH" ~f:(function
| None -> Some dune_folder
| Some path -> Some (sprintf "%s:%s" dune_folder path))
in
Output.with_error
~accepted_exit_codes:eenv.exit_codes
Expand Down
5 changes: 4 additions & 1 deletion test/blackbox-tests/test-cases/pkg/different-dune-in-path.t
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,8 @@ Make lockfiles for the packages.
> (build
> (run dune build -p %{pkg-self:name} @install))
>
> (depends dune)
>
> (source
> (fetch
> (url $PWD/foo.tar)))
Expand All @@ -51,6 +53,8 @@ Make lockfiles for the packages.
> ; Exercise that the dune exe can be located when it's launched by a subprocess.
> (run sh -c "dune build -p %{pkg-self:name} @install"))
>
> (depends dune)
>
> (source
> (fetch
> (url $PWD/bar.tar)))
Expand Down Expand Up @@ -91,7 +95,6 @@ Call Dune with an absolute PATH as argv[0]:
$ PATH=$fakepath $DUNE build "$pkg_root/$foo_digest/target/"
Fake dune! (args: build -p foo @install)
$ PATH=$fakepath $DUNE build "$pkg_root/$bar_digest/target/"
Fake dune! (args: build -p bar @install)

Make sure that fake dune is not picked up when dune is called with argv[0] = "dune":

Expand Down
Loading