1/* Part of SWI-Prolog 2 3 Author: Markus Triska and Matt Lilley 4 WWW: http://www.swi-prolog.org 5 Copyright (c) 2004-2017, SWI-Prolog Foundation 6 VU University Amsterdam 7 All rights reserved. 8 9 Redistribution and use in source and binary forms, with or without 10 modification, are permitted provided that the following conditions 11 are met: 12 13 1. Redistributions of source code must retain the above copyright 14 notice, this list of conditions and the following disclaimer. 15 16 2. Redistributions in binary form must reproduce the above copyright 17 notice, this list of conditions and the following disclaimer in 18 the documentation and/or other materials provided with the 19 distribution. 20 21 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 22 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 23 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 24 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 25 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 26 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 27 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 28 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 29 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 30 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 31 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 32 POSSIBILITY OF SUCH DAMAGE. 33*/ 34 35:- module(crypto, 36 [ crypto_n_random_bytes/2, % +N, -Bytes 37 crypto_data_hash/3, % +Data, -Hash, +Options 38 crypto_file_hash/3, % +File, -Hash, +Options 39 crypto_context_new/2, % -Context, +Options 40 crypto_data_context/3, % +Data, +C0, -C 41 crypto_context_hash/2, % +Context, -Hash 42 crypto_open_hash_stream/3, % +InStream, -HashStream, +Options 43 crypto_stream_hash/2, % +HashStream, -Hash 44 crypto_password_hash/2, % +Password, ?Hash 45 crypto_password_hash/3, % +Password, ?Hash, +Options 46 crypto_data_hkdf/4, % +Data, +Length, -Bytes, +Options 47 ecdsa_sign/4, % +Key, +Data, -Signature, +Options 48 ecdsa_verify/4, % +Key, +Data, +Signature, +Options 49 crypto_data_decrypt/6, % +CipherText, +Algorithm, +Key, +IV, -PlainText, +Options 50 crypto_data_encrypt/6, % +PlainText, +Algorithm, +Key, +IV, -CipherText, +Options 51 hex_bytes/2, % ?Hex, ?List 52 rsa_private_decrypt/4, % +Key, +Ciphertext, -Plaintext, +Enc 53 rsa_private_encrypt/4, % +Key, +Plaintext, -Ciphertext, +Enc 54 rsa_public_decrypt/4, % +Key, +Ciphertext, -Plaintext, +Enc 55 rsa_public_encrypt/4, % +Key, +Plaintext, -Ciphertext, +Enc 56 rsa_sign/4, % +Key, +Data, -Signature, +Options 57 rsa_verify/4, % +Key, +Data, +Signature, +Options 58 crypto_modular_inverse/3, % +X, +M, -Y 59 crypto_generate_prime/3, % +N, -P, +Options 60 crypto_is_prime/2, % +P, +Options 61 crypto_name_curve/2, % +Name, -Curve 62 crypto_curve_order/2, % +Curve, -Order 63 crypto_curve_generator/2, % +Curve, -Generator 64 crypto_curve_scalar_mult/4 % +Curve, +Scalar, +Point, -Result 65 ]). 66:- autoload(library(apply),[foldl/4,maplist/3]). 67:- autoload(library(base64),[base64_encoded/3]). 68:- autoload(library(error),[must_be/2,domain_error/2]). 69:- autoload(library(lists),[append/3,select/3,reverse/2]). 70:- autoload(library(option),[option/3,option/2]). 71 72:- use_foreign_library(foreign(crypto4pl)).
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.
136/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - 137 SHA256 is the current default for several hash-related predicates. 138 It is deemed sufficiently secure for the foreseeable future. Yet, 139 application programmers must be aware that the default may change in 140 future versions. The hash predicates all yield the algorithm they 141 used if a Prolog variable is used for the pertaining option. 142- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */ 143 144default_hash(sha256). 145 146functor_hash_options(F, Hash, Options0, [Option|Options]) :- 147 Option =.. [F,Hash], 148 ( select(Option, Options0, Options) -> 149 ( var(Hash) -> 150 default_hash(Hash) 151 ; must_be(atom, Hash) 152 ) 153 ; Options = Options0, 154 default_hash(Hash) 155 ).
md5
(insecure), sha1
(insecure), ripemd160
,
sha224
, sha256
, sha384
, sha512
, sha3_224
, sha3_256
,
sha3_384
, sha3_512
, blake2s256
or blake2b512
. The BLAKE
digest algorithms require OpenSSL 1.1.0 or greater, and the SHA-3
algorithms require OpenSSL 1.1.1 or greater. The default is a
cryptographically secure algorithm. If you specify a variable,
then that variable is unified with the algorithm that was used.utf8
. The
other meaningful value is octet
, claiming that Data contains
raw bytes.
192crypto_data_hash(Data, Hash, Options) :-
193 crypto_context_new(Context0, Options),
194 crypto_data_context(Data, Context0, Context),
195 crypto_context_hash(Context, Hash).
202crypto_file_hash(File, Hash, Options) :- 203 setup_call_cleanup(open(File, read, In, [type(binary)]), 204 crypto_stream_hash(In, Hash, Options), 205 close(In)). 206 207crypto_stream_hash(Stream, Hash, Options) :- 208 crypto_context_new(Context0, Options), 209 update_hash(Stream, Context0, Context), 210 crypto_context_hash(Context, Hash). 211 212update_hash(In, Context0, Context) :- 213 ( at_end_of_stream(In) 214 -> Context = Context0 215 ; read_pending_codes(In, Data, []), 216 crypto_data_context(Data, Context0, Context1), 217 update_hash(In, Context1, Context) 218 ).
230crypto_context_new(Context, Options0) :-
231 functor_hash_options(algorithm, _, Options0, Options),
232 '_crypto_context_new'(Context, Options).
This predicate allows a hash to be computed in chunks, which may be important while working with Metalink (RFC 5854), BitTorrent or similar technologies, or simply with big files.
246crypto_data_context(Data, Context0, Context) :-
247 '_crypto_hash_context_copy'(Context0, Context),
248 '_crypto_update_hash_context'(Data, Context).
257crypto_context_hash(Context, Hash) :-
258 '_crypto_hash_context_copy'(Context, Copy),
259 '_crypto_hash_context_hash'(Copy, List),
260 hex_bytes(Hash, List).
true
(default), closing the filter stream also closes the
original (parent) stream.
272crypto_open_hash_stream(OrgStream, HashStream, Options) :-
273 crypto_context_new(Context, Options),
274 '_crypto_open_hash_stream'(OrgStream, HashStream, Context).
286crypto_stream_hash(Stream, Hash) :- 287 '_crypto_stream_hash_context'(Stream, Context), 288 crypto_context_hash(Context, Hash). 289 290/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - 291 The so-called modular crypt format (MCF) is a standard for encoding 292 password hash strings. However, there's no official specification 293 document describing it. Nor is there a central registry of 294 identifiers or rules. This page describes what is known about it: 295 296 https://pythonhosted.org/passlib/modular_crypt_format.html 297 298 As of 2016, the MCF is deprecated in favor of the PHC String Format: 299 300 https://github.com/P-H-C/phc-string-format/blob/master/phc-sf-spec.md 301 302 This is what we are using below. For the time being, it is best to 303 treat these hashes as opaque atoms in applications. Please let me 304 know if you need to rely on any specifics of this format. 305- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
crypto_password_hash(Password, Hash, [])
and computes a
password-based hash using the default options.
314crypto_password_hash(Password, Hash) :-
315 ( nonvar(Hash) ->
316 must_be(atom, Hash),
317 split_string(Hash, "$", "$", Parts),
318 ( Parts = ["pbkdf2-sha512",Ps,SaltB64,HashB64] ->
319 atom_to_term(Ps, t=Iterations, []),
320 bytes_base64(SaltBytes, SaltB64),
321 bytes_base64(HashBytes, HashB64),
322 '_crypto_password_hash_pbkdf2'(Password, SaltBytes, Iterations, HashBytes)
323 ; Parts = ["2a", _, _],
324 sub_atom(Hash, 0, 29, 31, Setting),
325 '_crypto_password_hash_bcrypt'(Password, Setting, Hash)
326 )
327 ; crypto_password_hash(Password, Hash, [])
328 ).
Another important distinction is that equal passwords must yield, with very high probability, different hashes. For this reason, cryptographically strong random numbers are automatically added to the password before a hash is derived.
Hash is unified with an atom that contains the computed hash and all parameters that were used, except for the password. Instead of storing passwords, store these hashes. Later, you can verify the validity of a password with crypto_password_hash/2, comparing the then entered password to the stored hash. If you need to export this atom, you should treat it as opaque ASCII data with up to 255 bytes of length. The maximal length may increase in the future.
Admissible options are:
pbkdf2-sha512
(the default) and bcrypt
.Currently, PBKDF2 with SHA-512 is used as the hash derivation function, using 128 bits of salt. All default parameters, including the algorithm, are subject to change, and other algorithms will also become available in the future. Since computed hashes store all parameters that were used during their derivation, such changes will not affect the operation of existing deployments. Note though that new hashes will then be computed with the new default parameters.
381crypto_password_hash(Password, Hash, Options) :- 382 must_be(list, Options), 383 option(cost(C), Options, 17), 384 Iterations is 2^C, 385 option(algorithm(Algorithm), Options, 'pbkdf2-sha512'), 386 memberchk(Algorithm, ['pbkdf2-sha512', bcrypt]), 387 ( option(salt(SaltBytes), Options) -> 388 true 389 ; crypto_n_random_bytes(16, SaltBytes) 390 ), 391 ( Algorithm == 'pbkdf2-sha512' 392 -> '_crypto_password_hash_pbkdf2'(Password, SaltBytes, Iterations, HashBytes), 393 bytes_base64(HashBytes, HashB64), 394 bytes_base64(SaltBytes, SaltB64), 395 format(atom(Hash), 396 "$pbkdf2-sha512$t=~d$~w$~w", [Iterations,SaltB64,HashB64]) 397 ; bcrypt_bytes_base64(SaltBytes, SaltB64), 398 option(cost(Cost), Options, 11), 399 format(string(Setting), "$2a$~|~`0t~d~2+$~w", [Cost, SaltB64]), 400 '_crypto_password_hash_bcrypt'(Password, Setting, Hash) 401 ). 402 403 404/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - 405 Bidirectional Bytes <-> Base64 conversion as required by PHC format. 406 407 Note that *no padding* must be used, and that we must be able 408 to encode the whole range of bytes, not only UTF-8 sequences! 409- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */ 410 411bytes_base64(Bytes, Base64) :- 412 ( var(Bytes) -> 413 base64_encoded(Atom, Base64, [padding(false), encoding(iso_latin_1)]), 414 atom_codes(Atom, Bytes) 415 ; atom_codes(Atom, Bytes), 416 base64_encoded(Atom, Base64, [padding(false), encoding(iso_latin_1)]) 417 ). 418 419% Bcrypt uses a different alphabeta for base64 encoding, annoyingly 420bcrypt_bytes_base64(Bytes, Base64) :- 421 ( var(Bytes) -> 422 base64_encoded(Atom, Base64, [padding(false), encoding(utf8), 423 charset(openbsd)]), 424 atom_codes(Atom, Bytes) 425 ; atom_codes(Atom, Bytes), 426 base64_encoded(Atom, Base64, [padding(false), encoding(utf8), 427 charset(openbsd)]) 428 ).
Admissible options are:
utf8
(default) or octet
, denoting
the representation of Data as in crypto_data_hash/3.
The info/1 option can be used to generate multiple keys from a
single master key, using for example values such as key
and
iv
, or the name of a file that is to be encrypted.
This predicate requires OpenSSL 1.1.0 or greater.
465crypto_data_hkdf(Data, L, Bytes, Options0) :-
466 functor_hash_options(algorithm, Algorithm, Options0, Options),
467 option(salt(SaltBytes), Options, []),
468 option(info(Info), Options, ''),
469 option(encoding(Enc), Options, utf8),
470 '_crypto_data_hkdf'(Data, SaltBytes, Info, Algorithm, Enc, L, Bytes).
hex
) assumes that Data is
an atom, string, character list or code list representing the
data in hexadecimal notation. See rsa_sign/4 for an example.
Options:
hex
. Alternatives
are octet
, utf8
and text
.487ecdsa_sign(private_key(ec(Private,Public0,Curve)), Data0, Signature, Options) :- 488 option(encoding(Enc0), Options, hex), 489 hex_encoding(Enc0, Data0, Enc, Data), 490 hex_bytes(Public0, Public), 491 '_crypto_ecdsa_sign'(ec(Private,Public,Curve), Data, Enc, Signature). 492 493hex_encoding(hex, Data0, octet, Data) :- !, 494 hex_bytes(Data0, Data). 495hex_encoding(Enc, Data, Enc, Data).
Options:
hex
. Alternatives
are octet
, utf8
and text
.
508ecdsa_verify(public_key(ec(Private,Public0,Curve)), Data0, Signature0, Options) :-
509 option(encoding(Enc0), Options, hex),
510 hex_encoding(Enc0, Data0, Enc, Data),
511 hex_bytes(Public0, Public),
512 hex_bytes(Signature0, Signature),
513 '_crypto_ecdsa_verify'(ec(Private,Public,Curve), Data, Enc, Signature).
Example:
?- hex_bytes('501ACE', Bs). Bs = [80, 26, 206].
537hex_bytes(Hs, Bytes) :- 538 ( ground(Hs) -> 539 string_chars(Hs, Chars), 540 ( phrase(hex_bytes(Chars), Bytes) 541 -> true 542 ; domain_error(hex_encoding, Hs) 543 ) 544 ; must_be(list(between(0,255)), Bytes), 545 phrase(bytes_hex(Bytes), Chars), 546 atom_chars(Hs, Chars) 547 ). 548 549hex_bytes([]) --> []. 550hex_bytes([H1,H2|Hs]) --> [Byte], 551 { char_type(H1, xdigit(High)), 552 char_type(H2, xdigit(Low)), 553 Byte is High*16 + Low }, 554 hex_bytes(Hs). 555 556bytes_hex([]) --> []. 557bytes_hex([B|Bs]) --> 558 { High is B>>4, 559 Low is B /\ 0xf, 560 char_type(C0, xdigit(High)), 561 char_type(C1, xdigit(Low)) 562 }, 563 [C0,C1], 564 bytes_hex(Bs).
Options:
utf8
. Alternatives
are utf8
and octet
.pkcs1
. Alternatives
are pkcs1_oaep
, sslv23
and none
. Note that none
should
only be used if you implement cryptographically sound padding
modes in your application code as encrypting unpadded data with
RSA is insecuresha1
, sha224
, sha256
, sha384
or sha512
. The
default is a cryptographically secure algorithm. If you
specify a variable, then it is unified with the algorithm that
was used.hex
. Alternatives
are octet
, utf8
and text
.
This predicate can be used to compute a sha256WithRSAEncryption
signature as follows:
sha256_with_rsa(PemKeyFile, Password, Data, Signature) :- Algorithm = sha256, read_key(PemKeyFile, Password, Key), crypto_data_hash(Data, Hash, [algorithm(Algorithm), encoding(octet)]), rsa_sign(Key, Hash, Signature, [type(Algorithm)]). read_key(File, Password, Key) :- setup_call_cleanup( open(File, read, In, [type(binary)]), load_private_key(In, Password, Key), close(In)).
Note that a hash that is computed by crypto_data_hash/3 can be directly used in rsa_sign/4 as well as ecdsa_sign/4.
632rsa_sign(Key, Data0, Signature, Options0) :-
633 functor_hash_options(type, Type, Options0, Options),
634 option(encoding(Enc0), Options, hex),
635 hex_encoding(Enc0, Data0, Enc, Data),
636 rsa_sign(Key, Type, Enc, Data, Signature).
Options:
sha1
,
sha224
, sha256
, sha384
or sha512
. The default is the
same as for rsa_sign/4. This option must match the algorithm
that was used for signing. When operating with different parties,
the used algorithm must be communicated over an authenticated
channel.hex
. Alternatives
are octet
, utf8
and text
.
657rsa_verify(Key, Data0, Signature0, Options0) :-
658 functor_hash_options(type, Type, Options0, Options),
659 option(encoding(Enc0), Options, hex),
660 hex_encoding(Enc0, Data0, Enc, Data),
661 hex_bytes(Signature0, Signature),
662 rsa_verify(Key, Type, Enc, Data, Signature).
utf8
.
Alternatives are utf8
and octet
.block
. You can disable padding by supplying none
here.698crypto_data_decrypt(CipherText, Algorithm, Key, IV, PlainText, Options) :- 699 ( option(tag(Tag), Options) -> 700 option(min_tag_length(MinTagLength), Options, 16), 701 length(Tag, TagLength), 702 compare(C, TagLength, MinTagLength), 703 tag_length_ok(C, Tag) 704 ; Tag = [] 705 ), 706 '_crypto_data_decrypt'(CipherText, Algorithm, Key, IV, 707 Tag, PlainText, Options). 708 709% This test is important to prevent truncation attacks of the tag. 710 711tag_length_ok(=, _). 712tag_length_ok(>, _). 713tag_length_ok(<, Tag) :- domain_error(tag_is_too_short, Tag).
PlainText must be a string, atom or list of codes or characters, and CipherText is created as a string. Key and IV are typically lists of bytes, though atoms and strings are also permitted. Algorithm must be an algorithm which your copy of OpenSSL knows about.
Keys and IVs can be chosen at random (using for example crypto_n_random_bytes/2) or derived from input keying material (IKM) using for example crypto_data_hkdf/4. This input is often a shared secret, such as a negotiated point on an elliptic curve, or the hash that was computed from a password via crypto_password_hash/3 with a freshly generated and specified salt.
Reusing the same combination of Key and IV typically leaks at least
some information about the plaintext. For example, identical
plaintexts will then correspond to identical ciphertexts. For some
algorithms, reusing an IV with the same Key has disastrous results
and can cause the loss of all properties that are otherwise
guaranteed. Especially in such cases, an IV is also called a
nonce (number used once). If an IV is not needed for your
algorithm (such as 'aes-128-ecb'
) then any value can be provided
as it will be ignored by the underlying implementation. Note that
such algorithms do not provide semantic security and are thus
insecure. You should use stronger algorithms instead.
It is safe to store and transfer the used initialization vector (or nonce) in plain text, but the key must be kept secret.
Commonly used algorithms include:
'chacha20-poly1305'
'aes-128-gcm'
'aes-128-cbc'
Options:
utf8
. Alternatives
are utf8
and octet
.block
. You can disable padding by supplying none
here. If
padding is disabled for block ciphers, then the length of the
ciphertext must be a multiple of the block size.For example, with OpenSSL 1.1.0 and greater, we can use the ChaCha20 stream cipher with the Poly1305 authenticator. This cipher uses a 256-bit key and a 96-bit nonce, i.e., 32 and 12 bytes, respectively:
?- Algorithm = 'chacha20-poly1305', crypto_n_random_bytes(32, Key), crypto_n_random_bytes(12, IV), crypto_data_encrypt("this is some input", Algorithm, Key, IV, CipherText, [tag(Tag)]), crypto_data_decrypt(CipherText, Algorithm, Key, IV, RecoveredText, [tag(Tag)]). Algorithm = 'chacha20-poly1305', Key = [65, 147, 140, 197, 27, 60, 198, 50, 218|...], IV = [253, 232, 174, 84, 168, 208, 218, 168, 228|...], CipherText = <binary string>, Tag = [248, 220, 46, 62, 255, 9, 178, 130, 250|...], RecoveredText = "this is some input".
In this example, we use crypto_n_random_bytes/2 to generate a key and nonce from cryptographically secure random numbers. For repeated applications, you must ensure that a nonce is only used once together with the same key. Note that for authenticated encryption schemes, the tag that was computed during encryption is necessary for decryption. It is safe to store and transfer the tag in plain text.
835crypto_data_encrypt(PlainText, Algorithm, Key, IV, CipherText, Options) :-
836 ( option(tag(AuthTag), Options) ->
837 option(tag_length(AuthLength), Options, 16)
838 ; AuthTag = _,
839 AuthLength = -1
840 ),
841 '_crypto_data_encrypt'(PlainText, Algorithm, Key, IV,
842 AuthLength, AuthTag, CipherText, Options).
851crypto_modular_inverse(X, M, Y) :- 852 integer_serialized(X, XS), 853 integer_serialized(M, MS), 854 '_crypto_modular_inverse'(XS, MS, YHex), 855 hex_to_integer(YHex, Y). 856 857integer_serialized(I, serialized(S)) :- 858 must_be(integer, I), 859 integer_atomic_sign(I, Sign), 860 Abs is abs(I), 861 format(atom(A0), "~16r", [Abs]), 862 atom_length(A0, L), 863 Rem is L mod 2, 864 hex_pad(Rem, Sign, A0, S). 865 866integer_atomic_sign(I, S) :- 867 Sign is sign(I), 868 sign_atom(Sign, S). 869 870sign_atom(-1, '-'). 871sign_atom( 0, ''). 872sign_atom( 1, ''). 873 874hex_pad(0, Sign, A0, A) :- atom_concat(Sign, A0, A). 875hex_pad(1, Sign, A0, A) :- atomic_list_concat([Sign,'0',A0], A). 876 877pow256(Byte, N0-I0, N-I) :- 878 N is N0 + Byte*256^I0, 879 I is I0 + 1. 880 881hex_to_integer(Hex, N) :- 882 hex_bytes(Hex, Bytes0), 883 reverse(Bytes0, Bytes), 884 foldl(pow256, Bytes, 0-0, N-_).
true
(default is false
), then a safe prime
is generated. This means that P is of the form 2*Q + 1 where Q
is also prime.
896crypto_generate_prime(Bits, P, Options) :-
897 must_be(list, Options),
898 option(safe(Safe), Options, false),
899 '_crypto_generate_prime'(Bits, Hex, Safe, Options),
900 hex_to_integer(Hex, P).
912crypto_is_prime(P0, Options) :-
913 must_be(integer, P0),
914 must_be(list, Options),
915 option(iterations(N), Options, -1),
916 integer_serialized(P0, P),
917 '_crypto_is_prime'(P, N).
prime256v1
and
secp256k1
.
If you have OpenSSL installed, you can get a list of supported curves via:
$ openssl ecparam -list_curves
940crypto_curve_order(Curve, Order) :-
941 '_crypto_curve_order'(Curve, Hex),
942 hex_to_integer(Hex, Order).
949crypto_curve_generator(Curve, point(X,Y)) :-
950 '_crypto_curve_generator'(Curve, X0, Y0),
951 hex_to_integer(X0, X),
952 hex_to_integer(Y0, Y).
959crypto_curve_scalar_mult(Curve, S0, point(X0,Y0), point(A,B)) :- 960 maplist(integer_serialized, [S0,X0,Y0], [S,X,Y]), 961 '_crypto_curve_scalar_mult'(Curve, S, X, Y, A0, B0), 962 hex_to_integer(A0, A), 963 hex_to_integer(B0, B). 964 965 966 /******************************* 967 * Sandboxing * 968 *******************************/ 969 970:- multifile sandbox:safe_primitive/1. 971 972sandbox:safe_primitive(crypto:hex_bytes(_,_)). 973sandbox:safe_primitive(crypto:crypto_n_random_bytes(_,_)). 974 975sandbox:safe_primitive(crypto:crypto_data_hash(_,_,_)). 976sandbox:safe_primitive(crypto:crypto_data_context(_,_,_)). 977sandbox:safe_primitive(crypto:crypto_context_new(_,_)). 978sandbox:safe_primitive(crypto:crypto_context_hash(_,_)). 979 980sandbox:safe_primitive(crypto:crypto_password_hash(_,_)). 981sandbox:safe_primitive(crypto:crypto_password_hash(_,_,_)). 982sandbox:safe_primitive(crypto:crypto_data_hkdf(_,_,_,_)). 983 984sandbox:safe_primitive(crypto:ecdsa_sign(_,_,_,_)). 985sandbox:safe_primitive(crypto:ecdsa_verify(_,_,_,_)). 986 987sandbox:safe_primitive(crypto:rsa_sign(_,_,_,_)). 988sandbox:safe_primitive(crypto:rsa_verify(_,_,_,_)). 989sandbox:safe_primitive(crypto:rsa_public_encrypt(_,_,_,_)). 990sandbox:safe_primitive(crypto:rsa_public_decrypt(_,_,_,_)). 991sandbox:safe_primitive(crypto:rsa_private_encrypt(_,_,_,_)). 992sandbox:safe_primitive(crypto:rsa_private_decrypt(_,_,_,_)). 993 994sandbox:safe_primitive(crypto:crypto_data_decrypt(_,_,_,_,_,_)). 995sandbox:safe_primitive(crypto:crypto_data_encrypt(_,_,_,_,_,_)). 996 997sandbox:safe_primitive(crypto:crypto_modular_inverse(_,_,_)). 998sandbox:safe_primitive(crypto:crypto_generate_prime(_,_,_)). 999sandbox:safe_primitive(crypto:crypto_is_prime(_,_)). 1000 1001sandbox:safe_primitive(crypto:crypto_name_curve(_,_)). 1002sandbox:safe_primitive(crypto:crypto_curve_order(_,_)). 1003sandbox:safe_primitive(crypto:crypto_curve_generator(_,_)). 1004sandbox:safe_primitive(crypto:crypto_curve_scalar_mult(_,_,_,_)). 1005 1006 /******************************* 1007 * MESSAGES * 1008 *******************************/ 1009 1010:- multifile 1011 prolog:error_message//1. 1012 1013prologerror_message(ssl_error(ID, _Library, Function, Reason)) --> 1014 [ 'SSL(~w) ~w: ~w'-[ID, Function, Reason] ]
Cryptography and authentication library
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)
andlibrary(md5)
by providing a unified interface to all available digest algorithms.The underlying OpenSSL library (
libcrypto
) is dynamically loaded if eitherlibrary(crypto)
orlibrary(ssl)
are loaded. Therefore, if your application useslibrary(ssl)
, you can uselibrary(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 tolibrary(crypto)
.