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 bbcf51604..342a3a4ea 100644
--- a/stdlib/digest.mli
+++ b/stdlib/digest.mli
@@ -33,8 +33,12 @@ val substring : string -> int -> int -> t
characters. *)
external channel : in_channel -> int -> t = "md5_chan"
-(** [Digest.channel ic len] reads [len] characters from channel [ic]
- and returns their digest. *)
+(** If [len] is nonnegative, [Digest.channel ic len] reads [len]
+ characters from channel [ic] and returns their digest, or raises
+ [End_of_file] if end-of-file is reached before [len] characters
+ are read. If [len] is negative, [Digest.channel ic len] reads
+ characters from [ic] until end-of-file is reached and return their
+ digest. *)
val file : string -> t
(** Return the digest of the file whose name is given. *)
@@ -45,3 +49,5 @@ val output : out_channel -> t -> unit
val input : in_channel -> t
(** Read a digest from the given input channel. *)
+val to_hex : t -> string
+(** Return the printable hexadecimal representation of the given digest. *)