Skip to content

Commit

Permalink
Add transitive closure for re_exports in requires
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
rgrinberg committed Sep 12, 2019
1 parent 34e8240 commit 09e38d1
Show file tree
Hide file tree
Showing 2 changed files with 4 additions and 26 deletions.
13 changes: 3 additions & 10 deletions src/dune/lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -941,8 +941,6 @@ module rec Resolve : sig
-> variants:(Loc.t * Variant.Set.t) option
-> forbidden_libraries:Loc.t Map.t
-> lib list Or_exn.t

val re_exports_closure : lib list -> lib list Or_exn.t
end = struct
open Resolve

Expand Down Expand Up @@ -1153,7 +1151,7 @@ end = struct
and many = Result.List.iter ~f:one
in
let+ () = many ts in
!res
List.rev !res

let resolve_complex_deps db deps ~allow_private_deps ~stack =
let res, resolved_selects =
Expand Down Expand Up @@ -1261,6 +1259,7 @@ end = struct
in
(deps, pps)
in
let deps = deps >>= re_exports_closure in
(deps, pps, resolved_selects)

(* Compute transitive closure of libraries to figure which ones will trigger
Expand Down Expand Up @@ -1500,13 +1499,7 @@ module Compile = struct
>>= closure_with_overlap_checks db ~linking:false ~variants:None
~forbidden_libraries:Map.empty )
in
let direct_requires =
let* requires = t.requires in
let+ re_exports =
t.re_exports >>= Resolve.re_exports_closure in
requires @ re_exports
in
{ direct_requires
{ direct_requires = t.requires
; requires_link
; resolved_selects = t.resolved_selects
; pps = t.pps
Expand Down
17 changes: 1 addition & 16 deletions test/blackbox-tests/test-cases/re-exported-deps/run.t
Original file line number Diff line number Diff line change
@@ -1,27 +1,12 @@
dependencies can be exported transitively:
$ dune exec ./foo.exe --root transitive
Entering directory 'transitive'
pkg.aaa: exported: pkg.bbb
pkg.bbb: exported: pkg.ccc
Entering directory 'transitive'
ocamlc .foo.eobjs/byte/dune__exe__Foo.{cmi,cmo,cmt} (exit 2)
(cd _build/default && /Users/rgrinberg/.opam/4.08.0/bin/ocamlc.opt -w @1..3@5..28@30..39@43@46..47@49..57@61..62-40 -strict-sequence -strict-formats -short-paths -keep-locs -g -bin-annot -I .foo.eobjs/byte -I .aaa.objs/byte -I .aaa.objs/native -no-alias-deps -opaque -o .foo.eobjs/byte/dune__exe__Foo.cmo -c -impl foo.ml)
File "foo.ml", line 2, characters 11-14:
2 | module B = Bbb
^^^
Error (warning 49): no cmi file was found in path for module Bbb
File "foo.ml", line 3, characters 11-14:
3 | module C = Ccc
^^^
Error (warning 49): no cmi file was found in path for module Ccc
[1]

transtive deps expressed in the dune-package

$ dune build @install --root transitive
Entering directory 'transitive'
pkg.aaa: exported: pkg.bbb
pkg.bbb: exported: pkg.ccc
$ cat transitive/_build/install/default/lib/pkg/dune-package
(lang dune 2.0)
(name pkg)
Expand All @@ -31,7 +16,7 @@ transtive deps expressed in the dune-package
(archives (byte aaa/aaa.cma) (native aaa/aaa.cmxa))
(plugins (byte aaa/aaa.cma) (native aaa/aaa.cmxs))
(foreign_archives (native aaa/aaa$ext_lib))
(requires pkg.bbb)
(requires pkg.ccc pkg.bbb)
(main_module_name Aaa)
(modes byte native)
(modules (singleton (name Aaa) (obj_name aaa) (visibility public) (impl)))
Expand Down

0 comments on commit 09e38d1

Please sign in to comment.