@@ -14,50 +14,44 @@ category: "Module System"
14
14
15
15
In OCaml, every piece of code is wrapped into a module. Optionally, a module
16
16
itself can be a submodule of another module, pretty much like directories in a
17
- file system - but we don't do this very often .
17
+ file system.
18
18
19
19
When you write a program, let's say using two files ` amodule.ml ` and
20
20
` bmodule.ml ` , each of these files automatically defines a module named
21
21
` Amodule ` and a module named ` Bmodule ` that provide whatever you put into the
22
22
files.
23
23
24
24
Here is the code that we have in our file ` amodule.ml ` :
25
-
26
25
<!-- $MDX file=examples/amodule.ml -->
27
26
``` ocaml
28
27
let hello () = print_endline "Hello"
29
28
```
30
29
31
30
And here is what we have in ` bmodule.ml ` :
32
-
33
31
<!-- $MDX file=examples/bmodule.ml -->
34
32
``` ocaml
35
33
let () = Amodule.hello ()
36
34
```
37
35
38
- ### Automatised Compilation
39
-
40
- In order to compile them using the [ Dune] ( https://dune.build/ ) build system,
41
- which is now the standard on OCaml, at least two configuration files are
42
- required:
36
+ In order to compile them using the [ Dune] ( https://dune.build/ ) build system, at least two configuration files are required:
43
37
44
- * The ` dune-project ` file, which contains project-wide configuration data.
38
+ * The ` dune-project ` file contains project-wide configuration data.
45
39
Here's a very minimal one:
40
+ ``` lisp
41
+ (lang dune 3.7)
46
42
```
47
- (lang dune 3.4)
48
- ```
49
- * The ` dune ` file, which contains actual build directives. A project may have several
43
+ * The ` dune ` file contains actual build directives. A project may have several
50
44
of them, depending on the organisation of the sources. This is sufficient for
51
45
our example:
52
- ```
46
+ ``` lisp
53
47
(executable (name bmodule))
54
48
```
55
49
56
50
Here is how to create the configuration files, build the source, and run the
57
51
executable.
58
52
<!-- $MDX dir=examples -->
59
53
``` bash
60
- $ echo " (lang dune 3.4 )" > dune-project
54
+ $ echo " (lang dune 3.7 )" > dune-project
61
55
$ echo " (executable (name bmodule))" > dune
62
56
$ dune build
63
57
$ dune exec ./bmodule.exe
@@ -74,39 +68,9 @@ In a real-world project, it is preferable to start by creating the `dune`
74
68
configuration files and directory structure using the ` dune init project `
75
69
command.
76
70
77
- ### Manual Compilation
78
-
79
- Alternatively, it is possible, but not recommended, to compile the files by
80
- directly calling the compiler, either by using a single command:
81
-
82
- <!-- $MDX dir=examples -->
83
- ``` sh
84
- $ ocamlopt -o hello amodule.ml bmodule.ml
85
- ```
86
-
87
- Or, as a build system does, one by one:
88
-
89
- <!-- $MDX dir=examples -->
90
- ``` sh
91
- $ ocamlopt -c amodule.ml
92
- $ ocamlopt -c bmodule.ml
93
- $ ocamlopt -o hello amodule.cmx bmodule.cmx
94
- ```
95
-
96
- In both cases, a standalone executable is created
97
- <!-- $MDX dir=examples -->
98
- ``` sh
99
- $ ./hello
100
- Hello
101
- ```
102
-
103
- Note: It's necessary to place the source files in the correct order. The dependencies must come before
104
- the dependent. In the first example above, putting ` bmodule.ml ` before ` amodule.ml `
105
- will result in an ` Unbound module ` error.
106
-
107
71
### Naming and Scoping
108
72
109
- Now we have an executable that prints ` Hello ` . As you can see, if you want to
73
+ Now we have an executable that prints ` Hello ` . If you want to
110
74
access anything from a given module, use the name of the module (always
111
75
starting with a capital letter) followed by a dot and the thing that you want to use.
112
76
It may be a value, a type constructor, or anything else that a given module can
@@ -141,15 +105,15 @@ let () = List.iter (printf "%s\n") data
141
105
There are also local ` open ` s:
142
106
143
107
``` ocaml
144
- # let map_3d_matrix f m =
145
- let open Array in
146
- map (map (map f)) m ;;
147
- val map_3d_matrix :
148
- ('a -> 'b) -> 'a array array array -> 'b array array array = <fun>
149
- # let map_3d_matrix' f =
150
- Array.(map (map (map f)) );;
151
- val map_3d_matrix ' :
152
- ('a -> 'b) -> 'a array array array -> 'b array array array = <fun>
108
+ # let sum_sq m =
109
+ let open List in
110
+ init m Fun.id |> map (fun i -> i * i) |> fold_left ( + ) 0 ;;
111
+ val sum_sq : int -> int = <fun>
112
+
113
+ # let sym_sq' m =
114
+ Array.(init m Fun.id |> map (fun i -> i * i) |> fold_left ( + ) 0 );;
115
+ val sum_sq ' : int -> int = <fun>
116
+
153
117
```
154
118
155
119
## Interfaces and Signatures
@@ -162,8 +126,8 @@ is better that a module only provides what it is meant to provide, not any of
162
126
the auxiliary functions and types that are used internally.
163
127
164
128
For this, we have to define a module interface, which will act as a mask over
165
- the module's implementation. Just like a module derives from an ` .ml ` file, the
166
- corresponding module interface or signature derives from an ` .mli ` file. It
129
+ the module's implementation. Just like a module derives from a ` .ml ` file, the
130
+ corresponding module interface or signature derives from a ` .mli ` file. It
167
131
contains a list of values with their type. Let's rewrite our ` amodule.ml ` file
168
132
to something called ` amodule2.ml ` :
169
133
@@ -204,7 +168,7 @@ let () = Amodule2.hello ()
204
168
205
169
The .` mli ` files must be compiled before the matching ` .ml ` files. This is done
206
170
automatically by Dune. We update the ` dune ` file to allow the compilation
207
- of this example aside of the previous one.
171
+ of this example aside from the previous one.
208
172
209
173
<!-- $MDX dir=examples -->
210
174
``` bash
@@ -216,22 +180,6 @@ $ dune exec ./bmodule2.exe
216
180
Hello 2
217
181
```
218
182
219
- Here is how the same result can be achieved by calling the compiler manually.
220
- Notice the ` .mli ` file is compiled using bytecode compiler ` ocamlc ` , while
221
- ` .ml ` files are compiled to native code using ` ocamlopt ` :
222
-
223
- <!-- $MDX dir=examples -->
224
- ``` sh
225
- $ ocamlc -c amodule2.mli
226
- $ ocamlopt -c amodule2.ml
227
- $ ocamlopt -c bmodule2.ml
228
- $ ocamlopt -o hello2 amodule2.cmx bmodule2.cmx
229
- $ ./hello
230
- Hello
231
- $ ./hello2
232
- Hello 2
233
- ```
234
-
235
183
## Abstract Types
236
184
237
185
What about type definitions? We saw that values such as functions can be
@@ -371,175 +319,38 @@ interfaces.
371
319
### Displaying the Interface of a Module
372
320
373
321
You can use the OCaml toplevel to visualise the contents of an existing
374
- module, such as ` List ` :
322
+ module, such as ` Fun ` :
375
323
376
324
``` ocaml
377
- # #show List ;;
378
- module List :
325
+ # #show Fun ;;
326
+ module Fun :
379
327
sig
380
- type 'a t = 'a list = [] | (::) of 'a * 'a list
381
- val length : 'a t -> int
382
- val compare_lengths : 'a t -> 'b t -> int
383
- val compare_length_with : 'a t -> int -> int
384
- val cons : 'a -> 'a t -> 'a t
385
- val hd : 'a t -> 'a
386
- val tl : 'a t -> 'a t
387
- val nth : 'a t -> int -> 'a
388
- val nth_opt : 'a t -> int -> 'a option
389
- val rev : 'a t -> 'a t
390
- val init : int -> (int -> 'a) -> 'a t
391
- val append : 'a t -> 'a t -> 'a t
392
- val rev_append : 'a t -> 'a t -> 'a t
393
- val concat : 'a t t -> 'a t
394
- val flatten : 'a t t -> 'a t
395
- val equal : ('a -> 'a -> bool) -> 'a t -> 'a t -> bool
396
- val compare : ('a -> 'a -> int) -> 'a t -> 'a t -> int
397
- val iter : ('a -> unit) -> 'a t -> unit
398
- val iteri : (int -> 'a -> unit) -> 'a t -> unit
399
- val map : ('a -> 'b) -> 'a t -> 'b t
400
- val mapi : (int -> 'a -> 'b) -> 'a t -> 'b t
401
- val rev_map : ('a -> 'b) -> 'a t -> 'b t
402
- val filter_map : ('a -> 'b option) -> 'a t -> 'b t
403
- val concat_map : ('a -> 'b t) -> 'a t -> 'b t
404
- val fold_left_map : ('a -> 'b -> 'a * 'c) -> 'a -> 'b t -> 'a * 'c t
405
- val fold_left : ('a -> 'b -> 'a) -> 'a -> 'b t -> 'a
406
- val fold_right : ('a -> 'b -> 'b) -> 'a t -> 'b -> 'b
407
- val iter2 : ('a -> 'b -> unit) -> 'a t -> 'b t -> unit
408
- val map2 : ('a -> 'b -> 'c) -> 'a t -> 'b t -> 'c t
409
- val rev_map2 : ('a -> 'b -> 'c) -> 'a t -> 'b t -> 'c t
410
- val fold_left2 : ('a -> 'b -> 'c -> 'a) -> 'a -> 'b t -> 'c t -> 'a
411
- val fold_right2 : ('a -> 'b -> 'c -> 'c) -> 'a t -> 'b t -> 'c -> 'c
412
- val for_all : ('a -> bool) -> 'a t -> bool
413
- val exists : ('a -> bool) -> 'a t -> bool
414
- val for_all2 : ('a -> 'b -> bool) -> 'a t -> 'b t -> bool
415
- val exists2 : ('a -> 'b -> bool) -> 'a t -> 'b t -> bool
416
- val mem : 'a -> 'a t -> bool
417
- val memq : 'a -> 'a t -> bool
418
- val find : ('a -> bool) -> 'a t -> 'a
419
- val find_opt : ('a -> bool) -> 'a t -> 'a option
420
- val find_map : ('a -> 'b option) -> 'a t -> 'b option
421
- val filter : ('a -> bool) -> 'a t -> 'a t
422
- val find_all : ('a -> bool) -> 'a t -> 'a t
423
- val filteri : (int -> 'a -> bool) -> 'a t -> 'a t
424
- val partition : ('a -> bool) -> 'a t -> 'a t * 'a t
425
- val partition_map : ('a -> ('b, 'c) Either.t) -> 'a t -> 'b t * 'c t
426
- val assoc : 'a -> ('a * 'b) t -> 'b
427
- val assoc_opt : 'a -> ('a * 'b) t -> 'b option
428
- val assq : 'a -> ('a * 'b) t -> 'b
429
- val assq_opt : 'a -> ('a * 'b) t -> 'b option
430
- val mem_assoc : 'a -> ('a * 'b) t -> bool
431
- val mem_assq : 'a -> ('a * 'b) t -> bool
432
- val remove_assoc : 'a -> ('a * 'b) t -> ('a * 'b) t
433
- val remove_assq : 'a -> ('a * 'b) t -> ('a * 'b) t
434
- val split : ('a * 'b) t -> 'a t * 'b t
435
- val combine : 'a t -> 'b t -> ('a * 'b) t
436
- val sort : ('a -> 'a -> int) -> 'a t -> 'a t
437
- val stable_sort : ('a -> 'a -> int) -> 'a t -> 'a t
438
- val fast_sort : ('a -> 'a -> int) -> 'a t -> 'a t
439
- val sort_uniq : ('a -> 'a -> int) -> 'a t -> 'a t
440
- val merge : ('a -> 'a -> int) -> 'a t -> 'a t -> 'a t
441
- val to_seq : 'a t -> 'a Seq.t
442
- val of_seq : 'a Seq.t -> 'a t
328
+ external id : 'a -> 'a = "%identity"
329
+ val const : 'a -> 'b -> 'a
330
+ val flip : ('a -> 'b -> 'c) -> 'b -> 'a -> 'c
331
+ val negate : ('a -> bool) -> 'a -> bool
332
+ val protect : finally:(unit -> unit) -> (unit -> 'a) -> 'a
333
+ exception Finally_raised of exn
443
334
end
444
335
```
445
336
446
- There is online documentation for each library.
337
+ There is online documentation for each library, for instance [ ` Fun ` ] ( /api/Fun.html )
447
338
448
339
### Module Inclusion
449
340
450
341
Let's say we feel that a function is missing from the standard ` List ` module,
451
- but we really want it as if it were part of it. In an ` extensions .ml` file, we
342
+ but we really want it as if it were part of it. In an ` extlib .ml` file, we
452
343
can achieve this effect by using the ` include ` directive:
453
344
454
345
``` ocaml
455
- # module List = struct
346
+ module List = struct
456
347
include List
457
- let rec optmap f = function
458
- | [] -> []
459
- | hd :: tl ->
460
- match f hd with
461
- | None -> optmap f tl
462
- | Some x -> x :: optmap f tl
463
- end;;
464
- module List :
465
- sig
466
- type 'a t = 'a list = [] | (::) of 'a * 'a list
467
- val length : 'a t -> int
468
- val compare_lengths : 'a t -> 'b t -> int
469
- val compare_length_with : 'a t -> int -> int
470
- val cons : 'a -> 'a t -> 'a t
471
- val hd : 'a t -> 'a
472
- val tl : 'a t -> 'a t
473
- val nth : 'a t -> int -> 'a
474
- val nth_opt : 'a t -> int -> 'a option
475
- val rev : 'a t -> 'a t
476
- val init : int -> (int -> 'a) -> 'a t
477
- val append : 'a t -> 'a t -> 'a t
478
- val rev_append : 'a t -> 'a t -> 'a t
479
- val concat : 'a t t -> 'a t
480
- val flatten : 'a t t -> 'a t
481
- val equal : ('a -> 'a -> bool) -> 'a t -> 'a t -> bool
482
- val compare : ('a -> 'a -> int) -> 'a t -> 'a t -> int
483
- val iter : ('a -> unit) -> 'a t -> unit
484
- val iteri : (int -> 'a -> unit) -> 'a t -> unit
485
- val map : ('a -> 'b) -> 'a t -> 'b t
486
- val mapi : (int -> 'a -> 'b) -> 'a t -> 'b t
487
- val rev_map : ('a -> 'b) -> 'a t -> 'b t
488
- val filter_map : ('a -> 'b option) -> 'a t -> 'b t
489
- val concat_map : ('a -> 'b t) -> 'a t -> 'b t
490
- val fold_left_map : ('a -> 'b -> 'a * 'c) -> 'a -> 'b t -> 'a * 'c t
491
- val fold_left : ('a -> 'b -> 'a) -> 'a -> 'b t -> 'a
492
- val fold_right : ('a -> 'b -> 'b) -> 'a t -> 'b -> 'b
493
- val iter2 : ('a -> 'b -> unit) -> 'a t -> 'b t -> unit
494
- val map2 : ('a -> 'b -> 'c) -> 'a t -> 'b t -> 'c t
495
- val rev_map2 : ('a -> 'b -> 'c) -> 'a t -> 'b t -> 'c t
496
- val fold_left2 : ('a -> 'b -> 'c -> 'a) -> 'a -> 'b t -> 'c t -> 'a
497
- val fold_right2 : ('a -> 'b -> 'c -> 'c) -> 'a t -> 'b t -> 'c -> 'c
498
- val for_all : ('a -> bool) -> 'a t -> bool
499
- val exists : ('a -> bool) -> 'a t -> bool
500
- val for_all2 : ('a -> 'b -> bool) -> 'a t -> 'b t -> bool
501
- val exists2 : ('a -> 'b -> bool) -> 'a t -> 'b t -> bool
502
- val mem : 'a -> 'a t -> bool
503
- val memq : 'a -> 'a t -> bool
504
- val find : ('a -> bool) -> 'a t -> 'a
505
- val find_opt : ('a -> bool) -> 'a t -> 'a option
506
- val find_map : ('a -> 'b option) -> 'a t -> 'b option
507
- val filter : ('a -> bool) -> 'a t -> 'a t
508
- val find_all : ('a -> bool) -> 'a t -> 'a t
509
- val filteri : (int -> 'a -> bool) -> 'a t -> 'a t
510
- val partition : ('a -> bool) -> 'a t -> 'a t * 'a t
511
- val partition_map : ('a -> ('b, 'c) Either.t) -> 'a t -> 'b t * 'c t
512
- val assoc : 'a -> ('a * 'b) t -> 'b
513
- val assoc_opt : 'a -> ('a * 'b) t -> 'b option
514
- val assq : 'a -> ('a * 'b) t -> 'b
515
- val assq_opt : 'a -> ('a * 'b) t -> 'b option
516
- val mem_assoc : 'a -> ('a * 'b) t -> bool
517
- val mem_assq : 'a -> ('a * 'b) t -> bool
518
- val remove_assoc : 'a -> ('a * 'b) t -> ('a * 'b) t
519
- val remove_assq : 'a -> ('a * 'b) t -> ('a * 'b) t
520
- val split : ('a * 'b) t -> 'a t * 'b t
521
- val combine : 'a t -> 'b t -> ('a * 'b) t
522
- val sort : ('a -> 'a -> int) -> 'a t -> 'a t
523
- val stable_sort : ('a -> 'a -> int) -> 'a t -> 'a t
524
- val fast_sort : ('a -> 'a -> int) -> 'a t -> 'a t
525
- val sort_uniq : ('a -> 'a -> int) -> 'a t -> 'a t
526
- val merge : ('a -> 'a -> int) -> 'a t -> 'a t -> 'a t
527
- val to_seq : 'a t -> 'a Seq.t
528
- val of_seq : 'a Seq.t -> 'a t
529
- val optmap : ('a -> 'b option) -> 'a t -> 'b t
530
- end
348
+ let uncons = function
349
+ | [] -> None
350
+ | hd :: tl -> Some (hd, tl)
351
+ end
531
352
```
532
353
533
- It creates a module ` Extensions.List ` that has everything the standard ` List `
534
- module has, plus a new ` optmap ` function. From another file, all we have to do
535
- to override the default ` List ` module is ` open Extensions ` at the beginning of
536
- the ` .ml ` file:
537
-
538
- <!-- $MDX skip -->
539
- ``` ocaml
540
- open Extensions
541
-
542
- ...
543
-
544
- List.optmap ...
545
- ```
354
+ It creates a module ` Extlib.List ` that has everything the standard ` List `
355
+ module has, plus a new ` uncons ` function. From another ` .ml ` file, all we have to do
356
+ to override the default ` List ` module is add ` open Extlib ` at the beginning.
0 commit comments