Skip to content

Commit

Permalink
melange: interpret melc --where as a list of :-separated paths (#…
Browse files Browse the repository at this point in the history
…7176)

* melange: interpret `melc --where` as a list of `:`-separated paths

Signed-off-by: Antonio Nuno Monteiro <anmonteiro@gmail.com>
  • Loading branch information
anmonteiro authored Feb 28, 2023
1 parent f36109e commit 497c0e3
Show file tree
Hide file tree
Showing 3 changed files with 30 additions and 19 deletions.
27 changes: 16 additions & 11 deletions src/dune_rules/melange/melange_binary.ml
Original file line number Diff line number Diff line change
Expand Up @@ -13,20 +13,25 @@ let where =
@@ Process.run_capture_line ~display:Quiet Process.Strict bin
[ "--where" ]
in
Path.of_string where
where
in
let memo =
Memo.create "melange-where" ~input:(module Path) ~cutoff:Path.equal impl
Memo.create "melange-where" ~input:(module Path) ~cutoff:String.equal impl
in
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 ~loc ~dir in
match melc with
| Error _ -> Memo.return None
| Ok melc ->
let+ res = Memo.exec memo melc in
Some res)
let+ melange_dirs =
match Env.get env "MELANGELIB" with
| Some p -> Memo.return (Some p)
| None -> (
let* melc = melc sctx ~loc ~dir in
match melc with
| Error _ -> Memo.return None
| Ok melc ->
let+ res = Memo.exec memo melc in
Some res)
in
match melange_dirs with
| None -> []
| Some dirs -> Bin.parse_path dirs
5 changes: 1 addition & 4 deletions src/dune_rules/melange/melange_binary.mli
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,4 @@ val melc :
-> Action.Prog.t Memo.t

val where :
Super_context.t
-> loc:Loc.t option
-> dir:Path.Build.t
-> Path.t option Memo.t
Super_context.t -> loc:Loc.t option -> dir:Path.Build.t -> Path.t list Memo.t
17 changes: 13 additions & 4 deletions src/dune_rules/merlin/merlin.ml
Original file line number Diff line number Diff line change
Expand Up @@ -466,12 +466,18 @@ module Unprocessed = struct
} as t) sctx ~dir ~more_src_dirs ~expander =
let open Action_builder.O in
let+ config =
let* stdlib_dir =
let* stdlib_dir, extra_obj_dirs =
Action_builder.of_memo
@@
match t.config.mode with
| `Ocaml -> Memo.return (Some stdlib_dir)
| `Melange -> Melange_binary.where sctx ~loc:None ~dir
| `Ocaml -> Memo.return (Some stdlib_dir, [])
| `Melange -> (
let open Memo.O in
let+ dirs = Melange_binary.where sctx ~loc:None ~dir in
match dirs with
| [] -> (None, [])
| [ stdlib_dir ] -> (Some stdlib_dir, [])
| stdlib_dir :: extra_obj_dirs -> (Some stdlib_dir, extra_obj_dirs))
in
let* flags = flags
and* src_dirs, obj_dirs =
Expand All @@ -481,7 +487,10 @@ module Unprocessed = struct
let+ dirs = src_dirs sctx lib in
(lib, dirs))
>>| List.fold_left
~init:(Path.set_of_source_paths source_dirs, objs_dirs)
~init:
( Path.set_of_source_paths source_dirs
, Path.Set.union objs_dirs (Path.Set.of_list extra_obj_dirs)
)
~f:(fun (src_dirs, obj_dirs) (lib, more_src_dirs) ->
( Path.Set.union src_dirs more_src_dirs
, let public_cmi_dir =
Expand Down

0 comments on commit 497c0e3

Please sign in to comment.