1 % (c) 2009-2021 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]).
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).').
13
14 foreign_resource(probhash,[sha1]).
15 foreign(sha1,sha1(+address(char),+integer,[-term])).
16
17 :- dynamic is_initialised/0.
18
19 :- use_module(probsrc(pathes_lib),[safe_load_foreign_resource/2]).
20
21 init_probhash :- is_initialised,!.
22 init_probhash :-
23 safe_load_foreign_resource(probhash,probhash),
24 assertz(is_initialised).
25
26
27 % input: term
28 % output: hash value as a biginteger (the byte order is reversed)
29 hash_term(Term,Hash) :- raw_sha_hash(Term,H), hash_to_int(H,Hash).
30
31
32
33
34
35 % input: raw hash
36 % output: hash value as a biginteger (the byte order is reversed)
37 hash_to_int(X,Y) :- hash_to_int(X,0,Y).
38 hash_to_int([],A,A).
39 hash_to_int([H|T],A,R) :- A2 is A * 256 + H, hash_to_int(T,A2,R).
40
41 % raw sha hashing, input is a term, output a raw hash, i.e., a list of 20 bytes
42 raw_sha_hash(Term,Digest) :-
43 init_probhash,
44 fast_buf_write(Term,Len,Addr),
45 sha1(Addr,Len,Digest).
46
47 % input: raw hash value
48 % output: hash value as an atom
49 hash_to_atom(H,ResultAtom) :-
50 raw_sha_hash(H,H2), hash_to_int(H2,X),
51 number_codes(X, C),atom_codes(ResultAtom,C).
52
53 % input: raw hash value
54 % output: hash value as 5 32-bit chunks
55 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]) :-
56 hash_to_int([V1,V2,V3,V4],H1),
57 hash_to_int([V5,V6,V7,V8],H2),
58 hash_to_int([V9,V10,V11,V12],H3),
59 hash_to_int([V13,V14,V15,V16],H4),
60 hash_to_int([V17,V18,V19,V20],H5).