Skip to content

Commit 19c7e41

Browse files
committed
Updated with first round of comments
1 parent 3dc00bf commit 19c7e41

File tree

1 file changed

+134
-11
lines changed

1 file changed

+134
-11
lines changed

rfcs/type_arguments_for_modules.md

Lines changed: 134 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -4,18 +4,106 @@
44
This RFC proposes to extend a bit the module language by adding the possibility
55
of giving types arguments to modules.
66

7-
The goal of this feature is to simplify replace cases where the user might want
7+
The goal of this feature is to simplify cases where the user might want
88
to have a module containing only a single type by directly writing the type.
99
In those cases we currently force the user to define a module containing that
1010
type.
1111

12-
## Proof of concept
12+
## Use cases
1313

14-
A first draft of this feature is implemented at
15-
https://github.com/samsa1/ocaml/tree/module_type_arg .
14+
The motivation for this feature came from people working on modular explicits
15+
and modular implicits. However, this feature will also benefit OCaml even
16+
without modular implicits.
1617

17-
It features types as arguments in modules expression and type paths
18-
as arguments in modules paths.
18+
### Modular explicits/implicits
19+
20+
This feature becomes very important when taking into account modular explicits
21+
and [modular implicits](https://arxiv.org/pdf/1512.01895). Because interactions
22+
between the code language and the module language becomes much more frequent.
23+
24+
In the case of modular implicits, a signature is given in order to search for a
25+
compatible module. However, basic types are not compatible with parametrized
26+
types.
27+
28+
Thus, the module following module :
29+
30+
```ocaml
31+
module AddList = struct
32+
type 'a t = 'a list
33+
let add = List.concat
34+
end
35+
```
36+
37+
does not match the signature of addition.
38+
39+
```ocaml
40+
module type Add = sig
41+
type t
42+
val add : t -> t -> t
43+
end
44+
```
45+
46+
A way to fix this is to add a type argument to the `AddList` module.
47+
48+
```ocaml
49+
module AddList (A : Any) = struct
50+
type t = A.t list
51+
let add : t -> t -> t = List.concat
52+
```
53+
54+
However, this becomes problematic with modular implicits because you need to
55+
define a sufficient amount of modules to access any possible types. This lead
56+
Patrick Reader and Daniel Vlasits to write a whole file of modules containing
57+
only a type field :
58+
https://github.com/modular-implicits/imp/blob/master/lib/any.mli.
59+
60+
61+
62+
### Use cases in current OCaml
63+
64+
Is some cases a parametric module requires as argument a type without any
65+
structure attached to it. This is useful when we just want to store the type
66+
but never look into it. Cases where this pattern occurs exists in the OCaml code
67+
base.
68+
69+
70+
#### State monad in algebraic effects tutorial
71+
72+
For example when implementing a state monad such as the
73+
one in the example available at :
74+
https://github.com/ocaml-multicore/ocaml-effects-tutorial/blob/998376931b7fdaed5d54cb96b39b301b993ba995/sources/state2.ml#L13-L40.
75+
76+
```ocaml
77+
module type STATE = sig
78+
type t
79+
val put : t -> unit
80+
val get : unit -> t
81+
val history : unit -> t list
82+
val run : (unit -> unit) -> init:t -> unit
83+
end
84+
85+
module State (S : sig type t end) : STATE with type t = S.t = struct
86+
87+
type t = S.t
88+
89+
type _ Effect.t += Get : t Effect.t
90+
91+
let get () = perform Get
92+
93+
let put v = failwith "not implemented"
94+
95+
let history () = failwith "not implemented"
96+
97+
let run f ~init = failwith "not implemented"
98+
end
99+
```
100+
101+
#### In ocamlgraph
102+
103+
Another example of usage that feature in the OCaml would be in
104+
[ocamlgraph](https://github.com/backtracking/ocamlgraph). Where some parametric
105+
modules such as `Imperative.Graph.AbstractLabeled` requires a module containing
106+
a single type as argument (here the types for vertex labels).
19107

20108
## Proposed change
21109

@@ -37,8 +125,36 @@ module M3 = M(type [`A | `B])
37125
let f (x : M(type int).t) = x
38126
```
39127

128+
## Proof of concept
40129

41-
## Important restraints
130+
A first draft of this feature is implemented at
131+
https://github.com/samsa1/ocaml/tree/module_type_arg .
132+
133+
It features types as arguments in modules expression and type paths
134+
as arguments in modules paths.
135+
136+
## Semantic change
137+
138+
This feature does not change the semantic, it is just adds conciseness.
139+
140+
The reason behind this is that all module expression using type arguments could
141+
be rewritten to a module expression using a module wrapping the type.
142+
143+
For example :
144+
145+
```ocaml
146+
1: module F (type a) = BODY [a]
147+
2: F (type p)
148+
```
149+
150+
could be encoded as the following.
151+
152+
```ocaml
153+
1: module F (A : Type) = BODY [A.t]
154+
2: F (struct type t = p end)
155+
```
156+
157+
## Important restrictions
42158

43159
This feature needs some restraints in order to be sound.
44160

@@ -55,12 +171,17 @@ type t2 = M(type int).t
55171
let f (x : t1) = (x : t2)
56172
```
57173

174+
This also mean that when defining a type-functor `functor (type a) -> ME1`,
175+
the same restrictions on `ME1` apply than on `ME2` in `functor (M : S) -> ME2`.
176+
58177
### Paths in paths
59178

60-
Only type paths should be authorized when doing an application inside
61-
a type path.
179+
Only [type constructors](https://ocaml.org/manual/5.2/names.html#typeconstr)
180+
should be authorized inside a module path. The reason for this restriction is
181+
that adding too much complexity inside paths would add a circular dependency
182+
between path comparison and type unification.
62183

63-
In other words, `M(type <m: int>).t` should be rejected.
184+
For example, `M(type <m: int>).t` should be rejected.
64185

65186
### Type application must be compiled as an empty structure
66187

@@ -82,9 +203,11 @@ let r2 = let module M = F(type float) in M.r
82203
If `F(type _)` does not launch any computation then `r1` and `r2` will be the
83204
same reference but with incompatible types.
84205

206+
Side note : for safety reason the functor above should have been generative.
207+
85208
## Possible extensions
86209

87210
This feature could be extended with other similar patterns to be a bit more expressive.
88211

89212
- Implement the same feature with module types,
90-
- Allow using parametric types in paths (for example `int list`).
213+
- Allow using parametric types in paths (for example `M(type int list).t`).

0 commit comments

Comments
 (0)