From 20f61d7fb41f69ceed84b2a30a119719db7a4533 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?T=C3=B6r=C3=B6k=20Edwin?= Date: Fri, 9 Dec 2016 00:45:15 +0200 Subject: [PATCH 1/2] Documentation: improve @since annotations Add missing @since annotations for OCaml versions 4.00.0 - 4.05.0, and fix existing annotations as needed: Format.ikprintf: clarify ambiguity on @since 4.0 annotation See https://github.com/ocaml/ocaml/commit/b81519668f7fa3d84f1453dc022a0d4a9b722eb8 Hashtbl.is_randomized and ListLabels.sort_uniq should be @since 4.03 List.sort_uniq is 4.02 but ListLabels.sort_uniq is 4.03 See: https://github.com/ocaml/ocaml/commit/512d128918544ae1da0c808e811f3a7f177524d2 https://github.com/ocaml/ocaml/commit/189d29bfcf98525f63c1c3c4a4a2be9989a62ef7 --- otherlibs/bigarray/bigarray.mli | 14 +++++++++----- otherlibs/num/big_int.mli | 2 +- otherlibs/num/num.mli | 6 ++++++ otherlibs/unix/unix.mli | 18 ++++++++++++------ otherlibs/unix/unixLabels.mli | 15 ++++++++++----- stdlib/arg.mli | 17 +++++++++++++---- stdlib/arrayLabels.mli | 16 ++++++++++------ stdlib/buffer.mli | 3 ++- stdlib/bytesLabels.mli | 19 +++++++++++-------- stdlib/ephemeron.mli | 1 + stdlib/format.mli | 15 ++++++++++----- stdlib/hashtbl.mli | 17 +++++++++++++---- stdlib/listLabels.mli | 7 ++++--- stdlib/pervasives.mli | 4 +++- stdlib/printexc.mli | 3 ++- stdlib/printf.mli | 2 +- stdlib/stringLabels.mli | 15 ++++++++------- stdlib/sys.mli | 2 +- 18 files changed, 117 insertions(+), 59 deletions(-) diff --git a/otherlibs/bigarray/bigarray.mli b/otherlibs/bigarray/bigarray.mli index f1ddbdf52..db1c11a28 100644 --- a/otherlibs/bigarray/bigarray.mli +++ b/otherlibs/bigarray/bigarray.mli @@ -453,7 +453,8 @@ Unix.map_file raises Unix_error."] similar to those of {!Bigarray.Genarray}, but specialized to the case of zero-dimensional arrays that only contain a single scalar value. Statically knowing the number of dimensions of the array allows - faster operations, and more precise static type-checking. *) + faster operations, and more precise static type-checking. + @since 4.05.0 *) module Array0 : sig type ('a, 'b, 'c) t (** The type of zero-dimensional big arrays whose elements have @@ -554,7 +555,8 @@ module Array1 : sig (** Extract a scalar (zero-dimensional slice) of the given one-dimensional big array. The integer parameter is the index of the scalar to extract. See {!Bigarray.Genarray.slice_left} and - {!Bigarray.Genarray.slice_right} for more details. *) + {!Bigarray.Genarray.slice_right} for more details. + @since 4.05.0 *) external blit: ('a, 'b, 'c) t -> ('a, 'b, 'c) t -> unit = "caml_ba_blit" @@ -842,7 +844,7 @@ end external genarray_of_array0 : ('a, 'b, 'c) Array0.t -> ('a, 'b, 'c) Genarray.t = "%identity" (** Return the generic big array corresponding to the given zero-dimensional - big array. *) + big array. @since 4.05.0 *) external genarray_of_array1 : ('a, 'b, 'c) Array1.t -> ('a, 'b, 'c) Genarray.t = "%identity" @@ -862,7 +864,8 @@ external genarray_of_array3 : val array0_of_genarray : ('a, 'b, 'c) Genarray.t -> ('a, 'b, 'c) Array0.t (** Return the zero-dimensional big array corresponding to the given generic big array. Raise [Invalid_argument] if the generic big array - does not have exactly zero dimension. *) + does not have exactly zero dimension. + @since 4.05.0 *) val array1_of_genarray : ('a, 'b, 'c) Genarray.t -> ('a, 'b, 'c) Array1.t (** Return the one-dimensional big array corresponding to the given @@ -900,7 +903,8 @@ val reshape : ('a, 'b, 'c) Genarray.t -> int array -> ('a, 'b, 'c) Genarray.t val reshape_0 : ('a, 'b, 'c) Genarray.t -> ('a, 'b, 'c) Array0.t (** Specialized version of {!Bigarray.reshape} for reshaping to - zero-dimensional arrays. *) + zero-dimensional arrays. + @since 4.05.0 *) val reshape_1 : ('a, 'b, 'c) Genarray.t -> int -> ('a, 'b, 'c) Array1.t (** Specialized version of {!Bigarray.reshape} for reshaping to diff --git a/otherlibs/num/big_int.mli b/otherlibs/num/big_int.mli index 0e37de08b..07c407295 100644 --- a/otherlibs/num/big_int.mli +++ b/otherlibs/num/big_int.mli @@ -273,4 +273,4 @@ val round_futur_last_digit : bytes -> int -> int -> bool val approx_big_int: int -> big_int -> string val round_big_int_to_float: big_int -> bool -> float -(* @since 4.03.0 *) +(** @since 4.03.0 *) diff --git a/otherlibs/num/num.mli b/otherlibs/num/num.mli index 9148554ff..4d3793b98 100644 --- a/otherlibs/num/num.mli +++ b/otherlibs/num/num.mli @@ -173,13 +173,19 @@ val num_of_string_opt: string -> num option val int_of_num : num -> int val int_of_num_opt: num -> int option +(** @since 4.05.0 *) + val num_of_int : int -> num val nat_of_num : num -> nat val nat_of_num_opt: num -> nat option +(** @since 4.05.0 *) + val num_of_nat : nat -> num val num_of_big_int : big_int -> num val big_int_of_num : num -> big_int val big_int_of_num_opt: num -> big_int option +(** @since 4.05.0 *) + val ratio_of_num : num -> ratio val num_of_ratio : ratio -> num val float_of_num : num -> float diff --git a/otherlibs/unix/unix.mli b/otherlibs/unix/unix.mli index 6762c2531..cd25e2cb1 100644 --- a/otherlibs/unix/unix.mli +++ b/otherlibs/unix/unix.mli @@ -301,11 +301,13 @@ val single_write : file_descr -> bytes -> int -> int -> int val write_substring : file_descr -> string -> int -> int -> int (** Same as [write], but take the data from a string instead of a byte - sequence. *) + sequence. + @since 4.02.0 *) val single_write_substring : file_descr -> string -> int -> int -> int (** Same as [single_write], but take the data from a string instead of - a byte sequence. *) + a byte sequence. + @since 4.02.0 *) (** {6 Interfacing with the standard input/output library} *) @@ -513,7 +515,8 @@ val map_file : file is shrunk. [Invalid_argument] or [Failure] may be raised in cases where argument - validation fails. *) + validation fails. + @since 4.05.0 *) (** {6 Operations on file names} *) @@ -822,7 +825,8 @@ val has_symlink : unit -> bool (** Returns [true] if the user is able to create symbolic links. On Windows, this indicates that the user not only has the SeCreateSymbolicLinkPrivilege but is also running elevated, if necessary. On other platforms, this is - simply indicates that the symlink system call is available. *) + simply indicates that the symlink system call is available. + @since 4.03.0 *) val readlink : string -> string (** Read the contents of a symbolic link. *) @@ -1278,7 +1282,8 @@ val send : file_descr -> bytes -> int -> int -> msg_flag list -> int val send_substring : file_descr -> string -> int -> int -> msg_flag list -> int (** Same as [send], but take the data from a string instead of a byte - sequence. *) + sequence. + @since 4.02.0 *) val sendto : file_descr -> bytes -> int -> int -> msg_flag list -> sockaddr -> int @@ -1287,7 +1292,8 @@ val sendto : val sendto_substring : file_descr -> string -> int -> int -> msg_flag list -> sockaddr -> int (** Same as [sendto], but take the data from a string instead of a - byte sequence. *) + byte sequence. + @since 4.02.0 *) (** {6 Socket options} *) diff --git a/otherlibs/unix/unixLabels.mli b/otherlibs/unix/unixLabels.mli index 5a6c80cfd..b65e8b12d 100644 --- a/otherlibs/unix/unixLabels.mli +++ b/otherlibs/unix/unixLabels.mli @@ -284,12 +284,14 @@ val single_write : file_descr -> buf:bytes -> pos:int -> len:int -> int val write_substring : file_descr -> buf:string -> pos:int -> len:int -> int (** Same as [write], but take the data from a string instead of a byte - sequence. *) + sequence. + @since 4.02.0 *) val single_write_substring : file_descr -> buf:string -> pos:int -> len:int -> int (** Same as [single_write], but take the data from a string instead of - a byte sequence. *) + a byte sequence. + @since 4.02.0 *) (** {6 Interfacing with the standard input/output library} *) @@ -630,7 +632,8 @@ val has_symlink : unit -> bool (** Returns [true] if the user is able to create symbolic links. On Windows, this indicates that the user not only has the SeCreateSymbolicLinkPrivilege but is also running elevated, if necessary. On other platforms, this is - simply indicates that the symlink system call is available. *) + simply indicates that the symlink system call is available. + @since 4.03.0 *) val readlink : string -> string (** Read the contents of a link. *) @@ -1035,7 +1038,8 @@ val send : val send_substring : file_descr -> buf:string -> pos:int -> len:int -> mode:msg_flag list -> int (** Same as [send], but take the data from a string instead of a byte - sequence. *) + sequence. + @since 4.02.0 *) val sendto : file_descr -> buf:bytes -> pos:int -> len:int -> mode:msg_flag list -> @@ -1046,7 +1050,8 @@ val sendto_substring : file_descr -> buf:string -> pos:int -> len:int -> mode:msg_flag list -> sockaddr -> int (** Same as [sendto], but take the data from a string instead of a - byte sequence. *) + byte sequence. + @since 4.02.0 *) diff --git a/stdlib/arg.mli b/stdlib/arg.mli index 789f48343..e7d942ede 100644 --- a/stdlib/arg.mli +++ b/stdlib/arg.mli @@ -110,6 +110,7 @@ val parse_dynamic : is to parse command lines of the form: - command subcommand [options] where the list of options depends on the value of the subcommand argument. + @since 4.01.0 *) val parse_argv : ?current: int ref -> string array -> @@ -130,6 +131,7 @@ val parse_argv_dynamic : ?current:int ref -> string array -> (** Same as {!Arg.parse_argv}, except that the [speclist] argument is a reference and may be updated during the parsing. See {!Arg.parse_dynamic}. + @since 4.01.0 *) val parse_and_expand_argv_dynamic : int ref -> string array ref -> @@ -137,12 +139,14 @@ val parse_and_expand_argv_dynamic : int ref -> string array ref -> (** Same as {!Arg.parse_argv_dynamic}, except that the [argv] argument is a reference and may be updated during the parsing of [Expand] arguments. See {!Arg.parse_argv_dynamic}. + @since 4.05.0 *) val parse_expand: (key * spec * doc) list -> anon_fun -> usage_msg -> unit (** Same as {!Arg.parse}, except that the [Expand] arguments are allowed and the {!current} reference is not updated. + @since 4.05.0 *) exception Help of string @@ -182,17 +186,22 @@ val current : int ref val read_arg: string -> string array (** [Arg.read_arg file] reads newline-terminated command line arguments from - file [file]. *) + file [file]. + @since 4.05.0 *) val read_arg0: string -> string array (** Identical to {!Arg.read_arg} but assumes null character terminated command line - arguments. *) + arguments. + @since 4.05.0 *) + val write_arg: string -> string array -> unit (** [Arg.write_arg file args] writes the arguments [args] newline-terminated into the file [file]. If the any of the arguments in [args] contains a - newline, use {!Arg.write_arg0} instead. *) + newline, use {!Arg.write_arg0} instead. + @since 4.05.0 *) val write_arg0: string -> string array -> unit (** Identical to {!Arg.write_arg} but uses the null character for terminator - instead of newline. *) + instead of newline. + @since 4.05.0 *) diff --git a/stdlib/arrayLabels.mli b/stdlib/arrayLabels.mli index 546c40fa7..868f73a57 100644 --- a/stdlib/arrayLabels.mli +++ b/stdlib/arrayLabels.mli @@ -165,14 +165,14 @@ val iter2 : f:('a -> 'b -> unit) -> 'a array -> 'b array -> unit (** [Array.iter2 f a b] applies function [f] to all the elements of [a] and [b]. Raise [Invalid_argument] if the arrays are not the same size. - @since 4.03.0 *) + @since 4.05.0 *) val map2 : f:('a -> 'b -> 'c) -> 'a array -> 'b array -> 'c array (** [Array.map2 f a b] applies function [f] to all the elements of [a] and [b], and builds an array with the results returned by [f]: [[| f a.(0) b.(0); ...; f a.(Array.length a - 1) b.(Array.length b - 1)|]]. Raise [Invalid_argument] if the arrays are not the same size. - @since 4.03.0 *) + @since 4.05.0 *) (** {6 Array scanning} *) @@ -181,20 +181,24 @@ val map2 : f:('a -> 'b -> 'c) -> 'a array -> 'b array -> 'c array val exists : f:('a -> bool) -> 'a array -> bool (** [Array.exists p [|a1; ...; an|]] checks if at least one element of the array satisfies the predicate [p]. That is, it returns - [(p a1) || (p a2) || ... || (p an)]. *) + [(p a1) || (p a2) || ... || (p an)]. + @since 4.03.0 *) val for_all : f:('a -> bool) -> 'a array -> bool (** [Array.for_all p [|a1; ...; an|]] checks if all elements of the array satisfy the predicate [p]. That is, it returns - [(p a1) && (p a2) && ... && (p an)]. *) + [(p a1) && (p a2) && ... && (p an)]. + @since 4.03.0 *) val mem : 'a -> set:'a array -> bool (** [mem x a] is true if and only if [x] is equal - to an element of [a]. *) + to an element of [a]. + @since 4.03.0 *) val memq : 'a -> set:'a array -> bool (** Same as {!Array.mem}, but uses physical equality instead of structural - equality to compare list elements. *) + equality to compare list elements. + @since 4.03.0 *) external create_float: int -> float array = "caml_make_float_vect" (** [Array.create_float n] returns a fresh float array of length [n], diff --git a/stdlib/buffer.mli b/stdlib/buffer.mli index 37a72acfa..71d87970e 100644 --- a/stdlib/buffer.mli +++ b/stdlib/buffer.mli @@ -135,4 +135,5 @@ val output_buffer : out_channel -> t -> unit val truncate : t -> int -> unit (** [truncate b len] truncates the length of [b] to [len] Note: the internal byte sequence is not shortened. - Raise [Invalid_argument] if [len < 0] or [len > length b]. *) + Raise [Invalid_argument] if [len < 0] or [len > length b]. + @since 4.05.0 *) diff --git a/stdlib/bytesLabels.mli b/stdlib/bytesLabels.mli index 7dacca88e..8c061fc69 100644 --- a/stdlib/bytesLabels.mli +++ b/stdlib/bytesLabels.mli @@ -84,7 +84,8 @@ val extend : bytes -> left:int -> right:int -> bytes the corresponding side of [s]. Raise [Invalid_argument] if the result length is negative or - longer than {!Sys.max_string_length} bytes. *) + longer than {!Sys.max_string_length} bytes. + @since 4.05.0 *) val fill : bytes -> pos:int -> len:int -> char -> unit (** [fill s start len c] modifies [s] in place, replacing [len] @@ -115,7 +116,8 @@ val blit_string : Raise [Invalid_argument] if [srcoff] and [len] do not designate a valid range of [src], or if [dstoff] and [len] - do not designate a valid range of [dst]. *) + do not designate a valid range of [dst]. + @since 4.05.0 *) val concat : sep:bytes -> bytes list -> bytes (** [concat sep sl] concatenates the list of byte sequences [sl], @@ -127,7 +129,8 @@ val cat : bytes -> bytes -> bytes as new byte sequence. Raise [Invalid_argument] if the result is longer than - {!Sys.max_string_length} bytes. *) + {!Sys.max_string_length} bytes. + @since 4.05.0 *) val iter : f:(char -> unit) -> bytes -> unit (** [iter f s] applies function [f] in turn to all the bytes of [s]. @@ -259,22 +262,22 @@ val uncapitalize : bytes -> bytes val uppercase_ascii : bytes -> bytes (** Return a copy of the argument, with all lowercase letters translated to uppercase, using the US-ASCII character set. - @since 4.03.0 *) + @since 4.05.0 *) val lowercase_ascii : bytes -> bytes (** Return a copy of the argument, with all uppercase letters translated to lowercase, using the US-ASCII character set. - @since 4.03.0 *) + @since 4.05.0 *) val capitalize_ascii : bytes -> bytes (** Return a copy of the argument, with the first character set to uppercase, using the US-ASCII character set. - @since 4.03.0 *) + @since 4.05.0 *) val uncapitalize_ascii : bytes -> bytes (** Return a copy of the argument, with the first character set to lowercase, using the US-ASCII character set. - @since 4.03.0 *) + @since 4.05.0 *) type t = bytes (** An alias for the type of byte sequences. *) @@ -287,7 +290,7 @@ val compare: t -> t -> int val equal: t -> t -> bool (** The equality function for byte sequences. - @since 4.03.0 *) + @since 4.05.0 *) (**/**) diff --git a/stdlib/ephemeron.mli b/stdlib/ephemeron.mli index 5f326ed69..3eecfd0e0 100644 --- a/stdlib/ephemeron.mli +++ b/stdlib/ephemeron.mli @@ -64,6 +64,7 @@ Ephemerons are defined in a language agnostic way in this paper: B. Hayes, Ephemerons: a New Finalization Mechanism, OOPSLA'9 + @since 4.03.0 *) module type S = sig diff --git a/stdlib/format.mli b/stdlib/format.mli index 0a504a68e..7ff5fda2c 100644 --- a/stdlib/format.mli +++ b/stdlib/format.mli @@ -387,7 +387,7 @@ type formatter_out_functions = { out_flush : unit -> unit; out_newline : unit -> unit; out_spaces : int -> unit; -} +} (** @since 4.01.0 *) val set_formatter_out_functions : formatter_out_functions -> unit (** [set_formatter_out_functions f] @@ -404,12 +404,14 @@ val set_formatter_out_functions : formatter_out_functions -> unit application at hand). The two functions [f.out_spaces] and [f.out_newline] are normally connected to [f.out_string] and [f.out_flush]: respective default values for [f.out_space] and [f.out_newline] are - [f.out_string (String.make n ' ') 0 n] and [f.out_string "\n" 0 1]. *) + [f.out_string (String.make n ' ') 0 n] and [f.out_string "\n" 0 1]. + @since 4.01.0 *) val get_formatter_out_functions : unit -> formatter_out_functions (** Return the current output functions of the pretty-printer, including line splitting and indentation functions. Useful to record the - current setting and restore it afterwards. *) + current setting and restore it afterwards. + @since 4.01.0 *) (** {6:tagsmeaning Changing the meaning of printing semantic tags} *) @@ -557,13 +559,15 @@ val pp_get_formatter_tag_functions : val pp_set_formatter_out_functions : formatter -> formatter_out_functions -> unit +(** @since 4.01.0 *) val pp_get_formatter_out_functions : formatter -> unit -> formatter_out_functions (** These functions are the basic ones: usual functions operating on the standard formatter are defined via partial evaluation of these primitives. For instance, - [print_string] is equal to [pp_print_string std_formatter]. *) + [print_string] is equal to [pp_print_string std_formatter]. + @since 4.01.0 *) val pp_flush_formatter : formatter -> unit (** [pp_flush_formatter fmt] flushes [fmt]'s internal queue, ensuring that all @@ -571,7 +575,8 @@ val pp_flush_formatter : formatter -> unit operation will close all boxes and reset the state of the formatter. This will not flush [fmt]'s output. In most cases, the user may want to use - {!pp_print_flush} instead. *) + {!pp_print_flush} instead. + @since 4.04.0 *) (** {6 Convenience formatting functions.} *) diff --git a/stdlib/hashtbl.mli b/stdlib/hashtbl.mli index a5666b150..d3c0ef3e3 100644 --- a/stdlib/hashtbl.mli +++ b/stdlib/hashtbl.mli @@ -193,8 +193,9 @@ val randomize : unit -> unit val is_randomized : unit -> bool (** return if the tables are currently created in randomized mode by default - @since 4.02.0 *) + @since 4.03.0 *) +(** @since 4.00.0 *) type statistics = { num_bindings: int; (** Number of bindings present in the table. @@ -276,20 +277,25 @@ module type S = type 'a t val create : int -> 'a t val clear : 'a t -> unit - val reset : 'a t -> unit + val reset : 'a t -> unit (** @since 4.00.0 *) + val copy : 'a t -> 'a t val add : 'a t -> key -> 'a -> unit val remove : 'a t -> key -> unit val find : 'a t -> key -> 'a val find_opt : 'a t -> key -> 'a option + (** @since 4.05.0 *) + val find_all : 'a t -> key -> 'a list val replace : 'a t -> key -> 'a -> unit val mem : 'a t -> key -> bool val iter : (key -> 'a -> unit) -> 'a t -> unit val filter_map_inplace: (key -> 'a -> 'a option) -> 'a t -> unit + (** @since 4.03.0 *) + val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b val length : 'a t -> int - val stats: 'a t -> statistics + val stats: 'a t -> statistics (** @since 4.00.0 *) end (** The output signature of the functor {!Hashtbl.Make}. *) @@ -334,12 +340,15 @@ module type SeededS = val add : 'a t -> key -> 'a -> unit val remove : 'a t -> key -> unit val find : 'a t -> key -> 'a - val find_opt : 'a t -> key -> 'a option + val find_opt : 'a t -> key -> 'a option (** @since 4.05.0 *) + val find_all : 'a t -> key -> 'a list val replace : 'a t -> key -> 'a -> unit val mem : 'a t -> key -> bool val iter : (key -> 'a -> unit) -> 'a t -> unit val filter_map_inplace: (key -> 'a -> 'a option) -> 'a t -> unit + (** @since 4.03.0 *) + val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b val length : 'a t -> int val stats: 'a t -> statistics diff --git a/stdlib/listLabels.mli b/stdlib/listLabels.mli index 8976b7170..52ded3f95 100644 --- a/stdlib/listLabels.mli +++ b/stdlib/listLabels.mli @@ -49,7 +49,7 @@ val compare_length_with : 'a list -> len:int -> int val cons : 'a -> 'a list -> 'a list (** [cons x xs] is [x :: xs] - @since 4.03.0 + @since 4.05.0 *) val tl : 'a list -> 'a list @@ -261,7 +261,8 @@ val assq : 'a -> ('a * 'b) list -> 'b val assq_opt: 'a -> ('a * 'b) list -> 'b option (** Same as {!List.assoc_opt}, but uses physical equality instead of - structural equality to compare keys. *) + structural equality to compare keys. + @since 4.05.0 *) val mem_assoc : 'a -> map:('a * 'b) list -> bool (** Same as {!List.assoc}, but simply return true if a binding exists, @@ -332,7 +333,7 @@ val fast_sort : cmp:('a -> 'a -> int) -> 'a list -> 'a list val sort_uniq : cmp:('a -> 'a -> int) -> 'a list -> 'a list (** Same as {!List.sort}, but also remove duplicates. - @since 4.02.0 *) + @since 4.03.0 *) val merge : cmp:('a -> 'a -> int) -> 'a list -> 'a list -> 'a list (** Merge two lists: diff --git a/stdlib/pervasives.mli b/stdlib/pervasives.mli index 55b0fef73..7e829ba94 100644 --- a/stdlib/pervasives.mli +++ b/stdlib/pervasives.mli @@ -743,7 +743,8 @@ val read_float_opt: unit -> float option (** Flush standard output, then read one line from standard input and convert it to a floating-point number. Returns [None] if the line read is not a valid - representation of a floating-point number. *) + representation of a floating-point number. + @since 4.05.0 *) (** {7 General output functions} *) @@ -1032,6 +1033,7 @@ external decr : int ref -> unit = "%decr" (** {6 Result type} *) +(** @since 4.03.0 *) type ('a,'b) result = Ok of 'a | Error of 'b (** {6 Operations on format strings} *) diff --git a/stdlib/printexc.mli b/stdlib/printexc.mli index bd8e86f7e..310022d6c 100644 --- a/stdlib/printexc.mli +++ b/stdlib/printexc.mli @@ -137,7 +137,7 @@ external raise_with_backtrace: exn -> raw_backtrace -> 'a (** Reraise the exception using the given raw_backtrace for the origin of the exception - @since 4.03.0 + @since 4.05.0 *) (** {6 Current call stack} *) @@ -215,6 +215,7 @@ type location = { @since 4.02 *) +(** @since 4.02.0 *) module Slot : sig type t = backtrace_slot diff --git a/stdlib/printf.mli b/stdlib/printf.mli index c10f0c6c7..92a3b16ea 100644 --- a/stdlib/printf.mli +++ b/stdlib/printf.mli @@ -150,7 +150,7 @@ val kfprintf : (out_channel -> 'd) -> out_channel -> val ikfprintf : ('b -> 'd) -> 'b -> ('a, 'b, 'c, 'd) format4 -> 'a (** Same as [kfprintf] above, but does not print anything. Useful to ignore some material when conditionally printing. - @since 4.0 + @since 4.01.0 *) val ksprintf : (string -> 'd) -> ('a, unit, string, 'd) format4 -> 'a diff --git a/stdlib/stringLabels.mli b/stdlib/stringLabels.mli index ba09b8a90..6be1b50bf 100644 --- a/stdlib/stringLabels.mli +++ b/stdlib/stringLabels.mli @@ -53,7 +53,8 @@ val init : int -> f:(int -> char) -> string (** [init n f] returns a string of length [n], with character [i] initialized to the result of [f i]. - Raise [Invalid_argument] if [n < 0] or [n > ]{!Sys.max_string_length}. *) + Raise [Invalid_argument] if [n < 0] or [n > ]{!Sys.max_string_length}. + @since 4.02.0 *) val copy : string -> string (** Return a copy of the given string. *) @@ -242,22 +243,22 @@ val uncapitalize : string -> string val uppercase_ascii : string -> string (** Return a copy of the argument, with all lowercase letters translated to uppercase, using the US-ASCII character set. - @since 4.03.0 *) + @since 4.05.0 *) val lowercase_ascii : string -> string (** Return a copy of the argument, with all uppercase letters translated to lowercase, using the US-ASCII character set. - @since 4.03.0 *) + @since 4.05.0 *) val capitalize_ascii : string -> string (** Return a copy of the argument, with the first character set to uppercase, using the US-ASCII character set. - @since 4.03.0 *) + @since 4.05.0 *) val uncapitalize_ascii : string -> string (** Return a copy of the argument, with the first character set to lowercase, using the US-ASCII character set. - @since 4.03.0 *) + @since 4.05.0 *) type t = string (** An alias for the type of strings. *) @@ -270,7 +271,7 @@ val compare: t -> t -> int val equal: t -> t -> bool (** The equal function for strings. - @since 4.03.0 *) + @since 4.05.0 *) val split_on_char: sep:char -> string -> string list (** [String.split_on_char sep s] returns the list of all (possibly empty) @@ -284,7 +285,7 @@ val split_on_char: sep:char -> string -> string list (String.split_on_char sep s) = s]). - No string in the result contains the [sep] character. - @since 4.04.0 + @since 4.05.0 *) (**/**) diff --git a/stdlib/sys.mli b/stdlib/sys.mli index 1461c1250..2359d41b8 100644 --- a/stdlib/sys.mli +++ b/stdlib/sys.mli @@ -105,7 +105,7 @@ type backend_type = val backend_type : backend_type (** Backend type currently executing the OCaml program. - @ since 4.04.0 + @since 4.04.0 *) val unix : bool From d1cd849d3fcce456e3d457a2b54eb33f85056279 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?T=C3=B6r=C3=B6k=20Edwin?= Date: Fri, 9 Dec 2016 00:57:31 +0200 Subject: [PATCH 2/2] Documentation tool: add tools/lintapidiff.ml Run 'make lintapidiff' in the root of a git checkout to get a list of potentially missing or wrong @since annotations. The tool is not built by default, you have to first run 'make world.opt', and then run 'make lintapidiff'. lintapidiff doesn't support stop comments: add explicit list of changes to ignore. see copyright header for license. --- Changes | 5 + Makefile | 14 ++ tools/Makefile | 15 +++ tools/lintapidiff.ml | 313 +++++++++++++++++++++++++++++++++++++++++++ 4 files changed, 347 insertions(+) create mode 100644 tools/lintapidiff.ml diff --git a/Changes b/Changes index db3f90bfd..6f2d29675 100644 --- a/Changes +++ b/Changes @@ -139,6 +139,11 @@ Next version (4.05.0): that extend non-terminal symbols in the language reference section. (Florian Angeletti, review by Gabriel Scherer) +- GPR#916: new tool lintapidiff, use it to update the manual with + @since annotations for API changes introduced between 4.00-4.05. + (Edwin Török, review by Gabriel Scherer, discussion with Alain Frisch, + David Allsopp, Sébastien Hinderer, Damien Doligez and Xavier Leroy) + - GPR#939: activate the caml_example environment in the language extensions section of the manual. Convert some existing code examples to this format. diff --git a/Makefile b/Makefile index 86e8752a6..0b2a398fd 100644 --- a/Makefile +++ b/Makefile @@ -1081,6 +1081,20 @@ checkstack: rm -f tools/checkstack$(EXE) endif +# Lint @since and @deprecated annotations + +.PHONY: lintapidiff +lintapidiff: + $(MAKE) -C tools lintapidiff.opt + git ls-files -- 'otherlibs/*/*.mli' 'stdlib/*.mli' |\ + grep -Ev internal\|obj\|spacetime\|stdLabels\|moreLabels |\ + tools/lintapidiff.opt $(shell git tag|grep '^[0-9]*.[0-9]*.[0-9]*$$'|grep -v '^[12].') + +# Make clean in the test suite + +clean:: + cd testsuite; $(MAKE) clean + # Make MacOS X package ifeq "$(UNIX_OR_WIN32)" "unix" .PHONY: package-macosx diff --git a/tools/Makefile b/tools/Makefile index 466382ecb..d997f49d7 100644 --- a/tools/Makefile +++ b/tools/Makefile @@ -338,6 +338,21 @@ install:: # Scan object files for required primitives $(call byte_and_opt,primreq,config.cmo primreq.cmo,) +LINTAPIDIFF=../compilerlibs/ocamlcommon.cmxa \ + ../compilerlibs/ocamlbytecomp.cmxa \ + ../compilerlibs/ocamlmiddleend.cmxa \ + ../asmcomp/printclambda.cmx \ + ../asmcomp/export_info.cmx \ + ../otherlibs/str/str.cmxa \ + lintapidiff.cmx + +lintapidiff.opt: INCLUDES+= -I ../otherlibs/str +lintapidiff.opt: $(LINTAPIDIFF) + $(CAMLOPT) $(LINKFLAGS) -I .. -o $@ $(LINTAPIDIFF) +clean:: + rm -f -- lintapidiff.opt lintapidiff.cm? lintapidiff.o + + clean:: rm -f "objinfo_helper$(EXE)" "objinfo_helper$(EXE).manifest" diff --git a/tools/lintapidiff.ml b/tools/lintapidiff.ml new file mode 100644 index 000000000..87cf1d4b7 --- /dev/null +++ b/tools/lintapidiff.ml @@ -0,0 +1,313 @@ +(**************************************************************************) +(* *) +(* OCaml *) +(* *) +(* Copyright 2016--2017 Edwin Török *) +(* *) +(* All rights reserved. This file is distributed under the terms of *) +(* the GNU Lesser General Public License version 2.1, with the *) +(* special exception on linking described in the file LICENSE. *) +(* *) +(**************************************************************************) + +(* Detects newly added symbols that are missing "@since" annotations, + or removed symbols that didn't have "@deprecated" annotation before. + + Handles: values, exceptions. + Ignores: variants, record fields, classes, module aliasing or includes, ... + Out of scope: changes in arity, parameters, ... + + Missing attributes on undocumented identifiers in undocumented modules + are not reported. + + Use 'make lintapidiff' in the root directory to run +*) +open Location +open Parsetree + +(* oldest Ocaml version that we show missing @since errors for *) +let oldest = "4.00.0" + +(* do not check @since annotations for these *) +let ignore_changes_for = [ + "type Pervasives.format6" (* this used to be a built-in type *); + (* discarded by stop comments: *) + "type Unix.map_file_impl"; + "value Unix.map_file_impl"; +] + +module IdMap = Map.Make(String) + +module Version : sig + type t + val oldest : t + val is_same : t -> t -> bool + val is_strictly_older: t -> than:t -> bool + val of_string_exn : string -> t + val pp : Format.formatter -> t -> unit +end = struct + type t = int * int * int + + let is_same a b = a = b + let is_strictly_older a ~than = a < than + let of_string_exn str = + try Scanf.sscanf str "%u.%u.%u" (fun a b c -> (a,b,c)) + with _ -> Scanf.sscanf str "%u.%u" (fun a b -> (a,b,0)) + + let oldest = of_string_exn oldest + let pp ppf (major,minor,patch) = + Format.fprintf ppf "%u.%02u.%u" major minor patch +end + +module Doc = struct + type t = { + since: Version.t option; + deprecated: bool; + loc: Location.t; + has_doc_parent: bool; + has_doc: bool; + } + + let empty = {since = None; deprecated=false; loc=Location.none; + has_doc_parent=false;has_doc=false} + + let since = Str.regexp "\\(.\\|\n\\)*@since +\\([^ ]+\\).*" + + let find_attr lst attrs = + try Some (List.find (fun (loc, _) -> List.mem loc.txt lst) attrs) + with Not_found -> None + + let get_doc lst attrs = match find_attr lst attrs with + | Some (_, PStr [{pstr_desc=Pstr_eval( + {pexp_desc=Pexp_constant(Pconst_string (doc, _));_}, _);_}]) + when doc <> "/*" && doc <> "" -> Some doc + | _ -> None + + let is_deprecated attrs = + find_attr ["ocaml.deprecated"; "deprecated"] attrs <> None || + match get_doc ["ocaml.text"] attrs with (* for toplevel module annotation *) + | None -> false + | Some text -> + try Misc.search_substring "@deprecated" text 0 >= 0 + with Not_found -> false + + let get parent_info loc attrs = + let doc = get_doc ["ocaml.doc"; "ocaml.text"] attrs in + { + since = (match doc with + | Some doc -> + if Str.string_match since doc 0 then + Some (Str.matched_group 2 doc |> String.trim + |> Version.of_string_exn) + else parent_info.since + | None -> parent_info.since); + deprecated = parent_info.deprecated || is_deprecated attrs; + loc; + has_doc_parent = parent_info.has_doc_parent || parent_info.has_doc; + has_doc = doc <> None + } +end + +module Ast = struct + let add_path ~f prefix path name attrs inherits map = + let path = Path.Pdot (path, name.txt, 0) in + let id = prefix ^ " " ^ (Printtyp.string_of_path path) in + (* inherits: annotation on parent is inherited by all children, + so it suffices to annotate just the new module, and not all its elements + *) + let info = f inherits name.loc attrs in + IdMap.add id info map + + let rec add_item ~f path inherits map item = + let rec add_module_type path ty (inherits, map) = + let self = add_item ~f path inherits in + match ty.pmty_desc with + | Pmty_signature lst -> List.fold_left self map lst + | Pmty_functor ({txt;_}, _, m) -> + let path = Path.Papply(path, Path.Pident (Ident.create txt)) in + add_module_type path m (inherits, map) + | Pmty_ident _ | Pmty_with _ | Pmty_typeof _| Pmty_extension _ + | Pmty_alias _ -> map + in + let enter_path path name ty attrs map = + let path = Path.Pdot (path, name.txt, 0) in + let inherits = f inherits name.loc attrs in + add_module_type path ty (inherits, map) + in + let add_module map m = + enter_path path m.pmd_name m.pmd_type m.pmd_attributes map + in + match item.psig_desc with + | Psig_value vd -> + add_path ~f "value" path vd.pval_name vd.pval_attributes inherits map + | Psig_type (_,lst) -> + List.fold_left (fun map t -> + add_path ~f "type" path t.ptype_name t.ptype_attributes inherits map + ) map lst + | Psig_exception e -> + add_path ~f "exception" path e.pext_name e.pext_attributes inherits map + | Psig_module m -> add_module map m + | Psig_recmodule lst -> List.fold_left add_module map lst + | Psig_modtype s -> + begin match s.pmtd_type with + | None -> map + | Some ty -> + enter_path path s.pmtd_name ty s.pmtd_attributes map + end + | Psig_typext _|Psig_open _|Psig_include _|Psig_class _|Psig_class_type _ + | Psig_attribute _|Psig_extension _ -> map + + let add_items ~f path (inherits,map) items = + (* module doc *) + let inherits = List.fold_left (fun inherits -> function + | {psig_desc=Psig_attribute a;_} + when (Doc.get_doc ["ocaml.doc";"ocaml.text"][a] <> None) -> + f inherits (Location.none) [a] + | _ -> inherits + ) inherits items in + List.fold_left (add_item ~f path inherits) map items + + let parse_file ~orig ~f ~init input = + try + let id = + orig |> Filename.chop_extension |> Filename.basename |> + String.capitalize_ascii |> Ident.create in + let ast = Pparse.file ~tool_name:"lintapidiff" Format.err_formatter input + Parse.interface Pparse.Signature in + Location.input_name := orig; + add_items ~f (Path.Pident id) (init,IdMap.empty) ast + with e -> + Format.eprintf "%a@." Location.report_exception e; + raise e +end + +module Git = struct + let with_show ~f rev path = + let obj = rev ^ ":" ^ path in + let suffix = Printf.sprintf "-%s:%s" rev (Filename.basename path) in + let tmp = Filename.temp_file "lintapidiff" suffix in + let cmd = Printf.sprintf "git show %s >%s 2>/dev/null" + (Filename.quote obj) (Filename.quote tmp) in + Misc.try_finally (fun () -> + match Sys.command cmd with + | 0 -> Ok (f tmp) + | 128 -> Error `Not_found + | r -> + Location.errorf ~loc:(in_file obj) "exited with code %d" r |> + Format.eprintf "%a@." Location.report_error; + Error `Exit) + (fun () -> Misc.remove_file tmp) +end + +module Diff = struct + type seen_info = { + last_not_seen: Version.t option; + first_seen: Version.t; + deprecated: bool; + } + + let err k (loc, msg, seen, latest) = + let info_seen ppf = function + | None -> + Format.fprintf ppf "%s was not seen in any analyzed version" k + | Some a -> + begin match a.last_not_seen with + | Some v -> + Format.fprintf ppf "%s was not seen in version %a" k Version.pp v + | None -> Format.fprintf ppf "%s was seen in all analyzed versions" k + end; + Format.fprintf ppf "@,%s was seen in version %a" + k Version.pp a.first_seen; + if a.deprecated then + Format.fprintf ppf "@,%s was marked as deprecated" k + in + let info_latest ppf = function + | None -> Format.fprintf ppf "%s was deleted in HEAD" k + | Some s -> + begin match s.Doc.since with + | Some v -> Format.fprintf ppf "%s has @since %a" k Version.pp v + | None -> Format.fprintf ppf "%s has no @since annotation" k + end; + if s.Doc.deprecated then + Format.fprintf ppf "@,%s is marked as deprecated" k + in + Location.errorf ~loc "@[%s %s@,%a@,%a@]" msg k + info_seen seen info_latest latest |> + Format.eprintf "%a@." Location.report_error + + let parse_file_at_rev ~path (prev,accum) rev = + let merge _ a b = match a, b with + | Some a, Some b -> + Some { a with deprecated=b.deprecated } + | None, Some a -> Some { a with last_not_seen=prev } + | Some _, None -> None (* deleted *) + | None, None -> assert false + in + let first_seen = Version.of_string_exn rev in + let empty = {last_not_seen=None;first_seen;deprecated=false} in + let f = Ast.parse_file ~orig:path ~init:empty ~f:(fun _ _ attrs -> + { last_not_seen=None;first_seen; deprecated=Doc.is_deprecated attrs }) in + let map = match Git.with_show ~f rev path with + | Ok r -> r + | Error `Not_found -> IdMap.empty + | Error `Exit -> raise Exit in + Some first_seen, IdMap.merge merge accum map + + let check_changes ~first ~last default k seen latest = + let is_old v = Version.is_strictly_older v ~than:Version.oldest || + Version.is_same v first + in + if List.mem k ignore_changes_for then None (* ignored *) + else let open! Doc in + match (seen:seen_info option), latest with + | None, None -> assert false + | _, Some {has_doc_parent=false;has_doc=false;deprecated=false;_} -> + None (* undocumented *) + | Some {deprecated=true;_}, None -> None (* deleted deprecated *) + | Some _, None -> + Some (default, "deleted non-deprecated", seen, latest) + | _, Some {deprecated=true;since=None;_} -> None (* marked as deprecated *) + | None, Some {loc; since=None; _} -> + Some (loc, "missing @since for new", seen, latest) + | Some {first_seen;_}, Some {loc; since=None;_} -> + if is_old first_seen then None + else Some (loc, "missing @since", seen, latest) + | Some {first_seen;_}, Some {loc; since=Some s;_} -> + if Version.is_same first_seen s then None (* OK, @since matches *) + else Some (loc, "mismatched @since", seen, latest) + | None, Some {loc; since=Some s;_} -> + if Version.is_strictly_older s ~than:last || + Version.is_same s last then + Some (loc, "too old @since for new", seen, latest) + else None + + let file path tags = + let _,syms_vers = List.fold_left (parse_file_at_rev ~path) + (None,IdMap.empty) tags in + let current = Ast.parse_file ~orig:path ~f:Doc.get ~init:Doc.empty path in + let loc = Location.in_file path in + let first = List.hd tags |> Version.of_string_exn + and last = List.hd (List.rev tags) |> Version.of_string_exn in + IdMap.merge (check_changes ~first ~last loc) syms_vers current +end + +let rec read_lines accum = + match input_line stdin with + | line -> read_lines (line :: accum) + | exception End_of_file -> accum + +let () = + let tags = Sys.argv |> Array.to_list |> List.tl in + if tags = [] then begin + Printf.eprintf "tags list is empty!\n"; + exit 1; + end; + let paths = read_lines [] in + Printf.printf "Parsing\n%!"; + let count = List.fold_left (fun count path -> + let problems = Diff.file path tags in + IdMap.iter Diff.err problems; + count + IdMap.cardinal problems + ) 0 paths in + Printf.printf "Found %d potential problems\n%!" count; + if count > 0 then exit 2