Skip to content

Commit

Permalink
Revert library redirect handling
Browse files Browse the repository at this point in the history
Move library redirect creation back to [Gen_rules]. While this is less
elegant, the previous check in [Scope] was much more fragile. It relied
on a name collision to always be caused by a redirect, which is not
something that might be guaranteed in the future.

Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Oct 13, 2020
1 parent 2e87d9c commit 3777712
Show file tree
Hide file tree
Showing 4 changed files with 30 additions and 16 deletions.
26 changes: 16 additions & 10 deletions src/dune_rules/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1918,25 +1918,31 @@ module Library_redirect = struct
module Local = struct
type nonrec t = (Loc.t * Lib_name.Local.t) t

let for_lib (lib : Library.t) ~new_public_name ~loc : t =
{ loc; new_public_name; old_name = lib.name; project = lib.project }

let of_private_lib (lib : Library.t) : t option =
match lib.visibility with
| Public _
| Private None ->
None
| Private (Some package) ->
let loc, name = lib.name in
let new_public_name = (loc, Lib_name.mangled package.name name) in
Some (for_lib lib ~loc ~new_public_name)

let of_lib (lib : Library.t) : t option =
let open Option.O in
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.mangled package.name name)
| Private _ -> None
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
}
let loc = fst public_name in
Some (for_lib lib ~loc ~new_public_name:public_name)
end
end

Expand Down
2 changes: 2 additions & 0 deletions src/dune_rules/dune_file.mli
Original file line number Diff line number Diff line change
Expand Up @@ -365,6 +365,8 @@ module Library_redirect : sig

module Local : sig
type nonrec t = (Loc.t * Lib_name.Local.t) t

val of_private_lib : Library.t -> t option
end
end

Expand Down
10 changes: 9 additions & 1 deletion src/dune_rules/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -381,7 +381,15 @@ let filter_out_stanzas_from_hidden_packages ~visible_pkgs =
| None -> true
| Some package -> Package.Name.Map.mem visible_pkgs package.name
in
Option.some_if include_stanza stanza)
if include_stanza then
Some stanza
else
match stanza with
| Library l ->
let open Option.O in
let+ redirect = Dune_file.Library_redirect.Local.of_private_lib l in
Dune_file.Library_redirect redirect
| _ -> None)

let gen ~contexts ?only_packages conf =
let open Fiber.O in
Expand Down
8 changes: 3 additions & 5 deletions src/dune_rules/scope.ml
Original file line number Diff line number Diff line change
Expand Up @@ -76,11 +76,9 @@ module DB = struct
match (v1, v2) with
| Found info1, Found info2 ->
Error (Lib_info.loc info1, Lib_info.loc info2)
| Found info, Redirect (loc, r)
| Redirect (loc, r), Found info -> (
match Lib_name.analyze r with
| Private _ -> Ok (Found_or_redirect.found info)
| Public _ -> Error (loc, Lib_info.loc info) )
| Found info, Redirect (loc, _)
| Redirect (loc, _), Found info ->
Error (loc, Lib_info.loc info)
| Redirect (loc1, lib1), Redirect (loc2, lib2) ->
if Lib_name.equal lib1 lib2 then
Ok v1
Expand Down

0 comments on commit 3777712

Please sign in to comment.