summaryrefslogtreecommitdiffstats
path: root/stdlib/digest.mli
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/digest.mli')
-rw-r--r--stdlib/digest.mli10
1 files changed, 8 insertions, 2 deletions
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]