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 committed Feb 28, 2023
1 parent 9340ec2 commit e6dc5c2
Show file tree
Hide file tree
Showing 3 changed files with 6 additions and 14 deletions.
9 changes: 3 additions & 6 deletions src/dune_rules/melange/melange_binary.ml
Original file line number Diff line number Diff line change
Expand Up @@ -32,9 +32,6 @@ let where =
let+ res = Memo.exec memo melc in
Some res)
in
Option.map
~f:(fun dirs ->
String.split ~on:Bin.path_sep dirs
|> List.map ~f:Path.External.of_string)
melange_dirs
|> Option.value ~default:[]
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.External.t list Memo.t
Super_context.t -> loc:Loc.t option -> dir:Path.Build.t -> Path.t list Memo.t
6 changes: 2 additions & 4 deletions src/dune_rules/merlin/merlin.ml
Original file line number Diff line number Diff line change
Expand Up @@ -476,10 +476,8 @@ module Unprocessed = struct
let+ dirs = Melange_binary.where sctx ~loc:None ~dir in
match dirs with
| [] -> (None, [])
| [ stdlib_dir ] -> (Some (Path.external_ stdlib_dir), [])
| stdlib_dir :: extra_obj_dirs ->
( Some (Path.external_ stdlib_dir)
, List.map ~f:Path.external_ extra_obj_dirs ))
| [ 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 Down

0 comments on commit e6dc5c2

Please sign in to comment.