@@ -9,7 +9,6 @@ module test_stdlib_chaining_maps
99 use :: stdlib_kinds, only : dp, int8, int32
1010 use stdlib_hashmaps, only : chaining_hashmap_type, int_depth, int_index
1111 use stdlib_hashmap_wrappers
12- use stdlib_strings, only: to_string
1312
1413 implicit none
1514 private
@@ -25,7 +24,7 @@ module test_stdlib_chaining_maps
2524 integer, parameter :: test_size = rand_size*4
2625 integer, parameter :: test_16 = 2**4
2726 integer, parameter :: test_256 = 2**8
28- integer, parameter :: key_types = 3
27+ integer, parameter :: key_types = 2
2928 public :: collect_stdlib_chaining_maps
3029
3130contains
@@ -84,7 +83,9 @@ contains
8483 real(dp) :: rand2(2)
8584 integer(int32) :: rand_object(rand_size)
8685
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
8889 do index=1, rand_size
8990 call random_number(rand2)
9091 if (rand2(1) < 0.5_dp) then
@@ -118,21 +119,18 @@ contains
118119 allocate( dummy, source=dummy_val )
119120 call set ( other, dummy )
120121
121- ! Test all key interfaces
122+ ! Test base int8 key interface
122123 call set( key, test_8_bits( index2:index2+test_block-1, 1 ) )
123124 call map % map_entry( key, other, conflict )
124125 call check(error, .not.conflict, "Unable to map int8 entry because of a key conflict.")
125126
127+ ! Test int32 key interface
128+ ! Use transfer to create int32 vector from generated int8 vector.
126129 call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
127130 call map % map_entry( key, other, conflict )
128131 call check(error, .not.conflict, "Unable to map int32 entry because of a key conflict.")
129132
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-
134133 if (allocated(error)) return
135-
136134 end do
137135
138136 end subroutine
@@ -155,10 +153,6 @@ contains
155153 call map % key_test( key, present )
156154 call check(error, present, "Int32 KEY not found in map KEY_TEST.")
157155
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-
162156 if (allocated(error)) return
163157 end do
164158
@@ -182,10 +176,6 @@ contains
182176 call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
183177 call map % get_other_data( key, other, exists )
184178 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.")
189179 end do
190180
191181 end subroutine
@@ -207,10 +197,6 @@ contains
207197 call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
208198 call map % remove(key, existed)
209199 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.")
214200 end do
215201
216202 end subroutine
@@ -275,7 +261,6 @@ module test_stdlib_open_maps
275261 use :: stdlib_kinds, only : dp, int8, int32
276262 use stdlib_hashmaps, only : open_hashmap_type, int_depth, int_index
277263 use stdlib_hashmap_wrappers
278- use stdlib_strings, only: to_string
279264
280265 implicit none
281266 private
@@ -291,7 +276,7 @@ module test_stdlib_open_maps
291276 integer, parameter :: test_size = rand_size*4
292277 integer, parameter :: test_16 = 2**4
293278 integer, parameter :: test_256 = 2**8
294- integer, parameter :: key_types = 3
279+ integer, parameter :: key_types = 2
295280
296281 public :: collect_stdlib_open_maps
297282
@@ -350,7 +335,9 @@ contains
350335 integer :: index, key_type
351336 real(dp) :: rand2(2)
352337 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.
354341 do key_type = 1, key_types
355342 do index=1, rand_size
356343 call random_number(rand2)
@@ -385,21 +372,18 @@ contains
385372 allocate( dummy, source=dummy_val )
386373 call set ( other, dummy )
387374
388- ! Test all key interfaces
375+ ! Test base int8 key interface
389376 call set( key, test_8_bits( index2:index2+test_block-1, 1 ) )
390377 call map % map_entry( key, other, conflict )
391378 call check(error, .not.conflict, "Unable to map int8 entry because of a key conflict.")
392379
380+ ! Test int32 key interface
381+ ! Use transfer to create int32 vector from generated int8 vector.
393382 call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
394383 call map % map_entry( key, other, conflict )
395384 call check(error, .not.conflict, "Unable to map int32 entry because of a key conflict.")
396385
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-
401386 if (allocated(error)) return
402-
403387 end do
404388
405389 end subroutine
@@ -423,12 +407,7 @@ contains
423407 call map % key_test( key, present )
424408 call check(error, present, "Int32 KEY not found in map KEY_TEST.")
425409
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
432411 end do
433412
434413 end subroutine
@@ -451,10 +430,6 @@ contains
451430 call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
452431 call map % get_other_data( key, other, exists )
453432 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.")
458433 end do
459434
460435 end subroutine
@@ -476,10 +451,6 @@ contains
476451 call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
477452 call map % remove(key, existed)
478453 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.")
483454 end do
484455
485456 end subroutine
0 commit comments