Skip to content

Commit 14cc984

Browse files
rjboukit-ty-kate
authored andcommitted
doc: add '@raise' tags
1 parent f16a964 commit 14cc984

15 files changed

+80
-63
lines changed

master_changes.md

+1
Original file line numberDiff line numberDiff line change
@@ -121,6 +121,7 @@ users)
121121
* Remove redundant `+` in version BNF definition (it is already present in `identchar`) [#6252 @rjbou]
122122
* mli documentation: fix code blocks [#6150 @rjbou]
123123
* mli documentation: fix code blocks, references [#6150 @rjbou]
124+
* mli documentation: fix code blocks, references, add `@raise` tags [#6150 @rjbou]
124125
* Unhide `OpamProcess` functions [#6150 @rjbou]
125126

126127
## Security fixes

src/client/opamConfigCommand.mli

+8-7
Original file line numberDiff line numberDiff line change
@@ -82,14 +82,15 @@ val whole_of_update_op: update_op -> whole_op
8282
defined fields in {!OpamFile.Config.t}. On revert, field is reverted to its
8383
initial value as defined in {!OpamInitDefaults.init_config}, to default
8484
value otherwise ({!OpamFile.Config.empty}).
85-
May raise [OpamStd.Sys.Exit]. *)
85+
@raise OpamStd.Sys.Exit ([`Bad_argument], [2]) if the field is not found or not
86+
modifiable, or the value have a parse error. *)
8687
val set_opt_global: rw global_state -> string -> update_op -> rw global_state
8788

8889
(** As {!set_opt_global}, {!set_opt_switch} updates switch config file in
8990
<opamroot>/<switch>/.opam-switch/switch-config. If switch state is given,
9091
uses its config and returns it with then new config. Otherwise, loads the
9192
raw switch state and returns [None].
92-
Raises [OpamStd.Sys.Exit 50] ([`Configuration_error]) if no switch is set *)
93+
@raise OpamStd.Sys.Exit ([`Configuration_error], [50]) if no switch is set *)
9394
val set_opt_switch:
9495
'a global_state -> ?st:rw switch_state -> string -> update_op
9596
-> rw switch_state option
@@ -99,11 +100,11 @@ val set_opt_switch:
99100
the new variables to current set. If switch state is given, uses its
100101
config and returns it with then new config. Otherwise, loads the raw switch
101102
state and returns [None].
102-
Raises [OpamStd.Sys.Exit 2] ([`Bad_argument]) if field is not modifiable *)
103+
@raise OpamStd.Sys.Exit ([`Bad_argument], [2]) if field is not modifiable *)
103104
val set_var_global:
104105
rw global_state -> string -> whole_op -> rw global_state
105106

106-
(** Raises [OpamStd.Sys.Exit 50] ([`Configuration_error]) if no switch is set *)
107+
(** @raise OpamStd.Sys.Exit ([`Configuration_error], [50]) if no switch is set *)
107108
val set_var_switch:
108109
'a global_state -> ?st:rw switch_state -> string -> whole_op
109110
-> rw switch_state option
@@ -118,7 +119,7 @@ val options_list:
118119
?st:unlocked switch_state -> 'a global_state -> unit
119120
val options_list_global: 'a global_state -> unit
120121

121-
(** Raises [OpamStd.Sys.Exit 50] ([`Configuration_error]) if no switch is set *)
122+
(** @raise OpamStd.Sys.Exit ([`Configuration_error], [50]) if no switch is set *)
122123
val options_list_switch:
123124
?st:unlocked switch_state -> 'a global_state -> unit
124125

@@ -129,7 +130,7 @@ val vars_list:
129130
?st:'a switch_state -> 'b global_state -> unit
130131
val vars_list_global: 'a global_state -> unit
131132

132-
(** Raises [OpamStd.Sys.Exit 50] ([`Configuration_error]) if no switch is set *)
133+
(** @raise OpamStd.Sys.Exit ([`Configuration_error], [50]) if no switch is set *)
133134
val vars_list_switch:
134135
?st:'a switch_state -> 'b global_state -> unit
135136

@@ -142,7 +143,7 @@ val vars_list_switch:
142143

143144
val option_show_global: 'a global_state -> string -> unit
144145

145-
(** Raises [OpamStd.Sys.Exit 50] ([`Configuration_error]) if no switch is set *)
146+
(** @raise OpamStd.Sys.Exit ([`Configuration_error], [50]) if no switch is set *)
146147
val option_show_switch:
147148
'a global_state -> ?st:unlocked switch_state -> string -> unit
148149

src/client/opamPinCommand.mli

+2-1
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,8 @@ exception Nothing_to_do
3131
3232
If [force], don't abort even if the source can't be fetched from [target]
3333
34-
May raise [Aborted] or [Nothing_to_do]. *)
34+
@raise Aborted
35+
@raise Nothing_to_do *)
3536
val source_pin:
3637
rw switch_state -> name ->
3738
?version:version -> ?edit:bool -> ?opam:OpamFile.OPAM.t -> ?quiet:bool ->

src/core/opamFilename.mli

+6-4
Original file line numberDiff line numberDiff line change
@@ -287,15 +287,17 @@ val find_in_parents: (Dir.t -> bool) -> Dir.t -> Dir.t option
287287
val flock: [< OpamSystem.lock_flag ] -> ?dontblock:bool -> t -> OpamSystem.lock
288288

289289
(** Calls [f] while holding a lock file. Ensures the lock is properly released
290-
on [f] exit. Raises [OpamSystem.Locked] if [dontblock] is set and the lock
291-
can't be acquired. [f] is passed the file_descr of the lock. *)
290+
on [f] exit. [f] is passed the file_descr of the lock.
291+
@raise OpamSystem.Locked if [dontblock] is set and the lock
292+
can't be acquired. *)
292293
val with_flock: [< OpamSystem.lock_flag ] -> ?dontblock:bool -> t ->
293294
(Unix.file_descr -> 'a) -> 'a
294295

295296
(** Calls [f] with the file lock upgraded to at least [flag], then restores the
296297
previous lock level. Upgrade to [`Lock_write] should never be used in
297-
blocking mode as it would deadlock. Raises [OpamSystem.Locked] (but keeps
298-
the lock as is) if [dontblock] is set and the lock can't be upgraded. *)
298+
blocking mode as it would deadlock.
299+
@raise OpamSystem.Locked (but keeps the lock as is) if [dontblock] is set
300+
and the lock can't be upgraded. *)
299301
val with_flock_upgrade:
300302
[< OpamSystem.actual_lock_flag ] -> ?dontblock:bool -> OpamSystem.lock -> (Unix.file_descr -> 'a) -> 'a
301303

src/core/opamParallel.mli

+2-2
Original file line numberDiff line numberDiff line change
@@ -35,8 +35,8 @@ exception Aborted
3535
(** Simply parallel execution of tasks *)
3636

3737
(** In the simple iter, map and reduce cases, ints are the indexes of the jobs
38-
in the list. First list is return code of sucessfull commands, second those
39-
which raised expcetions, and third one those which were canceled. *)
38+
in the list. First list is return code of successful commands, second those
39+
which raised exceptions, and third one those which were canceled. *)
4040
exception Errors of int list * (int * exn) list * int list
4141

4242
val iter: jobs:int -> command:('a -> unit OpamProcess.job) -> ?dry_run:bool ->

src/core/opamStd.mli

+11-10
Original file line numberDiff line numberDiff line change
@@ -22,8 +22,9 @@ module type SET = sig
2222

2323
val is_singleton: t -> bool
2424

25-
(** Returns one element, assuming the set is a singleton. Raises [Not_found]
26-
on an empty set, [Failure] on a non-singleton. *)
25+
(** Returns one element, assuming the set is a singleton.
26+
@raise Not_found on an empty set
27+
@raise Failure on a non-singleton *)
2728
val choose_one : t -> elt
2829

2930
val choose_opt: t -> elt option
@@ -36,16 +37,16 @@ module type SET = sig
3637
val find: (elt -> bool) -> t -> elt
3738
val find_opt: (elt -> bool) -> t -> elt option
3839

39-
(** Raises Failure in case the element is already present *)
40+
(** @raise Failure in case the element is already present *)
4041
val safe_add: elt -> t -> t
4142

4243
(** Accumulates the resulting sets of a function of elements until a fixpoint
4344
is reached *)
4445
val fixpoint: (elt -> t) -> t -> t
4546

4647
(** [map_reduce f op t] applies [f] to every element of [t] and combines the
47-
results using associative operator [op]. Raises [Invalid_argument] on an
48-
empty set, or returns [default] if it is defined. *)
48+
results using associative operator [op].
49+
@raise Invalid_argument on an empty set if [default] is not defined *)
4950
val map_reduce: ?default:'a -> (elt -> 'a) -> ('a -> 'a -> 'a) -> t -> 'a
5051

5152
module Op : sig
@@ -81,16 +82,16 @@ module type MAP = sig
8182

8283
val of_list: (key * 'a) list -> 'a t
8384

84-
(** Raises Failure in case the element is already present *)
85+
(** @raise Failure in case the element is already present *)
8586
val safe_add: key -> 'a -> 'a t -> 'a t
8687

8788
(** [update k f zero map] updates the binding of [k] in [map] using function
8889
[f], applied to the current value bound to [k] or [zero] if none *)
8990
val update: key -> ('a -> 'a) -> 'a -> 'a t -> 'a t
9091

9192
(** [map_reduce f op t] applies [f] to every binding of [t] and combines the
92-
results using associative operator [op]. Raises [Invalid_argument] on an
93-
empty map, or returns [default] if it is defined. *)
93+
results using associative operator [op].
94+
@raise Invalid_argument on an empty map if [default] is not defined *)
9495
val map_reduce:
9596
?default:'b -> (key -> 'a -> 'b) -> ('b -> 'b -> 'b) -> 'a t -> 'b
9697

@@ -611,7 +612,7 @@ module Sys : sig
611612
[Unix.execvpe]. *)
612613
exception Exec of string * string array * string array
613614

614-
(** Raises [Exit i] *)
615+
(** Raise exception {!Exit} [i] *)
615616
(* val exit: int -> 'a *)
616617

617618
type exit_reason =
@@ -624,7 +625,7 @@ module Sys : sig
624625

625626
val get_exit_code : exit_reason -> int
626627

627-
(** Raises [Exit], with the code associated to the exit reason *)
628+
(** Raise exception {!Exit}, with the code associated to the exit reason *)
628629
val exit_because: exit_reason -> 'a
629630

630631
(**/**)

src/core/opamSystem.mli

+14-10
Original file line numberDiff line numberDiff line change
@@ -18,17 +18,18 @@ exception Command_not_found of string
1818

1919
exception Permission_denied of string
2020

21-
(** raise {!Process_error} *)
21+
(** Raise exception {!Process_error} with the given [result] *)
2222
val process_error: OpamProcess.result -> 'a
2323

24-
(** raise {!Process_error} if the process didn't return 0 *)
24+
(** Raise exception {!Process_error} with the given [result]
25+
if the process didn't return 0 *)
2526
val raise_on_process_error: OpamProcess.result -> unit
2627

2728
(** Exception raised when a computation in the current process
2829
fails. *)
2930
exception Internal_error of string
3031

31-
(** Raise {!Internal_error} *)
32+
(** Raise exception {!Internal_error} with the given string format *)
3233
val internal_error: ('a, unit, string, 'b) format4 -> 'a
3334

3435
(** [with_tmp_dir fn] executes [fn] creates a temporary directory and
@@ -171,9 +172,10 @@ val directories_with_links: string -> string list
171172
command and output will be displayed (at command end for the
172173
latter, if concurrent commands are running). [name] is used for
173174
naming log files. [text] is what is displayed in the status line
174-
for this command. May raise Command_not_found, unless
175-
[resolve_path] is set to false (in which case you can end up
176-
with a process error instead) *)
175+
for this command.
176+
177+
@raise Command_not_found, unless [resolve_path] is set to false (in which
178+
case you can end up with a process error instead) *)
177179
val make_command:
178180
?verbose:bool -> ?env:string array -> ?name:string -> ?text:string ->
179181
?metadata:(string * string) list -> ?allow_stdin:bool -> ?stdout:string ->
@@ -286,9 +288,10 @@ exception Locked
286288
val release_all_locks: unit -> unit
287289

288290
(** Acquires a lock on the given file.
289-
Raises [Locked] if the lock can't be acquired and [dontblock] is set. Raises
290-
{!OpamStd.Sys.Exit} if [safe_mode] is set and a write lock is required. Also
291-
raises Unix errors if the lock file can't be opened. *)
291+
292+
@raise Locked if the lock can't be acquired and [dontblock] is set
293+
@raise OpamStd.Sys.Exit if [safe_mode] is set and a write lock is required.
294+
@raise Unix.Unix_error if the lock file can't be opened. *)
292295
val flock: [< lock_flag ] -> ?dontblock:bool -> string -> lock
293296

294297
(** Updates an existing lock to the given level. Raises the same exceptions as
@@ -308,7 +311,8 @@ val lock_isatleast: [< lock_flag ] -> lock -> bool
308311
(** Returns the current kind of the lock *)
309312
val get_lock_flag: lock -> lock_flag
310313

311-
(** Returns the underlying fd for the lock or raises Not_found for `No_lock *)
314+
(** Returns the underlying fd for the lock
315+
@raise Not_found for [`No_lock] *)
312316
val get_lock_fd: lock -> Unix.file_descr
313317

314318
(** {2 Misc} *)

src/format/opamFile.mli

+2-1
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,8 @@ module type IO_FILE = sig
4141
(** Write some contents to a file *)
4242
val write: t typed_file -> t -> unit
4343

44-
(** Read file contents. Raise an error if the file does not exist. *)
44+
(** Read file contents.
45+
@raise OpamSystem.Internal_error if the file does not exist. *)
4546
val read: t typed_file -> t
4647

4748
(** Returns [None] on non-existing file *)

src/format/opamFilter.mli

+17-14
Original file line numberDiff line numberDiff line change
@@ -69,17 +69,18 @@ type env = full_variable -> variable_contents option
6969
self-reference [_] *)
7070
type fident = name option list * variable * (string * string) option
7171

72-
(** Maps on all variables appearing in a filter. The case where package
73-
variables are renamed differently and appear in a filter ident of the form
74-
[%{pkg1+pkg2:var}%] is not supported and raises [Invalid_argument]. *)
72+
(** Maps on all variables appearing in a filter.
73+
74+
@raise Invalid_argument when package variables are renamed differently and
75+
appear in a filter ident of the form [%{pkg1+pkg2:var}%] *)
7576
val map_variables: (full_variable -> full_variable) -> filter -> filter
7677

7778
(** Same limitation as [map_variables] *)
7879
val map_variables_in_string:
7980
(full_variable -> full_variable) -> string -> string
8081

81-
(** Does not handle rewriting the variables to different names (which can't be
82-
expressed with a {!fident} anymore), and raises [Invalid_argument] *)
82+
(** @raise Invalid_argument when rewriting the variables to different names
83+
(which can't be expressed with a {!fident} anymore) *)
8384
val map_variables_in_fident:
8485
(full_variable -> full_variable) -> fident -> fident
8586

@@ -88,25 +89,27 @@ val distribute_negations: ?neg:bool -> filter -> filter
8889

8990
(** Rewrites string interpolations within a string. [default] is applied to the
9091
fident string (e.g. what's between [%{] and [}%]) when the expansion is
91-
undefined. If unspecified, this raises [Failure].
92+
undefined.
9293
9394
With [partial], [default] defaults to the identity, and is otherwise
9495
expected to return a fident. In this case, the returned string is supposed
9596
to be expanded again (expansion results are escaped, escapes are otherwise
96-
kept). This makes the function idempotent *)
97+
kept). This makes the function idempotent.
98+
99+
@raise Failure if [default] is unspecified *)
97100
val expand_string:
98101
?partial:bool -> ?default:(string -> string) -> env -> string -> string
99102

100103
(** Returns the (beginning, end) offsets and substrings of any unclosed [%{]
101104
expansions *)
102105
val unclosed_expansions: string -> ((int * int) * string) list
103106

104-
(** Computes the value of a filter. May raise [Failure] if [default] isn't
105-
provided *)
107+
(** Computes the value of a filter.
108+
@raise Failure if [default] isn't provided *)
106109
val eval: ?default:variable_contents -> env -> filter -> variable_contents
107110

108-
not a valid bool and no default supplied. *)
109111
(** Like {!eval} but casts the result to a bool.
112+
@raise Invalid_argument if not a valid bool and no [default] supplied *)
110113
val eval_to_bool: ?default:bool -> env -> filter -> bool
111114

112115
(** Same as {!eval_to_bool}, but takes an option as filter and returns always
@@ -126,8 +129,8 @@ val ident_of_var: full_variable -> fident
126129
(** A fident accessor directly referring a variable with the given name *)
127130
val ident_of_string: string -> fident
128131

129-
(** Resolves a filter ident. Like {!eval}, may raise Failure if no default is
130-
provided *)
132+
(** Resolves a filter ident.
133+
@raise Failure if no default is provided, like {!eval} *)
131134
val ident_value: ?default:variable_contents -> env -> fident -> variable_contents
132135

133136
(** Like {!ident_value}, but casts the result to a string *)
@@ -170,8 +173,8 @@ val of_formula: ('a -> filter) -> 'a generic_formula -> filter
170173
doesn't resolve to a valid version, the constraint is dropped unless
171174
[default_version] is specified.
172175
173-
May raise, as other filter functions, if [default] is not provided and
174-
filters don't resolve. *)
176+
@raise Invalid_argument as other filter functions, if [default] is not
177+
provided and filters don't resolve *)
175178
val filter_formula:
176179
?default_version:version -> ?default:bool ->
177180
env -> filtered_formula -> formula

src/format/opamFormat.mli

+2-2
Original file line numberDiff line numberDiff line change
@@ -45,8 +45,8 @@ val lines_map :
4545
(** {3 Pps for the type [value], used by opam-syntax files ([opamfile])} *)
4646

4747
module V : sig
48-
(** These base converters raise [Unexpected] when not run on the right input
49-
(which is then converted to [Bad_format] by the parser. *)
48+
(** These base converters raise {!Unexpected} when not run on the right input
49+
(which is then converted to {!Bad_format} by the parser. *)
5050

5151
val bool : (value, bool) t
5252
val int : (value, int) t

src/format/opamPackage.mli

+1-1
Original file line numberDiff line numberDiff line change
@@ -116,7 +116,7 @@ val packages_of_names: Set.t -> Name.Set.t -> Set.t
116116
val filter_name_out: Set.t -> Name.t -> Set.t
117117

118118
(** Return the maximal available version of a package name from a set.
119-
Raises [Not_found] if no such package available. *)
119+
@raise Not_found if no such package available. *)
120120
val max_version: Set.t -> Name.t -> t
121121

122122
(** Compare two packages *)

src/format/opamPp.mli

+2-2
Original file line numberDiff line numberDiff line change
@@ -24,10 +24,10 @@ exception Bad_format of bad_format
2424
exception Bad_format_list of bad_format list
2525
exception Bad_version of bad_format * OpamVersion.t option
2626

27-
(** Raise [Bad_format]. *)
27+
(** Raise exception {!Bad_format}. *)
2828
val bad_format: ?pos:pos -> ('a, unit, string, 'b) format4 -> 'a
2929

30-
(** Raise [Bad_version]. *)
30+
(** Raise exception {!Bad_version}. *)
3131
val bad_version: OpamVersion.t option -> ?pos:pos -> ('a, unit, string, 'b) format4 -> 'a
3232

3333
val string_of_bad_format: ?file:string -> exn -> string

src/format/opamTypesBase.mli

+7-5
Original file line numberDiff line numberDiff line change
@@ -63,15 +63,17 @@ val env_array: env -> string array
6363

6464
exception Parse_variable of string * string
6565

66-
(** Parses the data suitable for a filter.FIdent from a string. May raise
67-
[Failure msg] on bad package names. A self-reference [_] parses to [None] *)
66+
(** Parses the data suitable for a filter.FIdent from a string. A
67+
self-reference [_] parses to [None].
68+
@raise Failure on bad package names.*)
6869
val filter_ident_of_string:
6970
string -> name option list * variable * (string * string) option
7071

7172
(** Like {!filter_ident_of_string} but parses also [%{?pkg+:var:}%] syntax for
72-
variables with package name that contains a [+]. if [accept] is [false],
73-
[Parse_variable (pkg,var)] is raised when several [+] are encountered in
74-
package name, i.e. [pkg++:var]. *)
73+
variables with package name that contains a [+].
74+
75+
@raise {!Parse_variable} [(pkg,var)] if [accept] is [false] when several
76+
[+] are encountered in package name, i.e. [pkg++:var]. *)
7577
val filter_ident_of_string_interp:
7678
?accept:bool -> string
7779
-> name option list * variable * (string * string) option

src/repository/opamRepository.mli

+4-3
Original file line numberDiff line numberDiff line change
@@ -22,9 +22,10 @@ val packages_with_prefixes: dirname -> string option package_map
2222

2323
(** {2 Repository backends} *)
2424

25-
(** Update {i $opam/repo/$repo}. Raises [Failure] in case the update couldn't be
26-
achieved. Returns [`No_changes] if the update did not bring any changes, and
27-
[`Changes] otherwise. *)
25+
(** Update {i $opam/repo/$repo}. Returns [`No_changes] if the update did not
26+
bring any changes, and [`Changes] otherwise.
27+
28+
@raise Failure in case the update couldn't be achieved. *)
2829
val update: repository -> dirname -> [`Changes | `No_changes] OpamProcess.job
2930

3031
(** [pull_shared_tree ?cache_dir ?cache_url labels_dirnames checksums urls]

0 commit comments

Comments
 (0)