Skip to content

Commit fcd8bb4

Browse files
committed
Add functor units and functor packs RFC
1 parent c6e52d5 commit fcd8bb4

File tree

1 file changed

+333
-0
lines changed

1 file changed

+333
-0
lines changed
Lines changed: 333 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,333 @@
1+
# Functor units and functor packs
2+
3+
## Summary
4+
5+
OCaml's module system has great facilities for structuring your code
6+
in the large. It supports encapsulation, parameterisation and even
7+
recursion. Unfortunately not all of these facilities are available
8+
across multiple files. The `-pack` feature allows you to group
9+
multiple files together under an interface, but there isn't really
10+
a way to parameterise a group of files all at once.
11+
12+
This proposal aims to support parameterisation of groups of files by
13+
extending functors to work on groups of files via the `-pack`
14+
mechanism.
15+
16+
## Motivation
17+
18+
Parameterising a group of top-level modules by another module is a
19+
commonly requested feature. Doing it by hand can be quite painful
20+
because each module must be parameterised by both the main parameter
21+
and the applied forms of all the other parameterised modules that
22+
it depends on. For example, if `B` depends on `A` and they are both
23+
parameterised by `Param` then you get the equivalent of:
24+
25+
```ocaml
26+
module A (Param : S) : T with module Param := S
27+
28+
module B (Param : S) (A : T with module Param := S) :
29+
R with module Param := S and module A := A
30+
```
31+
32+
which gets more awkward the more modules are included.
33+
34+
## Details
35+
36+
This proposal is split into 2 sub-proposals:
37+
38+
1. Functor units - allowing compilation units to be functors
39+
2. Functor packs - allowing packed units to be functors
40+
41+
The first part can be upstreamed before the second part is completed.
42+
43+
### Supporting ml files as functors
44+
45+
The aim for this part is to allow an .ml file to be compiled to a functor
46+
rather than a structure. The idea is that the user:
47+
48+
1. Writes ".mli" files for the parameters of the functor and compiles them
49+
with a command-line option like "-parameter-of Foo" where "Foo" is the
50+
name of the functor.
51+
52+
2. Compiles the ".mli" and ".ml" files for the `Foo` module with options
53+
like "-parameter Arg" where "Arg" is the name of one of the
54+
parameters. "Arg" will be available as a module in these files, just
55+
as it would be for the body of a functor. The module type in the
56+
resulting ".cmi" file is that of a functor taking the given
57+
parameters. The code in the resulting ".cmo"/".cmx" file is also that
58+
of a functor taking the given parameters.
59+
60+
Note that the restrictions on what can appear in the body of a functor,
61+
e.g. unwrapping first-class modules must be applied to such modules.
62+
63+
Any attempt to use an interface compiled with "-parameter-of Foo"
64+
outside of `Foo` should give a clear error message.
65+
66+
### Supporting packed functors
67+
68+
The aim for this part is to extend the support in the previous section
69+
to allow packing to be used for creating a functor out of multiple
70+
files. This is achieved by allowing the `-parameter` command-line argument
71+
to be passed when packing a file.
72+
73+
The idea is that the user:
74+
75+
1. Writes ".mli" files for the parameters of the functor and compiles
76+
them with a command-line option like "-parameter-of Pck".
77+
78+
2. Compiles the ".mli" and ".ml" files for the modules in the body of the
79+
functor with an option like "-for-pack Pck(Arg)", where `Pck` is the
80+
name of the packed functor and `Arg` is the name of its parameter.
81+
82+
3. (optional) Compiles the ".mli" of the intended interface for the
83+
packed functor with "-parameter Arg" as an option. This file
84+
describes the return type of the functor, and so it has access to the
85+
parameter modules, but not the component modules of the pack.
86+
87+
3. Runs "ocamlc -pack" passing it "-parameter" options for each
88+
parameter, and the ".cmi" and ".cmo" files of the pack's
89+
sub-modules. This then creates a ".cmi" and ".cmo" file for a module
90+
`Pck` that is a functor from the parameters modules to a module
91+
containing all the sub-modules.
92+
93+
So if we have a parameter `Arg`, and body modules `Foo` and `Bar`, where
94+
`Bar` depends on `Foo`, then we essentially compile `Foo` to:
95+
96+
```ocaml
97+
module Foo (Arg : ...arg.mli...) : sig
98+
...foo.mli...
99+
end = struct
100+
...foo.ml...
101+
end
102+
```
103+
104+
and `Bar` to:
105+
106+
```ocaml
107+
module Bar (Arg : ...arg.mli...) (Foo : ...foo.mli...) : sig
108+
...bar.mli...
109+
end = struct
110+
...bar.ml...
111+
end
112+
```
113+
114+
and finally create `Pck` equivalent to:
115+
116+
```ocaml
117+
module Pck (Arg : ...arg.mli...) : sig
118+
module Foo : sig ...foo.mli... end
119+
module Bar : sig ...bar.mli... end
120+
end = struct
121+
module Foo = Foo(Arg)
122+
module Bar = Bar(Arg)(Foo)
123+
end
124+
```
125+
126+
Although this will all be implemented at the level of `Lambda` code rather
127+
than elaborating to actual OCaml syntax.
128+
129+
### Interface in dune
130+
131+
These features provide more options for how files are compiled. It is
132+
worth considering how such features might be presented to users
133+
through their build systems. I'll describe a potential interface for
134+
dune, but I would expect the presentation of these features in other
135+
build systems to be similar.
136+
137+
#### Exposing `-pack`
138+
139+
Packing could be exposed through dune using a `(pack)` construct
140+
in the list of modules of a library or executable. For example:
141+
142+
```
143+
(library (
144+
(name foo)
145+
(modules
146+
(pack ((name bar) (modules (a b)))))))
147+
```
148+
149+
The user can provide a `bar.mli` file that is the interface of the pack,
150+
but they cannot provide a `bar.ml`.
151+
152+
#### Exposing `-parameter`
153+
154+
Adding a parameter to a module would be exposed using a `parameter`
155+
field in an entry in the `modules` list:
156+
157+
```
158+
(library (
159+
(name foo)
160+
(modules (
161+
a
162+
((name b) (parameters (arg)))))))
163+
```
164+
165+
This would expect an `arg.mli` to describe the parameter, which would be
166+
built with `-parameter-of Bar`. `b.mli` would be built with `-parameter
167+
Arg`.
168+
169+
#### Exposing `-pack` with `-parameter`
170+
171+
Packed functors could be exposed using a `(parameters ...)` field in
172+
the pack construct. For example:
173+
174+
```
175+
(library (
176+
(name foo)
177+
(modules
178+
(pack ((name bar) (parameters (arg)) (modules (a b)))))))
179+
```
180+
181+
This would expect an `arg.mli` to describe the parameter, which would be
182+
built with `-parameter-of Bar`.
183+
184+
#### Exposing these features directly on libraries
185+
186+
In the long run we might also want to expose these features as part
187+
of the library stanza, for creating a library module as a pack. We
188+
could do that with a `(packed true)` field on libraries as well
189+
as a `(parameters ...)` field -- which would imply `(packed true)`:
190+
191+
```
192+
(library (
193+
(name foo)
194+
(parameters (arg))))
195+
```
196+
197+
### Interaction with other tooling
198+
199+
#### Merlin support
200+
201+
I don't think merlin needs any special support to work fine. The only
202+
thing is that the restrictions on first-class modules when used in the
203+
body of a functor would not be reported as errors. Adding a flag to
204+
`.merlin` files would allow that to be addressed.
205+
206+
#### Odoc support
207+
208+
This proposal will require some small additions to odoc but they are
209+
pretty easy to handle.
210+
211+
### Full example
212+
213+
As a demonstration, here's the complete source for a library `Lib`
214+
containing a packed functor `Pck` with two submodules `Foo` and `Bar`:
215+
216+
dune
217+
```
218+
(library (
219+
(name lib)
220+
(modules (
221+
(pack ((name pck) (parameters (arg)) (modules foo bar)))))))
222+
```
223+
224+
arg.mli
225+
226+
```
227+
type t
228+
229+
val a : t
230+
231+
val b : t
232+
233+
val print : t -> unit
234+
```
235+
236+
foo.mli
237+
238+
```
239+
type t = Arg.t list
240+
241+
val mk : t -> t
242+
243+
val iter : t -> (Arg.t -> unit) -> unit
244+
```
245+
246+
foo.ml
247+
248+
```
249+
type t = Arg.t list
250+
251+
let mk t = t
252+
253+
let iter = List.iter
254+
```
255+
256+
bar.mli
257+
258+
```
259+
val run : Foo.t -> unit
260+
```
261+
262+
bar.ml
263+
264+
```
265+
let run t =
266+
Arg.print Arg.a;
267+
Foo.iter (fun t -> Arg.print t);
268+
Arg.print Arg.b
269+
```
270+
271+
pck.mli (optional)
272+
273+
```
274+
module Foo : sig
275+
276+
type t
277+
278+
val mk : Arg.t list -> t
279+
280+
end
281+
282+
module Bar : sig
283+
284+
val run : Foo.t -> unit
285+
286+
end
287+
```
288+
289+
lib.ml (optional)
290+
291+
```
292+
module Pck = Pck
293+
```
294+
295+
Here is some code using the functor:
296+
297+
```
298+
module Int = struct
299+
type t = int
300+
let a = 1
301+
let b = 5
302+
let print = print_int
303+
end
304+
305+
module L = Lib.Pck(Int)
306+
307+
let () = L.Bar.run (L.Foo.mk [2; 3; 4])
308+
```
309+
310+
## Drawbacks
311+
312+
- This builds on the `-pack` mechanism, which has some drawbacks:
313+
314+
1. Touching any component triggers recompilation of all clients of
315+
the packed module.
316+
317+
2. Linking part of a packed module forces linking the whole packed
318+
module.
319+
320+
For these reasons most existing uses of `-pack` have been replaced
321+
by approaches based on module aliases.
322+
323+
These issues might be avoidable with some other approach. Although
324+
it couldn't be based on module aliases, since those approaches rely
325+
on being able to refer to *the* module `M` but thanks to
326+
side-effects you cannot talk about *the* module `F(X)` only *a*
327+
module `F(X)`.
328+
329+
## Alternatives
330+
331+
- A common alternative to this proposal at the moment is `sed`. That
332+
has many obvious drawbacks, but does avoid adding new compilation
333+
flags to the compiler.

0 commit comments

Comments
 (0)