Skip to content

Commit

Permalink
merlin: print absolute path to melc
Browse files Browse the repository at this point in the history
Signed-off-by: Javier Chavarri <[email protected]>
  • Loading branch information
jchavarri committed Nov 29, 2022
1 parent c16eec2 commit c6e8bd6
Show file tree
Hide file tree
Showing 2 changed files with 36 additions and 13 deletions.
39 changes: 30 additions & 9 deletions src/dune_rules/merlin.ml
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,7 @@ module Processed = struct
; flags : string list
; extensions : string Ml_kind.Dict.t list
; mode : [ `Ocaml | `Melange ]
; melc_compiler : Action.Prog.t
}

(* ...but modules can have different preprocessing specifications*)
Expand Down Expand Up @@ -69,9 +70,9 @@ module Processed = struct

let serialize_path = Path.to_absolute_filename

let melc_ppx_flg = "melc -as-ppx -bs-jsx 3"

let to_sexp ~pp { stdlib_dir; obj_dirs; src_dirs; flags; extensions; mode } =
let to_sexp ~pp
{ stdlib_dir; obj_dirs; src_dirs; flags; extensions; mode; melc_compiler }
=
let make_directive tag value = Sexp.List [ Atom tag; value ] in
let make_directive_of_path tag path =
make_directive tag (Sexp.Atom (serialize_path path))
Expand Down Expand Up @@ -107,10 +108,19 @@ module Processed = struct
in
match mode with
| `Ocaml -> flags
| `Melange ->
make_directive "FLG"
(Sexp.List [ Atom (Pp_kind.to_flag Ppx); Atom melc_ppx_flg ])
:: flags
| `Melange -> (
match melc_compiler with
| Error _ -> flags
| Ok path ->
make_directive "FLG"
(Sexp.List
[ Atom (Pp_kind.to_flag Ppx)
; Atom (serialize_path path)
; Atom "-as-ppx"
; Atom "-bs-jsx"
; Atom "3"
])
:: flags)
in
let suffixes =
List.map extensions ~f:(fun { Ml_kind.Dict.impl; intf } ->
Expand Down Expand Up @@ -161,7 +171,8 @@ module Processed = struct
match mode with
| `Ocaml -> ()
| `Melange ->
print ("# FLG -ppx " ^ quote_for_dot_merlin melc_ppx_flg ^ "\n")
print
("# FLG -ppx " ^ quote_for_dot_merlin "melc -as-ppx -bs-jsx 3" ^ "\n")
in
Buffer.contents b

Expand Down Expand Up @@ -222,6 +233,7 @@ module Processed = struct
; flags
; extensions
; mode
; melc_compiler = _
}
}
->
Expand Down Expand Up @@ -441,12 +453,21 @@ module Unprocessed = struct
obj_dir_of_lib `Public mode (Lib_info.obj_dir info)
in
Path.Set.add obj_dirs public_cmi_dir )))
and+ melc_compiler =
Action_builder.of_memo (Melange_binary.melc sctx ~dir)
in
let src_dirs =
Path.Set.union src_dirs
(Path.Set.of_list_map ~f:Path.source more_src_dirs)
in
{ Processed.stdlib_dir; src_dirs; obj_dirs; flags; extensions; mode }
{ Processed.stdlib_dir
; src_dirs
; obj_dirs
; flags
; extensions
; mode
; melc_compiler
}
and+ pp_config = pp_config t sctx ~expander in
let modules =
(* And copy for each module the resulting pp flags *)
Expand Down
10 changes: 6 additions & 4 deletions test/blackbox-tests/test-cases/melange/merlin.t
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,8 @@

$ melc_where="$(melc -where)"
$ export BUILD_PATH_PREFIX_MAP="/MELC_WHERE=$melc_where:$BUILD_PATH_PREFIX_MAP"
$ melc_compiler="$(which melc)"
$ export BUILD_PATH_PREFIX_MAP="/MELC_COMPILER=$melc_compiler:$BUILD_PATH_PREFIX_MAP"

$ cat >dune-project <<EOF
> (lang dune 3.6)
Expand Down Expand Up @@ -31,9 +33,9 @@
All 3 entries (Foo, Foo__ and Bar) contain a ppx directive

$ dune ocaml merlin dump-config $PWD | grep -i "ppx"
(FLG (-ppx "melc -as-ppx -bs-jsx 3"))
(FLG (-ppx "melc -as-ppx -bs-jsx 3"))
(FLG (-ppx "melc -as-ppx -bs-jsx 3"))
(FLG (-ppx /MELC_COMPILER -as-ppx -bs-jsx 3))
(FLG (-ppx /MELC_COMPILER -as-ppx -bs-jsx 3))
(FLG (-ppx /MELC_COMPILER -as-ppx -bs-jsx 3))

$ target=output
$ cat >dune <<EOF
Expand All @@ -51,7 +53,7 @@ All 3 entries (Foo, Foo__ and Bar) contain a ppx directive
The melange.emit entry contains a ppx directive

$ dune ocaml merlin dump-config $PWD | grep -i "ppx"
(FLG (-ppx "melc -as-ppx -bs-jsx 3"))
(FLG (-ppx /MELC_COMPILER -as-ppx -bs-jsx 3))

$ dune ocaml dump-dot-merlin $PWD
EXCLUDE_QUERY_DIR
Expand Down

0 comments on commit c6e8bd6

Please sign in to comment.