This library provides bindings to functionality of OpenSSL that is related to cryptography and authentication, not necessarily involving connections, sockets or streams.
The hash functionality of this library subsumes and extends that of
library(sha)
, library(hash_stream)
and library(md5)
by providing a
unified interface to all available digest algorithms.
The underlying OpenSSL library (libcrypto
) is dynamically loaded if
either library(crypto)
or library(ssl)
are loaded. Therefore, if
your application uses library(ssl)
, you can use library(crypto)
for
hashing without increasing the memory footprint of your application. In
other cases, the specialised hashing libraries are more lightweight but
less general alternatives to library(crypto)
.
One way to relate such a list of bytes to an integer is to use CLP(FD) constraints as follows:
:- use_module(library(clpfd)). bytes_integer(Bs, N) :- foldl(pow, Bs, 0-0, N-_). pow(B, N0-I0, N-I) :- B in 0..255, N #= N0 + B*256^I0, I #= I0 + 1.
With this definition, you can generate a random 256-bit integer from a list of 32 random bytes:
?- crypto_n_random_bytes(32, Bs), bytes_integer(Bs, I). Bs = [98, 9, 35, 100, 126, 174, 48, 176, 246|...], I = 109798276762338328820827...(53 digits omitted).
The above relation also works in the other direction, letting you translate an integer to a list of bytes. In addition, you can use hex_bytes/2 to convert bytes to tokens that can be easily exchanged in your applications. This also works if you have compiled SWI-Prolog without support for large integers.
The following predicates are exported, but not or incorrectly documented.