diff --git a/master_changes.md b/master_changes.md index 04184c31932..b584dc8cf57 100644 --- a/master_changes.md +++ b/master_changes.md @@ -121,6 +121,7 @@ users) * Remove redundant `+` in version BNF definition (it is already present in `identchar`) [#6252 @rjbou] * mli documentation: fix code blocks [#6150 @rjbou] * mli documentation: fix code blocks, references [#6150 @rjbou] + * mli documentation: fix code blocks, references, add `@raise` tags [#6150 @rjbou] * Unhide `OpamProcess` functions [#6150 @rjbou] ## Security fixes diff --git a/src/client/opamConfigCommand.mli b/src/client/opamConfigCommand.mli index dd6343e411e..a205bd376a5 100644 --- a/src/client/opamConfigCommand.mli +++ b/src/client/opamConfigCommand.mli @@ -82,14 +82,15 @@ val whole_of_update_op: update_op -> whole_op defined fields in {!OpamFile.Config.t}. On revert, field is reverted to its initial value as defined in {!OpamInitDefaults.init_config}, to default value otherwise ({!OpamFile.Config.empty}). - May raise [OpamStd.Sys.Exit]. *) + @raise OpamStd.Sys.Exit ([`Bad_argument], [2]) if the field is not found or not + modifiable, or the value have a parse error. *) val set_opt_global: rw global_state -> string -> update_op -> rw global_state (** As {!set_opt_global}, {!set_opt_switch} updates switch config file in //.opam-switch/switch-config. If switch state is given, uses its config and returns it with then new config. Otherwise, loads the raw switch state and returns [None]. - Raises [OpamStd.Sys.Exit 50] ([`Configuration_error]) if no switch is set *) + @raise OpamStd.Sys.Exit ([`Configuration_error], [50]) if no switch is set *) val set_opt_switch: 'a global_state -> ?st:rw switch_state -> string -> update_op -> rw switch_state option @@ -99,11 +100,11 @@ val set_opt_switch: the new variables to current set. If switch state is given, uses its config and returns it with then new config. Otherwise, loads the raw switch state and returns [None]. - Raises [OpamStd.Sys.Exit 2] ([`Bad_argument]) if field is not modifiable *) + @raise OpamStd.Sys.Exit ([`Bad_argument], [2]) if field is not modifiable *) val set_var_global: rw global_state -> string -> whole_op -> rw global_state -(** Raises [OpamStd.Sys.Exit 50] ([`Configuration_error]) if no switch is set *) +(** @raise OpamStd.Sys.Exit ([`Configuration_error], [50]) if no switch is set *) val set_var_switch: 'a global_state -> ?st:rw switch_state -> string -> whole_op -> rw switch_state option @@ -118,7 +119,7 @@ val options_list: ?st:unlocked switch_state -> 'a global_state -> unit val options_list_global: 'a global_state -> unit -(** Raises [OpamStd.Sys.Exit 50] ([`Configuration_error]) if no switch is set *) +(** @raise OpamStd.Sys.Exit ([`Configuration_error], [50]) if no switch is set *) val options_list_switch: ?st:unlocked switch_state -> 'a global_state -> unit @@ -129,7 +130,7 @@ val vars_list: ?st:'a switch_state -> 'b global_state -> unit val vars_list_global: 'a global_state -> unit -(** Raises [OpamStd.Sys.Exit 50] ([`Configuration_error]) if no switch is set *) +(** @raise OpamStd.Sys.Exit ([`Configuration_error], [50]) if no switch is set *) val vars_list_switch: ?st:'a switch_state -> 'b global_state -> unit @@ -142,7 +143,7 @@ val vars_list_switch: val option_show_global: 'a global_state -> string -> unit -(** Raises [OpamStd.Sys.Exit 50] ([`Configuration_error]) if no switch is set *) +(** @raise OpamStd.Sys.Exit ([`Configuration_error], [50]) if no switch is set *) val option_show_switch: 'a global_state -> ?st:unlocked switch_state -> string -> unit diff --git a/src/client/opamPinCommand.mli b/src/client/opamPinCommand.mli index 5edde0c7453..483cb25d752 100644 --- a/src/client/opamPinCommand.mli +++ b/src/client/opamPinCommand.mli @@ -31,7 +31,8 @@ exception Nothing_to_do If [force], don't abort even if the source can't be fetched from [target] - May raise [Aborted] or [Nothing_to_do]. *) + @raise Aborted + @raise Nothing_to_do *) val source_pin: rw switch_state -> name -> ?version:version -> ?edit:bool -> ?opam:OpamFile.OPAM.t -> ?quiet:bool -> diff --git a/src/core/opamFilename.mli b/src/core/opamFilename.mli index e9ae596b87d..ba3763bb454 100644 --- a/src/core/opamFilename.mli +++ b/src/core/opamFilename.mli @@ -287,15 +287,17 @@ val find_in_parents: (Dir.t -> bool) -> Dir.t -> Dir.t option val flock: [< OpamSystem.lock_flag ] -> ?dontblock:bool -> t -> OpamSystem.lock (** Calls [f] while holding a lock file. Ensures the lock is properly released - on [f] exit. Raises [OpamSystem.Locked] if [dontblock] is set and the lock - can't be acquired. [f] is passed the file_descr of the lock. *) + on [f] exit. [f] is passed the file_descr of the lock. + @raise OpamSystem.Locked if [dontblock] is set and the lock + can't be acquired. *) val with_flock: [< OpamSystem.lock_flag ] -> ?dontblock:bool -> t -> (Unix.file_descr -> 'a) -> 'a (** Calls [f] with the file lock upgraded to at least [flag], then restores the previous lock level. Upgrade to [`Lock_write] should never be used in - blocking mode as it would deadlock. Raises [OpamSystem.Locked] (but keeps - the lock as is) if [dontblock] is set and the lock can't be upgraded. *) + blocking mode as it would deadlock. + @raise OpamSystem.Locked (but keeps the lock as is) if [dontblock] is set + and the lock can't be upgraded. *) val with_flock_upgrade: [< OpamSystem.actual_lock_flag ] -> ?dontblock:bool -> OpamSystem.lock -> (Unix.file_descr -> 'a) -> 'a diff --git a/src/core/opamParallel.mli b/src/core/opamParallel.mli index 2c16ccb9ec6..aa89a13bf9f 100644 --- a/src/core/opamParallel.mli +++ b/src/core/opamParallel.mli @@ -35,8 +35,8 @@ exception Aborted (** Simply parallel execution of tasks *) (** In the simple iter, map and reduce cases, ints are the indexes of the jobs - in the list. First list is return code of sucessfull commands, second those - which raised expcetions, and third one those which were canceled. *) + in the list. First list is return code of successful commands, second those + which raised exceptions, and third one those which were canceled. *) exception Errors of int list * (int * exn) list * int list val iter: jobs:int -> command:('a -> unit OpamProcess.job) -> ?dry_run:bool -> diff --git a/src/core/opamStd.mli b/src/core/opamStd.mli index 51e36e71baa..e3aea4ada7d 100644 --- a/src/core/opamStd.mli +++ b/src/core/opamStd.mli @@ -22,8 +22,9 @@ module type SET = sig val is_singleton: t -> bool - (** Returns one element, assuming the set is a singleton. Raises [Not_found] - on an empty set, [Failure] on a non-singleton. *) + (** Returns one element, assuming the set is a singleton. + @raise Not_found on an empty set + @raise Failure on a non-singleton *) val choose_one : t -> elt val choose_opt: t -> elt option @@ -36,7 +37,7 @@ module type SET = sig val find: (elt -> bool) -> t -> elt val find_opt: (elt -> bool) -> t -> elt option - (** Raises Failure in case the element is already present *) + (** @raise Failure in case the element is already present *) val safe_add: elt -> t -> t (** Accumulates the resulting sets of a function of elements until a fixpoint @@ -44,8 +45,8 @@ module type SET = sig val fixpoint: (elt -> t) -> t -> t (** [map_reduce f op t] applies [f] to every element of [t] and combines the - results using associative operator [op]. Raises [Invalid_argument] on an - empty set, or returns [default] if it is defined. *) + results using associative operator [op]. + @raise Invalid_argument on an empty set if [default] is not defined *) val map_reduce: ?default:'a -> (elt -> 'a) -> ('a -> 'a -> 'a) -> t -> 'a module Op : sig @@ -81,7 +82,7 @@ module type MAP = sig val of_list: (key * 'a) list -> 'a t - (** Raises Failure in case the element is already present *) + (** @raise Failure in case the element is already present *) val safe_add: key -> 'a -> 'a t -> 'a t (** [update k f zero map] updates the binding of [k] in [map] using function @@ -89,8 +90,8 @@ module type MAP = sig val update: key -> ('a -> 'a) -> 'a -> 'a t -> 'a t (** [map_reduce f op t] applies [f] to every binding of [t] and combines the - results using associative operator [op]. Raises [Invalid_argument] on an - empty map, or returns [default] if it is defined. *) + results using associative operator [op]. + @raise Invalid_argument on an empty map if [default] is not defined *) val map_reduce: ?default:'b -> (key -> 'a -> 'b) -> ('b -> 'b -> 'b) -> 'a t -> 'b @@ -611,7 +612,7 @@ module Sys : sig [Unix.execvpe]. *) exception Exec of string * string array * string array - (** Raises [Exit i] *) + (** Raise exception {!Exit} [i] *) (* val exit: int -> 'a *) type exit_reason = @@ -624,7 +625,7 @@ module Sys : sig val get_exit_code : exit_reason -> int - (** Raises [Exit], with the code associated to the exit reason *) + (** Raise exception {!Exit}, with the code associated to the exit reason *) val exit_because: exit_reason -> 'a (**/**) diff --git a/src/core/opamSystem.mli b/src/core/opamSystem.mli index c3e0fe4534d..e015d23af5f 100644 --- a/src/core/opamSystem.mli +++ b/src/core/opamSystem.mli @@ -18,17 +18,18 @@ exception Command_not_found of string exception Permission_denied of string -(** raise {!Process_error} *) +(** Raise exception {!Process_error} with the given [result] *) val process_error: OpamProcess.result -> 'a -(** raise {!Process_error} if the process didn't return 0 *) +(** Raise exception {!Process_error} with the given [result] + if the process didn't return 0 *) val raise_on_process_error: OpamProcess.result -> unit (** Exception raised when a computation in the current process fails. *) exception Internal_error of string -(** Raise {!Internal_error} *) +(** Raise exception {!Internal_error} with the given string format *) val internal_error: ('a, unit, string, 'b) format4 -> 'a (** [with_tmp_dir fn] executes [fn] creates a temporary directory and @@ -171,9 +172,10 @@ val directories_with_links: string -> string list command and output will be displayed (at command end for the latter, if concurrent commands are running). [name] is used for naming log files. [text] is what is displayed in the status line - for this command. May raise Command_not_found, unless - [resolve_path] is set to false (in which case you can end up - with a process error instead) *) + for this command. + + @raise Command_not_found, unless [resolve_path] is set to false (in which + case you can end up with a process error instead) *) val make_command: ?verbose:bool -> ?env:string array -> ?name:string -> ?text:string -> ?metadata:(string * string) list -> ?allow_stdin:bool -> ?stdout:string -> @@ -286,9 +288,10 @@ exception Locked val release_all_locks: unit -> unit (** Acquires a lock on the given file. - Raises [Locked] if the lock can't be acquired and [dontblock] is set. Raises - {!OpamStd.Sys.Exit} if [safe_mode] is set and a write lock is required. Also - raises Unix errors if the lock file can't be opened. *) + + @raise Locked if the lock can't be acquired and [dontblock] is set + @raise OpamStd.Sys.Exit if [safe_mode] is set and a write lock is required. + @raise Unix.Unix_error if the lock file can't be opened. *) val flock: [< lock_flag ] -> ?dontblock:bool -> string -> lock (** Updates an existing lock to the given level. Raises the same exceptions as @@ -308,7 +311,8 @@ val lock_isatleast: [< lock_flag ] -> lock -> bool (** Returns the current kind of the lock *) val get_lock_flag: lock -> lock_flag -(** Returns the underlying fd for the lock or raises Not_found for `No_lock *) +(** Returns the underlying fd for the lock + @raise Not_found for [`No_lock] *) val get_lock_fd: lock -> Unix.file_descr (** {2 Misc} *) diff --git a/src/format/opamFile.mli b/src/format/opamFile.mli index 5c67528abfb..9ac19f15b87 100644 --- a/src/format/opamFile.mli +++ b/src/format/opamFile.mli @@ -41,7 +41,8 @@ module type IO_FILE = sig (** Write some contents to a file *) val write: t typed_file -> t -> unit - (** Read file contents. Raise an error if the file does not exist. *) + (** Read file contents. + @raise OpamSystem.Internal_error if the file does not exist. *) val read: t typed_file -> t (** Returns [None] on non-existing file *) diff --git a/src/format/opamFilter.mli b/src/format/opamFilter.mli index 04c31189540..21ae2c36b9f 100644 --- a/src/format/opamFilter.mli +++ b/src/format/opamFilter.mli @@ -69,17 +69,18 @@ type env = full_variable -> variable_contents option self-reference [_] *) type fident = name option list * variable * (string * string) option -(** Maps on all variables appearing in a filter. The case where package - variables are renamed differently and appear in a filter ident of the form - [%{pkg1+pkg2:var}%] is not supported and raises [Invalid_argument]. *) +(** Maps on all variables appearing in a filter. + + @raise Invalid_argument when package variables are renamed differently and + appear in a filter ident of the form [%{pkg1+pkg2:var}%] *) val map_variables: (full_variable -> full_variable) -> filter -> filter (** Same limitation as [map_variables] *) val map_variables_in_string: (full_variable -> full_variable) -> string -> string -(** Does not handle rewriting the variables to different names (which can't be - expressed with a {!fident} anymore), and raises [Invalid_argument] *) +(** @raise Invalid_argument when rewriting the variables to different names + (which can't be expressed with a {!fident} anymore) *) val map_variables_in_fident: (full_variable -> full_variable) -> fident -> fident @@ -88,12 +89,14 @@ val distribute_negations: ?neg:bool -> filter -> filter (** Rewrites string interpolations within a string. [default] is applied to the fident string (e.g. what's between [%{] and [}%]) when the expansion is - undefined. If unspecified, this raises [Failure]. + undefined. With [partial], [default] defaults to the identity, and is otherwise expected to return a fident. In this case, the returned string is supposed to be expanded again (expansion results are escaped, escapes are otherwise - kept). This makes the function idempotent *) + kept). This makes the function idempotent. + + @raise Failure if [default] is unspecified *) val expand_string: ?partial:bool -> ?default:(string -> string) -> env -> string -> string @@ -101,12 +104,12 @@ val expand_string: expansions *) val unclosed_expansions: string -> ((int * int) * string) list -(** Computes the value of a filter. May raise [Failure] if [default] isn't - provided *) +(** Computes the value of a filter. + @raise Failure if [default] isn't provided *) val eval: ?default:variable_contents -> env -> filter -> variable_contents - not a valid bool and no default supplied. *) (** Like {!eval} but casts the result to a bool. + @raise Invalid_argument if not a valid bool and no [default] supplied *) val eval_to_bool: ?default:bool -> env -> filter -> bool (** 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 (** A fident accessor directly referring a variable with the given name *) val ident_of_string: string -> fident -(** Resolves a filter ident. Like {!eval}, may raise Failure if no default is - provided *) +(** Resolves a filter ident. + @raise Failure if no default is provided, like {!eval} *) val ident_value: ?default:variable_contents -> env -> fident -> variable_contents (** Like {!ident_value}, but casts the result to a string *) @@ -170,8 +173,8 @@ val of_formula: ('a -> filter) -> 'a generic_formula -> filter doesn't resolve to a valid version, the constraint is dropped unless [default_version] is specified. - May raise, as other filter functions, if [default] is not provided and - filters don't resolve. *) + @raise Invalid_argument as other filter functions, if [default] is not + provided and filters don't resolve *) val filter_formula: ?default_version:version -> ?default:bool -> env -> filtered_formula -> formula diff --git a/src/format/opamFormat.mli b/src/format/opamFormat.mli index f8a1776641e..302fb9f413f 100644 --- a/src/format/opamFormat.mli +++ b/src/format/opamFormat.mli @@ -45,8 +45,8 @@ val lines_map : (** {3 Pps for the type [value], used by opam-syntax files ([opamfile])} *) module V : sig - (** These base converters raise [Unexpected] when not run on the right input - (which is then converted to [Bad_format] by the parser. *) + (** These base converters raise {!Unexpected} when not run on the right input + (which is then converted to {!Bad_format} by the parser. *) val bool : (value, bool) t val int : (value, int) t diff --git a/src/format/opamPackage.mli b/src/format/opamPackage.mli index 5c352c325fe..6c3a49e073d 100644 --- a/src/format/opamPackage.mli +++ b/src/format/opamPackage.mli @@ -116,7 +116,7 @@ val packages_of_names: Set.t -> Name.Set.t -> Set.t val filter_name_out: Set.t -> Name.t -> Set.t (** Return the maximal available version of a package name from a set. - Raises [Not_found] if no such package available. *) + @raise Not_found if no such package available. *) val max_version: Set.t -> Name.t -> t (** Compare two packages *) diff --git a/src/format/opamPp.mli b/src/format/opamPp.mli index 7123862b0b9..d6c0555af19 100644 --- a/src/format/opamPp.mli +++ b/src/format/opamPp.mli @@ -24,10 +24,10 @@ exception Bad_format of bad_format exception Bad_format_list of bad_format list exception Bad_version of bad_format * OpamVersion.t option -(** Raise [Bad_format]. *) +(** Raise exception {!Bad_format}. *) val bad_format: ?pos:pos -> ('a, unit, string, 'b) format4 -> 'a -(** Raise [Bad_version]. *) +(** Raise exception {!Bad_version}. *) val bad_version: OpamVersion.t option -> ?pos:pos -> ('a, unit, string, 'b) format4 -> 'a val string_of_bad_format: ?file:string -> exn -> string diff --git a/src/format/opamTypesBase.mli b/src/format/opamTypesBase.mli index 72808763de2..4985f0f3424 100644 --- a/src/format/opamTypesBase.mli +++ b/src/format/opamTypesBase.mli @@ -63,15 +63,17 @@ val env_array: env -> string array exception Parse_variable of string * string -(** Parses the data suitable for a filter.FIdent from a string. May raise - [Failure msg] on bad package names. A self-reference [_] parses to [None] *) +(** Parses the data suitable for a filter.FIdent from a string. A + self-reference [_] parses to [None]. + @raise Failure on bad package names.*) val filter_ident_of_string: string -> name option list * variable * (string * string) option (** Like {!filter_ident_of_string} but parses also [%{?pkg+:var:}%] syntax for - variables with package name that contains a [+]. if [accept] is [false], - [Parse_variable (pkg,var)] is raised when several [+] are encountered in - package name, i.e. [pkg++:var]. *) + variables with package name that contains a [+]. + + @raise {!Parse_variable} [(pkg,var)] if [accept] is [false] when several + [+] are encountered in package name, i.e. [pkg++:var]. *) val filter_ident_of_string_interp: ?accept:bool -> string -> name option list * variable * (string * string) option diff --git a/src/repository/opamRepository.mli b/src/repository/opamRepository.mli index 840faa79666..53a1b4bb055 100644 --- a/src/repository/opamRepository.mli +++ b/src/repository/opamRepository.mli @@ -22,9 +22,10 @@ val packages_with_prefixes: dirname -> string option package_map (** {2 Repository backends} *) -(** Update {i $opam/repo/$repo}. Raises [Failure] in case the update couldn't be - achieved. Returns [`No_changes] if the update did not bring any changes, and - [`Changes] otherwise. *) +(** Update {i $opam/repo/$repo}. Returns [`No_changes] if the update did not + bring any changes, and [`Changes] otherwise. + + @raise Failure in case the update couldn't be achieved. *) val update: repository -> dirname -> [`Changes | `No_changes] OpamProcess.job (** [pull_shared_tree ?cache_dir ?cache_url labels_dirnames checksums urls] diff --git a/src/solver/opamCudf.mli b/src/solver/opamCudf.mli index 6f7b36e99be..ce67c312e52 100644 --- a/src/solver/opamCudf.mli +++ b/src/solver/opamCudf.mli @@ -101,7 +101,7 @@ exception Cyclic_actions of Cudf.package action list list [reduce_actions] to reduce it to a graph including reinstall and up/down-grade actions. - May raise [Cyclic_actions]. *) + @raise Cyclic_actions *) val atomic_actions: simple_universe:Cudf.universe -> complete_universe:Cudf.universe ->