diff options
Diffstat (limited to 'stdlib')
-rw-r--r-- | stdlib/digest.ml | 4 | ||||
-rw-r--r-- | stdlib/digest.mli | 10 | ||||
-rw-r--r-- | stdlib/gc.mli | 2 | ||||
-rw-r--r-- | stdlib/marshal.mli | 4 | ||||
-rw-r--r-- | stdlib/pervasives.ml | 1 | ||||
-rw-r--r-- | stdlib/pervasives.mli | 11 | ||||
-rw-r--r-- | stdlib/stdLabels.mli | 2 | ||||
-rw-r--r-- | stdlib/string.mli | 10 |
8 files changed, 29 insertions, 15 deletions
diff --git a/stdlib/digest.ml b/stdlib/digest.ml index e6b6b3589..14cb4ebd9 100644 --- a/stdlib/digest.ml +++ b/stdlib/digest.ml @@ -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 diff --git a/stdlib/digest.mli b/stdlib/digest.mli index 7fa1f15d6..583d2a46b 100644 --- a/stdlib/digest.mli +++ b/stdlib/digest.mli @@ -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] diff --git a/stdlib/gc.mli b/stdlib/gc.mli index d2f2d9761..c4ed39930 100644 --- a/stdlib/gc.mli +++ b/stdlib/gc.mli @@ -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]. *) diff --git a/stdlib/marshal.mli b/stdlib/marshal.mli index 1099773a3..d16ce5ef9 100644 --- a/stdlib/marshal.mli +++ b/stdlib/marshal.mli @@ -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 diff --git a/stdlib/pervasives.ml b/stdlib/pervasives.ml index 8fc04fb2c..83b1fcf7e 100644 --- a/stdlib/pervasives.ml +++ b/stdlib/pervasives.ml @@ -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 = diff --git a/stdlib/pervasives.mli b/stdlib/pervasives.mli index 37c593a82..fae87ba12 100644 --- a/stdlib/pervasives.mli +++ b/stdlib/pervasives.mli @@ -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. *) diff --git a/stdlib/stdLabels.mli b/stdlib/stdLabels.mli index 090a43e28..c607a9987 100644 --- a/stdlib/stdLabels.mli +++ b/stdlib/stdLabels.mli @@ -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] diff --git a/stdlib/string.mli b/stdlib/string.mli index 3cbf63c1b..45ef65756 100644 --- a/stdlib/string.mli +++ b/stdlib/string.mli @@ -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 *) |