Skip to content

Commit

Permalink
Improve FLG -ppx generation
Browse files Browse the repository at this point in the history
over-approximate the ppx invocation in directories where multiple stanzas with
different ppx setups are defined

Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Mar 14, 2019
1 parent 6e5580e commit 8a559df
Show file tree
Hide file tree
Showing 2 changed files with 13 additions and 14 deletions.
25 changes: 12 additions & 13 deletions src/merlin.ml
Original file line number Diff line number Diff line change
Expand Up @@ -14,20 +14,19 @@ module Preprocess = struct
| _, (Action _ as action) -> action
| (Future_syntax _ as future_syntax), _
| _, (Future_syntax _ as future_syntax) -> future_syntax
| Pps { loc = _; pps = pps1; flags = flags1; staged = s1 },
| Pps { loc ; pps = pps1; flags = flags1; staged = s1 },
Pps { loc = _; pps = pps2; flags = flags2; staged = s2 } ->
match
match Bool.compare s1 s2 with
| Gt| Lt as ne -> ne
| Eq ->
match List.compare flags1 flags2 ~compare:String.compare with
| Gt | Lt as ne -> ne
| Eq ->
List.compare pps1 pps2 ~compare:(fun (_, a) (_, b) ->
Lib_name.compare a b)
with
| Eq -> a
| _ -> No_preprocessing
if Bool.(<>) s1 s2
|| List.compare flags1 flags2 ~compare:String.compare <> Eq then
No_preprocessing
else
let pps =
let not_in_pps1 (_, pp) =
List.for_all pps1 ~f:(fun (_, pp') ->
Lib_name.compare pp' pp <> Eq) in
pps1 @ List.filter ~f:not_in_pps1 pps2
in
Pps { loc ; pps; flags = flags1 ; staged = s1 }
end

let quote_for_merlin s =
Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/github1946/run.t
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
$ dune build --display short --profile release | grep "FLG -ppx"
[1]
FLG -ppx '$TESTCASE_ROOT/_build/default/.ppx/4e93360991c22787c855ecab6b44c222/ppx.exe --as-ppx --cookie '\''library-name="usesppx1"'\'''

0 comments on commit 8a559df

Please sign in to comment.