Skip to content

Commit c4d49c8

Browse files
committed
Add cross-reference detected by ocamldoc
1 parent 9369c35 commit c4d49c8

21 files changed

+94
-94
lines changed

otherlibs/unix/unix.mli

+4-4
Original file line numberDiff line numberDiff line change
@@ -15,8 +15,8 @@
1515

1616
(** Interface to the Unix system.
1717
18-
Note: all the functions of this module (except [error_message] and
19-
[handle_unix_error]) are liable to raise the [Unix_error]
18+
Note: all the functions of this module (except {!error_message} and
19+
{!handle_unix_error}) are liable to raise the {!Unix_error}
2020
exception whenever the underlying system call signals an error. *)
2121

2222

@@ -112,7 +112,7 @@ val error_message : error -> string
112112

113113
val handle_unix_error : ('a -> 'b) -> 'a -> 'b
114114
(** [handle_unix_error f x] applies [f] to [x] and returns the result.
115-
If the exception [Unix_error] is raised, it prints a message
115+
If the exception {!Unix_error} is raised, it prints a message
116116
describing the error and exits with code 2. *)
117117

118118

@@ -789,7 +789,7 @@ val lockf : file_descr -> lock_command -> int -> unit
789789

790790
val kill : int -> int -> unit
791791
(** [kill pid sig] sends signal number [sig] to the process
792-
with id [pid]. On Windows, only the [Sys.sigkill] signal
792+
with id [pid]. On Windows, only the {!Sys.sigkill} signal
793793
is emulated. *)
794794

795795
type sigprocmask_command =

parsing/ast_mapper.mli

+4-4
Original file line numberDiff line numberDiff line change
@@ -113,9 +113,9 @@ val tool_name: unit -> string
113113
calling it ["ocamlc"], ["ocamlopt"], ["ocamldoc"], ["ocamldep"],
114114
["ocaml"], ... Some global variables that reflect command-line
115115
options are automatically synchronized between the calling tool
116-
and the ppx preprocessor: [Clflags.include_dirs],
117-
[Config.load_path], [Clflags.open_modules], [Clflags.for_package],
118-
[Clflags.debug]. *)
116+
and the ppx preprocessor: {!Clflags.include_dirs},
117+
{!Config.load_path}, {!Clflags.open_modules}, {!Clflags.for_package},
118+
{!Clflags.debug}. *)
119119

120120

121121
val apply: source:string -> target:string -> mapper -> unit
@@ -127,7 +127,7 @@ val apply: source:string -> target:string -> mapper -> unit
127127
val run_main: (string list -> mapper) -> unit
128128
(** Entry point to call to implement a standalone -ppx rewriter from a
129129
mapper, parametrized by the command line arguments. The current
130-
unit name can be obtained from [Location.input_name]. This
130+
unit name can be obtained from {!Location.input_name}. This
131131
function implements proper error reporting for uncaught
132132
exceptions. *)
133133

stdlib/arg.mli

+5-5
Original file line numberDiff line numberDiff line change
@@ -116,12 +116,12 @@ val parse_argv : ?current: int ref -> string array ->
116116
(key * spec * doc) list -> anon_fun -> usage_msg -> unit
117117
(** [Arg.parse_argv ~current args speclist anon_fun usage_msg] parses
118118
the array [args] as if it were the command line. It uses and updates
119-
the value of [~current] (if given), or [Arg.current]. You must set
119+
the value of [~current] (if given), or {!Arg.current}. You must set
120120
it before calling [parse_argv]. The initial value of [current]
121121
is the index of the program name (argument 0) in the array.
122-
If an error occurs, [Arg.parse_argv] raises [Arg.Bad] with
122+
If an error occurs, [Arg.parse_argv] raises {!Arg.Bad} with
123123
the error message as argument. If option [-help] or [--help] is
124-
given, [Arg.parse_argv] raises [Arg.Help] with the help message
124+
given, [Arg.parse_argv] raises {!Arg.Help} with the help message
125125
as argument.
126126
*)
127127

@@ -151,13 +151,13 @@ exception Help of string
151151
exception Bad of string
152152
(** Functions in [spec] or [anon_fun] can raise [Arg.Bad] with an error
153153
message to reject invalid arguments.
154-
[Arg.Bad] is also raised by [Arg.parse_argv] in case of an error. *)
154+
[Arg.Bad] is also raised by {!Arg.parse_argv} in case of an error. *)
155155

156156
val usage : (key * spec * doc) list -> usage_msg -> unit
157157
(** [Arg.usage speclist usage_msg] prints to standard error
158158
an error message that includes the list of valid options. This is
159159
the same message that {!Arg.parse} prints in case of error.
160-
[speclist] and [usage_msg] are the same as for [Arg.parse]. *)
160+
[speclist] and [usage_msg] are the same as for {!Arg.parse}. *)
161161

162162
val usage_string : (key * spec * doc) list -> usage_msg -> string
163163
(** Returns the message that would have been printed by {!Arg.usage},

stdlib/array.mli

+2-2
Original file line numberDiff line numberDiff line change
@@ -80,7 +80,7 @@ val make_matrix : int -> int -> 'a -> 'a array array
8080
with the notation [m.(x).(y)].
8181
8282
Raise [Invalid_argument] if [dimx] or [dimy] is negative or
83-
greater than [Sys.max_array_length].
83+
greater than {!Sys.max_array_length}.
8484
If the value of [e] is a floating-point number, then the maximum
8585
size is only [Sys.max_array_length / 2]. *)
8686

@@ -93,7 +93,7 @@ val append : 'a array -> 'a array -> 'a array
9393
concatenation of the arrays [v1] and [v2]. *)
9494

9595
val concat : 'a array list -> 'a array
96-
(** Same as [Array.append], but concatenates a list of arrays. *)
96+
(** Same as {!Array.append}, but concatenates a list of arrays. *)
9797

9898
val sub : 'a array -> int -> int -> 'a array
9999
(** [Array.sub a start len] returns a fresh array of length [len],

stdlib/arrayLabels.mli

+2-2
Original file line numberDiff line numberDiff line change
@@ -71,7 +71,7 @@ val make_matrix : dimx:int -> dimy:int -> 'a -> 'a array array
7171
with the notation [m.(x).(y)].
7272
7373
Raise [Invalid_argument] if [dimx] or [dimy] is negative or
74-
greater than [Sys.max_array_length].
74+
greater than {!Sys.max_array_length}.
7575
If the value of [e] is a floating-point number, then the maximum
7676
size is only [Sys.max_array_length / 2]. *)
7777

@@ -85,7 +85,7 @@ val append : 'a array -> 'a array -> 'a array
8585
concatenation of the arrays [v1] and [v2]. *)
8686

8787
val concat : 'a array list -> 'a array
88-
(** Same as [Array.append], but concatenates a list of arrays. *)
88+
(** Same as {!Array.append}, but concatenates a list of arrays. *)
8989

9090
val sub : 'a array -> pos:int -> len:int -> 'a array
9191
(** [Array.sub a start len] returns a fresh array of length [len],

stdlib/bytes.mli

+1-1
Original file line numberDiff line numberDiff line change
@@ -399,7 +399,7 @@ let bytes_length (s : bytes) =
399399
400400
The caller may not mutate [s] while the string is borrowed (it has
401401
temporarily given up ownership). This affects concurrent programs,
402-
but also higher-order functions: if [String.length] returned
402+
but also higher-order functions: if {!String.length} returned
403403
a closure to be called later, [s] should not be mutated until this
404404
closure is fully applied and returns ownership.
405405
*)

stdlib/ephemeron.mli

+4-4
Original file line numberDiff line numberDiff line change
@@ -138,8 +138,8 @@ module K1 : sig
138138

139139
val blit_key : ('k,_) t -> ('k,_) t -> unit
140140
(** [Ephemeron.K1.blit_key eph1 eph2] sets the key of [eph2] with
141-
the key of [eph1]. Contrary to using [Ephemeron.K1.get_key]
142-
followed by [Ephemeron.K1.set_key] or [Ephemeon.K1.unset_key]
141+
the key of [eph1]. Contrary to using {!Ephemeron.K1.get_key}
142+
followed by {!Ephemeron.K1.set_key} or {!Ephemeron.K1.unset_key}
143143
this function does not prevent the incremental GC from erasing
144144
the value in its current cycle. *)
145145

@@ -172,8 +172,8 @@ module K1 : sig
172172

173173
val blit_data : (_,'d) t -> (_,'d) t -> unit
174174
(** [Ephemeron.K1.blit_data eph1 eph2] sets the data of [eph2] with
175-
the data of [eph1]. Contrary to using [Ephemeron.K1.get_data]
176-
followed by [Ephemeron.K1.set_data] or [Ephemeon.K1.unset_data]
175+
the data of [eph1]. Contrary to using {!Ephemeron.K1.get_data}
176+
followed by {!Ephemeron.K1.set_data} or {!Ephemeron.K1.unset_data}
177177
this function does not prevent the incremental GC from erasing
178178
the value in its current cycle. *)
179179

stdlib/format.mli

+3-3
Original file line numberDiff line numberDiff line change
@@ -457,7 +457,7 @@ type formatter
457457
margin, maximum indentation limit, maximum number of boxes
458458
simultaneously opened, ellipsis, and so on, are specific to
459459
each pretty-printer and may be fixed independently.
460-
Given a [Pervasives.out_channel] output channel [oc], a new formatter
460+
Given a {!Pervasives.out_channel} output channel [oc], a new formatter
461461
writing to that channel is simply obtained by calling
462462
[formatter_of_out_channel oc].
463463
Alternatively, the [make_formatter] function allocates a new
@@ -500,7 +500,7 @@ val make_formatter :
500500
(string -> int -> int -> unit) -> (unit -> unit) -> formatter
501501
(** [make_formatter out flush] returns a new formatter that writes according
502502
to the output function [out], and the flushing function [flush]. For
503-
instance, a formatter to the [Pervasives.out_channel] [oc] is returned by
503+
instance, a formatter to the {!Pervasives.out_channel} [oc] is returned by
504504
[make_formatter (Pervasives.output oc) (fun () -> Pervasives.flush oc)]. *)
505505

506506
(** {6 Basic functions to use with formatters} *)
@@ -604,7 +604,7 @@ val fprintf : formatter -> ('a, formatter, unit) format -> 'a
604604
605605
The format [fmt] is a character string which contains three types of
606606
objects: plain characters and conversion specifications as specified in
607-
the [Printf] module, and pretty-printing indications specific to the
607+
the {!Printf} module, and pretty-printing indications specific to the
608608
[Format] module.
609609
610610
The pretty-printing indication characters are introduced by

stdlib/genlex.mli

+2-2
Original file line numberDiff line numberDiff line change
@@ -67,7 +67,7 @@ val make_lexer : string list -> char Stream.t -> token Stream.t
6767
belongs to this list, and as [Ident s] otherwise.
6868
A special character [s] is returned as [Kwd s] if [s]
6969
belongs to this list, and cause a lexical error (exception
70-
[Stream.Error] with the offending lexeme as its parameter) otherwise.
70+
{!Stream.Error} with the offending lexeme as its parameter) otherwise.
7171
Blanks and newlines are skipped. Comments delimited by [(*] and [*)]
72-
are skipped as well, and can be nested. A [Stream.Failure] exception
72+
are skipped as well, and can be nested. A {!Stream.Failure} exception
7373
is raised if end of stream is unexpectedly reached.*)

stdlib/lazy.mli

+3-3
Original file line numberDiff line numberDiff line change
@@ -48,18 +48,18 @@ external force : 'a t -> 'a = "%lazy_force"
4848
If [x] has already been forced, [Lazy.force x] returns the
4949
same value again without recomputing it. If it raised an exception,
5050
the same exception is raised again.
51-
Raise [Undefined] if the forcing of [x] tries to force [x] itself
51+
Raise {!Undefined} if the forcing of [x] tries to force [x] itself
5252
recursively.
5353
*)
5454

5555
val force_val : 'a t -> 'a
5656
(** [force_val x] forces the suspension [x] and returns its
5757
result. If [x] has already been forced, [force_val x]
5858
returns the same value again without recomputing it.
59-
Raise [Undefined] if the forcing of [x] tries to force [x] itself
59+
Raise {!Undefined} if the forcing of [x] tries to force [x] itself
6060
recursively.
6161
If the computation of [x] raises an exception, it is unspecified
62-
whether [force_val x] raises the same exception or [Undefined].
62+
whether [force_val x] raises the same exception or {!Undefined}.
6363
*)
6464

6565
val from_fun : (unit -> 'a) -> 'a t

stdlib/obj.mli

+1-1
Original file line numberDiff line numberDiff line change
@@ -50,7 +50,7 @@ external field : t -> int -> t = "%obj_field"
5050
5151
For experts only:
5252
[set_field] et al can be made safe by first wrapping the block in
53-
[Sys.opaque_identity], so any information about its contents will not
53+
{!Sys.opaque_identity}, so any information about its contents will not
5454
be propagated.
5555
*)
5656
external set_field : t -> int -> t -> unit = "%obj_set_field"

stdlib/pervasives.mli

+5-5
Original file line numberDiff line numberDiff line change
@@ -1078,12 +1078,12 @@ type ('a,'b) result = Ok of 'a | Error of 'b
10781078
10791079
- ['b] is the type of input source for formatted input functions and the
10801080
type of output target for formatted output functions.
1081-
For [printf]-style functions from module [Printf], ['b] is typically
1081+
For [printf]-style functions from module {!Printf}, ['b] is typically
10821082
[out_channel];
1083-
for [printf]-style functions from module [Format], ['b] is typically
1084-
[Format.formatter];
1085-
for [scanf]-style functions from module [Scanf], ['b] is typically
1086-
[Scanf.Scanning.in_channel].
1083+
for [printf]-style functions from module {!Format}, ['b] is typically
1084+
{!Format.formatter};
1085+
for [scanf]-style functions from module {!Scanf}, ['b] is typically
1086+
{!Scanf.Scanning.in_channel}.
10871087
10881088
Type argument ['b] is also the type of the first argument given to
10891089
user's defined printing functions for [%a] and [%t] conversions,

stdlib/queue.mli

+2-2
Original file line numberDiff line numberDiff line change
@@ -41,14 +41,14 @@ val push : 'a -> 'a t -> unit
4141

4242
val take : 'a t -> 'a
4343
(** [take q] removes and returns the first element in queue [q],
44-
or raises [Empty] if the queue is empty. *)
44+
or raises {!Empty} if the queue is empty. *)
4545

4646
val pop : 'a t -> 'a
4747
(** [pop] is a synonym for [take]. *)
4848

4949
val peek : 'a t -> 'a
5050
(** [peek q] returns the first element in queue [q], without removing
51-
it from the queue, or raises [Empty] if the queue is empty. *)
51+
it from the queue, or raises {!Empty} if the queue is empty. *)
5252

5353
val top : 'a t -> 'a
5454
(** [top] is a synonym for [peek]. *)

stdlib/random.mli

+1-1
Original file line numberDiff line numberDiff line change
@@ -66,7 +66,7 @@ val bool : unit -> bool
6666

6767
(** {6 Advanced functions} *)
6868

69-
(** The functions from module [State] manipulate the current state
69+
(** The functions from module {!State} manipulate the current state
7070
of the random generator explicitly.
7171
This allows using one or several deterministic PRNGs,
7272
even in a multi-threaded program, without interference from

0 commit comments

Comments
 (0)