Skip to content

Commit

Permalink
fix: better cycle detection for virtual libraries
Browse files Browse the repository at this point in the history
An implementation of a virtual library must always depend on the virtual
library directly and not through a dependency. This is becaue the
implementation + vlib form a single archive during linking.

Signed-off-by: Rudi Grinberg <[email protected]>

ps-id: BF2B3D35-1494-48B4-90F2-60647E2C1DD5
  • Loading branch information
rgrinberg committed Oct 25, 2021
1 parent a0e9a3a commit 2247ad0
Show file tree
Hide file tree
Showing 2 changed files with 84 additions and 20 deletions.
89 changes: 72 additions & 17 deletions src/dune_rules/lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -187,6 +187,16 @@ module Error = struct
]
, [] )

let vlib_in_closure ~loc ~impl ~vlib =
let impl = Lib_info.name impl in
let vlib = Lib_info.name vlib in
User_error.make ~loc
[ Pp.textf
"Virtual library %S is used by a dependency of %S. This is not \
allowed."
(Lib_name.to_string vlib) (Lib_name.to_string impl)
]

let only_ppx_deps_allowed ~loc dep =
let name = Lib_info.name dep in
make ~loc
Expand Down Expand Up @@ -312,6 +322,9 @@ module T = struct
; sub_systems : Sub_system0.Instance.t Memo.Lazy.t Sub_system_name.Map.t
; modules : Modules.t Memo.Lazy.t option
; src_dirs : Path.Set.t Memo.Lazy.t
; (* all the virtual libraries in the closure. we need this to avoid
introducing impl -> lib -> vlib cycles. *)
vlib_closure : t Id.Map.t Resolve.t
}

let compare (x : t) (y : t) = Id.compare x.unique_id y.unique_id
Expand Down Expand Up @@ -1061,6 +1074,7 @@ module rec Resolve_names : sig
; pps : lib list Resolve.t
; selects : Resolved_select.t list
; re_exports : lib list Resolve.t
; vlib : lib list Resolve.t
}

val resolve_deps_and_add_runtime_deps :
Expand Down Expand Up @@ -1101,6 +1115,30 @@ end = struct
| Public (_, _) -> From_same_project
in
let resolve name = resolve_dep db name ~private_deps in
let* resolved =
let open Resolve.Build.O in
let* pps =
let instrumentation_backend =
instrumentation_backend db.instrument_with resolve
in
Lib_info.preprocess info
|> Preprocess.Per_module.with_instrumentation ~instrumentation_backend
>>| Preprocess.Per_module.pps
in
let dune_version = Lib_info.dune_version info in
Lib_info.requires info
|> resolve_deps_and_add_runtime_deps db ~private_deps ~dune_version ~pps
|> Memo.Build.map ~f:Resolve.return
in
let vlib_closure_parents =
let open Resolve.O in
let* resolved = resolved in
let* requires = resolved.requires in
Resolve.List.fold_left ~init:Id.Map.empty requires
~f:(fun acc (lib : lib) ->
let+ vlib_closure = lib.vlib_closure in
Id.Map.superpose acc vlib_closure)
in
let* implements =
match Lib_info.implements info with
| None -> Memo.Build.return None
Expand All @@ -1115,6 +1153,30 @@ end = struct
in
Memo.Build.map res ~f:Option.some
in
let requires =
let open Resolve.O in
match implements with
| None -> resolved >>= fun r -> r.requires
| Some vlib ->
let* vlib = vlib in
let* vlib_closure_parents = vlib_closure_parents in
if Id.Map.mem vlib_closure_parents vlib.unique_id then
let loc = Lib_info.loc info in
Error.vlib_in_closure ~loc ~impl:info ~vlib:vlib.info |> Resolve.fail
else
let* resolved = resolved in
let+ requires = resolved.requires in
List.filter requires ~f:(fun lib -> not (equal lib vlib))
in
let vlib_closure =
let open Resolve.O in
let* vlib_closure_parents = vlib_closure_parents in
let+ requires = requires in
List.fold_left requires ~init:vlib_closure_parents ~f:(fun acc lib ->
match Lib_info.virtual_ lib.info with
| None -> acc
| Some _ -> Id.Map.set acc lib.unique_id lib)
in
let resolve_impl impl_name =
let open Resolve.Build.O in
let* impl = resolve impl_name in
Expand Down Expand Up @@ -1161,25 +1223,10 @@ end = struct
(Package.Name.to_string p')
])))
in
let* resolved =
let open Resolve.Build.O in
let* pps =
let instrumentation_backend =
instrumentation_backend db.instrument_with resolve
in
Lib_info.preprocess info
|> Preprocess.Per_module.with_instrumentation ~instrumentation_backend
>>| Preprocess.Per_module.pps
in
let dune_version = Lib_info.dune_version info in
Lib_info.requires info
|> resolve_deps_and_add_runtime_deps db ~private_deps ~dune_version ~pps
|> Memo.Build.map ~f:Resolve.return
in
let* requires =
Memo.Build.return
(let open Resolve.O in
let* requires = resolved >>= fun r -> r.requires in
let* requires = requires in
match implements with
| None -> Resolve.return requires
| Some impl ->
Expand Down Expand Up @@ -1252,6 +1299,7 @@ end = struct
~f:(fun name info ->
Memo.Lazy.create (fun () ->
Sub_system.instantiate name info (Lazy.force t) ~resolve))
; vlib_closure
})
in
let t = Lazy.force t in
Expand Down Expand Up @@ -1381,6 +1429,7 @@ end = struct
; pps : lib list Resolve.t
; selects : Resolved_select.t list
; re_exports : lib list Resolve.t
; vlib : lib list Resolve.t
}

let resolve_complex_deps db deps ~private_deps : resolved_deps Memo.Build.t =
Expand Down Expand Up @@ -1522,7 +1571,13 @@ end = struct
let* runtime_deps = runtime_deps in
re_exports_closure (resolved @ runtime_deps)
and+ pps = pps in
{ requires; pps; selects; re_exports }
let vlib =
Resolve.map requires
~f:
(List.filter ~f:(fun lib ->
Option.is_some (Lib_info.virtual_ lib.info)))
in
{ requires; pps; selects; re_exports; vlib }

let resolve_deps_and_add_runtime_deps db deps ~private_deps ~pps ~dune_version
=
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -19,13 +19,22 @@ where vlib is a virtual library, and impl implements this library.
$ cat >impl/dune <<EOF
> (library (name impl) (implements vlib) (libraries lib))
> EOF
$ dune build @all
File "impl/dune", line 1, characters 0-55:
1 | (library (name impl) (implements vlib) (libraries lib))
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Error: Virtual library "vlib" is used by a dependency of "impl". This is not
allowed.
[1]

The implementation impl was built, but it's not usable:

$ echo 'Vlib.run ()' > foo.ml
$ echo "(executable (name foo) (libraries impl))" > dune
$ dune exec ./foo.exe
File "_none_", line 1:
Error: No implementations provided for the following modules:
Vlib referenced from lib/lib.cmxa(Lib)
File "impl/dune", line 1, characters 0-55:
1 | (library (name impl) (implements vlib) (libraries lib))
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Error: Virtual library "vlib" is used by a dependency of "impl". This is not
allowed.
[1]

0 comments on commit 2247ad0

Please sign in to comment.