Skip to content

Commit ff834d5

Browse files
committed
Deploying to stdlib-fpm from @ 9f1aa24 🚀
1 parent a990ad3 commit ff834d5

10 files changed

+3467
-0
lines changed

src/stdlib_hash_32bit.f90

Lines changed: 366 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,366 @@
1+
2+
module stdlib_hash_32bit
3+
4+
use, intrinsic :: iso_fortran_env, only : &
5+
character_storage_size
6+
7+
use stdlib_kinds, only: &
8+
dp, &
9+
int8, &
10+
int16, &
11+
int32, &
12+
int64
13+
14+
implicit none
15+
16+
private
17+
18+
integer, parameter, public :: &
19+
int_hash = int32
20+
!! The number of bits in the output hash
21+
22+
! pow32_over_phi is the odd integer that most closely approximates 2**32/phi,
23+
! where phi is the golden ratio 1.618...
24+
integer(int32), parameter :: &
25+
pow32_over_phi = int( z'9E3779B9', int32 )
26+
27+
! The number of bits used by each integer type
28+
integer, parameter :: &
29+
! Should be 8
30+
bits_int8 = bit_size(0_int8), &
31+
! Should be 16
32+
bits_int16 = bit_size(0_int16), &
33+
! Should be 32
34+
bits_int32 = bit_size(0_int32), &
35+
! Should be 64
36+
bits_int64 = bit_size(0_int64)
37+
38+
integer, parameter :: &
39+
! Should be 1
40+
bytes_int8 = bits_int8/bits_int8, &
41+
! Should be 2
42+
bytes_int16 = bits_int16/bits_int8, &
43+
! Should be 4
44+
bytes_int32 = bits_int32/bits_int8, &
45+
! Should be 8
46+
bytes_int64 = bits_int64/bits_int8
47+
48+
integer, parameter :: &
49+
bits_char = character_storage_size, &
50+
bytes_char = bits_char/bits_int8
51+
52+
! Dealing with different endians
53+
logical, parameter, public :: &
54+
little_endian = ( 1 == transfer([1_int8, 0_int8], 0_int16) )
55+
56+
public :: &
57+
fibonacci_hash, &
58+
fnv_1_hash, &
59+
fnv_1a_hash, &
60+
new_nmhash32_seed, &
61+
new_nmhash32x_seed, &
62+
new_water_hash_seed,&
63+
nmhash32, &
64+
nmhash32x, &
65+
odd_random_integer, &
66+
universal_mult_hash,&
67+
water_hash
68+
69+
70+
interface fnv_1_hash
71+
!! Version: experimental
72+
!!
73+
!! FNV_1 interfaces
74+
!! ([Specification](../page/specs/stdlib_hash_procedures.html#fnv_1_hash-calculates-a-hash-code-from-a-key))
75+
pure module function int8_fnv_1( key ) result(hash_code)
76+
!! FNV_1 hash function for rank 1 array keys of kind int8
77+
integer(int8), intent(in) :: key(:)
78+
integer(int_hash) :: hash_code
79+
end function int8_fnv_1
80+
81+
pure module function int16_fnv_1( key ) result(hash_code)
82+
!! FNV_1 hash function for rank 1 array keys of kind int16
83+
integer(int16), intent(in) :: key(:)
84+
integer(int_hash) :: hash_code
85+
end function int16_fnv_1
86+
87+
pure module function int32_fnv_1( key ) result(hash_code)
88+
!! FNV_1 hash function for rank 1 array keys of kind int32
89+
integer(int32), intent(in) :: key(:)
90+
integer(int_hash) :: hash_code
91+
end function int32_fnv_1
92+
93+
pure module function int64_fnv_1( key ) result(hash_code)
94+
!! FNV_1 hash function for rank 1 array keys of kind int64
95+
integer(int64), intent(in) :: key(:)
96+
integer(int_hash) :: hash_code
97+
end function int64_fnv_1
98+
99+
100+
elemental module function character_fnv_1( key ) result(hash_code)
101+
!! FNV_1 hash function for default character string keys
102+
character(*), intent(in) :: key
103+
integer(int_hash) :: hash_code
104+
end function character_fnv_1
105+
106+
end interface fnv_1_hash
107+
108+
interface fnv_1a_hash
109+
!! Version: experimental
110+
!!
111+
!! FNV_1A interfaces
112+
!! ([Specification](../page/specs/stdlib_hash_procedures.html#fnv_1a_hash-calculates-a-hash-code-from-a-key))
113+
pure module function int8_fnv_1a( key ) result(hash_value)
114+
!! FNV_1A hash function for rank 1 array keys of kind int8
115+
integer(int8), intent(in) :: key(:)
116+
integer(int_hash) :: hash_value
117+
end function int8_fnv_1a
118+
119+
pure module function int16_fnv_1a( key ) result(hash_value)
120+
!! FNV_1A hash function for rank 1 array keys of kind int16
121+
integer(int16), intent(in) :: key(:)
122+
integer(int_hash) :: hash_value
123+
end function int16_fnv_1a
124+
125+
pure module function int32_fnv_1a( key ) result(hash_value)
126+
!! FNV_1A hash function for rank 1 array keys of kind int32
127+
integer(int32), intent(in) :: key(:)
128+
integer(int_hash) :: hash_value
129+
end function int32_fnv_1a
130+
131+
pure module function int64_fnv_1a( key ) result(hash_value)
132+
!! FNV_1A hash function for rank 1 array keys of kind int64
133+
integer(int64), intent(in) :: key(:)
134+
integer(int_hash) :: hash_value
135+
end function int64_fnv_1a
136+
137+
138+
elemental module function character_fnv_1a( key ) result(hash_value)
139+
!! FNV_1A hash function for default character string keys
140+
character(*), intent(in) :: key
141+
integer(int_hash) :: hash_value
142+
end function character_fnv_1a
143+
144+
end interface fnv_1a_hash
145+
146+
interface nmhash32
147+
!! Version: experimental
148+
!!
149+
!! NMHASH32 interfaces
150+
!! ([Specification](../page/specs/stdlib_hash_procedures.html#nmhash32-calculates-a-hash-code-from-a-key-and-a-seed))
151+
pure module function int8_nmhash32( key, seed ) &
152+
result(hash_value)
153+
!! NMHASH32 hash function for rank 1 array keys of kind int8
154+
integer(int8), intent(in) :: key(0:)
155+
integer(int32), intent(in) :: seed
156+
integer(int32) :: hash_value
157+
end function int8_nmhash32
158+
159+
pure module function int16_nmhash32( key, seed ) &
160+
result(hash_value)
161+
!! NMHASH32 hash function for rank 1 array keys of kind int16
162+
integer(int16), intent(in) :: key(0:)
163+
integer(int32), intent(in) :: seed
164+
integer(int32) :: hash_value
165+
end function int16_nmhash32
166+
167+
pure module function int32_nmhash32( key, seed ) &
168+
result(hash_value)
169+
!! NMHASH32 hash function for rank 1 array keys of kind int32
170+
integer(int32), intent(in) :: key(0:)
171+
integer(int32), intent(in) :: seed
172+
integer(int32) :: hash_value
173+
end function int32_nmhash32
174+
175+
pure module function int64_nmhash32( key, seed ) &
176+
result(hash_value)
177+
!! NMHASH32 hash function for rank 1 array keys of kind int64
178+
integer(int64), intent(in) :: key(0:)
179+
integer(int32), intent(in) :: seed
180+
integer(int32) :: hash_value
181+
end function int64_nmhash32
182+
183+
184+
elemental module function character_nmhash32( key, seed ) &
185+
result(hash_value)
186+
!! NMHASH32 hash function for default character string keys
187+
character(*), intent(in) :: key
188+
integer(int32), intent(in) :: seed
189+
integer(int32) :: hash_value
190+
end function character_nmhash32
191+
192+
end interface nmhash32
193+
194+
interface nmhash32x
195+
!! Version: experimental
196+
!!
197+
!! NMHASH32X interfaces
198+
!! ([Specification](file:///home/jvandenp/stdlib/API-doc/page/specs/stdlib_hash_procedures.html#nmhash32x-calculates-a-hash-code-from-a-key-and-a-seed))
199+
pure module function int8_nmhash32x( key, seed ) &
200+
result(hash_value)
201+
!! NMHASH32 hash function for rank 1 array keys of kind int8
202+
integer(int8), intent(in) :: key(0:)
203+
integer(int32), intent(in) :: seed
204+
integer(int32) :: hash_value
205+
end function int8_nmhash32x
206+
207+
pure module function int16_nmhash32x( key, seed ) &
208+
result(hash_value)
209+
!! NMHASH32 hash function for rank 1 array keys of kind int16
210+
integer(int16), intent(in) :: key(0:)
211+
integer(int32), intent(in) :: seed
212+
integer(int32) :: hash_value
213+
end function int16_nmhash32x
214+
215+
pure module function int32_nmhash32x( key, seed ) &
216+
result(hash_value)
217+
!! NMHASH32 hash function for rank 1 array keys of kind int32
218+
integer(int32), intent(in) :: key(0:)
219+
integer(int32), intent(in) :: seed
220+
integer(int32) :: hash_value
221+
end function int32_nmhash32x
222+
223+
pure module function int64_nmhash32x( key, seed ) &
224+
result(hash_value)
225+
!! NMHASH32 hash function for rank 1 array keys of kind int64
226+
integer(int64), intent(in) :: key(0:)
227+
integer(int32), intent(in) :: seed
228+
integer(int32) :: hash_value
229+
end function int64_nmhash32x
230+
231+
232+
elemental module function character_nmhash32x( key, seed ) &
233+
result(hash_value)
234+
!! NMHASH32 hash function for default character string keys
235+
character(*), intent(in) :: key
236+
integer(int32), intent(in) :: seed
237+
integer(int32) :: hash_value
238+
end function character_nmhash32x
239+
240+
end interface nmhash32x
241+
242+
interface water_hash
243+
!! Version: experimental
244+
!!
245+
!! WATER_HASH interfaces
246+
!! ([Specification](../page/specs/stdlib_hash_procedures.html#water_hash-calculates-a-hash-code-from-a-key-and-a-seed))
247+
pure module function int8_water_hash( key, seed ) &
248+
result(hash_code)
249+
!! WATER HASH function for rank 1 array keys of kind int8
250+
integer(int8), intent(in) :: key(0:)
251+
integer(int64), intent(in) :: seed
252+
integer(int_hash) :: hash_code
253+
end function int8_water_hash
254+
pure module function int16_water_hash( key, seed ) &
255+
result(hash_code)
256+
!! WATER HASH function for rank 1 array keys of kind int16
257+
integer(int16), intent(in) :: key(0:)
258+
integer(int64), intent(in) :: seed
259+
integer(int_hash) :: hash_code
260+
end function int16_water_hash
261+
pure module function int32_water_hash( key, seed ) &
262+
result(hash_code)
263+
!! WATER HASH function for rank 1 array keys of kind int32
264+
integer(int32), intent(in) :: key(0:)
265+
integer(int64), intent(in) :: seed
266+
integer(int_hash) :: hash_code
267+
end function int32_water_hash
268+
pure module function int64_water_hash( key, seed ) &
269+
result(hash_code)
270+
!! WATER HASH function for rank 1 array keys of kind int64
271+
integer(int64), intent(in) :: key(0:)
272+
integer(int64), intent(in) :: seed
273+
integer(int_hash) :: hash_code
274+
end function int64_water_hash
275+
276+
elemental module function character_water_hash( key, seed ) &
277+
result(hash_code)
278+
!! WATER hash function for default character string keys
279+
character(*), intent(in) :: key
280+
integer(int64), intent(in) :: seed
281+
integer(int_hash) :: hash_code
282+
end function character_water_hash
283+
284+
end interface water_hash
285+
286+
interface new_water_hash_seed
287+
!! Version: experimental
288+
!!
289+
!! ([Specification](file:///home/jvandenp/stdlib/API-doc/page/specs/stdlib_hash_procedures.html#new_water_hash_seed-returns-a-valid-input-seed-for-water_hash))
290+
module subroutine new_water_hash_seed( seed )
291+
integer(int64), intent(inout) :: seed
292+
end subroutine new_water_hash_seed
293+
294+
end interface new_water_hash_seed
295+
296+
interface new_nmhash32_seed
297+
!! Version: experimental
298+
!!
299+
!! ([Specification](../page/specs/stdlib_hash_procedures.html#new_nmhash32_seed-returns-a-valid-input-seed-for-nmhash32)
300+
301+
module subroutine new_nmhash32_seed( seed )
302+
integer(int32), intent(inout) :: seed
303+
end subroutine new_nmhash32_seed
304+
305+
end interface new_nmhash32_seed
306+
307+
interface new_nmhash32x_seed
308+
!! Version: experimental
309+
!!
310+
!! ([Specification](../page/specs/stdlib_hash_procedures.html#new_nmhash32x_seed-returns-a-valid-input-seed-for-nmhash32x))
311+
312+
module subroutine new_nmhash32x_seed( seed )
313+
integer(int32), intent(inout) :: seed
314+
end subroutine new_nmhash32x_seed
315+
316+
end interface new_nmhash32x_seed
317+
318+
contains
319+
320+
elemental function fibonacci_hash( key, nbits ) result( sample )
321+
!! Version: experimental
322+
!!
323+
!! Maps the 32 bit integer `key` to an unsigned integer value with only `nbits`
324+
!! bits where `nbits` is less than 32
325+
!! ([Specification](../page/specs/stdlib_hash_procedures.html#fibonacci_hash-maps-an-integer-to-a-smaller-number-of-bits))
326+
327+
integer(int32), intent(in) :: key
328+
integer, intent(in) :: nbits
329+
integer(int32) :: sample
330+
331+
sample = ishft( key*pow32_over_phi, -32 + nbits )
332+
333+
end function fibonacci_hash
334+
335+
elemental function universal_mult_hash( key, seed, nbits ) result( sample )
336+
!! Version: experimental
337+
!!
338+
!! Uses the "random" odd 32 bit integer `seed` to map the 32 bit integer `key` to
339+
!! an unsigned integer value with only `nbits` bits where `nbits` is less than 32
340+
!! ([Specification](../page/specs/stdlib_hash_procedures.html#universal_mult_hash-maps-an-integer-to-a-smaller-number-of-bits))
341+
integer(int32), intent(in) :: key
342+
integer(int32), intent(in) :: seed
343+
integer, intent(in) :: nbits
344+
integer(int32) :: sample
345+
346+
sample = ishft( key*seed, -32 + nbits )
347+
348+
end function universal_mult_hash
349+
350+
subroutine odd_random_integer( harvest )
351+
!! Version: experimental
352+
!!
353+
!! Returns a 32 bit pseudo random integer, `harvest`, distributed uniformly over
354+
!! the odd integers of the `int32` kind.
355+
!! ([Specification](../page/specs/stdlib_hash_procedures.html#odd_random_integer-returns-an-odd-integer))
356+
integer(int32), intent(out) :: harvest
357+
real(dp) :: sample
358+
359+
call random_number( sample )
360+
harvest = int( floor( sample * 2_int64**32, int64 ) - 2_int64**31, &
361+
int32 )
362+
harvest = ishft( harvest, 1 ) + 1_int32
363+
364+
end subroutine odd_random_integer
365+
366+
end module stdlib_hash_32bit

0 commit comments

Comments
 (0)