Skip to content

Commit

Permalink
Lift the package restriction
Browse files Browse the repository at this point in the history
Now, the private library just needs to be in the same project

Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Aug 29, 2020
1 parent b2d257a commit b37d9b1
Show file tree
Hide file tree
Showing 5 changed files with 13 additions and 17 deletions.
2 changes: 1 addition & 1 deletion src/dune_rules/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -778,7 +778,7 @@ module Library = struct
let status =
match conf.visibility with
| Private pkg -> Lib_info.Status.Private (conf.project, pkg)
| Public p -> Public (Dune_project.name conf.project, p.package)
| Public p -> Public (conf.project, p.package)
in
let virtual_library = is_virtual conf in
let foreign_archives = foreign_lib_files conf ~dir ~ext_lib in
Expand Down
11 changes: 6 additions & 5 deletions src/dune_rules/lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -718,16 +718,17 @@ module Dep_stack = struct
end

type private_deps =
| From_package of Package.t
| From_project of Dune_project.t
| Allow_all

let check_private_deps lib ~loc ~(allow_private_deps : private_deps) =
match allow_private_deps with
| Allow_all -> Ok lib
| From_package p -> (
| From_project project -> (
match Lib_info.status lib.info with
| Private (_, Some (p' : Package.t)) ->
if Package.Name.equal p.name p'.name then
| Private (_, Some (package : Package.t)) ->
let packages = Dune_project.packages project in
if Package.Name.Map.mem packages package.name then
Ok lib
else
Error.private_deps_not_allowed ~loc lib.info
Expand Down Expand Up @@ -1004,7 +1005,7 @@ end = struct
| Private _
| Installed ->
Allow_all
| Public (_, p) -> From_package p
| Public (project, _) -> From_project project
in
let resolve name = resolve_dep db name ~allow_private_deps ~stack in
let implements =
Expand Down
9 changes: 5 additions & 4 deletions src/dune_rules/lib_info.ml
Original file line number Diff line number Diff line change
Expand Up @@ -141,15 +141,15 @@ end
module Status = struct
type t =
| Installed
| Public of Dune_project.Name.t * Package.t
| Public of Dune_project.t * Package.t
| Private of Dune_project.t * Package.t option

let to_dyn x =
let open Dyn.Encoder in
match x with
| Installed -> constr "Installed" []
| Public (name, package) ->
constr "Public" [ Dune_project.Name.to_dyn name; Package.to_dyn package ]
constr "Public" [ Dune_project.to_dyn name; Package.to_dyn package ]
| Private (proj, package) ->
constr "Private"
[ Dune_project.to_dyn proj; option Package.to_dyn package ]
Expand All @@ -162,8 +162,9 @@ module Status = struct

let project_name = function
| Installed -> None
| Private (project, _) -> Some (Dune_project.name project)
| Public (name, _) -> Some name
| Private (project, _)
| Public (project, _) ->
Some (Dune_project.name project)
end

module Source = struct
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/lib_info.mli
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ open Stdune
module Status : sig
type t =
| Installed
| Public of Dune_project.Name.t * Package.t
| Public of Dune_project.t * Package.t
| Private of Dune_project.t * Package.t option

val is_private : t -> bool
Expand Down
6 changes: 0 additions & 6 deletions test/blackbox-tests/test-cases/private-package-lib.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -100,12 +100,6 @@ It's not possible to use secret from a different package:
> (libraries secret))
> EOF
$ dune build @all
File "bar/dune", line 3, characters 12-18:
3 | (libraries secret))
^^^^^^
Error: Library "secret" is private, it cannot be a dependency of a public
library. You need to give "secret" a public name.
[1]

Executables on the other hand are allowed:

Expand Down

0 comments on commit b37d9b1

Please sign in to comment.