1 % (c) 2009-2025 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(hashing,[my_term_hash/2, term_depth_hash/3, efficient_index/1]).
6
7 :- use_module(library(types),[must_be/4]).
8 :- use_module(tools_platform, [is_tagged_integer/1, platform_is_64_bit/0]).
9
10 :- use_module(module_information,[module_info/2]).
11 :- module_info(group,state_space).
12 :- module_info(description,'This module computes hash values (mainly for states) for efficient indexing.').
13
14 % --------------------------------------------
15
16 :- use_module(self_check).
17
18 :- assert_must_succeed(( hashing:my_term_hash([1,2,3],X), hashing:efficient_index(X) )).
19 :- assert_must_succeed(( hashing:my_term_hash([1,2,3],X), hashing:my_term_hash([1,2,4],Y), X\=Y )).
20
21 :- if(current_prolog_flag(dialect, sicstus)).
22
23 % On SICStus, use term_hash/3 with specific options.
24 :- use_module(library(terms),[term_hash/3]).
25 :- if(platform_is_64_bit).
26 my_term_hash(T,Res) :- super_hash(T,Res).
27 :- else.
28 my_term_hash(T,Res) :- term_hash(T,
29 [range(smallint), /* will use full 32 bit on 64 bit systems, 28 bit on 32 bit system */
30 algorithm(sdbm), % other options jenkins, hsieh, default
31 depth(infinite),if_var(ignore)],Res).
32 % collisions seem with more recent versions of SICStus to no longer be a problem !?
33 % sdbm seems to generate less collisions
34 :- endif.
35
36 % On 64-bit machines we can use the following for efficient indexing:
37 :- public super_hash/2.
38 super_hash(Term,Hash) :-
39 term_hash(Term,[range(smallint),algorithm(sdbm),depth(infinite),if_var(ignore)],H1),
40 term_hash(Term,[range(smallint32),algorithm(jenkins),depth(infinite),if_var(ignore)],H2),
41 Hash is H1 + (H2 << 32). % should be in range 0.. 2**60
42 % we could still try and use negative numbers
43
44 term_depth_hash(Term, Depth, Hash) :-
45 term_hash(Term,[range(smallint),algorithm(sdbm),depth(Depth),if_var(ignore)],H1),
46 term_hash(Term,[range(smallint32),algorithm(jenkins),depth(Depth),if_var(ignore)],H2),
47 Hash is H1 + (H2 << 32).
48 %term_depth_hash(Term, Depth, Hash) :-
49 % term_hash(Term, [if_var(ignore), depth(Depth)], Hash).
50
51 :- else. % end of sicstus
52
53 :- if(predicate_property(variant_hash(_, _), _)).
54 % Use SWI's variant_hash/2 if possible, which can handle variables in T.
55 my_term_hash(T,Res) :- variant_hash(T,Res).
56 % Note: in ProB's state space only ground terms should be stored; but my_term_hash is also used in other circumstances
57 % One could also use variant_sha1; reduces collisions but is more expensive
58 % currently SWI's term_hash generates collisions, e.g., when model checking:
59 % prob_examples/public_examples/B/PerformanceTests/ModelChecking/Lift_1Million_v2.mch
60 :- else.
61 % Fallback to basic term_hash/2 if no version with variable support is available.
62 my_term_hash(T,Res) :-
63 term_hash(T,Res),
64 (var(Res) -> must_be(T, ground, my_term_hash(T,Res), 1) ; true).
65 :- endif.
66
67 % term_depth_hash/3 allows hashing with a depth limit like term_hash/4,
68 % but tries to not limit the range.
69 :- use_module(library(terms),[term_hash/4]).
70 :- if((current_prolog_flag(dialect, swi), current_prolog_flag(max_tagged_integer, MaxTI), MaxTI >= 2147483647)).
71 term_depth_hash(Term, Depth, Hash) :-
72 % 2**31 - 1 is the maximum Range allowed by SWI.
73 % (We only use this maximum if max_tagged_integer is large enough to handle it, i. e. on 64-bit.)
74 term_hash(Term, Depth, 2147483647, Hash),
75 (var(Hash) -> must_be(Term, ground, term_depth_hash(Term,Depth,Hash), 1) ; true).
76 :- else.
77 term_depth_hash(Term, Depth, Hash) :-
78 % 2**24 - 1 is a relatively safe portable maximum
79 % and is also max_tagged_integer on 32-bit SWI.
80 term_hash(Term, Depth, 16777215, Hash),
81 (var(Hash) -> must_be(Term, ground, term_depth_hash(Term,Depth,Hash), 1) ; true).
82 :- endif.
83
84 :- endif.
85
86 % check if a hash value is an efficient for first argument indexing
87 efficient_index(X) :- number(X), is_tagged_integer(X).
88