Skip to content

Commit

Permalink
fix: allow inline test expansion everywhere
Browse files Browse the repository at this point in the history
do not require populating this field everywhere

Signed-off-by: Rudi Grinberg <[email protected]>

<!-- ps-id: 721b8898-b290-481d-9d0a-ce6d9b9f7161 -->
  • Loading branch information
rgrinberg committed Mar 2, 2024
1 parent 63fb514 commit 0822985
Show file tree
Hide file tree
Showing 2 changed files with 8 additions and 11 deletions.
9 changes: 6 additions & 3 deletions src/dune_rules/expander.ml
Original file line number Diff line number Diff line change
Expand Up @@ -449,7 +449,7 @@ let ocaml_config_var (var : Pform.Var.t) (ocaml_config : Ocaml_config.t) =
| _ -> Code_error.raise "not a ocaml_config variables" [ "var", Pform.Var.to_dyn var ]
;;

let expand_pform_var (context : Context.t) ~source (var : Pform.Var.t) =
let expand_pform_var (context : Context.t) ~dir ~source (var : Pform.Var.t) =
let open Memo.O in
let ocaml = Context.ocaml context in
match var with
Expand All @@ -462,7 +462,6 @@ let expand_pform_var (context : Context.t) ~source (var : Pform.Var.t) =
| Partition
| Impl_files
| Intf_files
| Inline_tests
| Test
| Corrected_suffix ->
(* These would be part of [bindings] *)
Expand Down Expand Up @@ -534,6 +533,10 @@ let expand_pform_var (context : Context.t) ~source (var : Pform.Var.t) =
|> string
|> Memo.return
|> static
| Inline_tests ->
(let+ inline_tests = Env_stanza_db.inline_tests ~dir in
Dune_env.Inline_tests.to_string inline_tests |> string)
|> static
;;

let ocaml_config_macro source macro_invocation context =
Expand Down Expand Up @@ -660,7 +663,7 @@ let expand_pform_gen ~(context : Context.t) ~bindings ~dir ~source (pform : Pfor
| Some x -> Direct x
| None ->
(match pform with
| Var var -> expand_pform_var context ~source var
| Var var -> expand_pform_var context ~dir ~source var
| Macro macro_invocation -> expand_pform_macro context ~dir ~source macro_invocation)
;;

Expand Down
10 changes: 2 additions & 8 deletions src/dune_rules/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -49,14 +49,8 @@ let expander_for_artifacts ~scope ~external_env ~root_expander ~dir =
;;

let extend_expander t ~dir ~expander_for_artifacts =
let+ artifacts_host = artifacts_host t ~dir
and+ bindings =
let+ inline_tests = Env_stanza_db.inline_tests ~dir in
let str = Dune_env.Inline_tests.to_string inline_tests in
Pform.Map.singleton (Var Inline_tests) [ Value.String str ]
in
Expander.add_bindings ~bindings expander_for_artifacts
|> Expander.set_artifacts ~artifacts_host
let+ artifacts_host = artifacts_host t ~dir in
Expander.set_artifacts expander_for_artifacts ~artifacts_host
;;

let expander t ~dir =
Expand Down

0 comments on commit 0822985

Please sign in to comment.