@@ -9,6 +9,7 @@ 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
1213
1314 implicit none
1415 private
@@ -25,7 +26,6 @@ module test_stdlib_chaining_maps
2526 integer, parameter :: test_16 = 2**4
2627 integer, parameter :: test_256 = 2**8
2728 integer, parameter :: key_types = 3
28- character(len=*), parameter :: char_type = ' '
2929 public :: collect_stdlib_chaining_maps
3030
3131contains
@@ -83,7 +83,6 @@ contains
8383 integer :: index, key_type
8484 real(dp) :: rand2(2)
8585 integer(int32) :: rand_object(rand_size)
86- integer :: key_type
8786
8887 do key_type = 1, key_types
8988 do index=1, rand_size
@@ -122,15 +121,15 @@ contains
122121 ! Test all key interfaces
123122 call set( key, test_8_bits( index2:index2+test_block-1, 1 ) )
124123 call map % map_entry( key, other, conflict )
125- call check(error, .not.conflict, "Unable to map entry because of a key conflict.")
124+ call check(error, .not.conflict, "Unable to map int8 entry because of a key conflict.")
126125
127- call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) )
126+ call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [ 0_int32] ) )
128127 call map % map_entry( key, other, conflict )
129- call check(error, .not.conflict, "Unable to map entry because of a key conflict.")
128+ call check(error, .not.conflict, "Unable to map int32 entry because of a key conflict.")
130129
131- call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) )
130+ call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) )
132131 call map % map_entry( key, other, conflict )
133- call check(error, .not.conflict, "Unable to map entry because of a key conflict.")
132+ call check(error, .not.conflict, "Unable to map character entry because of a key conflict.")
134133
135134 if (allocated(error)) return
136135
@@ -150,15 +149,15 @@ contains
150149 do index2=1, test_size, test_block
151150 call set( key, test_8_bits( index2:index2+test_block-1, 1 ) )
152151 call map % key_test( key, present )
153- call check(error, present, "KEY not found in map KEY_TEST.")
152+ call check(error, present, "Int8 KEY not found in map KEY_TEST.")
154153
155- call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) )
154+ call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [ 0_int32] ) )
156155 call map % key_test( key, present )
157- call check(error, present, "KEY not found in map KEY_TEST.")
156+ call check(error, present, "Int32 KEY not found in map KEY_TEST.")
158157
159- call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) )
158+ call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) )
160159 call map % key_test( key, present )
161- call check(error, present, "KEY not found in map KEY_TEST.")
160+ call check(error, present, "Character KEY not found in map KEY_TEST.")
162161
163162 if (allocated(error)) return
164163 end do
@@ -178,15 +177,15 @@ contains
178177 do index2=1, test_size, test_block
179178 call set( key, test_8_bits( index2:index2+test_block-1, 1 ) )
180179 call map % get_other_data( key, other, exists )
181- call check(error, exists, "Unable to get data because key not found in map.")
180+ call check(error, exists, "Unable to get data because int8 key not found in map.")
182181
183- call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) )
182+ call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [ 0_int32] ) )
184183 call map % get_other_data( key, other, exists )
185- call check(error, exists, "Unable to get data because key not found in map.")
184+ call check(error, exists, "Unable to get data because int32 key not found in map.")
186185
187- call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) )
186+ call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) )
188187 call map % get_other_data( key, other, exists )
189- call check(error, exists, "Unable to get data because key not found in map.")
188+ call check(error, exists, "Unable to get data because character key not found in map.")
190189 end do
191190
192191 end subroutine
@@ -203,15 +202,15 @@ contains
203202 do index2=1, test_size, test_block
204203 call set( key, test_8_bits( index2:index2+test_block-1, 1 ) )
205204 call map % remove(key, existed)
206- call check(error, existed, "Key not found in entry removal.")
205+ call check(error, existed, "Int8 Key not found in entry removal.")
207206
208- call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) )
207+ call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [ 0_int32] ) )
209208 call map % remove(key, existed)
210- call check(error, existed, "Key not found in entry removal.")
209+ call check(error, existed, "Int32 Key not found in entry removal.")
211210
212- call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) )
211+ call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) )
213212 call map % remove(key, existed)
214- call check(error, existed, "Key not found in entry removal.")
213+ call check(error, existed, "Character Key not found in entry removal.")
215214 end do
216215
217216 end subroutine
@@ -276,6 +275,7 @@ module test_stdlib_open_maps
276275 use :: stdlib_kinds, only : dp, int8, int32
277276 use stdlib_hashmaps, only : open_hashmap_type, int_depth, int_index
278277 use stdlib_hashmap_wrappers
278+ use stdlib_strings, only: to_string
279279
280280 implicit none
281281 private
@@ -388,15 +388,15 @@ contains
388388 ! Test all key interfaces
389389 call set( key, test_8_bits( index2:index2+test_block-1, 1 ) )
390390 call map % map_entry( key, other, conflict )
391- call check(error, .not.conflict, "Unable to map entry because of a key conflict.")
391+ call check(error, .not.conflict, "Unable to map int8 entry because of a key conflict.")
392392
393- call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) )
393+ call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [ 0_int32] ) )
394394 call map % map_entry( key, other, conflict )
395- call check(error, .not.conflict, "Unable to map entry because of a key conflict.")
395+ call check(error, .not.conflict, "Unable to map int32 entry because of a key conflict.")
396396
397- call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) )
397+ call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) )
398398 call map % map_entry( key, other, conflict )
399- call check(error, .not.conflict, "Unable to map entry because of a key conflict.")
399+ call check(error, .not.conflict, "Unable to map character entry because of a key conflict.")
400400
401401 if (allocated(error)) return
402402
@@ -417,15 +417,15 @@ contains
417417
418418 call set( key, test_8_bits( index2:index2+test_block-1, 1 ) )
419419 call map % key_test( key, present )
420- call check(error, present, "KEY not found in map KEY_TEST.")
420+ call check(error, present, "Int8 KEY not found in map KEY_TEST.")
421421
422- call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) )
422+ call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [ 0_int32] ) )
423423 call map % key_test( key, present )
424- call check(error, present, "KEY not found in map KEY_TEST.")
424+ call check(error, present, "Int32 KEY not found in map KEY_TEST.")
425425
426- call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) )
426+ call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) )
427427 call map % key_test( key, present )
428- call check(error, present, "KEY not found in map KEY_TEST.")
428+ call check(error, present, "Character KEY not found in map KEY_TEST.")
429429
430430 if (allocated(error)) return
431431
@@ -446,15 +446,15 @@ contains
446446 do index2=1, test_size, test_block
447447 call set( key, test_8_bits( index2:index2+test_block-1, 1 ) )
448448 call map % get_other_data( key, other, exists )
449- call check(error, exists, "Unable to get data because key not found in map.")
449+ call check(error, exists, "Unable to get data because int8 key not found in map.")
450450
451- call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) )
451+ call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [ 0_int32] ) )
452452 call map % get_other_data( key, other, exists )
453- call check(error, exists, "Unable to get data because key not found in map.")
453+ call check(error, exists, "Unable to get data because int32 key not found in map.")
454454
455- call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) )
455+ call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) )
456456 call map % get_other_data( key, other, exists )
457- call check(error, exists, "Unable to get data because key not found in map.")
457+ call check(error, exists, "Unable to get data because character key not found in map.")
458458 end do
459459
460460 end subroutine
@@ -471,15 +471,15 @@ contains
471471 do index2=1, test_size, test_block
472472 call set( key, test_8_bits( index2:index2+test_block-1, 1 ) )
473473 call map % remove(key, existed)
474- call check(error, existed, "Key not found in entry removal.")
474+ call check(error, existed, "Int8 Key not found in entry removal.")
475475
476- call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), 0_int32 ) )
476+ call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [ 0_int32] ) )
477477 call map % remove(key, existed)
478- call check(error, existed, "Key not found in entry removal.")
478+ call check(error, existed, "Int32 Key not found in entry removal.")
479479
480- call set( key, transfer( test_8_bits( index2:index2+test_block-1, 3 ), char_type ) )
480+ call set( key, to_string( transfer( test_8_bits( index2:index2+test_block-1, 3 ), 0_int32 ) ) )
481481 call map % remove(key, existed)
482- call check(error, existed, "Key not found in entry removal.")
482+ call check(error, existed, "Character Key not found in entry removal.")
483483 end do
484484
485485 end subroutine
0 commit comments