1 % (c) 2009-2024 Lehrstuhl fuer Softwaretechnik und Programmiersprachen,
2 % Heinrich Heine Universitaet Duesseldorf
3 % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html)
4
5 :- module(probhash, [hash_term/2, hash_to_atom/2, raw_sha_hash/2, raw_sha_hash_file/3]).
6 :- use_module(library(fastrw),[ fast_buf_read/2,
7 fast_buf_write/3 ]).
8
9 :- use_module('../../src/module_information.pl').
10
11 :- module_info(group,infrastructure).
12 :- module_info(description,'This is the interface to C code for generating good hashes (SHA-1, 160 bits).').
13
14 foreign_resource(probhash,[sha1,sha1_file]).
15 foreign(sha1,sha1(+address(char),+integer,[-term])).
16 foreign(sha1_file,sha1_file(+atom,[-term])).
17
18 :- dynamic is_initialised/0.
19
20 :- use_module(probsrc(pathes_lib),[safe_load_foreign_resource/2]).
21
22 init_probhash :- is_initialised,!.
23 init_probhash :-
24 safe_load_foreign_resource(probhash,probhash),
25 assertz(is_initialised).
26
27
28 % input: term
29 % output: hash value as a biginteger (the byte order is reversed)
30 hash_term(Term,Hash) :- raw_sha_hash(Term,H), hash_to_int(H,Hash).
31
32 :- use_module(library(file_systems),[file_exists/1]).
33
34 :- use_module(probsrc(error_manager),[add_error/4]).
35 raw_sha_hash_file(Atom,_,Span) :-
36 \+ file_exists(Atom),!,
37 add_error(probhash,'File does not exist: ',Atom,Span),fail.
38 raw_sha_hash_file(Atom,Hash,_) :-
39 init_probhash,
40 sha1_file(Atom,Hash).
41
42
43
44 % input: raw hash
45 % output: hash value as a biginteger (the byte order is reversed)
46 hash_to_int(X,Y) :- hash_to_int(X,0,Y).
47 hash_to_int([],A,A).
48 hash_to_int([H|T],A,R) :- A2 is A * 256 + H, hash_to_int(T,A2,R).
49
50 % raw sha hashing, input is a term, output a raw hash, i.e., a list of 20 bytes
51 raw_sha_hash(Term,Digest) :-
52 init_probhash,
53 fast_buf_write(Term,Len,Addr),
54 sha1(Addr,Len,Digest).
55
56 % input: raw hash value
57 % output: hash value as an atom
58 hash_to_atom(H,ResultAtom) :-
59 raw_sha_hash(H,H2), hash_to_int(H2,X),
60 number_codes(X, C),atom_codes(ResultAtom,C).
61
62 % input: raw hash value
63 % output: hash value as 5 32-bit chunks
64 hash_to_32bit([V1,V2,V3,V4,V5,V6,V7,V8,V9,V10,V11,V12,V13,V14,V15,V16,V17,V18,V19,V20],[H1,H2,H3,H4,H5]) :-
65 hash_to_int([V1,V2,V3,V4],H1),
66 hash_to_int([V5,V6,V7,V8],H2),
67 hash_to_int([V9,V10,V11,V12],H3),
68 hash_to_int([V13,V14,V15,V16],H4),
69 hash_to_int([V17,V18,V19,V20],H5).