1 % (c) 2009-2013 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, [add_term/3, reset_probhash/0, 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 init_probhash :- is_initialised,!.
20 init_probhash :-
21 load_foreign_resource(library(probhash)),
22 assert(is_initialised).
23
24 % input: term
25 % output: hash value as a biginteger (the byte order is reversed)
26 hash_term(Term,Hash) :- raw_sha_hash(Term,H), hash_to_int(H,Hash).
27
28 :- dynamic hash_id/1.
29 :- dynamic hash_h1h2/2.
30 :- dynamic hash_h2h3/2.
31 :- dynamic hash_h3h4/2.
32 :- dynamic hash_h4h5/2.
33 :- dynamic hash_h5id/2.
34
35 reset_probhash :-
36 retractall(hash_id(_)), assert(hash_id(0)),
37 retractall(hash_h1h2(_,_)), retractall(hash_h2h3(_,_)),
38 retractall(hash_h3h4(_,_)), retractall(hash_h4h5(_,_)),
39 retractall(hash_h5id(_,_)).
40
41 hash_id(0).
42
43 gen_new_id(X) :- hash_id(N), retract(hash_id(N)), X is N + 1, assert(hash_id(X)).
44
45 lookup(H1,H2,H3,H4,H5,X) :-
46 hash_h1h2(H1,H2), hash_h2h3(H2,H3), hash_h3h4(H3,H4), hash_h4h5(H4,H5), hash_h5id(H5,X).
47
48 store_hash(H1,H2,H3,H4,H5,X) :-
49 assert_hash_h1h2(H1,H2), assert_hash_h2h3(H2,H3), assert_hash_h3h4(H3,H4),
50 assert_hash_h4h5(H4,H5), assert(hash_h5id(H5,X)).
51
52 assert_hash_h1h2(X,Y) :- hash_h1h2(X,Y) -> true ; assert(hash_h1h2(X,Y)).
53 assert_hash_h2h3(X,Y) :- hash_h2h3(X,Y) -> true ; assert(hash_h2h3(X,Y)).
54 assert_hash_h3h4(X,Y) :- hash_h3h4(X,Y) -> true ; assert(hash_h3h4(X,Y)).
55 assert_hash_h4h5(X,Y) :- hash_h4h5(X,Y) -> true ; assert(hash_h4h5(X,Y)).
56
57 add_term(Term, Id, New) :- raw_sha_hash(Term,TH), hash_to_32bit(TH,[H1,H2,H3,H4,H5]),
58 ( lookup(H1,H2,H3,H4,H5,X) ->
59 New=false, Id=X
60 ; otherwise ->
61 New = true, gen_new_id(Id), store_hash(H1,H2,H3,H4,H5,Id)).
62
63
64 % input: raw hash
65 % output: hash value as a biginteger (the byte order is reversed)
66 hash_to_int(X,Y) :- hash_to_int(X,0,Y).
67 hash_to_int([],A,A).
68 hash_to_int([H|T],A,R) :- A2 is A * 256 + H, hash_to_int(T,A2,R).
69
70 % raw sha hashing, input is a term, output a raw hash, i.e., a list of 20 bytes
71 raw_sha_hash(Term,Digest) :-
72 init_probhash,
73 fast_buf_write(Term,Len,Addr),
74 sha1(Addr,Len,Digest).
75
76 % input: raw hash value
77 % output: hash value as an atom
78 hash_to_atom(H,ResultAtom) :-
79 raw_sha_hash(H,H2), hash_to_int(H2,X),
80 number_codes(X, C),atom_codes(ResultAtom,C).
81
82 % input: raw hash value
83 % output: hash value as 5 32-bit chunks
84 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]) :-
85 hash_to_int([V1,V2,V3,V4],H1),
86 hash_to_int([V5,V6,V7,V8],H2),
87 hash_to_int([V9,V10,V11,V12],H3),
88 hash_to_int([V13,V14,V15,V16],H4),
89 hash_to_int([V17,V18,V19,V20],H5).