Skip to content

Commit 2741106

Browse files
committed
Added hashmaps test files
Added the test codes hashmaps/test_chaining_maps.f90, hashmaps/test_open_maps.f90; and the hashmaps/CMakeLists.txt, and hashmaps/Makefile.manual to compile them. Modified CMakeLists.txt and Maakeefile.manual so that the hashmaps subdirectory would be added to the test directories to be compiled. [ticket: X]
1 parent 42f3f12 commit 2741106

File tree

6 files changed

+598
-0
lines changed

6 files changed

+598
-0
lines changed

src/tests/CMakeLists.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,7 @@ add_subdirectory(ascii)
2020
add_subdirectory(bitsets)
2121
add_subdirectory(hash_functions)
2222
add_subdirectory(hash_functions_perf)
23+
add_subdirectory(hashmaps)
2324
add_subdirectory(io)
2425
add_subdirectory(linalg)
2526
add_subdirectory(logger)

src/tests/Makefile.manual

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ all test clean::
1717
$(MAKE) -f Makefile.manual --directory=bitsets $@
1818
$(MAKE) -f Makefile.manual --directory=hash_functions_perf $@
1919
$(MAKE) -f Makefile.manual --directory=hash_functions $@
20+
$(MAKE) -f Makefile.manual --directory=hashmaps $@
2021
$(MAKE) -f Makefile.manual --directory=io $@
2122
$(MAKE) -f Makefile.manual --directory=logger $@
2223
$(MAKE) -f Makefile.manual --directory=optval $@

src/tests/hashmaps/CMakeLists.txt

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
ADDTEST(chaining_maps)
2+
ADDTEST(open_maps)
3+

src/tests/hashmaps/Makefile.manual

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
PROGS_SRC = test_chaining_maps.f90 test_open_maps.f90
2+
3+
4+
include ../Makefile.manual.test.mk
Lines changed: 294 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,294 @@
1+
program test_chaining_maps
2+
!! Test various aspects of the runtime system.
3+
!! Running this program may require increasing the stack size to above 48 MBytes
4+
!! or decreasing rand_power to 20 or less
5+
6+
use stdlib_kinds, only: &
7+
dp, &
8+
int8, &
9+
int32
10+
11+
use stdlib_hashmaps, only : chaining_hashmap_type, int_depth, int_index
12+
use stdlib_hashmap_wrappers
13+
14+
implicit none
15+
16+
type dummy_type
17+
integer(int8), allocatable :: value(:)
18+
end type dummy_type
19+
20+
integer(int32), parameter :: huge32 = huge(0_int32)
21+
real(dp), parameter :: hugep1 = real(huge32, dp) + 1.0_dp
22+
integer, parameter :: rand_power = 18
23+
integer, parameter :: rand_size = 2**rand_power
24+
integer, parameter :: test_size = rand_size*4
25+
integer, parameter :: test_16 = 2**4
26+
integer, parameter :: test_256 = 2**8
27+
28+
integer :: index
29+
integer :: lun
30+
type(chaining_hashmap_type) :: map
31+
real(dp) :: rand2(2)
32+
integer(int32) :: rand_object(rand_size)
33+
integer(int8) :: test_8_bits(test_size)
34+
35+
open( newunit=lun, file="test_chaining_maps.txt", access="sequential", &
36+
action="write", form="formatted", position="rewind" )
37+
write(lun, '("| ", a17, " | ", a12, " | ", a15, " | ", a10, " |")') &
38+
'Algorithm', 'Process', 'Data Set', 'Time (s)'
39+
40+
do index=1, rand_size
41+
call random_number(rand2)
42+
if (rand2(1) < 0.5_dp) then
43+
rand_object(index) = ceiling(-rand2(2)*hugep1, int32) - 1
44+
else
45+
rand_object(index) = floor(rand2(2)*hugep1, int32)
46+
end if
47+
end do
48+
49+
test_8_bits(:) = transfer( rand_object, 0_int8, test_size )
50+
51+
call map % init( fnv_1_hasher, slots_bits=10 )
52+
call input_random_data( map, test_16, 'FNV-1', "16 byte words" )
53+
call test_inquire_data( map, test_16, 'FNV-1', "16 byte words" )
54+
call test_get_data( map, test_16, 'FNV-1', '16 byte words' )
55+
call report_rehash_times( map, fnv_1_hasher, 'FNV-1', '16 byte words' )
56+
call report_hash_statistics( map, 'FNV-1', '16 byte words' )
57+
call report_removal_times( map, test_16, 'FNV-1', '16 byte words' )
58+
59+
call map % init( fnv_1_hasher, slots_bits=10 )
60+
call input_random_data( map, test_256, 'FNV-1', "256 byte words" )
61+
call test_inquire_data( map, test_256, 'FNV-1', "256 byte words" )
62+
call test_get_data( map, test_256, 'FNV-1', '256 byte words' )
63+
call report_rehash_times( map, fnv_1_hasher, 'FNV-1', '256 byte words' )
64+
call report_hash_statistics( map, 'FNV-1', '256 byte words' )
65+
call report_removal_times( map, test_256, 'FNV-1', '256 byte words' )
66+
67+
call map % init( fnv_1a_hasher, slots_bits=10 )
68+
call input_random_data( map, test_16, 'FNV-1A', "16 byte words" )
69+
call test_inquire_data( map, test_16, 'FNV-1A', "16 byte words" )
70+
call test_get_data( map, test_16, 'FNV-1A', '16 byte words' )
71+
call report_rehash_times( map, fnv_1a_hasher, 'FNV-1', '16 byte words' )
72+
call report_hash_statistics( map, 'FNV-1A', '16 byte words' )
73+
call report_removal_times( map, test_16, 'FNV-1a', '16 byte words' )
74+
75+
call map % init( fnv_1a_hasher, slots_bits=10 )
76+
call input_random_data( map, test_256, 'FNV-1A', "256 byte words" )
77+
call test_inquire_data( map, test_256, 'FNV-1A', "256 byte words" )
78+
call test_get_data( map, test_256, 'FNV-1A', '256 byte words' )
79+
call report_rehash_times( map, fnv_1_hasher, 'FNV-1A', '256 byte words' )
80+
call report_hash_statistics( map, 'FNV-1A', '256 byte words' )
81+
call report_removal_times( map, test_256, 'FNV-1A', '256 byte words' )
82+
83+
call map % init( seeded_nmhash32_hasher, slots_bits=10 )
84+
call input_random_data( map, test_16, 'Seeded_Nmhash32', "16 byte words" )
85+
call test_inquire_data( map, test_16, 'Seeded_Nmhash32', "16 byte words" )
86+
call test_get_data( map, test_16, 'Seeded_Nmhash32', '16 byte words' )
87+
call report_rehash_times( map, seeded_nmhash32_hasher, 'Seeded_Nmhash32', &
88+
'16 byte words' )
89+
call report_hash_statistics( map, 'Seeded_Nmhash32', '16 byte words' )
90+
call report_removal_times( map, test_16, 'Seeded_Nmhash32', &
91+
'16 byte words' )
92+
93+
call map % init( seeded_nmhash32_hasher, slots_bits=10 )
94+
call input_random_data( map, test_256, 'Seeded_Nmhash32', "256 byte words" )
95+
call test_inquire_data( map, test_256, 'Seeded_Nmhash32', "256 byte words" )
96+
call test_get_data( map, test_256, 'Seeded_Nmhash32', '256 byte words' )
97+
call report_rehash_times( map, seeded_nmhash32_hasher, 'Seeded_Nmhash32', &
98+
'256 byte words' )
99+
call report_hash_statistics( map, 'Seeded_Nmhash32', '256 byte words' )
100+
call report_removal_times( map, test_256, 'Seeded_Nmhash32', &
101+
'256 byte words' )
102+
103+
call map % init( seeded_nmhash32x_hasher, slots_bits=10 )
104+
call input_random_data( map, test_16, 'Seeded_Nmhash32x', "16 byte words" )
105+
call test_inquire_data( map, test_16, 'Seeded_Nmhash32x', "16 byte words" )
106+
call test_get_data( map, test_16, 'Seeded_Nmhash32x', '16 byte words' )
107+
call report_rehash_times( map, seeded_nmhash32x_hasher, &
108+
'Seeded_Nmhash32x', '16 byte words' )
109+
call report_hash_statistics( map, 'Seeded_Nmhash32x', '16 byte words' )
110+
call report_removal_times( map, test_16, 'Seeded_Nmhash32x', &
111+
'16 byte words' )
112+
113+
call map % init( seeded_nmhash32x_hasher, slots_bits=10 )
114+
call input_random_data( map, test_256, 'Seeded_Nmhash32x', &
115+
"256 byte words" )
116+
call test_inquire_data( map, test_256, 'Seeded_Nmhash32x', &
117+
"256 byte words" )
118+
call test_get_data( map, test_256, 'Seeded_Nmhash32x', '256 byte words' )
119+
call report_rehash_times( map, seeded_nmhash32x_hasher, &
120+
'Seeded_Nmhash32x', '256 byte words' )
121+
call report_hash_statistics( map, 'Seeded_Nmhash32x', '256 byte words' )
122+
call report_removal_times( map, test_256, 'Seeded_Nmhash32x', &
123+
'256 byte words' )
124+
125+
call map % init( seeded_water_hasher, slots_bits=10 )
126+
call input_random_data( map, test_16, 'Seeded_Water', "16 byte words" )
127+
call test_inquire_data( map, test_16, 'Seeded_Water', "16 byte words" )
128+
call test_get_data( map, test_16, 'Seeded_Water', '16 byte words' )
129+
call report_rehash_times( map, seeded_water_hasher, &
130+
'Seeded_Water', '16 byte words' )
131+
call report_hash_statistics( map, 'Seeded_Water', '16 byte words' )
132+
call report_removal_times( map, test_16, 'Seeded_Water', &
133+
'16 byte words' )
134+
135+
call map % init( seeded_water_hasher, slots_bits=10 )
136+
call input_random_data( map, test_256, 'Seeded_Water', &
137+
"256 byte words" )
138+
call test_inquire_data( map, test_256, 'Seeded_Water', &
139+
"256 byte words" )
140+
call test_get_data( map, test_256, 'Seeded_Water', '256 byte words' )
141+
call report_rehash_times( map, seeded_water_hasher, &
142+
'Seeded_Water', '256 byte words' )
143+
call report_hash_statistics( map, 'Seeded_Water', '256 byte words' )
144+
call report_removal_times( map, test_256, 'Seeded_Water', &
145+
'256 byte words' )
146+
147+
contains
148+
149+
subroutine input_random_data( map, test_block, hash_name, size_name )
150+
type(chaining_hashmap_type), intent(inout) :: map
151+
integer(int_index), intent(in) :: test_block
152+
character(*), intent(in) :: hash_name
153+
character(*), intent(in) :: size_name
154+
class(*), allocatable :: dummy
155+
type(dummy_type) :: dummy_val
156+
integer :: index2
157+
type(key_type) :: key
158+
type(other_type) :: other
159+
real :: t1, t2, tdiff
160+
logical :: conflict
161+
162+
call cpu_time(t1)
163+
do index2=1, size(test_8_bits), test_block
164+
call set( key, test_8_bits( index2:index2+test_block-1 ) )
165+
if (allocated(dummy)) deallocate(dummy)
166+
dummy_val % value = test_8_bits( index2:index2+test_block-1 )
167+
allocate( dummy, source=dummy_val )
168+
call set ( other, dummy )
169+
call map % map_entry( key, other, conflict )
170+
if (conflict) &
171+
error stop "Unable to map entry because of a key conflict."
172+
end do
173+
call cpu_time(t2)
174+
tdiff = t2-t1
175+
write(lun, '("|", a18, " | ", a12, " | ", a15, " | ", f10.5, " |")') &
176+
trim(hash_name), 'Enter data', size_name, tdiff
177+
178+
end subroutine input_random_data
179+
180+
181+
subroutine test_inquire_data( map, test_block, hash_name, size_name )
182+
type(chaining_hashmap_type), intent(inout) :: map
183+
integer(int_index), intent(in) :: test_block
184+
character(*), intent(in) :: hash_name, size_name
185+
integer :: index2
186+
logical :: present
187+
type(key_type) :: key
188+
real :: t1, t2, tdiff
189+
190+
call cpu_time(t1)
191+
do index2=1, size(test_8_bits), test_block
192+
call set( key, test_8_bits( index2:index2+test_block-1 ) )
193+
call map % key_test( key, present )
194+
if (.not. present) &
195+
error stop "KEY not found in map KEY_TEST."
196+
end do
197+
call cpu_time(t2)
198+
tdiff = t2-t1
199+
write(lun, '("|", a18, " | ", a12, " | ", a15, " | ", f10.5, " |")') &
200+
trim(hash_name), 'Inquire data', size_name, tdiff
201+
202+
end subroutine test_inquire_data
203+
204+
205+
subroutine test_get_data( map, test_block, hash_name, size_name )
206+
type(chaining_hashmap_type), intent(inout) :: map
207+
integer(int_index), intent(in) :: test_block
208+
character(*), intent(in) :: hash_name, size_name
209+
integer :: index2
210+
type(key_type) :: key
211+
type(other_type) :: other
212+
logical :: exists
213+
real :: t1, t2, tdiff
214+
215+
call cpu_time(t1)
216+
do index2=1, size(test_8_bits), test_block
217+
call set( key, test_8_bits( index2:index2+test_block-1 ) )
218+
call map % get_other_data( key, other, exists )
219+
if (.not. exists) &
220+
error stop "Unable to get data because key not found in map."
221+
end do
222+
call cpu_time(t2)
223+
tdiff = t2-t1
224+
write(lun, '("|", a18, " | ", a12, " | ", a15, " | ", f10.5, " |")') &
225+
trim(hash_name), 'Get data', size_name, tdiff
226+
227+
end subroutine test_get_data
228+
229+
230+
subroutine report_rehash_times( map, hasher, hash_name, size_name )
231+
type(chaining_hashmap_type), intent(inout) :: map
232+
procedure(hasher_fun) :: hasher
233+
character(*), intent(in) :: hash_name, size_name
234+
real :: t1, t2, tdiff
235+
236+
call cpu_time(t1)
237+
call map % rehash( hasher )
238+
call cpu_time(t2)
239+
tdiff = t2-t1
240+
241+
write(lun, '("|", a18, " | ", a12, " | ", a15, " | ", f10.5, " |")') &
242+
trim(hash_name), 'Rehash data', size_name, tdiff
243+
244+
end subroutine report_rehash_times
245+
246+
247+
subroutine report_removal_times( map, test_block, hash_name, size_name )
248+
type(chaining_hashmap_type), intent(inout) :: map
249+
integer(int_index), intent(in) :: test_block
250+
character(*), intent(in) :: hash_name, size_name
251+
real :: t1, t2, tdiff
252+
type(key_type) :: key
253+
integer(int_index) :: index2
254+
logical :: existed
255+
256+
call cpu_time(t1)
257+
do index2=1, size(test_8_bits), test_block
258+
call set( key, test_8_bits( index2:index2+test_block-1 ) )
259+
call map % remove(key, existed)
260+
if ( .not. existed ) &
261+
error stop "Key not found in entry removal."
262+
end do
263+
call cpu_time(t2)
264+
tdiff = t2-t1
265+
266+
write(lun, '("|", a18, " | ", a12, " | ", a15, " | ", f10.5, " |")') &
267+
trim(hash_name), 'Remove data', size_name, tdiff
268+
flush(lun)
269+
270+
end subroutine report_removal_times
271+
272+
273+
subroutine report_hash_statistics( map, hash_name, size_name )
274+
type(chaining_hashmap_type), intent(inout) :: map
275+
character(*), intent(in) :: hash_name, size_name
276+
integer(int_depth) :: depth
277+
278+
write(lun, *)
279+
write(lun, '("Statistics for chaining hash table with ",' // &
280+
'A, " hasher on ", A, ".")' ) hash_name, size_name
281+
write(lun, '("Slots = ", I0)' ) map % num_slots()
282+
write(lun, '("Calls = ", I0)' ) map % calls()
283+
write(lun, '("Entries = ", I0)' ) map % entries()
284+
write(lun, '("Total probes = ", I0)' ) map % map_probes()
285+
write(lun, '("Loading = ", ES10.3)' ) map % loading()
286+
depth = map % total_depth()
287+
write(lun, '("Total depth = ", I0)' ) depth
288+
write(lun, '("Relative depth = ", ES10.3)') &
289+
real( depth ) / real( map % entries() )
290+
291+
end subroutine report_hash_statistics
292+
293+
294+
end program test_chaining_maps

0 commit comments

Comments
 (0)