-
Notifications
You must be signed in to change notification settings - Fork 76
/
digest.mli
179 lines (139 loc) · 6.64 KB
/
digest.mli
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
# 2 "digest.mli"
(**************************************************************************)
(* *)
(* OCaml *)
(* *)
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* *)
(* Copyright 1996 Institut National de Recherche en Informatique et *)
(* en Automatique. *)
(* *)
(* All rights reserved. This file is distributed under the terms of *)
(* the GNU Lesser General Public License version 2.1, with the *)
(* special exception on linking described in the file LICENSE. *)
(* *)
(**************************************************************************)
open! Stdlib
(** Message digest.
This module provides functions to compute 'digests', also known as
'hashes', of arbitrary-length strings or files.
The supported hashing algorithms are BLAKE2 and MD5. *)
(** {1 Basic functions} *)
(** The functions in this section use the MD5 hash function to produce
128-bit digests (16 bytes). MD5 is not cryptographically secure.
Hence, these functions should not be used for security-sensitive
applications. The BLAKE2 functions below are cryptographically secure. *)
type t = string
(** The type of digests: 16-byte strings. *)
val compare : t -> t -> int
(** The comparison function for 16-byte digests, with the same
specification as {!Stdlib.compare} and the implementation
shared with {!String.compare}. Along with the type [t], this
function [compare] allows the module [Digest] to be passed as
argument to the functors {!Set.Make} and {!Map.Make}.
@since 4.00 *)
val equal : t -> t -> bool
(** The equal function for 16-byte digests.
@since 4.03 *)
val string : string -> t
(** Return the digest of the given string. *)
val bytes : bytes -> t
(** Return the digest of the given byte sequence.
@since 4.02 *)
val substring : string -> int -> int -> t
(** [Digest.substring s ofs len] returns the digest of the substring
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.
@since 4.02 *)
val channel : in_channel -> int -> t
(** 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
all 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. *)
val output : out_channel -> t -> unit
(** Write a digest on the given output channel. *)
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.
@raise Invalid_argument if the argument is not exactly 16 bytes.
*)
val of_hex : string -> t
(** Convert a hexadecimal representation back into the corresponding digest.
@raise Invalid_argument if the argument is not exactly 32 hexadecimal
characters.
@since 5.2 *)
val from_hex : string -> t
(** Same function as {!Digest.of_hex}.
@since 4.00 *)
(** {1 Generic interface} *)
module type S = sig
type t = string
(** The type of digests. *)
val hash_length : int
(** The length of digests, in bytes. *)
val compare : t -> t -> int
(** Compare two digests, with the same specification as
{!Stdlib.compare}. *)
val equal : t -> t -> bool
(** Test two digests for equality. *)
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
(** [substring s ofs len] returns the digest of the substring
of [s] starting at index [ofs] and containing [len] characters. *)
val subbytes : bytes -> int -> int -> t
(** [subbytes s ofs len] returns the digest of the subsequence
of [s] starting at index [ofs] and containing [len] bytes. *)
val channel : in_channel -> int -> t
(** Read characters from the channel and return their digest.
See {!Digest.channel} for the full specification. *)
val file : string -> t
(** Return the digest of the file whose name is given. *)
val output : out_channel -> t -> unit
(** Write a digest on the given output channel. *)
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.
@raise Invalid_argument if the length of the argument
is not [hash_length], *)
val of_hex : string -> t
(** Convert a hexadecimal representation back into the corresponding digest.
@raise Invalid_argument if the length of the argument
is not [2 * hash_length], or if the arguments contains non-hexadecimal
characters. *)
end
(** The signature for a hash function that produces digests of length
[hash_length] from character strings, byte arrays, and files.
@since 5.2 *)
(** {1 Specific hash functions} *)
module BLAKE128 : S
(** [BLAKE128] is the BLAKE2b hash function producing
128-bit (16-byte) digests. It is cryptographically secure.
However, the small size of the digests enables brute-force attacks
in [2{^64}] attempts.
@since 5.2 *)
module BLAKE256 : S
(** [BLAKE256] is the BLAKE2b hash function producing
256-bit (32-byte) digests. It is cryptographically secure,
and the digests are large enough to thwart brute-force attacks.
@since 5.2 *)
module BLAKE512 : S
(** [BLAKE512] is the BLAKE2b hash function producing
512-bit (64-byte) digests. It is cryptographically secure,
and the digests are large enough to thwart brute-force attacks.
@since 5.2 *)
module MD5 : S
(** [MD5] is the MD5 hash function. It produces 128-bit (16-byte) digests
and is not cryptographically secure at all. It should be used only
for compatibility with earlier designs that mandate the use of MD5.
@since 5.2 *)