File tree Expand file tree Collapse file tree 4 files changed +39
-8
lines changed
test/blackbox-tests/test-cases/melange Expand file tree Collapse file tree 4 files changed +39
-8
lines changed Original file line number Diff line number Diff line change @@ -214,3 +214,7 @@ let rules ~obj_dir ~modules ~sandbox ~impl ~sctx ~dir =
214214 in
215215 Dep_graph. make ~dir ~per_module )
216216;;
217+
218+ let deps_of ~obj_dir ~modules ~sandbox ~impl ~dir ~sctx module_ =
219+ deps_of ~obj_dir ~modules ~sandbox ~impl ~dir ~sctx (Normal module_)
220+ ;;
Original file line number Diff line number Diff line change @@ -27,3 +27,14 @@ val rules
2727 -> sctx:Super_context. t
2828 -> dir:Path.Build. t
2929 -> Dep_graph.Ml_kind. t Memo. t
30+
31+ val deps_of
32+ : obj_dir:Path.Build. t Obj_dir. t
33+ -> modules:Modules.With_vlib. t
34+ -> sandbox:Sandbox_config. t
35+ -> impl:Virtual_rules. t
36+ -> dir:Path.Build. t
37+ -> sctx:Super_context. t
38+ -> Module. t
39+ -> ml_kind:Ml_kind. t
40+ -> Module. t list Action_builder. t Memo. t
Original file line number Diff line number Diff line change @@ -320,13 +320,29 @@ let build_js
320320 ; Dep src
321321 ]
322322 in
323- With_targets. map_build command ~f: ( fun command ->
324- let open Action_builder.O in
325- match local_modules_and_obj_dir with
326- | Some ( modules , obj_dir ) ->
323+ match local_modules_and_obj_dir with
324+ | Some ( modules , obj_dir ) ->
325+ With_targets. map_build command ~f: ( fun command ->
326+ let open Action_builder.O in
327327 let paths =
328328 let + module_deps =
329- Dep_rules. immediate_deps_of m modules ~obj_dir ~ml_kind: Impl
329+ let deps =
330+ let open Memo.O in
331+ let + deps, _ =
332+ Memo.Implicit_output. collect Rules. implicit_output (fun () ->
333+ Dep_rules. deps_of
334+ ~obj_dir
335+ ~modules
336+ ~sandbox: Sandbox_config. default
337+ ~impl: Virtual_rules. no_implements
338+ ~dir
339+ ~sctx
340+ ~ml_kind: Impl
341+ m)
342+ in
343+ deps
344+ in
345+ Action_builder. of_memo_join deps
330346 in
331347 List. fold_left module_deps ~init: [] ~f: (fun acc dep_m ->
332348 if Module. has dep_m ~ml_kind: Impl
@@ -338,8 +354,8 @@ let build_js
338354 cmj_file :: acc)
339355 else acc)
340356 in
341- Action_builder. dyn_paths_unit paths >>> command
342- | None -> command)
357+ Action_builder. dyn_paths_unit paths >>> command)
358+ | None -> command
343359 in
344360 Super_context. add_rule sctx ~dir ~loc ~mode build)
345361;;
Original file line number Diff line number Diff line change @@ -115,7 +115,7 @@ file, and it's not present
115115 > let x = "foo"
116116 > EOF
117117
118- $ DUNE_SANDBOX=none dune build @melange
118+ $ dune build @melange
119119
120120`foo.js` was manually written, therefore it's present. `sub.js` is an alias
121121file, and it's not present
You can’t perform that action at this time.
0 commit comments