@@ -51,6 +51,7 @@ program test_chaining_maps
51
51
call map % init( fnv_1_hasher, slots_bits= 10 )
52
52
call input_random_data( map, test_16, ' FNV-1' , " 16 byte words" )
53
53
call test_inquire_data( map, test_16, ' FNV-1' , " 16 byte words" )
54
+ call test_get_all_keys( map, test_16, ' FNV-1' , ' 16 byte words' )
54
55
call test_get_data( map, test_16, ' FNV-1' , ' 16 byte words' )
55
56
call report_rehash_times( map, fnv_1_hasher, ' FNV-1' , ' 16 byte words' )
56
57
call report_hash_statistics( map, ' FNV-1' , ' 16 byte words' )
@@ -60,6 +61,7 @@ program test_chaining_maps
60
61
call input_random_data( map, test_256, ' FNV-1' , " 256 byte words" )
61
62
call test_inquire_data( map, test_256, ' FNV-1' , " 256 byte words" )
62
63
call test_get_data( map, test_256, ' FNV-1' , ' 256 byte words' )
64
+ call test_get_all_keys( map, test_256, ' FNV-1' , ' 256 byte words' )
63
65
call report_rehash_times( map, fnv_1_hasher, ' FNV-1' , ' 256 byte words' )
64
66
call report_hash_statistics( map, ' FNV-1' , ' 256 byte words' )
65
67
call report_removal_times( map, test_256, ' FNV-1' , ' 256 byte words' )
@@ -68,6 +70,7 @@ program test_chaining_maps
68
70
call input_random_data( map, test_16, ' FNV-1A' , " 16 byte words" )
69
71
call test_inquire_data( map, test_16, ' FNV-1A' , " 16 byte words" )
70
72
call test_get_data( map, test_16, ' FNV-1A' , ' 16 byte words' )
73
+ call test_get_all_keys( map, test_16, ' FNV-1A' , ' 16 byte words' )
71
74
call report_rehash_times( map, fnv_1a_hasher, ' FNV-1' , ' 16 byte words' )
72
75
call report_hash_statistics( map, ' FNV-1A' , ' 16 byte words' )
73
76
call report_removal_times( map, test_16, ' FNV-1a' , ' 16 byte words' )
@@ -76,6 +79,7 @@ program test_chaining_maps
76
79
call input_random_data( map, test_256, ' FNV-1A' , " 256 byte words" )
77
80
call test_inquire_data( map, test_256, ' FNV-1A' , " 256 byte words" )
78
81
call test_get_data( map, test_256, ' FNV-1A' , ' 256 byte words' )
82
+ call test_get_all_keys( map, test_256, ' FNV-1A' , ' 256 byte words' )
79
83
call report_rehash_times( map, fnv_1_hasher, ' FNV-1A' , ' 256 byte words' )
80
84
call report_hash_statistics( map, ' FNV-1A' , ' 256 byte words' )
81
85
call report_removal_times( map, test_256, ' FNV-1A' , ' 256 byte words' )
@@ -84,6 +88,7 @@ program test_chaining_maps
84
88
call input_random_data( map, test_16, ' Seeded_Nmhash32' , " 16 byte words" )
85
89
call test_inquire_data( map, test_16, ' Seeded_Nmhash32' , " 16 byte words" )
86
90
call test_get_data( map, test_16, ' Seeded_Nmhash32' , ' 16 byte words' )
91
+ call test_get_all_keys( map, test_16, ' Seeded_Nmhash32' , ' 16 byte words' )
87
92
call report_rehash_times( map, seeded_nmhash32_hasher, ' Seeded_Nmhash32' , &
88
93
' 16 byte words' )
89
94
call report_hash_statistics( map, ' Seeded_Nmhash32' , ' 16 byte words' )
@@ -94,6 +99,7 @@ program test_chaining_maps
94
99
call input_random_data( map, test_256, ' Seeded_Nmhash32' , " 256 byte words" )
95
100
call test_inquire_data( map, test_256, ' Seeded_Nmhash32' , " 256 byte words" )
96
101
call test_get_data( map, test_256, ' Seeded_Nmhash32' , ' 256 byte words' )
102
+ call test_get_all_keys( map, test_256, ' Seeded_Nmhash32' , ' 256 byte words' )
97
103
call report_rehash_times( map, seeded_nmhash32_hasher, ' Seeded_Nmhash32' , &
98
104
' 256 byte words' )
99
105
call report_hash_statistics( map, ' Seeded_Nmhash32' , ' 256 byte words' )
@@ -104,6 +110,7 @@ program test_chaining_maps
104
110
call input_random_data( map, test_16, ' Seeded_Nmhash32x' , " 16 byte words" )
105
111
call test_inquire_data( map, test_16, ' Seeded_Nmhash32x' , " 16 byte words" )
106
112
call test_get_data( map, test_16, ' Seeded_Nmhash32x' , ' 16 byte words' )
113
+ call test_get_all_keys( map, test_16, ' Seeded_Nmhash32x' , ' 16 byte words' )
107
114
call report_rehash_times( map, seeded_nmhash32x_hasher, &
108
115
' Seeded_Nmhash32x' , ' 16 byte words' )
109
116
call report_hash_statistics( map, ' Seeded_Nmhash32x' , ' 16 byte words' )
@@ -116,6 +123,7 @@ program test_chaining_maps
116
123
call test_inquire_data( map, test_256, ' Seeded_Nmhash32x' , &
117
124
" 256 byte words" )
118
125
call test_get_data( map, test_256, ' Seeded_Nmhash32x' , ' 256 byte words' )
126
+ call test_get_all_keys( map, test_256, ' Seeded_Nmhash32x' , ' 256 byte words' )
119
127
call report_rehash_times( map, seeded_nmhash32x_hasher, &
120
128
' Seeded_Nmhash32x' , ' 256 byte words' )
121
129
call report_hash_statistics( map, ' Seeded_Nmhash32x' , ' 256 byte words' )
@@ -126,6 +134,7 @@ program test_chaining_maps
126
134
call input_random_data( map, test_16, ' Seeded_Water' , " 16 byte words" )
127
135
call test_inquire_data( map, test_16, ' Seeded_Water' , " 16 byte words" )
128
136
call test_get_data( map, test_16, ' Seeded_Water' , ' 16 byte words' )
137
+ call test_get_all_keys( map, test_16, ' Seeded_Water' , ' 16 byte words' )
129
138
call report_rehash_times( map, seeded_water_hasher, &
130
139
' Seeded_Water' , ' 16 byte words' )
131
140
call report_hash_statistics( map, ' Seeded_Water' , ' 16 byte words' )
@@ -138,6 +147,7 @@ program test_chaining_maps
138
147
call test_inquire_data( map, test_256, ' Seeded_Water' , &
139
148
" 256 byte words" )
140
149
call test_get_data( map, test_256, ' Seeded_Water' , ' 256 byte words' )
150
+ call test_get_all_keys( map, test_256, ' Seeded_Water' , ' 256 byte words' )
141
151
call report_rehash_times( map, seeded_water_hasher, &
142
152
' Seeded_Water' , ' 256 byte words' )
143
153
call report_hash_statistics( map, ' Seeded_Water' , ' 256 byte words' )
@@ -227,6 +237,37 @@ subroutine test_get_data( map, test_block, hash_name, size_name )
227
237
end subroutine test_get_data
228
238
229
239
240
+ subroutine test_get_all_keys ( map , test_block , hash_name , size_name )
241
+ type (chaining_hashmap_type), intent (inout ) :: map
242
+ integer (int_index), intent (in ) :: test_block
243
+ character (* ), intent (in ) :: hash_name, size_name
244
+ integer :: index2, key_idx
245
+ type (key_type) :: key
246
+ type (key_type), allocatable :: all_keys(:)
247
+ real :: t1, t2, tdiff
248
+
249
+ call cpu_time(t1)
250
+ call map % get_all_keys(all_keys)
251
+ call cpu_time(t2)
252
+ tdiff = t2- t1
253
+
254
+ if (size ( all_keys ) /= size ( test_8_bits )/ test_block) &
255
+ error stop " Number of keys is different from that of keys in a map."
256
+
257
+ do index2= 1 , size (test_8_bits), test_block
258
+ call set( key, test_8_bits( index2:index2+ test_block-1 ) )
259
+
260
+ key_idx = ( index2/ test_block ) + 1
261
+ if (.not. ( all_keys(key_idx) == key )) &
262
+ error stop " Invalid value of a key."
263
+ end do
264
+
265
+ write (lun, ' ("|", a18, " | ", a12, " | ", a15, " | ", f10.5, " |")' ) &
266
+ trim (hash_name), ' Get all keys' , size_name, tdiff
267
+
268
+ end subroutine test_get_all_keys
269
+
270
+
230
271
subroutine report_rehash_times ( map , hasher , hash_name , size_name )
231
272
type (chaining_hashmap_type), intent (inout ) :: map
232
273
procedure (hasher_fun) :: hasher
0 commit comments