Skip to content

Commit

Permalink
_
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg authored and anmonteiro committed Mar 9, 2023
1 parent 383b9b4 commit 2e73c70
Show file tree
Hide file tree
Showing 4 changed files with 23 additions and 32 deletions.
10 changes: 7 additions & 3 deletions src/dune_rules/dep_conf_eval.ml
Expand Up @@ -281,8 +281,7 @@ let unnamed ?(sandbox = Sandbox_config.no_special_requirements) ~expander l =
())
, List.fold_left l ~init:sandbox ~f:add_sandbox_config )

let unnamed_get_paths ?(sandbox = Sandbox_config.no_special_requirements)
~expander l =
let unnamed_get_paths ~expander l =
let expander = prepare_expander expander in
( (let+ paths =
List.fold_left l ~init:(Action_builder.return []) ~f:(fun acc x ->
Expand All @@ -291,4 +290,9 @@ let unnamed_get_paths ?(sandbox = Sandbox_config.no_special_requirements)
paths :: acc)
in
Path.Set.of_list (List.concat paths))
, List.fold_left l ~init:sandbox ~f:add_sandbox_config )
, List.fold_left l ~init:None ~f:(fun acc config ->
Some
(match acc with
| None ->
add_sandbox_config Sandbox_config.no_special_requirements config
| Some acc -> add_sandbox_config acc config)) )
5 changes: 2 additions & 3 deletions src/dune_rules/dep_conf_eval.mli
Expand Up @@ -15,10 +15,9 @@ val unnamed :
(** Evaluates unnamed dependency specifications. Returns the paths to the newly
evaluated dependencies. *)
val unnamed_get_paths :
?sandbox:Sandbox_config.t
-> expander:Expander.t
expander:Expander.t
-> Dep_conf.t list
-> Path.Set.t Action_builder.t * Sandbox_config.t
-> Path.Set.t Action_builder.t * Sandbox_config.t option

(** Evaluates named dependency specifications. Return the action build that
register dependencies as well as an expander that can be used to expand to
Expand Down
5 changes: 2 additions & 3 deletions src/dune_rules/install_rules.ml
Expand Up @@ -561,8 +561,8 @@ end = struct
, Dune_package.Entry.Deprecated_library_name
{ loc; old_public_name; new_public_name } ))
| Library lib ->
let info = Lib.Local.info lib in
let* dir_contents =
let info = Lib.Local.info lib in
let dir = Lib_info.src_dir info in
Dir_contents.get sctx ~dir
in
Expand Down Expand Up @@ -590,8 +590,8 @@ end = struct
Dir_contents.ocaml dir_contents
>>| Ml_sources.modules ~for_:(Library name)
and* melange_runtime_deps =
let info = Lib.info lib in
match Lib_info.melange_runtime_deps info with
| External _paths -> assert false
| Local dep_conf ->
let+ melange_runtime_deps =
let* expander =
Expand All @@ -600,7 +600,6 @@ end = struct
Melange_rules.eval_runtime_deps ~expander dep_conf
in
Path.Set.to_list melange_runtime_deps
| External _paths -> assert false
in
let+ sub_systems =
Lib.to_dune_lib lib
Expand Down
35 changes: 12 additions & 23 deletions src/dune_rules/melange/melange_rules.ml
Expand Up @@ -36,7 +36,7 @@ let lib_output_path ~output_dir ~lib_dir src =
|> Option.value_exn
|> String.drop_prefix_if_exists ~prefix:"/"
in
if dir = "" then output_dir else Path.relative output_dir dir
if dir = "" then output_dir else Path.Build.relative output_dir dir

let make_js_name ~js_ext ~output m =
let basename = Melange.js_basename m ^ js_ext in
Expand All @@ -45,10 +45,7 @@ let make_js_name ~js_ext ~output m =
let src_dir =
Module.file m ~ml_kind:Impl |> Option.value_exn |> Path.parent_exn
in
let output_dir =
let output_dir = Path.build output_dir in
lib_output_path ~output_dir ~lib_dir src_dir |> Path.as_in_build_dir_exn
in
let output_dir = lib_output_path ~output_dir ~lib_dir src_dir in
Path.Build.relative output_dir basename
| `Private_library_or_emit target_dir ->
let dst_dir =
Expand Down Expand Up @@ -252,35 +249,27 @@ let setup_emit_cmj_rules ~sctx ~dir ~scope ~expander ~dir_contents
Buildable_rules.with_lib_deps ctx compile_info ~dir ~f

module Runtime_deps = struct
let to_action_builder ~expander dep_conf =
let runtime_deps, _sandbox =
Dep_conf_eval.unnamed_get_paths ~expander dep_conf
in
runtime_deps

let targets ~output deps =
Path.Set.fold ~init:([], []) deps ~f:(fun src (copy, non_copy) ->
match output with
| `Public_library (lib_dir, output_dir) ->
((src, lib_output_path ~output_dir ~lib_dir src) :: copy, non_copy)
| `Private_library_or_emit output_dir -> (
match Path.as_in_build_dir src with
| None -> (copy, src :: non_copy)
| Some src_build ->
let target = Path.Build.drop_build_context_exn src_build in
((src, Path.Build.append_source output_dir target) :: copy, non_copy)
)
| `Public_library (lib_dir, output_dir) ->
let output_dir = Path.build output_dir in
( ( src
, lib_output_path ~output_dir ~lib_dir src
|> Path.as_in_build_dir_exn )
:: copy
, non_copy ))
))
end

let eval_runtime_deps ~expander (deps : Dep_conf.t list) =
let runtime_deps, sandbox = Dep_conf_eval.unnamed_get_paths ~expander deps in
Option.iter sandbox ~f:(fun _ ->
(* TODO loc *)
User_error.raise [ Pp.text "sandbox settings are not allowed" ]);
let open Memo.O in
let builder = Runtime_deps.to_action_builder ~expander deps in
let+ paths, _ = Action_builder.run builder Eager in
let+ paths, _ = Action_builder.run runtime_deps Eager in
paths

let setup_runtime_assets_rules sctx ~dir ~target_dir ~mode
Expand All @@ -293,14 +282,14 @@ let setup_runtime_assets_rules sctx ~dir ~target_dir ~mode
eval_runtime_deps ~expander mel.runtime_deps
| `Library lib_info -> (
match Lib_info.melange_runtime_deps lib_info with
| External paths -> Memo.return (Path.Set.of_list paths)
| Local dep_conf ->
let dir =
let info = Lib_info.as_local_exn lib_info in
Lib_info.src_dir info
in
let* expander = Super_context.expander sctx ~dir in
eval_runtime_deps ~expander dep_conf
| External paths -> Memo.return (Path.Set.of_list paths))
eval_runtime_deps ~expander dep_conf)
in
let copy, non_copy = Runtime_deps.targets ~output runtime_dep_paths in
let+ () =
Expand Down

0 comments on commit 2e73c70

Please sign in to comment.