@@ -68,3 +68,86 @@ be able to see ``foo`` independently of whether :doc:`implicit
6868transitive dependencies<dune-project/implicit_transitive_deps>` are
6969allowed or not. When they are allowed, which is the default, all transitive
7070dependencies are visible, whether they are marked as re-exported or not.
71+
72+ Instantiating Parameterised Dependencies
73+ ----------------------------------------
74+
75+ This feature requires OxCaml, see :doc: `/reference/dune/library_parameter `.
76+
77+ A parameterised dependency ``foo `` can be instantiated with the arguments
78+ ``bar ``, ``qux `` using the syntax:
79+
80+ .. code :: dune
81+
82+ (foo bar qux)
83+
84+ For example:
85+
86+ .. code :: dune
87+
88+ (library
89+ (name test)
90+ (libraries (foo bar qux)))
91+
92+ The library ``foo `` must have declared the set of parameters it expects, and
93+ the arguments given to the instantiation must implement a subset of these
94+ parameters. The ordering of the arguments does not matter, as the instantiation
95+ relies on the implemented parameter to uniquely identify each argument.
96+ For executables, the parameterised dependencies must be fully instantiated.
97+
98+ In the OCaml code, the instantiated library will be available under the module
99+ name ``Foo ``. To avoiding overlapping module names when instantiating the same
100+ dependency multiple times, the syntax ``:as `` allows renaming the module. For
101+ example:
102+
103+ .. code :: dune
104+
105+ (library
106+ (name test)
107+ (libraries
108+ (foo a b :as foo_a_b)
109+ (foo bar qux :as foo_bar_qux)))
110+
111+ Then the instantiations will be available under the names ``Foo_a_b `` and
112+ ``Foo_bar_qux ``.
113+
114+ Dependencies automatically inherit the parameters of their parent library.
115+ For example, assuming the parameterised library ``foo `` requires two
116+ parameters ``p `` and ``q ``:
117+
118+ .. code :: dune
119+
120+ (library
121+ (name test)
122+ (parameters p q)
123+ (libraries
124+ (foo :as foo_implicit)
125+ (foo an_implementation_of_q :as foo_q)
126+ (foo bar qux :as foo_bar_qux)
127+ other_foo))
128+
129+ Then ``foo_implicit `` is implicitly ``(foo p q) ``,
130+ while ``(foo an_implementation_of_q) `` will only inherit the parameter ``p ``.
131+
132+ If ``other_foo ``, which is not explicitly instantiated here, is also
133+ parameterised by the parameters ``p `` (and) or ``q ``, it will also inherit
134+ its parent arguments. Dune will report an error if a dependency requires
135+ parameters which have neither been given explicitly given via an instantiation
136+ and are not listed in the parent library parameters.
137+
138+ For unwrapped libaries, the instantiation of parameterised libraries is not
139+ currently generated. This is subject to change soon, but in the mean time,
140+ you'll need to manually declare the instantiations: If you depend on the
141+ instantiation ``(foo bar qux :as new_name) `` with ``bar `` an implementation of
142+ the parameter ``param_bar `` and ``qux `` an implementation of ``param_qux ``,
143+ then you'll need to write the following:
144+
145+ .. code :: ocaml
146+
147+ module New_name = Foo (Param_bar) (Bar) (Param_qux) (Qux) [@jane.non_erasable.instances]
148+
149+ .. note ::
150+
151+ While this reuses the OCaml functor application syntax, the attribute changes
152+ the meaning: The ``(Param) (Impl) `` must go together as a pair, but the
153+ ordering of the arguments otherwise does not matter.
0 commit comments