Fix label warnings

master
John Whitington 2020-07-31 15:51:11 +01:00
parent a5ed794b4c
commit 1c258b463f
10 changed files with 31 additions and 27 deletions

View File

@ -722,7 +722,8 @@ class virtual info =
Buffer.add_string b (f text)
with
Not_found ->
Odoc_info.warning (Odoc_messages.tag_not_handled tag)
if not (String.ends_with ~suffix:"nowarn" tag) then
Odoc_info.warning (Odoc_messages.tag_not_handled tag)
)
l

View File

@ -188,7 +188,8 @@ class virtual info =
(Buffer.contents buf) :: acc
with
Not_found ->
Odoc_info.warning (Odoc_messages.tag_not_handled tag);
if not (String.ends_with ~suffix:"nowarn" tag) then
Odoc_info.warning (Odoc_messages.tag_not_handled tag);
acc
)
[] l

View File

@ -517,7 +517,8 @@ class texi =
( linebreak :: (f text) @ [ Newline ] ) :: acc
with
Not_found ->
Odoc_info.warning (Odoc_messages.tag_not_handled tag) ;
if not (String.ends_with ~suffix:"nowarn" tag) then
Odoc_info.warning (Odoc_messages.tag_not_handled tag) ;
acc
) [] c_l))

View File

@ -138,7 +138,8 @@ class virtual info =
| _ -> acc @ (Newline :: (f text))
with
Not_found ->
Odoc_info.warning (Odoc_messages.tag_not_handled tag) ;
if not (String.ends_with ~suffix:"nowarn" tag) then
Odoc_info.warning (Odoc_messages.tag_not_handled tag) ;
acc
)
[]

View File

@ -151,7 +151,7 @@ val unsafe_environment : unit -> string array
details.
@since 4.12.0
@sinceunlabeled 4.06.0 *)
@sinceunlabelednowarn 4.06.0 *)
val getenv : string -> string
(** Return the value associated to a variable in the process
@ -333,7 +333,7 @@ val fsync : file_descr -> unit
(** Flush file buffers to disk.
@since 4.12.0
@sinceunlabeled 4.08.0 *)
@sinceunlabelednowarn 4.08.0 *)
val read : file_descr -> buf:bytes -> pos:int -> len:int -> int
(** [read fd ~buf ~pos ~len] reads [len] bytes from descriptor [fd],
@ -893,28 +893,28 @@ val process_in_pid : in_channel -> int
{!open_process_args_in}.
@since 4.12.0
@sinceunlabeled 4.08.0 *)
@sinceunlabelednowarn 4.08.0 *)
val process_out_pid : out_channel -> int
(** Return the pid of a process opened via {!open_process_out} or
{!open_process_args_out}.
@since 4.12.0
@sinceunlabeled 4.08.0 *)
@sinceunlabelednowarn 4.08.0 *)
val process_pid : in_channel * out_channel -> int
(** Return the pid of a process opened via {!open_process} or
{!open_process_args}.
@since 4.12.0
@sinceunlabeled 4.08.0 *)
@sinceunlabelednowarn 4.08.0 *)
val process_full_pid : in_channel * out_channel * in_channel -> int
(** Return the pid of a process opened via {!open_process_full} or
{!open_process_args_full}.
@since 4.12.0
@sinceunlabeled 4.08.0 *)
@sinceunlabelednowarn 4.08.0 *)
val close_process_in : in_channel -> process_status
(** Close channels opened by {!open_process_in},
@ -1161,7 +1161,7 @@ val sleepf : float -> unit
but fractions of seconds are supported.
@since 4.03.0
@sinceunlabeled 4.12.0 *)
@sinceunlabelednowarn 4.12.0 *)
val times : unit -> process_times
(** Return the execution times of the process.

View File

@ -203,7 +203,7 @@ val iter2 : f:('a -> 'b -> unit) -> 'a array -> 'b array -> unit
and [b].
@raise Invalid_argument if the arrays are not the same size.
@since 4.05.0
@sinceunlabeled 4.03.0
@sinceunlabelednowarn 4.03.0
*)
val map2 : f:('a -> 'b -> 'c) -> 'a array -> 'b array -> 'c array
@ -212,7 +212,7 @@ val map2 : f:('a -> 'b -> 'c) -> 'a array -> 'b array -> 'c array
[[| f a.(0) b.(0); ...; f a.(length a - 1) b.(length b - 1)|]].
@raise Invalid_argument if the arrays are not the same size.
@since 4.05.0
@sinceunlabeled 4.03.0 *)
@sinceunlabelednowarn 4.03.0 *)
(** {1 Array scanning} *)

View File

@ -295,25 +295,25 @@ 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.05.0
@sinceunlabeled 4.03.0 *)
@sinceunlabelednowarn 4.03.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.05.0
@sinceunlabeled 4.03.0 *)
@sinceunlabelednowarn 4.03.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.05.0
@sinceunlabeled 4.03.0 *)
@sinceunlabelednowarn 4.03.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.05.0
@sinceunlabeled 4.03.0 *)
@sinceunlabelednowarn 4.03.0 *)
type t = bytes
(** An alias for the type of byte sequences. *)
@ -327,7 +327,7 @@ val compare: t -> t -> int
val equal: t -> t -> bool
(** The equality function for byte sequences.
@since 4.05.0
@sinceunlabeled 4.03.0 *)
@sinceunlabelednowarn 4.03.0 *)
(** {1:unsafe Unsafe conversions (for advanced users)}

View File

@ -68,7 +68,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.05.0
@sinceunlabeled 4.03.0
@sinceunlabelednowarn 4.03.0
*)
val hd : 'a list -> 'a
@ -436,7 +436,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 {!sort}, but also remove duplicates.
@since 4.03.0
@sinceunlabeled 4.02.0
@sinceunlabelednowarn 4.02.0
*)
val merge : cmp:('a -> 'a -> int) -> 'a list -> 'a list -> 'a list

View File

@ -295,25 +295,25 @@ 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.05.0
@sinceunlabeled 4.03.0 *)
@sinceunlabelednowarn 4.03.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.05.0
@sinceunlabeled 4.03.0 *)
@sinceunlabelednowarn 4.03.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.05.0
@sinceunlabeled 4.03.0 *)
@sinceunlabelednowarn 4.03.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.05.0
@sinceunlabeled 4.03.0 *)
@sinceunlabelednowarn 4.03.0 *)
val starts_with :
prefix (* comment thwarts tools/unlabel *) :string -> string -> bool
@ -338,7 +338,7 @@ val split_on_char: sep:char -> string -> string list
- No string in the result contains the [sep] character.
@since 4.05.0
@sinceunlabeled 4.04.0
@sinceunlabelednowarn 4.04.0
*)
type t = string
@ -353,7 +353,7 @@ val compare: t -> t -> int
val equal: t -> t -> bool
(** The equal function for strings.
@since 4.05.0
@sinceunlabeled 4.03.0 *)
@sinceunlabelednowarn 4.03.0 *)
(** {1 Iterators} *)

View File

@ -35,7 +35,7 @@ LABLABREGEX="s/\([a-z_]+:([a-z\('])/\(\1/g"
TILDEREGEX="s/~([a-z_]*[ \]])/\1/g"
#@sinceunlabeled --> @since
SINCEREGEX="s/sinceunlabeled/since/g"
SINCEREGEX="s/sinceunlabelednowarn/since/g"
#Indent a non-blank line by two characters, for moreLabels templates
INDENTREGEX="s/^(.+)$/ \1/m"