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