You signed in with another tab or window. Reload to refresh your session.You signed out in another tab or window. Reload to refresh your session.You switched accounts on another tab or window. Reload to refresh your session.Dismiss alert
First we need to initialise MDX with some libraries and helpful values.
11
+
First, we need to initialise MDX with some libraries and helpful values:
12
12
13
13
{[
14
14
(* Prelude *)
@@ -24,7 +24,8 @@ let get_ok = function | Ok x -> x | Error (`Msg m) -> failwith m
24
24
25
25
{1 Desired Output}
26
26
27
-
[odoc] produces output files (html or others) in a structured directory tree, so before running [odoc], the structure of the output must be decided. For these docs, we want the following structure:
27
+
[odoc] produces output files (HTML or others) in a structured directory tree, so before running [odoc],
28
+
the structure of the output must be decided. For these docs, we want the following structure:
28
29
{ul {- [odoc/index.html] : main page
29
30
}{- [odoc/\{odoc_for_authors.html,...\}] : other documentation pages
30
31
}{- [odoc/odoc_model/index.html] : [odoc] model library subpage
@@ -37,9 +38,14 @@ let get_ok = function | Ok x -> x | Error (`Msg m) -> failwith m
37
38
}{- [odoc/deps/...] : other dependencies
38
39
}}
39
40
40
-
The [odoc] model for achieving this is that we have {e pages} ([.mld] files) that have {e children} which are either {e further pages} ([.mld] files) or {e modules} (from [.cmti] files). This {{!page-parent_child_spec} parent/child relationship} is specified on the command line. Parent pages must be {e compiled} by [odoc] before their children. Then compiling a page [mypage.mld] will produce the file [page-mypage.odoc].
41
+
The [odoc] model for achieving this is that we have {e pages} ([.mld] files) that have {e children}
42
+
which are either {e further pages} ([.mld] files) or {e modules} (from [.cmti] files).
43
+
This {{!page-parent_child_spec} parent/child relationship} is specified on the command line.
44
+
Parent pages must be {e compiled} by [odoc] before their children. Then compiling a page [mypage.mld]
45
+
will produce the file [page-mypage.odoc].
41
46
42
-
In the example below, there will be a file [odoc.mld] that corresponds with the top-level directory [odoc/]. It will be compiled as follows:
47
+
In the example below, there will be a file [odoc.mld] that corresponds with the top-level directory [odoc/].
When compiling any [.mld] file, the parent and all children must be specified. Parents can only be pages from other [.mld] files, and children may be pages (from [.mld] files) or modules (from [.cmti]/[.cmt] or [.cmi] files).
66
+
When compiling any [.mld] file, the parent and all children must be specified. Parents can only
67
+
be pages from other [.mld] files, but children may be pages (from [.mld] files) or modules
68
+
(from [.cmti]/[.cmt] or [.cmi] files).
61
69
62
-
The parent page must exist before the child page is created, and it must have had the child specified when it was initially compiled.
70
+
The parent page must exist before the child page is created, and it must have had the child specified
71
+
when it was initially compiled.
63
72
64
73
{1 Document Generation Phases}
65
74
66
75
Using [odoc] is a three-phase process:
67
76
{ol {- Compilation: [odoc compile]
68
77
69
-
This takes the output from the compiler in the form of [.cmti], [.cmt], or [.cmi] files (in order of preference), translates it into [odoc]'s internal format, and performs some initial expansion and resolution operations. For a given input [/path/to/file.cmti] it will output the file [/path/to/file.odoc] unless the [-o] option is used to override the output file. If there were [.cmi] dependencies required for OCaml to compile these files, then there will be equivalent [.odoc] dependencies needed for the [odoc compile] step. [odoc] will search for these dependencies in the paths specified with the [-I] directive on compilation. [odoc] provides a command to help with this: [odoc compile-deps]:
78
+
This takes the output from the compiler in the form of [.cmti], [.cmt], or [.cmi] files (in order of preference),
79
+
translates it into [odoc]'s internal format, and performs some initial expansion and resolution operations.
80
+
For a given input [/path/to/file.cmti], it will output the file [/path/to/file.odoc], unless the [-o] option
81
+
is used to override the output file. If there were [.cmi] dependencies required for OCaml to compile these files,
82
+
then there will be equivalent [.odoc] dependencies needed for the [odoc compile] step. [odoc] will search for
83
+
these dependencies in the paths specified with the [-I] directive on compilation. [odoc] provides a command to
84
+
help with this: [odoc compile-deps]:
70
85
71
86
As an example we can run [odoc compile-deps] on the file [../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Compile.cmti]:
so we can see we will need to run [odoc compile] against several [Stdlib] modules before we can compile [odoc_xref2__Compile.cmti]
97
+
It's necessary to run [odoc compile] against several [Stdlib] modules before we can compile [odoc_xref2__Compile.cmti]
83
98
}
84
99
{- Linking: [odoc link]
85
100
86
101
87
-
This takes the [odoc] files produced during the compilation step and performs the final steps of expansion and resolution. It is during this phase that all the references in the documentation comments are resolved. In order for these to be resolved, everything that is referenced must have been compiled already, and their [odoc] files must be on the
88
-
include path as specified by the [-I] arguments to [odoc link]. In this example, we achieve that by compiling all modules and [.mld] files before linking anything. The output of the
102
+
This takes the [odoc] files produced during the compilation step and performs the final steps of
103
+
expansion and resolution. It's during this phase that all the references in the documentation comments are
104
+
resolved. In order for these to be resolved, everything that's referenced must have been compiled already,
105
+
and their [odoc] files must be on the include path as specified by the [-I] arguments to [odoc link].
106
+
In this example, we achieve that by compiling all modules and [.mld] files before linking anything. The output of the
89
107
link step is an [odocl] file, which is in the same path as the original [odoc] file by default.
90
108
91
109
Please note: it's only necessary to link the non-hidden modules (i.e., without a double underscore).
92
110
}
93
111
{- Generation: [odoc html-generate]
94
112
95
113
96
-
Once the compile and link phases are complete, the resulting [odocl] files may be rendered in a variety of formats. In this example we output HTML.
114
+
Once the compile and link phases are complete, the resulting [odocl] files may be rendered in a variety
115
+
of formats. In this example, we output HTML:
97
116
}}
98
117
99
118
{1 [odoc] Documentation}
100
119
101
-
In this section [odoc] is used to generate the documentation of [odoc] and some of its dependent packages. We can make a few simplifying assumptions here:
102
-
{ol {- Since we're working with one leaf package, we can assume that there can be no module name clashes in the dependencies. As such, we can afford to put all of our [.odoc] files into one directory and then hard-code the include path to be this directory. When using [odoc] in a context where there may be module name clashes, it requires more careful partitioning of output directories.
120
+
In this section, [odoc] is used to generate the documentation of [odoc] and some of its dependent packages.
121
+
We can make a few simplifying assumptions here:
122
+
{ol {- Since we're working with one leaf package, we can assume that there can be no module name
123
+
clashes in the dependencies. As such, we can afford to put all of our [.odoc] files into one directory
124
+
and then hard-code the include path to be this directory. When using [odoc] in a context where there may
125
+
be module name clashes, it requires more careful partitioning of output directories.
103
126
}{- We'll do all of the compiling before any linking.
104
127
}}
105
128
@@ -180,9 +203,10 @@ let support_files () =
180
203
]}
181
204
182
205
We'll now make some library lists. We have not only external dependency libraries, but
183
-
[odoc] itself is also separated into libraries too. These two sets of libraries will be
206
+
[odoc] itself is also separated into libraries. These two sets of libraries will be
184
207
documented in different sections, so we'll keep them in separate lists.
185
-
Additionally we'll also construct a list containing the extra documentation pages. Finally let's create a list mapping the section to its parent, which matches
208
+
Additionally we'll construct a list containing the extra documentation pages. Finally,
209
+
let's create a list mapping the section to its parent, which matches
[odoc] operates on the compiler outputs. We need to find them for both the files compiled by Dune within this project and those in libraries we compile against.
280
+
[odoc] operates on the compiler outputs. We need to find them for both the files
281
+
compiled by Dune within this project and those in libraries we compile against.
257
282
The following uses [ocamlfind] to locate the library paths for our dependencies:
258
283
259
284
{[
@@ -273,7 +298,7 @@ let lib_paths =
273
298
]}
274
299
275
300
We need a function to find [odoc] inputs given a search path. [odoc]
276
-
operates on [.cmti], [.cmt] or [.cmi] files, in order of preference, and the following
301
+
operates on [.cmti], [.cmt], or [.cmi] files, in order of preference, and the following
277
302
function finds all matching files given a search path. Then it returns an [Fpath.Set.t]
278
303
that contains the [Fpath.t] values representing the absolute file path, without its extension.
279
304
@@ -304,7 +329,7 @@ let best_file base =
304
329
|> List.find (fun f -> Bos.OS.File.exists f |> get_ok)
305
330
]}
306
331
307
-
Many of the units will be 'hidden' -- that is, their name will be mangled by Dune
332
+
Many of the units will be 'hidden', meaning that Dune will mangle their name
308
333
in order to namespace them. This is achieved by prefixing the namespace module and
309
334
a double underscore, so we can tell by the existence of a double underscore that
310
335
a module is intended to be hidden. The following predicate tests for that condition:
@@ -313,7 +338,8 @@ a module is intended to be hidden. The following predicate tests for that condit
313
338
let is_hidden path = Astring.String.is_infix ~affix:"__" (Fpath.to_string path)
314
339
]}
315
340
316
-
To build the documentation, we start with these files. With the following function, we'll call [odoc compile-deps] on the file to
341
+
To build the documentation, we start with these files. With the following function, we'll
342
+
call [odoc compile-deps] on the file to
317
343
find all other compilation units upon which it depends:
318
344
319
345
{[
@@ -362,7 +388,9 @@ let all_units =
362
388
odoc_units @ lib_units |> List.flatten
363
389
]}
364
390
365
-
Now we'll compile all of the parent [.mld] files. To ensure that the parents are compiled before the children, we start with [odoc.mld], then [deps.mld], and so on. The result of this file is a list of the resulting [odoc] files.
391
+
Now we'll compile all of the parent [.mld] files. To ensure that the parents are
392
+
compiled before the children, we start with [odoc.mld], then [deps.mld], and so on. The result
393
+
of this file is a list of the resulting [odoc] files.
Now we get to the compilation phase. For each unit, we query its dependencies, then recursively call to compile these dependencies. Once this is done we compile the unit itself. If the unit has already been compiled we don't do anything. Note that we aren't checking the hashes of the dependencies which a build system should do to ensure that the module being compiled is the correct one. Again we benefit from the fact that we're creating the docs for one leaf package and that there must be no module name clashes in its dependencies. The result of this function is a list of the resulting [odoc] files.
431
+
Now we get to the compilation phase. For each unit, we query its dependencies,
432
+
then recursively call to compile these dependencies. Once this is done, we compile the unit itself.
433
+
If the unit has already been compiled, we don't do anything. Note that we aren't checking the
434
+
hashes of the dependencies which a build system should do to ensure that the module being compiled
435
+
is the correct one. Again, we benefit from the fact that we're creating the docs for one
436
+
leaf package and that there must be no module name clashes in its dependencies. The result
437
+
of this function is a list of the resulting [odoc] files.
404
438
405
439
{[
406
440
let compile_all () =
@@ -435,7 +469,9 @@ let compile_all () =
435
469
@ mld_odocs
436
470
]}
437
471
438
-
Linking is now straightforward. We only need to link non-hidden [odoc] files, as any hidden are almost certainly aliased inside the non-hidden ones (a result of namespacing usually, and these aliases will be expanded).
472
+
Linking is now straightforward. We only need to link non-hidden [odoc] files, as
473
+
any hidden ones are almost certainly aliased inside the non-hidden ones
474
+
(a result of namespacing, usually, and these aliases will be expanded).
439
475
440
476
{[
441
477
let link_all odoc_files =
@@ -455,7 +491,7 @@ let generate_all odocl_files =
455
491
support_files ()
456
492
]}
457
493
458
-
The following code actually executes all of the above, and we're done!
494
+
The following code executes all of the above, and we're done!
0 commit comments