bumped version to 4.00.0 (per Xavier's decision)

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@12212 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Damien Doligez 2012-03-08 22:27:57 +00:00
parent c5ef010a5a
commit 0ed38a9fb1
11 changed files with 50 additions and 38 deletions

View File

@ -1,4 +1,4 @@
3.13.0+dev12 (2012-03-08)
4.00.0+dev13 (2012-03-08)
# The version string is the first line of this file.
# It must be in the format described in stdlib/sys.mli

View File

@ -32,7 +32,8 @@ val compare : t -> t -> int
specification as {!Pervasives.compare} and the implementation
shared with {!String.compare}. Along with the type [t], this
function [compare] allows the module [Digest] to be passed as
argument to the functors {!Set.Make} and {!Map.Make}. *)
argument to the functors {!Set.Make} and {!Map.Make}.
@since 4.00.0 *)
val string : string -> t
(** Return the digest of the given string. *)
@ -65,4 +66,5 @@ val to_hex : t -> string
val from_hex : string -> t
(** Convert a hexadecimal representation back into the corresponding digest.
Raise [Invalid_argument] if the argument is not exactly 32 hexadecimal
characters. *)
characters.
@since 4.00.0 *)

View File

@ -39,7 +39,8 @@ val create : ?seed:int -> int -> ('a, 'b) t
for instance, it is recommended to create hash tables with a
randomly-chosen seed. This prevents a denial-of-service attack
whereas a malicious user sends input crafted to create many
collisions in the table and therefore slow the application down. *)
collisions in the table and therefore slow the application down.
@before 4.00.0 the [seed] parameter was not present. *)
val clear : ('a, 'b) t -> unit
(** Empty a hash table. *)
@ -125,7 +126,7 @@ val stats : ('a, 'b) t -> statistics
(** [Hashtbl.stats tbl] returns statistics about the table [tbl]:
number of buckets, size of the biggest bucket, distribution of
buckets by size.
@since 3.13.0 *)
@since 4.00.0 *)
(** {6 Functorial interface} *)
@ -180,7 +181,7 @@ module Make (H : HashedType) : S with type key = H.t
The operations perform similarly to those of the generic
interface, but use the hashing and equality functions
specified in the functor argument [H] instead of generic
equality and hashing. *)
equality and hashing. *)
module type SeededHashedType =
sig
@ -196,7 +197,7 @@ module type SeededHashedType =
below. *)
end
(** The input signature of the functor {!Hashtbl.MakeSeeded}.
@since 3.13.0 *)
@since 4.00.0 *)
module type SeededS =
sig
@ -217,7 +218,7 @@ module type SeededS =
val stats: 'a t -> statistics
end
(** The output signature of the functor {!Hashtbl.MakeSeeded}.
@since 3.13.0 *)
@since 4.00.0 *)
module MakeSeeded (H : SeededHashedType) : SeededS with type key = H.t
(** Functor building an implementation of the hashtable structure.
@ -228,7 +229,7 @@ module MakeSeeded (H : SeededHashedType) : SeededS with type key = H.t
interface, but use the seeded hashing and equality functions
specified in the functor argument [H] instead of generic
equality and hashing.
@since 3.13.0 *)
@since 4.00.0 *)
(** {6 The polymorphic hash functions} *)
@ -243,7 +244,7 @@ val hash : 'a -> int
val seeded_hash : int -> 'a -> int
(** A variant of {!Hashtbl.hash} that is further parameterized by
an integer seed.
@since 3.13.0 *)
@since 4.00.0 *)
val hash_param : int -> int -> 'a -> int
(** [Hashtbl.hash_param meaningful total x] computes a hash value for [x],
@ -266,4 +267,4 @@ val seeded_hash_param : int -> int -> int -> 'a -> int
(** A variant of {!Hashtbl.hash_param} that is further parameterized by
an integer seed. Usage:
[Hashtbl.seeded_hash_param meaningful total seed x].
@since 3.13.0 *)
@since 4.00.0 *)

View File

@ -63,16 +63,19 @@ val force_val : 'a t -> 'a;;
*)
val from_fun : (unit -> 'a) -> 'a t;;
(** [from_fun f] is the same as [lazy (f ())] but slightly more efficient. *)
(** [from_fun f] is the same as [lazy (f ())] but slightly more efficient.
@since 4.00.0 *)
val from_val : 'a -> 'a t;;
(** [from_val v] returns an already-forced suspension of [v].
This is for special purposes only and should not be confused with
[lazy (v)]. *)
[lazy (v)].
@since 4.00.0 *)
val is_val : 'a t -> bool;;
(** [is_val x] returns [true] if [x] has already been forced and
did not raise an exception. *)
did not raise an exception.
@since 4.00.0 *)
val lazy_from_fun : (unit -> 'a) -> 'a t;;
(** @deprecated synonym for [from_fun]. *)

View File

@ -79,7 +79,7 @@ val iteri : (int -> 'a -> unit) -> 'a list -> unit
(** Same as {!List.iter}, but the function is applied to the index of
the element as first argument (counting from 0), and the element
itself as second argument.
@since 3.13.0
@since 4.00.0
*)
val map : ('a -> 'b) -> 'a list -> 'b list
@ -91,7 +91,7 @@ val mapi : (int -> 'a -> 'b) -> 'a list -> 'b list
(** Same as {!List.map}, but the function is applied to the index of
the element as first argument (counting from 0), and the element
itself as second argument. Not tail-recursive.
@since 3.13.0
@since 4.00.0
*)
val rev_map : ('a -> 'b) -> 'a list -> 'b list

View File

@ -76,10 +76,10 @@ val iter : f:('a -> unit) -> 'a list -> unit
[begin f a1; f a2; ...; f an; () end]. *)
val iteri : f:(int -> 'a -> unit) -> 'a list -> unit
(** Same as {!List.iter}, but the
function is applied to the index of the element as first argument (counting from 0),
and the element itself as second argument.
@since 3.13.0
(** Same as {!List.iter}, but the function is applied to the index of
the element as first argument (counting from 0), and the element
itself as second argument.
@since 4.00.0
*)
val map : f:('a -> 'b) -> 'a list -> 'b list
@ -88,10 +88,10 @@ val map : f:('a -> 'b) -> 'a list -> 'b list
with the results returned by [f]. Not tail-recursive. *)
val mapi : f:(int -> 'a -> 'b) -> 'a list -> 'b list
(** Same as {!List.map}, but the
function is applied to the index of the element as first argument (counting from 0),
and the element itself as second argument.
@since 3.13.0
(** Same as {!List.map}, but the function is applied to the index of
the element as first argument (counting from 0), and the element
itself as second argument.
@since 4.00.0
*)
val rev_map : f:('a -> 'b) -> 'a list -> 'b list

View File

@ -320,7 +320,7 @@ external hypot : float -> float -> float
of the hypotenuse of a right-angled triangle with sides of length
[x] and [y], or, equivalently, the distance of the point [(x,y)]
to origin.
@since 3.13.0 *)
@since 4.00.0 *)
external cosh : float -> float = "caml_cosh_float" "cosh" "float"
(** Hyperbolic cosine. Argument is in radians. *)
@ -351,7 +351,7 @@ external copysign : float -> float -> float
and whose sign is that of [y]. If [x] is [nan], returns [nan].
If [y] is [nan], returns either [x] or [-. x], but it is not
specified which.
@since 3.13.0 *)
@since 4.00.0 *)
external mod_float : float -> float -> float = "caml_fmod_float" "fmod" "float"
(** [mod_float a b] returns the remainder of [a] with respect to

View File

@ -117,7 +117,7 @@ val stdin : in_channel;;
type file_name = string;;
(** A convenient alias to designate a file name.
@since 3.13.0
@since 4.00.0
*)
val open_in : file_name -> in_channel;;
@ -500,5 +500,5 @@ val unescaped : string -> string
lexical conventions of OCaml, replaced by their corresponding
special characters. If there is no escape sequence in the
argument, still return a copy, contrary to String.escaped.
@since 3.13.0
@since 4.00.0
*)

View File

@ -124,19 +124,22 @@ val iteri : (int -> char -> unit) -> string -> unit
(** Same as {!String.iter}, but the
function is applied to the index of the element as first argument
(counting from 0), and the character itself as second argument.
@since 3.13.0
@since 4.00.0
*)
val map : (char -> char) -> string -> string
(** [String.map f s] applies function [f] in turn to all
the characters of [s] and stores the results in a new string that
is returned. *)
is returned.
@since 4.00.0 *)
val trim : string -> string
(** Return a copy of the argument, without leading and trailing whitespace.
The characters regarded as whitespace are: [' '], ['\012'], ['\n'],
['\r'], and ['\t']. If there is no whitespace character in the argument,
return the original string itself, not a copy. *)
(** Return a copy of the argument, without leading and trailing
whitespace. The characters regarded as whitespace are: [' '],
['\012'], ['\n'], ['\r'], and ['\t']. If there is no leading nor
trailing whitespace character in the argument, return the original
string itself, not a copy.
@since 4.00.0 *)
val escaped : string -> string
(** Return a copy of the argument, with special characters

View File

@ -88,19 +88,21 @@ val iteri : f:(int -> char -> unit) -> string -> unit
(** Same as {!String.iter}, but the
function is applied to the index of the element as first argument
(counting from 0), and the character itself as second argument.
@since 3.13.0
@since 4.00.0
*)
val map : f:(char -> char) -> string -> string
(** [String.map f s] applies function [f] in turn to all
the characters of [s] and stores the results in a new string that
is returned. *)
is returned.
@since 4.00.0 *)
val trim : string -> string
(** Return a copy of the argument, without leading and trailing whitespace.
The characters regarded as whitespace are: [' '], ['\012'], ['\n'],
['\r'], and ['\t']. If there is no whitespace character in the argument,
return the original string itself, not a copy. *)
return the original string itself, not a copy.
@since 4.00.0 *)
val escaped : string -> string
(** Return a copy of the argument, with special characters

View File

@ -85,7 +85,8 @@ val word_size : int
program, in bits: 32 or 64. *)
val big_endian : bool
(** Whether the machine currently executing the Caml program is big-endian. *)
(** Whether the machine currently executing the Caml program is big-endian.
@since 4.00.0 *)
val max_string_length : int
(** Maximum length of a string. *)