@@ -9,7 +9,6 @@ module test_stdlib_chaining_maps
9
9
use :: stdlib_kinds, only : dp, int8, int32
10
10
use stdlib_hashmaps, only : chaining_hashmap_type, int_depth, int_index
11
11
use stdlib_hashmap_wrappers
12
- use stdlib_strings, only: to_string
13
12
14
13
implicit none
15
14
private
@@ -25,7 +24,7 @@ module test_stdlib_chaining_maps
25
24
integer, parameter :: test_size = rand_size*4
26
25
integer, parameter :: test_16 = 2**4
27
26
integer, parameter :: test_256 = 2**8
28
- integer, parameter :: key_types = 3
27
+ integer, parameter :: key_types = 2
29
28
public :: collect_stdlib_chaining_maps
30
29
31
30
contains
@@ -84,7 +83,9 @@ contains
84
83
real(dp) :: rand2(2)
85
84
integer(int32) :: rand_object(rand_size)
86
85
87
- do key_type = 1, key_types
86
+ ! Generate a unique int8 vector for each key type tested to avoid
87
+ ! dupilcate keys and mapping conflicts.
88
+ do key_type = 1, key_types
88
89
do index=1, rand_size
89
90
call random_number(rand2)
90
91
if (rand2(1) < 0.5_dp) then
@@ -118,21 +119,18 @@ contains
118
119
allocate( dummy, source=dummy_val )
119
120
call set ( other, dummy )
120
121
121
- ! Test all key interfaces
122
+ ! Test base int8 key interface
122
123
call set( key, test_8_bits( index2:index2+test_block-1, 1 ) )
123
124
call map % map_entry( key, other, conflict )
124
125
call check(error, .not.conflict, "Unable to map int8 entry because of a key conflict.")
125
126
127
+ ! Test int32 key interface
128
+ ! Use transfer to create int32 vector from generated int8 vector.
126
129
call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
127
130
call map % map_entry( key, other, conflict )
128
131
call check(error, .not.conflict, "Unable to map int32 entry because of a key conflict.")
129
132
130
- call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) )
131
- call map % map_entry( key, other, conflict )
132
- call check(error, .not.conflict, "Unable to map character entry because of a key conflict.")
133
-
134
133
if (allocated(error)) return
135
-
136
134
end do
137
135
138
136
end subroutine
@@ -155,10 +153,6 @@ contains
155
153
call map % key_test( key, present )
156
154
call check(error, present, "Int32 KEY not found in map KEY_TEST.")
157
155
158
- call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) )
159
- call map % key_test( key, present )
160
- call check(error, present, "Character KEY not found in map KEY_TEST.")
161
-
162
156
if (allocated(error)) return
163
157
end do
164
158
@@ -182,10 +176,6 @@ contains
182
176
call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
183
177
call map % get_other_data( key, other, exists )
184
178
call check(error, exists, "Unable to get data because int32 key not found in map.")
185
-
186
- call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) )
187
- call map % get_other_data( key, other, exists )
188
- call check(error, exists, "Unable to get data because character key not found in map.")
189
179
end do
190
180
191
181
end subroutine
@@ -207,10 +197,6 @@ contains
207
197
call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
208
198
call map % remove(key, existed)
209
199
call check(error, existed, "Int32 Key not found in entry removal.")
210
-
211
- call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) )
212
- call map % remove(key, existed)
213
- call check(error, existed, "Character Key not found in entry removal.")
214
200
end do
215
201
216
202
end subroutine
@@ -275,7 +261,6 @@ module test_stdlib_open_maps
275
261
use :: stdlib_kinds, only : dp, int8, int32
276
262
use stdlib_hashmaps, only : open_hashmap_type, int_depth, int_index
277
263
use stdlib_hashmap_wrappers
278
- use stdlib_strings, only: to_string
279
264
280
265
implicit none
281
266
private
@@ -291,7 +276,7 @@ module test_stdlib_open_maps
291
276
integer, parameter :: test_size = rand_size*4
292
277
integer, parameter :: test_16 = 2**4
293
278
integer, parameter :: test_256 = 2**8
294
- integer, parameter :: key_types = 3
279
+ integer, parameter :: key_types = 2
295
280
296
281
public :: collect_stdlib_open_maps
297
282
@@ -350,7 +335,9 @@ contains
350
335
integer :: index, key_type
351
336
real(dp) :: rand2(2)
352
337
integer(int32) :: rand_object(rand_size)
353
-
338
+
339
+ ! Generate a unique int8 vector for each key type tested to avoid
340
+ ! dupilcate keys and mapping conflicts.
354
341
do key_type = 1, key_types
355
342
do index=1, rand_size
356
343
call random_number(rand2)
@@ -385,21 +372,18 @@ contains
385
372
allocate( dummy, source=dummy_val )
386
373
call set ( other, dummy )
387
374
388
- ! Test all key interfaces
375
+ ! Test base int8 key interface
389
376
call set( key, test_8_bits( index2:index2+test_block-1, 1 ) )
390
377
call map % map_entry( key, other, conflict )
391
378
call check(error, .not.conflict, "Unable to map int8 entry because of a key conflict.")
392
379
380
+ ! Test int32 key interface
381
+ ! Use transfer to create int32 vector from generated int8 vector.
393
382
call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
394
383
call map % map_entry( key, other, conflict )
395
384
call check(error, .not.conflict, "Unable to map int32 entry because of a key conflict.")
396
385
397
- call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) )
398
- call map % map_entry( key, other, conflict )
399
- call check(error, .not.conflict, "Unable to map character entry because of a key conflict.")
400
-
401
386
if (allocated(error)) return
402
-
403
387
end do
404
388
405
389
end subroutine
@@ -423,12 +407,7 @@ contains
423
407
call map % key_test( key, present )
424
408
call check(error, present, "Int32 KEY not found in map KEY_TEST.")
425
409
426
- call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) )
427
- call map % key_test( key, present )
428
- call check(error, present, "Character KEY not found in map KEY_TEST.")
429
-
430
- if (allocated(error)) return
431
-
410
+ if (allocated(error)) return
432
411
end do
433
412
434
413
end subroutine
@@ -451,10 +430,6 @@ contains
451
430
call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
452
431
call map % get_other_data( key, other, exists )
453
432
call check(error, exists, "Unable to get data because int32 key not found in map.")
454
-
455
- call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) )
456
- call map % get_other_data( key, other, exists )
457
- call check(error, exists, "Unable to get data because character key not found in map.")
458
433
end do
459
434
460
435
end subroutine
@@ -476,10 +451,6 @@ contains
476
451
call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
477
452
call map % remove(key, existed)
478
453
call check(error, existed, "Int32 Key not found in entry removal.")
479
-
480
- call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) )
481
- call map % remove(key, existed)
482
- call check(error, existed, "Character Key not found in entry removal.")
483
454
end do
484
455
485
456
end subroutine
0 commit comments