safe-string: documentation fixes and add a couple of functions in Pervasives and Digest

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14721 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Damien Doligez 2014-05-01 21:54:15 +00:00
parent 05100e597e
commit 9baf42b72d
10 changed files with 32 additions and 17 deletions

View File

@ -196,7 +196,7 @@ Print version string and exit.
.B \-vnum
Print short version number and exit.
.TP
.BI \-w \ warning-list
.BI \-w \ warning\-list
Enable or disable warnings according to the argument
.IR warning-list .
See
@ -205,7 +205,7 @@ for the syntax of the
.I warning\-list
argument.
.TP
.BI \-warn-error \ warning-list
.BI \-warn\-error \ warning\-list
Mark as fatal the warnings described by the argument
.IR warning\-list .
Note that a warning is not triggered (and does not trigger an error) if

View File

@ -518,6 +518,7 @@ let print_newline () = output_char stdout '\n'; flush stdout
let prerr_char c = output_char stderr c
let prerr_string s = output_string stderr s
let prerr_bytes s = output_bytes stderr s
let prerr_int i = output_string stderr (string_of_int i)
let prerr_float f = output_string stderr (string_of_float f)
let prerr_endline s =

View File

@ -23,11 +23,15 @@ external channel: in_channel -> int -> t = "caml_md5_chan"
let string str =
unsafe_string str 0 (String.length str)
let bytes b = string (Bytes.unsafe_to_string b)
let substring str ofs len =
if ofs < 0 || len < 0 || ofs > String.length str - len
then invalid_arg "Digest.substring"
else unsafe_string str ofs len
let subbytes b ofs len = substring (Bytes.unsafe_to_string b) ofs len
let file filename =
let ic = open_in_bin filename in
let d = channel ic (-1) in

View File

@ -36,10 +36,16 @@ val compare : t -> t -> int
val string : string -> t
(** Return the digest of the given string. *)
val bytes : bytes -> t
(** Return the digest of the given byte sequence. *)
val substring : string -> int -> int -> t
(** [Digest.substring s ofs len] returns the digest of the substring
of [s] starting at character number [ofs] and containing [len]
characters. *)
of [s] starting at index [ofs] and containing [len] characters. *)
val subbytes : bytes -> int -> int -> t
(** [Digest.subbytes s ofs len] returns the digest of the subsequence
of [s] starting at index [ofs] and containing [len] bytes. *)
external channel : in_channel -> int -> t = "caml_md5_chan"
(** If [len] is nonnegative, [Digest.channel ic len] reads [len]

View File

@ -249,7 +249,7 @@ val finalise : ('a -> unit) -> 'a -> unit
another copy is still in use by the program.
The results of calling {!String.make}, {!String.create},
The results of calling {!String.make}, {!Bytes.make}, {!Bytes.create},
{!Array.make}, and {!Pervasives.ref} are guaranteed to be
heap-allocated and non-constant except when the length argument is [0].
*)

View File

@ -110,7 +110,7 @@ val to_channel : out_channel -> 'a -> extern_flags list -> unit
external to_bytes :
'a -> extern_flags list -> bytes = "caml_output_value_to_string"
(** [Marshal.to_string v flags] returns a byte sequence containing
(** [Marshal.to_bytes v flags] returns a byte sequence containing
the representation of [v].
The [flags] argument has the same meaning as for
{!Marshal.to_channel}. *)
@ -139,7 +139,7 @@ val from_bytes : bytes -> int -> 'a
(** [Marshal.from_bytes buff ofs] unmarshals a structured value
like {!Marshal.from_channel} does, except that the byte
representation is not read from a channel, but taken from
the string [buff], starting at position [ofs]. *)
the byte sequence [buff], starting at position [ofs]. *)
val from_string : string -> int -> 'a
(** Same as [from_bytes] but take a string as argument instead of a

View File

@ -420,6 +420,7 @@ let print_newline () = output_char stdout '\n'; flush stdout
let prerr_char c = output_char stderr c
let prerr_string s = output_string stderr s
let prerr_bytes s = output_bytes stderr s
let prerr_int i = output_string stderr (string_of_int i)
let prerr_float f = output_string stderr (string_of_float f)
let prerr_endline s =

View File

@ -14,8 +14,8 @@
(** The initially opened module.
This module provides the basic operations over the built-in types
(numbers, booleans, strings, exceptions, references, lists, arrays,
input-output channels, ...).
(numbers, booleans, byte sequences, strings, exceptions, references,
lists, arrays, input-output channels, ...).
This module is automatically opened at the beginning of each compilation.
All components of this module can therefore be referred by their short
@ -68,7 +68,7 @@ external ( <= ) : 'a -> 'a -> bool = "%lessequal"
external ( >= ) : 'a -> 'a -> bool = "%greaterequal"
(** Structural ordering functions. These functions coincide with
the usual orderings over integers, characters, strings
the usual orderings over integers, characters, strings, byte sequences
and floating-point numbers, and extend them to a
total ordering over all types.
The ordering is compatible with [( = )]. As in the case
@ -107,7 +107,7 @@ val max : 'a -> 'a -> 'a
external ( == ) : 'a -> 'a -> bool = "%eq"
(** [e1 == e2] tests for physical equality of [e1] and [e2].
On mutable types such as references, arrays, strings, records with
On mutable types such as references, arrays, byte sequences, records with
mutable fields and objects with mutable instance variables,
[e1 == e2] is true if and only if physical modification of [e1]
also affects [e2].
@ -618,6 +618,9 @@ val prerr_char : char -> unit
val prerr_string : string -> unit
(** Print a string on standard error. *)
val prerr_bytes : bytes -> unit
(** Print a byte sequence on standard error. *)
val prerr_int : int -> unit
(** Print an integer, in decimal, on standard error. *)

View File

@ -14,7 +14,7 @@
(** Standard labeled libraries.
This meta-module provides labelized version of the {!Array},
{!List} and {!String} modules.
{!Bytes}, {!List} and {!String} modules.
They only differ by their labels. Detailed interfaces can be found
in [arrayLabels.mli], [bytesLabels.mli], [listLabels.mli]

View File

@ -17,7 +17,7 @@
fixed-length sequence of (single-byte) characters. Each character
can be accessed in constant time through its index.
Given a string [s] of length [l], we can acces each of the [l]
Given a string [s] of length [l], we can access each of the [l]
characters of [s] via its index in the sequence. Indexes start at
[0], and we will call an index valid in [s] if it falls within the
range [[0...l-1]] (inclusive). A position is the point between two
@ -64,7 +64,7 @@ external set : bytes -> int -> char -> unit = "%string_safe_set"
Raise [Invalid_argument] if [n] is not a valid index in [s].
@deprecated This is a deprecated alias of {!Bytes.set}. *)
@deprecated This is a deprecated alias of {!Bytes.set}.[ ] *)
external create : int -> bytes = "caml_create_string" [@@ocaml.deprecated]
(** [String.create n] returns a fresh byte sequence of length [n].
@ -72,7 +72,7 @@ external create : int -> bytes = "caml_create_string" [@@ocaml.deprecated]
Raise [Invalid_argument] if [n < 0] or [n > ]{!Sys.max_string_length}.
@deprecated This is a deprecated alias of {!Bytes.create}. *)
@deprecated This is a deprecated alias of {!Bytes.create}.[ ] *)
val make : int -> char -> string
(** [String.make n c] returns a fresh string of length [n],
@ -98,7 +98,7 @@ val fill : bytes -> int -> int -> char -> unit [@@ocaml.deprecated]
Raise [Invalid_argument] if [start] and [len] do not
designate a valid range of [s].
@deprecated This is a deprecated alias of {!Bytes.fill}. *)
@deprecated This is a deprecated alias of {!Bytes.fill}.[ ] *)
val blit : string -> int -> bytes -> int -> int -> unit
(** [String.blit src srcoff dst dstoff len] copies [len] characters
@ -133,7 +133,7 @@ val map : (char -> char) -> string -> string
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 leading nor
['\012'], ['\n'], ['\r'], and ['\t']. If there is neither leading nor
trailing whitespace character in the argument, return the original
string itself, not a copy.
@since 4.00.0 *)