Skip to content

Commit

Permalink
fix(vlib): fix installation of vlib implementations
Browse files Browse the repository at this point in the history
An implementation of a virtual library should include all the binary
artifacts of the virtual library. This commit adds the inheritd vlib
artifacts to the .install file.

Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg committed Nov 12, 2021
1 parent 7557a8d commit c845701
Show file tree
Hide file tree
Showing 8 changed files with 76 additions and 16 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,6 +1,9 @@
Unreleased
----------

- Fix installation of implementations of virtual libraries (#5150, fix #3636,
@rgrinberg)

- Run tests in all modes defined. Previously, jsoo was excluded. (@hhugo,
#5049, fix #4951)

Expand Down
44 changes: 33 additions & 11 deletions src/dune_rules/install_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -117,12 +117,16 @@ end = struct
Install.Entry.Sourced.create ~loc entry
in
let* installable_modules =
let+ ml_sources = Dir_contents.ocaml dir_contents in
Ml_sources.modules ml_sources ~for_:(Library (Library.best_name lib))
|> Modules.fold_no_vlib ~init:[] ~f:(fun m acc -> m :: acc)
let* ml_sources = Dir_contents.ocaml dir_contents in
let modules =
Ml_sources.modules ml_sources ~for_:(Library (Library.best_name lib))
in
let+ impl = Virtual_rules.impl sctx ~lib ~scope in
let modules = Vimpl.impl_modules impl modules in
Modules.split_by_lib modules
in
let sources =
List.concat_map installable_modules ~f:(fun m ->
List.concat_map installable_modules.impl ~f:(fun m ->
List.map (Module.sources m) ~f:(fun source ->
(* We add the -gen suffix to a few files generated by dune, such
as the alias module. *)
Expand Down Expand Up @@ -153,7 +157,8 @@ end = struct
Path.basename dir' |> inside_subdir |> Option.some
in
let virtual_library = Library.is_virtual lib in
List.concat_map installable_modules ~f:(fun m ->
let modules =
let common m =
let cm_file kind = Obj_dir.Module.cm_file obj_dir m ~kind in
let if_ b (cm_kind, f) =
if b then
Expand All @@ -163,21 +168,38 @@ end = struct
else
[]
in
let cm_dir = cm_dir m in
let open Cm_kind in
[ if_ true (Cmi, cm_file Cmi)
; if_ native (Cmx, cm_file Cmx)
; if_ (byte && virtual_library) (Cmo, cm_file Cmo)
; if_
(native && virtual_library)
(Cmx, Obj_dir.Module.o_file obj_dir m ~ext_obj)
; List.filter_map Ml_kind.all ~f:(fun ml_kind ->
let open Option.O in
let+ cmt = Obj_dir.Module.cmt_file obj_dir m ~ml_kind in
(Cmi, cmt))
]
|> List.concat
|> List.map ~f:(fun (cm_kind, f) -> (cm_dir cm_kind, f)))
in
let set_dir m =
List.map ~f:(fun (cm_kind, p) -> (cm_dir m cm_kind, p))
in
let modules_impl =
List.concat_map installable_modules.impl ~f:(fun m ->
common m
@ List.filter_map Ml_kind.all ~f:(fun ml_kind ->
let open Option.O in
let+ cmt = Obj_dir.Module.cmt_file obj_dir m ~ml_kind in
(Cm_kind.Cmi, cmt))
|> set_dir m)
in
let modules_vlib =
List.concat_map installable_modules.vlib ~f:(fun m ->
if Module.kind m = Virtual then
[]
else
common m |> set_dir m)
in
modules_vlib @ modules_impl
in
modules
in
let* lib_files, dll_files =
let+ lib_files = lib_files ~dir ~dir_contents ~lib_config info in
Expand Down
23 changes: 23 additions & 0 deletions src/dune_rules/modules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -618,6 +618,29 @@ let rec fold_no_vlib t ~init ~f =
| Wrapped w -> Wrapped.fold w ~init ~f
| Impl { vlib = _; impl } -> fold_no_vlib impl ~f ~init

let rec map t ~f =
match t with
| Stdlib w -> Stdlib (Stdlib.map w ~f)
| Singleton m -> Singleton (f m)
| Unwrapped m -> Unwrapped (Module_name.Map.map m ~f)
| Wrapped w -> Wrapped (Wrapped.map w ~f)
| Impl { vlib; impl } -> Impl { vlib = map vlib ~f; impl = map impl ~f }

type split_by_lib =
{ vlib : Module.t list
; impl : Module.t list
}

let split_by_lib t =
let f m acc = m :: acc in
let init = [] in
match t with
| Impl { vlib; impl } ->
let vlib = fold_no_vlib vlib ~init ~f in
let impl = fold_no_vlib impl ~init ~f in
{ vlib; impl }
| _ -> { impl = fold_no_vlib t ~init ~f; vlib = [] }

let compat_for_exn t m =
match t with
| Singleton _
Expand Down
9 changes: 9 additions & 0 deletions src/dune_rules/modules.mli
Original file line number Diff line number Diff line change
Expand Up @@ -57,6 +57,8 @@ val fold_user_written : t -> f:(Module.t -> 'acc -> 'acc) -> init:'acc -> 'acc
val map_user_written :
t -> f:(Module.t -> Module.t Memo.Build.t) -> t Memo.Build.t

val map : t -> f:(Module.t -> Module.t) -> t

val fold_user_available : t -> f:(Module.t -> 'acc -> 'acc) -> init:'acc -> 'acc

(** Returns all the compatibility modules. *)
Expand Down Expand Up @@ -112,5 +114,12 @@ val as_singleton : t -> Module.t option

val source_dirs : t -> Path.Set.t

type split_by_lib =
{ vlib : Module.t list
; impl : Module.t list
}

val split_by_lib : t -> split_by_lib

(** [has_impl t] is true if there's at least one implementation in [t]*)
val has_impl : t -> bool
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,8 @@ Include variants and implementation information in dune-package
impl/impl$ext_lib
impl/impl.cma
impl/impl.cmxa
impl/vlib.cmi
impl/vlib.cmx
impl/vlib__Vmod.cmi
impl/vlib__Vmod.cmt
impl/vlib__Vmod.cmx
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -45,9 +45,6 @@ modules remain hidden.
> Vlib.Foo.run ()
> EOF
$ dune exec ./blah.exe
File "blah.ml", line 1, characters 0-12:
1 | Vlib.Foo.run ()
^^^^^^^^^^^^
Error: Unbound module Vlib
[1]
bar from vlib
Foo.run implemented
$ cd ..
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,8 @@ Install files for implementations and virtual libs have all the artifacts:
"_build/install/default/lib/impl/impl.cma"
"_build/install/default/lib/impl/impl.cmxa"
"_build/install/default/lib/impl/opam"
"_build/install/default/lib/impl/vlib.cmi"
"_build/install/default/lib/impl/vlib.cmx"
"_build/install/default/lib/impl/vlib__Foo.cmi"
"_build/install/default/lib/impl/vlib__Foo.cmt"
"_build/install/default/lib/impl/vlib__Foo.cmx"
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,8 @@ Check that default implementation data is installed in the dune package file.
a$ext_obj
a__X.cmi
a__X.cmti
default-impl/a.cmi
default-impl/a.cmx
default-impl/a__X.cmi
default-impl/a__X.cmt
default-impl/a__X.cmx
Expand Down

0 comments on commit c845701

Please sign in to comment.