Skip to content

Commit 22849f2

Browse files
committed
account for enabled_if in executables
Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
1 parent 848b2c9 commit 22849f2

File tree

4 files changed

+48
-33
lines changed

4 files changed

+48
-33
lines changed

src/dune_rules/expander.ml

+11-4
Original file line numberDiff line numberDiff line change
@@ -702,6 +702,10 @@ module With_deps_if_necessary = struct
702702
Value.to_string v ~dir:(Path.build t.dir)
703703
end
704704

705+
let make_eval_blang ~f ~dir = function
706+
| Blang.Const x -> Memo.Build.return x (* common case *)
707+
| blang -> Blang.eval blang ~dir:(Path.build dir) ~f
708+
705709
module With_reduced_var_set = struct
706710
open Memo.Build.O
707711

@@ -731,6 +735,11 @@ module With_reduced_var_set = struct
731735
let expand_str_partial ~context ~dir sw =
732736
String_with_vars.expand_as_much_as_possible ~dir:(Path.build dir) sw
733737
~f:(expand_pform_opt ~context ~bindings:Pform.Map.empty ~dir)
738+
739+
let eval_blang ~context ~dir blang =
740+
make_eval_blang
741+
~f:(expand_pform ~context ~bindings:Pform.Map.empty ~dir)
742+
~dir blang
734743
end
735744

736745
let expand_and_eval_set t set ~standard =
@@ -744,9 +753,7 @@ let expand_and_eval_set t set ~standard =
744753
Ordered_set_lang.eval set ~standard ~eq:String.equal ~parse:(fun ~loc:_ s ->
745754
s)
746755

747-
let eval_blang t = function
748-
| Blang.Const x -> Memo.Build.return x (* common case *)
749-
| blang ->
750-
Blang.eval blang ~dir:(Path.build t.dir) ~f:(No_deps.expand_pform t)
756+
let eval_blang t blang =
757+
make_eval_blang ~f:(No_deps.expand_pform t) ~dir:t.dir blang
751758

752759
let find_package t pkg = t.find_package pkg

src/dune_rules/expander.mli

+3
Original file line numberDiff line numberDiff line change
@@ -130,6 +130,9 @@ module With_reduced_var_set : sig
130130
-> dir:Path.Build.t
131131
-> String_with_vars.t
132132
-> String_with_vars.t Memo.Build.t
133+
134+
val eval_blang :
135+
context:Context.t -> dir:Path.Build.t -> Blang.t -> bool Memo.Build.t
133136
end
134137

135138
(** Expand forms of the form (:standard \ foo bar). Expansion is only possible

src/dune_rules/super_context.ml

+32-24
Original file line numberDiff line numberDiff line change
@@ -462,31 +462,39 @@ let get_installed_binaries stanzas ~(context : Context.t) =
462462
| Dune_file.Executables
463463
({ install_conf = Some { section = Section Bin; files; _ }; _ } as
464464
exes) -> (
465-
match exes.optional with
466-
| false -> binaries_from_install files
467-
| true ->
468-
let* compile_info =
469-
let project = Scope.project d.scope in
470-
let dune_version = Dune_project.dune_version project in
471-
let+ pps =
472-
Resolve.read_memo_build
473-
(Preprocess.Per_module.with_instrumentation
474-
exes.buildable.preprocess
475-
~instrumentation_backend:
476-
(Lib.DB.instrumentation_backend (Scope.libs d.scope)))
477-
>>| Preprocess.Per_module.pps
465+
let* enabled_if =
466+
Expander.With_reduced_var_set.eval_blang ~context ~dir:d.ctx_dir
467+
exes.enabled_if
468+
in
469+
match enabled_if with
470+
| false -> Memo.Build.return Path.Build.Set.empty
471+
| true -> (
472+
match exes.optional with
473+
| false -> binaries_from_install files
474+
| true ->
475+
let* compile_info =
476+
let project = Scope.project d.scope in
477+
let dune_version = Dune_project.dune_version project in
478+
let+ pps =
479+
Resolve.read_memo_build
480+
(Preprocess.Per_module.with_instrumentation
481+
exes.buildable.preprocess
482+
~instrumentation_backend:
483+
(Lib.DB.instrumentation_backend (Scope.libs d.scope)))
484+
>>| Preprocess.Per_module.pps
485+
in
486+
Lib.DB.resolve_user_written_deps_for_exes (Scope.libs d.scope)
487+
exes.names exes.buildable.libraries ~pps ~dune_version
488+
~allow_overlaps:
489+
exes.buildable.allow_overlapping_dependencies
478490
in
479-
Lib.DB.resolve_user_written_deps_for_exes (Scope.libs d.scope)
480-
exes.names exes.buildable.libraries ~pps ~dune_version
481-
~allow_overlaps:exes.buildable.allow_overlapping_dependencies
482-
in
483-
let available =
484-
Resolve.is_ok (Lib.Compile.direct_requires compile_info)
485-
in
486-
if available then
487-
binaries_from_install files
488-
else
489-
Memo.Build.return Path.Build.Set.empty)
491+
let available =
492+
Resolve.is_ok (Lib.Compile.direct_requires compile_info)
493+
in
494+
if available then
495+
binaries_from_install files
496+
else
497+
Memo.Build.return Path.Build.Set.empty))
490498
| _ -> Memo.Build.return Path.Build.Set.empty)
491499
>>| Path.Build.Set.union_all)
492500
>>| Path.Build.Set.union_all

test/blackbox-tests/test-cases/optional-executable.t/run.t

+2-5
Original file line numberDiff line numberDiff line change
@@ -154,11 +154,8 @@ In the same way as enabled_if:
154154
> (name bar))
155155
> EOF
156156

157-
$ PATH=./bin:$PATH dune build @run-x
158-
Error: No rule found for install bin/dunetestbar
159-
-> required by %{bin:dunetestbar} at dune:3
160-
-> required by alias run-x in dune:1
161-
[1]
157+
$ PATH=./bin:$PATH dune build @run-x --force
158+
binary path: $TESTCASE_ROOT/optional-binary-absent/./bin/dunetestbar
162159

163160
$ cd ..
164161

0 commit comments

Comments
 (0)