@@ -9,6 +9,7 @@ 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
12
13
13
14
implicit none
14
15
private
@@ -25,7 +26,6 @@ module test_stdlib_chaining_maps
25
26
integer, parameter :: test_16 = 2**4
26
27
integer, parameter :: test_256 = 2**8
27
28
integer, parameter :: key_types = 3
28
- character(len=*), parameter :: char_type = ' '
29
29
public :: collect_stdlib_chaining_maps
30
30
31
31
contains
@@ -83,7 +83,6 @@ contains
83
83
integer :: index, key_type
84
84
real(dp) :: rand2(2)
85
85
integer(int32) :: rand_object(rand_size)
86
- integer :: key_type
87
86
88
87
do key_type = 1, key_types
89
88
do index=1, rand_size
@@ -122,15 +121,15 @@ contains
122
121
! Test all key interfaces
123
122
call set( key, test_8_bits( index2:index2+test_block-1, 1 ) )
124
123
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.")
126
125
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] ) )
128
127
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.")
130
129
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 ) ) )
132
131
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.")
134
133
135
134
if (allocated(error)) return
136
135
@@ -150,15 +149,15 @@ contains
150
149
do index2=1, test_size, test_block
151
150
call set( key, test_8_bits( index2:index2+test_block-1, 1 ) )
152
151
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.")
154
153
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] ) )
156
155
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.")
158
157
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 ) ) )
160
159
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.")
162
161
163
162
if (allocated(error)) return
164
163
end do
@@ -178,15 +177,15 @@ contains
178
177
do index2=1, test_size, test_block
179
178
call set( key, test_8_bits( index2:index2+test_block-1, 1 ) )
180
179
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.")
182
181
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] ) )
184
183
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.")
186
185
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 ) ) )
188
187
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.")
190
189
end do
191
190
192
191
end subroutine
@@ -203,15 +202,15 @@ contains
203
202
do index2=1, test_size, test_block
204
203
call set( key, test_8_bits( index2:index2+test_block-1, 1 ) )
205
204
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.")
207
206
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] ) )
209
208
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.")
211
210
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 ) ) )
213
212
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.")
215
214
end do
216
215
217
216
end subroutine
@@ -276,6 +275,7 @@ module test_stdlib_open_maps
276
275
use :: stdlib_kinds, only : dp, int8, int32
277
276
use stdlib_hashmaps, only : open_hashmap_type, int_depth, int_index
278
277
use stdlib_hashmap_wrappers
278
+ use stdlib_strings, only: to_string
279
279
280
280
implicit none
281
281
private
@@ -388,15 +388,15 @@ contains
388
388
! Test all key interfaces
389
389
call set( key, test_8_bits( index2:index2+test_block-1, 1 ) )
390
390
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.")
392
392
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] ) )
394
394
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.")
396
396
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 ) ) )
398
398
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.")
400
400
401
401
if (allocated(error)) return
402
402
@@ -417,15 +417,15 @@ contains
417
417
418
418
call set( key, test_8_bits( index2:index2+test_block-1, 1 ) )
419
419
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.")
421
421
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] ) )
423
423
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.")
425
425
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 ) ) )
427
427
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.")
429
429
430
430
if (allocated(error)) return
431
431
@@ -446,15 +446,15 @@ contains
446
446
do index2=1, test_size, test_block
447
447
call set( key, test_8_bits( index2:index2+test_block-1, 1 ) )
448
448
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.")
450
450
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] ) )
452
452
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.")
454
454
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 ) ) )
456
456
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.")
458
458
end do
459
459
460
460
end subroutine
@@ -471,15 +471,15 @@ contains
471
471
do index2=1, test_size, test_block
472
472
call set( key, test_8_bits( index2:index2+test_block-1, 1 ) )
473
473
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.")
475
475
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] ) )
477
477
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.")
479
479
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 ) ) )
481
481
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.")
483
483
end do
484
484
485
485
end subroutine
0 commit comments