Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
Show all changes
24 commits
Select commit Hold shift + click to select a range
6a9a212
chore: set the parametized to wrapped
maiste May 26, 2025
8905390
feat(tmp): Singleton working version of parameterized library
maiste May 27, 2025
5d6b869
feat(tmp): support other library kind for parameterized library
maiste May 27, 2025
010c233
fix: rebase remove useless print
maiste Jul 3, 2025
c457847
test: add implementation tests
maiste Jul 4, 2025
c78c9b2
test: check both private and public lib work
maiste Jul 7, 2025
60ba6e7
fix: change parameter public lib behavior
maiste Jul 7, 2025
78b9abf
chore(fmt): apply dune formatter
maiste Jul 7, 2025
5d67d9a
doc: add implementation documentation
maiste Jul 7, 2025
74e9733
chore: fix error message for impossible case
maiste Jul 8, 2025
c598b26
test(promote): now export the main module (unique module)
maiste Jul 9, 2025
5d7bf1f
chore: add explnation comment for change
maiste Jul 9, 2025
bda4be2
chore(review): apply @art-w review
maiste Jul 10, 2025
1f71be2
test: check for nonexistent parameter
maiste Jul 22, 2025
741095e
test: implement a non parameter library
maiste Jul 22, 2025
0812eb6
test: apply promotion
maiste Jul 22, 2025
7fff187
remove [Library.is_parameter]
shonfeder Aug 26, 2025
e04a928
documentation and comment fixes
shonfeder Aug 26, 2025
85da315
test: add more edge cases
art-w Sep 4, 2025
1f393fa
refactor: move module implements to compilation context
art-w Sep 4, 2025
2049059
refactor: replace usage of is_parameter by match kind
art-w Sep 4, 2025
6874948
fix after review
art-w Sep 5, 2025
c9fa595
refactor(virtual_rules): distinguish between vimpl and parameters
art-w Sep 8, 2025
5d34b82
Merge branch 'main' into maiste/library_param_impl
shonfeder Sep 9, 2025
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
7 changes: 7 additions & 0 deletions doc/reference/dune/library.rst
Original file line number Diff line number Diff line change
Expand Up @@ -210,6 +210,13 @@ order to declare a multi-directory library, you need to use the
unless you use Dune to synthesize the ``depends`` and ``depopts`` sections
of your opam file.

.. describe:: (implements <name>)

``name`` defines the name of the virtual library or the parameter library you
are implementing.

See :doc:`/virtual-libraries` or :doc:`/reference/dune/library_parameter`.

.. describe:: (js_of_ocaml ...)

Sets options for JavaScript compilation, see :ref:`jsoo-field`.
Expand Down
10 changes: 5 additions & 5 deletions src/dune_rules/compilation_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -87,14 +87,14 @@ type t =
; requires_compile : Lib.t list Resolve.Memo.t
; requires_hidden : Lib.t list Resolve.Memo.t
; requires_link : Lib.t list Resolve.t Memo.Lazy.t
; implements : Virtual_rules.t
; includes : Includes.t
; preprocessing : Pp_spec.t
; opaque : bool
; stdlib : Ocaml_stdlib.t option
; js_of_ocaml : Js_of_ocaml.In_context.t option Js_of_ocaml.Mode.Pair.t
; sandbox : Sandbox_config.t
; package : Package.t option
; vimpl : Vimpl.t option
; melange_package_name : Lib_name.t option
; modes : Lib_mode.Map.Set.t
; bin_annot : bool
Expand All @@ -121,7 +121,7 @@ let sandbox t = t.sandbox
let set_sandbox t sandbox = { t with sandbox }
let package t = t.package
let melange_package_name t = t.melange_package_name
let vimpl t = t.vimpl
let implements t = t.implements
let modes t = t.modes
let bin_annot t = t.bin_annot
let context t = Super_context.context t.super_context
Expand All @@ -142,7 +142,7 @@ let create
~js_of_ocaml
~package
~melange_package_name
?vimpl
?(implements = Virtual_rules.no_implements)
?modes
?bin_annot
?loc
Expand Down Expand Up @@ -185,7 +185,7 @@ let create
~sandbox
~obj_dir
~sctx:super_context
~vimpl
~impl:implements
~modules
and+ bin_annot =
match bin_annot with
Expand All @@ -200,6 +200,7 @@ let create
; requires_compile = direct_requires
; requires_hidden = hidden_requires
; requires_link
; implements
; includes =
Includes.make ~project ~opaque ~direct_requires ~hidden_requires ocaml.lib_config
; preprocessing
Expand All @@ -208,7 +209,6 @@ let create
; js_of_ocaml
; sandbox
; package
; vimpl
; melange_package_name
; modes
; bin_annot
Expand Down
4 changes: 2 additions & 2 deletions src/dune_rules/compilation_context.mli
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ val create
-> js_of_ocaml:Js_of_ocaml.In_context.t option Js_of_ocaml.Mode.Pair.t
-> package:Package.t option
-> melange_package_name:Lib_name.t option
-> ?vimpl:Vimpl.t
-> ?implements:Virtual_rules.t
-> ?modes:Mode_conf.Set.Details.t Lib_mode.Map.t
-> ?bin_annot:bool
-> ?loc:Loc.t
Expand Down Expand Up @@ -65,7 +65,7 @@ val js_of_ocaml : t -> Js_of_ocaml.In_context.t option Js_of_ocaml.Mode.Pair.t
val sandbox : t -> Sandbox_config.t
val set_sandbox : t -> Sandbox_config.t -> t
val package : t -> Package.t option
val vimpl : t -> Vimpl.t option
val implements : t -> Virtual_rules.t
val melange_package_name : t -> Lib_name.t option
val modes : t -> Lib_mode.Map.Set.t
val for_wrapped_compat : t -> t
Expand Down
14 changes: 7 additions & 7 deletions src/dune_rules/dep_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -131,7 +131,7 @@ let rec deps_of
~obj_dir
~modules
~sandbox
~vimpl
~impl
~dir
~sctx
~ml_kind
Expand All @@ -156,14 +156,14 @@ let rec deps_of
in
match m with
| Imported_from_vlib _ ->
let vimpl = Option.value_exn vimpl in
let vimpl = Virtual_rules.vimpl_exn impl in
skip_if_source_absent (deps_of_vlib_module ~obj_dir ~vimpl ~dir ~sctx ~ml_kind) m
| Normal m ->
skip_if_source_absent
(deps_of_module ~modules ~sandbox ~sctx ~dir ~obj_dir ~ml_kind)
m
| Impl_of_virtual_module impl_or_vlib ->
deps_of ~obj_dir ~modules ~sandbox ~vimpl ~dir ~sctx ~ml_kind
deps_of ~obj_dir ~modules ~sandbox ~impl ~dir ~sctx ~ml_kind
@@
let m = Ml_kind.Dict.get impl_or_vlib ml_kind in
(match ml_kind with
Expand Down Expand Up @@ -198,20 +198,20 @@ let dict_of_func_concurrently f =
Ml_kind.Dict.make ~impl ~intf
;;

let for_module ~obj_dir ~modules ~sandbox ~vimpl ~dir ~sctx module_ =
let for_module ~obj_dir ~modules ~sandbox ~impl ~dir ~sctx module_ =
dict_of_func_concurrently
(deps_of ~obj_dir ~modules ~sandbox ~vimpl ~dir ~sctx (Normal module_))
(deps_of ~obj_dir ~modules ~sandbox ~impl ~dir ~sctx (Normal module_))
;;

let rules ~obj_dir ~modules ~sandbox ~vimpl ~sctx ~dir =
let rules ~obj_dir ~modules ~sandbox ~impl ~sctx ~dir =
match Modules.With_vlib.as_singleton modules with
| Some m -> Memo.return (Dep_graph.Ml_kind.dummy m)
| None ->
dict_of_func_concurrently (fun ~ml_kind ->
let+ per_module =
Modules.With_vlib.obj_map modules
|> Parallel_map.parallel_map ~f:(fun _obj_name m ->
deps_of ~obj_dir ~modules ~sandbox ~vimpl ~sctx ~dir ~ml_kind m)
deps_of ~obj_dir ~modules ~sandbox ~impl ~sctx ~dir ~ml_kind m)
in
Dep_graph.make ~dir ~per_module)
;;
4 changes: 2 additions & 2 deletions src/dune_rules/dep_rules.mli
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ val for_module
: obj_dir:Path.Build.t Obj_dir.t
-> modules:Modules.With_vlib.t
-> sandbox:Sandbox_config.t
-> vimpl:Vimpl.t option
-> impl:Virtual_rules.t
-> dir:Path.Build.t
-> sctx:Super_context.t
-> Module.t
Expand All @@ -23,7 +23,7 @@ val rules
: obj_dir:Path.Build.t Obj_dir.t
-> modules:Modules.With_vlib.t
-> sandbox:Sandbox_config.t
-> vimpl:Vimpl.t option
-> impl:Virtual_rules.t
-> sctx:Super_context.t
-> dir:Path.Build.t
-> Dep_graph.Ml_kind.t Memo.t
61 changes: 32 additions & 29 deletions src/dune_rules/install_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -97,14 +97,16 @@ end = struct
>>| Modules.With_vlib.modules
>>| Option.some
and+ foreign_archives =
match Lib_info.virtual_ lib with
| false -> Memo.return (Mode.Map.Multi.to_flat_list @@ Lib_info.foreign_archives lib)
| true ->
match Lib_info.kind lib with
| Dune_file _ ->
Memo.return (Mode.Map.Multi.to_flat_list @@ Lib_info.foreign_archives lib)
| Virtual ->
let+ foreign_sources = Dir_contents.foreign_sources dir_contents in
let name = Lib_info.name lib in
let files = Foreign_sources.for_lib foreign_sources ~name in
let { Lib_config.ext_obj; _ } = lib_config in
Foreign.Sources.object_files files ~dir ~ext_obj
| Parameter -> Memo.return []
in
List.rev_append
(List.rev_concat_map
Expand Down Expand Up @@ -209,7 +211,7 @@ end = struct
~libs:(Scope.libs scope)
~for_:(Library (Lib_info.lib_id info |> Lib_id.to_local_exn))
and+ impl = Virtual_rules.impl sctx ~lib ~scope in
Vimpl.impl_modules impl modules |> Modules.With_vlib.split_by_lib
Virtual_rules.impl_modules impl modules |> Modules.With_vlib.split_by_lib
in
let lib_src_dir = Lib_info.src_dir info in
let sources =
Expand Down Expand Up @@ -266,7 +268,6 @@ end = struct
let { Lib_mode.Map.ocaml = { Mode.Dict.byte; native } as ocaml; melange } =
Mode_conf.Lib.Set.eval lib.modes ~has_native
in
let is_parameter = Library.is_parameter lib in
let+ melange_runtime_entries = additional_deps lib.melange_runtime_deps
and+ public_headers = additional_deps lib.public_headers
and+ module_files =
Expand All @@ -293,26 +294,27 @@ end = struct
| Some f -> [ cm_kind, f ])
else []
in
let common =
let virtual_library = Library.is_virtual lib in
fun m ->
let cm_file kind = Obj_dir.Module.cm_file obj_dir m ~kind in
let open Lib_mode.Cm_kind in
let cmi = if_ (native || byte) (Ocaml Cmi, cm_file (Ocaml Cmi)) in
let rest =
if is_parameter
then []
else
[ if_ native (Ocaml Cmx, cm_file (Ocaml Cmx))
; if_ (byte && virtual_library) (Ocaml Cmo, cm_file (Ocaml Cmo))
; if_
(native && virtual_library)
(Ocaml Cmx, Obj_dir.Module.o_file obj_dir m ~ext_obj)
; if_ melange (Melange Cmi, cm_file (Melange Cmi))
; if_ melange (Melange Cmj, cm_file (Melange Cmj))
let common m =
let cm_file kind = Obj_dir.Module.cm_file obj_dir m ~kind in
let open Lib_mode.Cm_kind in
let cmi = if_ (native || byte) (Ocaml Cmi, cm_file (Ocaml Cmi)) in
let common_module_impls virtual_only =
(if_ native (Ocaml Cmx, cm_file (Ocaml Cmx)) :: virtual_only)
@ [ if_ melange (Melange Cmi, cm_file (Melange Cmi))
; if_ melange (Melange Cmj, cm_file (Melange Cmj))
]
in
let rest =
match (lib.kind : Lib_kind.t) with
| Parameter -> []
| Virtual ->
common_module_impls
[ if_ byte (Ocaml Cmo, cm_file (Ocaml Cmo))
; if_ native (Ocaml Cmx, Obj_dir.Module.o_file obj_dir m ~ext_obj)
]
in
cmi :: rest |> List.rev_concat
| _ -> common_module_impls []
in
cmi :: rest |> List.rev_concat
in
let set_dir m = List.rev_map ~f:(fun (cm_kind, p) -> cm_dir m cm_kind, p) in
let+ modules_impl =
Expand Down Expand Up @@ -354,9 +356,9 @@ end = struct
[ sources
; melange_runtime_entries
; List.rev_map module_files ~f:(fun (sub_dir, file) -> make_entry ?sub_dir Lib file)
; (match is_parameter with
| true -> []
| false ->
; (match lib.kind with
| Parameter -> []
| Virtual | Dune_file _ ->
List.rev_concat
[ List.rev_map lib_files ~f:(fun (section, file) -> make_entry section file)
; List.rev_map execs ~f:(make_entry Libexec)
Expand Down Expand Up @@ -837,8 +839,9 @@ end = struct
let* { Scope.DB.Lib_entry.Set.libraries; _ } = Action_builder.of_memo entries in
match
List.find_map libraries ~f:(fun lib ->
let info = Lib.Local.info lib in
Option.some_if (Lib_info.virtual_ info) lib)
match Lib_info.kind (Lib.Local.info lib) with
| Parameter | Virtual -> Some lib
| Dune_file _ -> None)
with
| None -> Action_builder.lines_of meta_template
| Some vlib ->
Expand Down
35 changes: 18 additions & 17 deletions src/dune_rules/lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -235,15 +235,16 @@ module Error = struct
]
;;

let not_virtual_lib ~loc ~impl ~not_vlib =
let impl = Lib_info.name impl in
let not_vlib = Lib_info.name not_vlib in
let not_implementable ~loc ~lib ~not_impl =
let lib = Lib_info.name lib in
let not_impl = Lib_info.name not_impl in
make
~loc
[ Pp.textf
"Library %S is not virtual. It cannot be implemented by %S."
(Lib_name.to_string not_vlib)
(Lib_name.to_string impl)
"Library %S is neither a virtual library nor a library parameter. It cannot be \
implemented by %S."
(Lib_name.to_string not_impl)
(Lib_name.to_string lib)
]
;;
end
Expand Down Expand Up @@ -724,12 +725,12 @@ end = struct
let rec loop acc = function
| [] -> Resolve.Memo.return acc
| (lib, stack) :: libs ->
let virtual_ = Lib_info.virtual_ lib.info in
(match lib.implements, virtual_ with
| None, false -> loop acc libs
| Some _, true -> assert false (* can't be virtual and implement *)
| None, true -> loop (Map.set acc lib (No_impl stack)) libs
| Some vlib, false ->
(match lib.implements, Lib_info.kind lib.info with
| None, Dune_file _ -> loop acc libs
| None, (Parameter | Virtual) -> loop (Map.set acc lib (No_impl stack)) libs
| Some _, (Parameter | Virtual) ->
assert false (* can't be virtual and implement *)
| Some vlib, Dune_file _ ->
let* vlib = Memo.return vlib in
(match Map.find acc vlib with
| None ->
Expand Down Expand Up @@ -945,11 +946,11 @@ end = struct
| Some ((loc, _) as name) ->
let res =
let open Resolve.Memo.O in
let* vlib = resolve_forbid_ignore name in
let virtual_ = Lib_info.virtual_ vlib.info in
match virtual_ with
| false -> Error.not_virtual_lib ~loc ~impl:info ~not_vlib:vlib.info
| true -> Resolve.Memo.return vlib
let* implements = resolve_forbid_ignore name in
match Lib_info.kind implements.info with
| Dune_file _ ->
Error.not_implementable ~loc ~lib:info ~not_impl:implements.info
| Parameter | Virtual -> Resolve.Memo.return implements
in
Memo.map res ~f:Option.some
in
Expand Down
Loading
Loading