Skip to content

Commit

Permalink
Fix copy_files handling when generating .merlin files
Browse files Browse the repository at this point in the history
Merlin generation would be broken in the presence of copy_files and any other
stanza with a preprocessing directive. This is because copy_files would have
No_preprocessing, and that would only successfully merge with non preprocessing
stanzas.

To fix the problem, we no longer rely on merging mechanism to add additional
directories for copy_files, the more_src_dirs argument aready exists for that.

Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
rgrinberg committed May 30, 2019
1 parent a5fe41d commit 634a73b
Show file tree
Hide file tree
Showing 3 changed files with 22 additions and 11 deletions.
4 changes: 4 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -87,6 +87,10 @@ unreleased
- Fix generation of `.merlin` whenever there's more than one stanza with the
same ppx preprocessing specification (#2209 ,fixes #2206, @rgrinberg)

- Fix generation of `.meriln` in the presence of the `copy_files` stanza and
preprocessing specifications of other stanazs. (#2211, fixes #2206,
@rgrinberg)

1.9.3 (06/05/2019)
------------------

Expand Down
22 changes: 17 additions & 5 deletions src/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -6,22 +6,25 @@ open Dune_file
open! No_io

module For_stanza = struct
type ('merlin, 'cctx, 'js) t =
type ('merlin, 'cctx, 'js, 'source_dirs) t =
{ merlin : 'merlin
; cctx : 'cctx
; js : 'js
; source_dirs : 'source_dirs
}

let empty_none =
{ merlin = None
; cctx = None
; js = None
; source_dirs = None
}

let empty_list =
{ merlin = []
; cctx = []
; js = []
; source_dirs = []
}

let cons_maybe hd_o tl =
Expand All @@ -32,16 +35,19 @@ module For_stanza = struct
let cons acc x =
{ merlin = cons_maybe x.merlin acc.merlin
; cctx = cons_maybe x.cctx acc.cctx
; source_dirs = cons_maybe x.source_dirs acc.source_dirs
; js =
match x.js with
| None -> acc.js
| Some js -> List.rev_append acc.js js

}

let rev t =
{ t with
merlin = List.rev t.merlin
; cctx = List.rev t.cctx
; source_dirs = List.rev t.source_dirs
}
end

Expand Down Expand Up @@ -85,6 +91,7 @@ module Gen(P : sig val sctx : Super_context.t end) = struct
merlin = Some merlin
; cctx = Some (lib.buildable.loc, cctx)
; js = None
; source_dirs = None
}
| Executables exes ->
let cctx, merlin =
Expand All @@ -100,6 +107,7 @@ module Gen(P : sig val sctx : Super_context.t end) = struct
List.map
[exe ^ ".bc.js" ; exe ^ ".bc.runtime.js"]
~f:(Path.Build.relative ctx_dir)))
; source_dirs = None
}
| Alias alias ->
Simple_rules.alias sctx alias ~dir ~expander;
Expand All @@ -113,19 +121,20 @@ module Gen(P : sig val sctx : Super_context.t end) = struct
merlin = Some merlin
; cctx = Some (tests.exes.buildable.loc, cctx)
; js = None
; source_dirs = None
}
| Copy_files { glob; _ } ->
let source_dirs =
let source_dir =
let loc = String_with_vars.loc glob in
let src_glob = Expander.expand_str expander glob in
Path.Source.relative src_dir src_glob ~error_loc:loc
|> Path.Source.parent_exn
|> Path.Source.Set.singleton
in
{ For_stanza.
merlin = Some (Merlin.make ~source_dirs ())
merlin = None
; cctx = None
; js = None
; source_dirs = Some source_dir
}
| Install { Install_conf. section = _; files; package = _ } ->
List.map files ~f:(fun fb ->
Expand All @@ -141,6 +150,7 @@ module Gen(P : sig val sctx : Super_context.t end) = struct
merlin = merlins
; cctx = cctxs
; js = js_targets
; source_dirs
} = List.fold_left stanzas
~init:{ For_stanza.empty_list with cctx = cctxs }
~f:(fun acc a -> For_stanza.cons acc (for_stanza a))
Expand All @@ -152,8 +162,10 @@ module Gen(P : sig val sctx : Super_context.t end) = struct
Option.iter (Merlin.merge_all ~allow_approx_merlin merlins)
~f:(fun m ->
let more_src_dirs =
List.map (Dir_contents.dirs dir_contents) ~f:(fun dc ->
Dir_contents.dirs dir_contents
|> List.map ~f:(fun dc ->
Path.Build.drop_build_context_exn (Dir_contents.dir dc))
|> List.rev_append source_dirs
in
Merlin.add_rules sctx ~dir:ctx_dir ~more_src_dirs ~expander ~dir_kind
(Merlin.add_source_dir m src_dir));
Expand Down
7 changes: 1 addition & 6 deletions test/blackbox-tests/test-cases/github2206/run.t
Original file line number Diff line number Diff line change
@@ -1,9 +1,4 @@
copy_files would break the generation of the preprocessing flags
$ dune build copy_files/.merlin
File "copy_files/dune", line 5, characters 21-63:
5 | (preprocess (action (run %{project_root}/pp.exe %{input-file}))))
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning: .merlin generated is inaccurate. Cannot mix preprocessed and non preprocessed specificiations.
Split the stanzas into different directories or silence this warning by adding (allow_approximate_merlin) to your dune-project.
$ cat copy_files/.merlin | grep "FLG -pp"
[1]
FLG -pp '$TESTCASE_ROOT/_build/default/pp.exe'

0 comments on commit 634a73b

Please sign in to comment.