Digest: modif channel, fix PR#924, ajout to_hex

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4437 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Damien Doligez 2002-02-25 16:37:15 +00:00
parent 5dd41d5bc9
commit f3a1293b03
6 changed files with 32 additions and 10 deletions

Binary file not shown.

Binary file not shown.

View File

@ -45,12 +45,20 @@ CAMLprim value md5_chan(value vchan, value len)
Lock(chan);
MD5Init(&ctx);
toread = Long_val(len);
while (toread > 0) {
read = getblock(chan, buffer,
toread > sizeof(buffer) ? sizeof(buffer) : toread);
if (read == 0) raise_end_of_file();
MD5Update(&ctx, (unsigned char *) buffer, read);
toread -= read;
if (toread < 0){
while (1){
read = getblock (chan, buffer, sizeof(buffer));
if (read == 0) break;
MD5Update (&ctx, (unsigned char *) buffer, read);
}
}else{
while (toread > 0) {
read = getblock(chan, buffer,
toread > sizeof(buffer) ? sizeof(buffer) : toread);
if (read == 0) raise_end_of_file();
MD5Update(&ctx, (unsigned char *) buffer, read);
toread -= read;
}
}
res = alloc_string(16);
MD5Final(&Byte_u(res, 0), &ctx);

View File

@ -30,7 +30,7 @@ let substring str ofs len =
let file filename =
let ic = open_in_bin filename in
let d = channel ic (in_channel_length ic) in
let d = channel ic (-1) in
close_in ic;
d
@ -41,3 +41,11 @@ let input chan =
let digest = String.create 16 in
really_input chan digest 0 16;
digest
let to_hex d =
let result = String.create 32 in
for i = 0 to 15 do
String.blit (Printf.sprintf "%02x" (int_of_char d.[i])) 0 result (2*i) 2;
done;
result
;;

View File

@ -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. *)

View File

@ -78,4 +78,4 @@ let catch_break on =
(* OCaml version numbers and strings, moved from utils/config.mlp.
Must be in the format described in sys.mli. *)
let ocaml_version = "3.04+6 (2002-02-05)"
let ocaml_version = "3.04+7 (2002-02-25)"