Skip to content

Commit

Permalink
Make package private libraries visible when installed
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Aug 29, 2020
1 parent 02db982 commit b2d257a
Show file tree
Hide file tree
Showing 3 changed files with 21 additions and 5 deletions.
18 changes: 15 additions & 3 deletions src/dune_rules/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1854,15 +1854,27 @@ module Library_redirect = struct

let of_lib (lib : Library.t) : t option =
let open Option.O in
let* public = lib.public in
if Lib_name.equal (Lib_name.of_local lib.name) (snd public.name) then
let* public_name =
match lib.visibility with
| Public plib -> Some plib.name
| Private None -> None
| Private (Some package) ->
let loc, name = lib.name in
Some
( loc
, Lib_name.of_string
(sprintf "%s.__private__.%s"
(Package.Name.to_string package.name)
(Lib_name.Local.to_string name)) )
in
if Lib_name.equal (Lib_name.of_local lib.name) (snd public_name) then
None
else
Some
{ loc = Loc.none
; project = lib.project
; old_name = lib.name
; new_public_name = public.name
; new_public_name = public_name
}
end
end
Expand Down
4 changes: 3 additions & 1 deletion src/dune_rules/lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1719,7 +1719,9 @@ module DB = struct
|> Lib_info.of_local
in
match conf.visibility with
| Private _ -> [ (Dune_file.Library.best_name conf, Found_or_redirect.found info) ]
| Private _ ->
[ (Dune_file.Library.best_name conf, Found_or_redirect.found info)
]
| Public p ->
let name = Dune_file.Public_lib.name p in
if Lib_name.equal name (Lib_name.of_local conf.name) then
Expand Down
4 changes: 3 additions & 1 deletion src/dune_rules/scope.ml
Original file line number Diff line number Diff line change
Expand Up @@ -77,8 +77,10 @@ module DB = struct
let named p loc = Option.some_if (name = p) loc in
match stanza with
| Library (_, { buildable = { loc; _ }; visibility = Public p; _ })
->
named (Dune_file.Public_lib.name p) loc
| Deprecated_library_name
{ loc; old_public_name = { public = p; _ }; _ } ->
{ Dune_file.Library_redirect.loc; old_name = p, _; _ } ->
Option.some_if (name = Dune_file.Public_lib.name p) loc
| _ -> None)
with
Expand Down

0 comments on commit b2d257a

Please sign in to comment.