Skip to content

Commit

Permalink
fix(melange): add loc to Melange_binary.{melc,where} (#6601)
Browse files Browse the repository at this point in the history
Signed-off-by: Antonio Nuno Monteiro <[email protected]>
  • Loading branch information
anmonteiro authored Nov 29, 2022
1 parent 5a09827 commit 405c0bc
Show file tree
Hide file tree
Showing 5 changed files with 24 additions and 17 deletions.
9 changes: 4 additions & 5 deletions src/dune_rules/melange_binary.ml
Original file line number Diff line number Diff line change
@@ -1,8 +1,7 @@
open Import

let melc sctx ~dir =
(* TODO loc should come from the mode field in the dune file *)
Super_context.resolve_program sctx ~loc:None ~dir ~hint:"opam install melange"
let melc sctx ~loc ~dir =
Super_context.resolve_program sctx ~loc ~dir ~hint:"opam install melange"
"melc"

let where =
Expand All @@ -18,13 +17,13 @@ let where =
let memo =
Memo.create "melange-where" ~input:(module Path) ~cutoff:Path.equal impl
in
fun sctx ~dir ->
fun sctx ~loc ~dir ->
let open Memo.O in
let* env = Super_context.env_node sctx ~dir >>= Env_node.external_env in
match Env.get env "MELANGELIB" with
| Some p -> Memo.return (Some (Path.of_string p))
| None -> (
let* melc = melc sctx ~dir in
let* melc = melc sctx ~loc ~dir in
match melc with
| Error _ -> Memo.return None
| Ok melc ->
Expand Down
12 changes: 10 additions & 2 deletions src/dune_rules/melange_binary.mli
Original file line number Diff line number Diff line change
@@ -1,5 +1,13 @@
open Import

val melc : Super_context.t -> dir:Path.Build.t -> Action.Prog.t Memo.t
val melc :
Super_context.t
-> loc:Loc.t option
-> dir:Path.Build.t
-> Action.Prog.t Memo.t

val where : Super_context.t -> dir:Path.Build.t -> Path.t option Memo.t
val where :
Super_context.t
-> loc:Loc.t option
-> dir:Path.Build.t
-> Path.t option Memo.t
15 changes: 7 additions & 8 deletions src/dune_rules/melange_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,7 @@ let build_js ~loc ~dir ~pkg_name ~mode ~module_system ~dst_dir ~obj_dir ~sctx
~lib_deps_js_includes ~js_ext m =
let cm_kind = Lib_mode.Cm_kind.Melange Cmj in
let open Memo.O in
let* compiler = Melange_binary.melc sctx ~dir in
let* compiler = Melange_binary.melc sctx ~loc:(Some loc) ~dir in
let src = Obj_dir.Module.cm_file_exn obj_dir m ~kind:cm_kind in
let output = make_js_name ~js_ext ~dst_dir m in
let obj_dir =
Expand All @@ -75,7 +75,7 @@ let build_js ~loc ~dir ~pkg_name ~mode ~module_system ~dst_dir ~obj_dir ~sctx
"--bs-module-type" :: js_modules_str :: pkg_name_args
in
let lib_deps_js_includes = Command.Args.as_any lib_deps_js_includes in
Super_context.add_rule sctx ~dir ?loc ~mode
Super_context.add_rule sctx ~dir ~loc ~mode
(Command.run
~dir:(Path.build (Super_context.context sctx).build_dir)
compiler
Expand Down Expand Up @@ -140,9 +140,8 @@ let add_rules_for_entries ~sctx ~dir ~expander ~dir_contents ~scope
let* () =
Memo.parallel_iter module_list ~f:(fun m ->
(* Should we check module kind? *)
build_js ~dir ~loc:(Some loc) ~pkg_name ~mode
~module_system:mel.module_system ~dst_dir ~obj_dir ~sctx
~lib_deps_js_includes ~js_ext m)
build_js ~dir ~loc ~pkg_name ~mode ~module_system:mel.module_system
~dst_dir ~obj_dir ~sctx ~lib_deps_js_includes ~js_ext m)
in
let* () =
match mel.alias with
Expand Down Expand Up @@ -181,6 +180,7 @@ let add_rules_for_libraries ~dir ~scope ~target_dir ~sctx ~requires_link ~mode
in
let lib = local_of_lib ~loc:mel.loc lib in
let info = Lib.Local.info lib in
let loc = Lib_info.loc info in
let lib_dir = Lib_info.src_dir info in
let obj_dir = Lib_info.obj_dir info in
let dst_dir = lib_output_dir ~target_dir ~lib_dir in
Expand All @@ -200,9 +200,8 @@ let add_rules_for_libraries ~dir ~scope ~target_dir ~sctx ~requires_link ~mode
in
Memo.parallel_iter source_modules
~f:
(build_js ~loc:None ~dir ~pkg_name ~mode
~module_system:mel.module_system ~dst_dir ~obj_dir ~sctx
~lib_deps_js_includes ~js_ext))
(build_js ~loc ~dir ~pkg_name ~mode ~module_system:mel.module_system
~dst_dir ~obj_dir ~sctx ~lib_deps_js_includes ~js_ext))

let compile_info ~scope (mel : Melange_stanzas.Emit.t) =
let open Memo.O in
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/merlin.ml
Original file line number Diff line number Diff line change
Expand Up @@ -395,7 +395,7 @@ module Unprocessed = struct
@@
match t.config.mode with
| `Ocaml -> Memo.return (Some stdlib_dir)
| `Melange -> Melange_binary.where sctx ~dir
| `Melange -> Melange_binary.where sctx ~loc:None ~dir
in
let+ flags = flags
and+ src_dirs, obj_dirs =
Expand Down
3 changes: 2 additions & 1 deletion src/dune_rules/module_compilation.ml
Original file line number Diff line number Diff line change
Expand Up @@ -96,7 +96,8 @@ let build_cm cctx ~force_write_cmi ~precompiled_cmi ~cm_kind (m : Module.t)
let* compiler =
match mode with
| Melange ->
let+ melc = Melange_binary.melc sctx ~dir in
let loc = CC.loc cctx in
let+ melc = Melange_binary.melc sctx ~loc ~dir in
Some melc
| Ocaml mode ->
Memo.return
Expand Down

0 comments on commit 405c0bc

Please sign in to comment.