Skip to content

Commit cdca0db

Browse files
authored
Merge pull request #11963 from maiste/library_parameter
Support the library_parameter stanza
2 parents 20531de + e45b5fa commit cdca0db

33 files changed

+711
-72
lines changed

doc/changes/11963.md

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
## Added
2+
3+
- (Experimental): Introduce the `library_parameter` stanza. It allows users to declare a parameter when
4+
using the OxCaml compiler (#11963, implements #12084, @maiste)

doc/reference/dune/index.rst

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -75,6 +75,12 @@ The following pages describe the available stanzas and their meanings.
7575
ocamllex
7676
ocamlyacc
7777

78+
.. toctree::
79+
:caption: Experimental
80+
:maxdepth: 1
81+
82+
library_parameter
83+
7884
.. toctree::
7985
:caption: Deprecated
8086
:maxdepth: 1
Lines changed: 109 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,109 @@
1+
library_parameter
2+
-----------------
3+
4+
.. warning::
5+
6+
This feature is experimental and requires the compiler you are using to
7+
support parameterized libraries.
8+
9+
The ``library_parameter`` stanza describes a parameter interface defined in a single ``.mli`` file. To enable this feature,
10+
you need to add ``(using oxcaml 0.1)`` :doc:`extension
11+
</reference/dune-project/using>` in your ``dune-project`` file.
12+
13+
.. describe:: (library_parameter ...)
14+
15+
.. versionadded:: 3.20
16+
17+
Define a parameter.
18+
19+
.. describe:: (name <parameter-name>)
20+
21+
``parameter-name`` is the name of the library parameter. It must be a valid
22+
OCaml module name as for :doc:`/reference/dune/library`.
23+
24+
This must be specified if no `public_name` is specified.
25+
26+
.. describe:: (public_name ...)
27+
28+
The name under which the library parameter can be referred as a dependency
29+
when it's not part of the current workspace, i.e., when it is installed.
30+
Without a ``(public_name ...)`` field, the library parameter won't be
31+
installed by Dune. The public name must start with the package name it's
32+
part of and optionally followed by a dot, then anything else you want. The
33+
package name must also be one of the packages that Dune knows about, as
34+
determined by the logic described in :doc:`/reference/packages`.
35+
36+
.. describe:: (package <package>)
37+
38+
Installs a private library parameter under the specified package. Such a
39+
parameter is now usable by public libraries defined in the same project.
40+
41+
.. describe:: (synopsis <string>)
42+
43+
A one-line description of the library parameter.
44+
45+
.. describe:: (modules <modules>)
46+
47+
Specifies a specific module to select as a `library_parameter`.
48+
49+
``<modules>`` uses the :doc:`/reference/ordered-set-language`, where
50+
elements are module names and don't need to start with an uppercase letter.
51+
52+
The library parameter **must** only declare one ``mli`` file as part of its
53+
modules.
54+
55+
.. describe:: (libraries <library-dependencies>)
56+
57+
Specifies the library parameter's dependencies.
58+
59+
See :doc:`/reference/library-dependencies` for more details.
60+
61+
.. describe:: (preprocesss <preprocess-spec>)
62+
63+
Specifies how to preprocess files when needed.
64+
65+
The default is ``no_preprocessing``, and other options are described
66+
in :doc:`/reference/preprocessing-spec`.
67+
68+
.. describe:: (preprocessor_deps (<deps-conf list>))
69+
70+
Specifies extra preprocessor dependencies preprocessor, i.e., if the
71+
preprocessor reads a generated file.
72+
73+
The specification of dependencies is described in
74+
:doc:`/concepts/dependency-spec`.
75+
76+
77+
.. describe:: (flags ...)
78+
79+
See :doc:`/concepts/ocaml-flags`.
80+
81+
.. describe:: (ocamlc_flags ...)
82+
83+
See :doc:`/concepts/ocaml-flags`.
84+
85+
.. describe:: (ocamlopt_flags ...)
86+
87+
See :doc:`/concepts/ocaml-flags`.
88+
89+
.. describe:: (optional)
90+
91+
If present, it indicates that the library parameter should only be built
92+
and installed if all the dependencies are available, either in the
93+
workspace or in the installed world.
94+
95+
.. describe:: (enabled_if <blang expression>)
96+
97+
Conditionally disables a library parameter.
98+
99+
A disabled library parameter cannot be built and will not be installed.
100+
101+
The condition is specified using the :doc:`/reference/boolean-language`, and
102+
the field allows for the ``%{os_type}`` variable, which is expanded to the
103+
type of OS being targeted by the current build. Its value is the same as the
104+
value of the ``os_type`` parameter in the output of ``ocamlc -config``.
105+
106+
.. describe:: (allow_overlapping_dependencies)
107+
108+
Allows external dependencies to overlap with libraries that are present in
109+
the workspace.

src/dune_lang/dune_lang.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -59,6 +59,7 @@ module Js_of_ocaml = Js_of_ocaml
5959
module Menhir = Menhir
6060
module Rule_mode_decoder = Rule_mode_decoder
6161
module Mode_conf = Mode_conf
62+
module Oxcaml = Oxcaml
6263

6364
(* CR-someday rgrinberg: perhaps wrap these under [Stanzas]? *)
6465
module Copy_files = Copy_files

src/dune_lang/lib_kind.ml

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -62,13 +62,15 @@ type t =
6262
| Normal
6363
| Ppx_deriver of Ppx_args.t
6464
| Ppx_rewriter of Ppx_args.t
65+
| Parameter
6566

6667
let equal = Poly.equal
6768

6869
let to_dyn x =
6970
let open Dyn in
7071
match x with
7172
| Normal -> variant "Normal" []
73+
| Parameter -> variant "Parameter" []
7274
| Ppx_deriver args -> variant "Ppx_deriver" [ Ppx_args.to_dyn args ]
7375
| Ppx_rewriter args -> variant "Ppx_rewriter" [ Ppx_args.to_dyn args ]
7476
;;
@@ -77,6 +79,7 @@ let decode =
7779
let open Decoder in
7880
sum
7981
[ "normal", return Normal
82+
; "parameter", return Parameter
8083
; ( "ppx_deriver"
8184
, let+ args = Ppx_args.decode in
8285
Ppx_deriver args )
@@ -90,6 +93,7 @@ let encode t =
9093
match
9194
match t with
9295
| Normal -> Dune_sexp.atom "normal"
96+
| Parameter -> Dune_sexp.atom "parameter"
9397
| Ppx_deriver x -> List (Dune_sexp.atom "ppx_deriver" :: Ppx_args.encode x)
9498
| Ppx_rewriter x -> List (Dune_sexp.atom "ppx_rewriter" :: Ppx_args.encode x)
9599
with

src/dune_lang/lib_kind.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ type t =
1717
| Normal
1818
| Ppx_deriver of Ppx_args.t
1919
| Ppx_rewriter of Ppx_args.t
20+
| Parameter
2021

2122
val to_dyn : t Dyn.builder
2223
val equal : t -> t -> bool

src/dune_rules/buildable_rules.ml

Lines changed: 17 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -55,6 +55,7 @@ let with_lib_deps (t : Context.t) merlin_ident ~dir ~f =
5555
type kind =
5656
| Executables of Buildable.t * (Loc.t * string) list
5757
| Library of Buildable.t * Lib_name.Local.t
58+
| Parameter of Buildable.t * Lib_name.Local.t
5859
| Melange of
5960
{ preprocess : Preprocess.With_instrumentation.t Preprocess.Per_module.t
6061
; preprocessor_deps : Dep_conf.t list
@@ -145,9 +146,22 @@ let modules_rules
145146
;;
146147

147148
let modules_rules sctx kind expander ~dir scope modules =
149+
let* () =
150+
match kind with
151+
| Executables _ | Library _ | Melange _ -> Memo.return ()
152+
| Parameter _ ->
153+
let* ocaml = Super_context.context sctx |> Context.ocaml in
154+
let ocaml_version = Ocaml_config.version_string ocaml.ocaml_config in
155+
if Ocaml.Version.supports_parametrized_library ocaml_version
156+
then Memo.return ()
157+
else
158+
User_error.raise
159+
[ Pp.text "The compiler you are using is not compatible with library parameter"
160+
]
161+
in
148162
let preprocess, preprocessor_deps, lint, empty_module_interface_if_absent =
149163
match kind with
150-
| Executables (buildable, _) | Library (buildable, _) ->
164+
| Executables (buildable, _) | Library (buildable, _) | Parameter (buildable, _) ->
151165
( buildable.preprocess
152166
, buildable.preprocessor_deps
153167
, buildable.lint
@@ -158,12 +172,12 @@ let modules_rules sctx kind expander ~dir scope modules =
158172
let lib_name =
159173
match kind with
160174
| Executables _ | Melange _ -> None
161-
| Library (_, name) -> Some name
175+
| Library (_, name) | Parameter (_, name) -> Some name
162176
in
163177
let empty_intf_modules =
164178
match kind with
165179
| Executables (_, modules) -> Some modules
166-
| Library _ | Melange _ -> None
180+
| Library _ | Melange _ | Parameter _ -> None
167181
in
168182
modules_rules
169183
~preprocess

src/dune_rules/buildable_rules.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ val with_lib_deps
2323
type kind =
2424
| Executables of Buildable.t * (Loc.t * string) list
2525
| Library of Buildable.t * Lib_name.Local.t
26+
| Parameter of Buildable.t * Lib_name.Local.t
2627
| Melange of
2728
{ preprocess : Preprocess.With_instrumentation.t Preprocess.Per_module.t
2829
; preprocessor_deps : Dep_conf.t list

src/dune_rules/gen_meta.ml

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -76,7 +76,7 @@ let gen_lib pub_name lib ~version =
7676
in
7777
let preds =
7878
match kind with
79-
| Normal -> []
79+
| Normal | Parameter -> []
8080
| Ppx_rewriter _ | Ppx_deriver _ -> [ Pos "ppx_driver" ]
8181
in
8282
let name lib =
@@ -127,7 +127,7 @@ let gen_lib pub_name lib ~version =
127127
; ppx_runtime_deps ppx_rt_deps
128128
])
129129
; (match kind with
130-
| Normal -> []
130+
| Normal | Parameter -> []
131131
| Ppx_rewriter _ | Ppx_deriver _ ->
132132
(* Deprecated ppx method support *)
133133
let no_ppx_driver = Neg "ppx_driver"
@@ -139,7 +139,7 @@ let gen_lib pub_name lib ~version =
139139
; requires ~preds:[ no_ppx_driver ] ppx_runtime_deps_for_deprecated_method
140140
]
141141
; (match kind with
142-
| Normal -> assert false
142+
| Normal | Parameter -> assert false
143143
| Ppx_rewriter _ ->
144144
[ rule "ppx" [ no_ppx_driver; no_custom_ppx ] Set "./ppx.exe --as-ppx"
145145
; rule "library_kind" [] Set "ppx_rewriter"

src/dune_rules/install_rules.ml

Lines changed: 27 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -79,7 +79,7 @@ module Stanzas_to_entries : sig
7979
end = struct
8080
let lib_ppxs ctx ~scope ~(lib : Library.t) =
8181
match lib.kind with
82-
| Normal | Ppx_deriver _ -> Memo.return []
82+
| Normal | Parameter | Ppx_deriver _ -> Memo.return []
8383
| Ppx_rewriter _ ->
8484
Library.best_name lib
8585
|> Ppx_driver.ppx_exe ctx ~scope
@@ -266,6 +266,7 @@ end = struct
266266
let { Lib_mode.Map.ocaml = { Mode.Dict.byte; native } as ocaml; melange } =
267267
Mode_conf.Lib.Set.eval lib.modes ~has_native
268268
in
269+
let is_parameter = Library.is_parameter lib in
269270
let+ melange_runtime_entries = additional_deps lib.melange_runtime_deps
270271
and+ public_headers = additional_deps lib.public_headers
271272
and+ module_files =
@@ -297,16 +298,21 @@ end = struct
297298
fun m ->
298299
let cm_file kind = Obj_dir.Module.cm_file obj_dir m ~kind in
299300
let open Lib_mode.Cm_kind in
300-
[ if_ (native || byte) (Ocaml Cmi, cm_file (Ocaml Cmi))
301-
; if_ native (Ocaml Cmx, cm_file (Ocaml Cmx))
302-
; if_ (byte && virtual_library) (Ocaml Cmo, cm_file (Ocaml Cmo))
303-
; if_
304-
(native && virtual_library)
305-
(Ocaml Cmx, Obj_dir.Module.o_file obj_dir m ~ext_obj)
306-
; if_ melange (Melange Cmi, cm_file (Melange Cmi))
307-
; if_ melange (Melange Cmj, cm_file (Melange Cmj))
308-
]
309-
|> List.rev_concat
301+
let cmi = if_ (native || byte) (Ocaml Cmi, cm_file (Ocaml Cmi)) in
302+
let rest =
303+
if is_parameter
304+
then []
305+
else
306+
[ if_ native (Ocaml Cmx, cm_file (Ocaml Cmx))
307+
; if_ (byte && virtual_library) (Ocaml Cmo, cm_file (Ocaml Cmo))
308+
; if_
309+
(native && virtual_library)
310+
(Ocaml Cmx, Obj_dir.Module.o_file obj_dir m ~ext_obj)
311+
; if_ melange (Melange Cmi, cm_file (Melange Cmi))
312+
; if_ melange (Melange Cmj, cm_file (Melange Cmj))
313+
]
314+
in
315+
cmi :: rest |> List.rev_concat
310316
in
311317
let set_dir m = List.rev_map ~f:(fun (cm_kind, p) -> cm_dir m cm_kind, p) in
312318
let+ modules_impl =
@@ -348,11 +354,16 @@ end = struct
348354
[ sources
349355
; melange_runtime_entries
350356
; List.rev_map module_files ~f:(fun (sub_dir, file) -> make_entry ?sub_dir Lib file)
351-
; List.rev_map lib_files ~f:(fun (section, file) -> make_entry section file)
352-
; List.rev_map execs ~f:(make_entry Libexec)
353-
; dll_files
354-
; install_c_headers
355-
; public_headers
357+
; (match is_parameter with
358+
| true -> []
359+
| false ->
360+
List.rev_concat
361+
[ List.rev_map lib_files ~f:(fun (section, file) -> make_entry section file)
362+
; List.rev_map execs ~f:(make_entry Libexec)
363+
; dll_files
364+
; install_c_headers
365+
; public_headers
366+
])
356367
]
357368
;;
358369

0 commit comments

Comments
 (0)