@@ -24,11 +24,13 @@ module test_stdlib_chaining_maps
24
24
integer, parameter :: test_size = rand_size*4
25
25
integer, parameter :: test_16 = 2**4
26
26
integer, parameter :: test_256 = 2**8
27
- ! key_type = 2 to support int8 and int32 key types tested. Can be
27
+ ! key_type = 5 to support int8 and int32 key types tested. Can be
28
28
! increased to generate additional unique int8 vectors additional key types.
29
- integer, parameter :: key_types = 2
29
+ integer, parameter :: key_types = 5
30
+ character(len=16) :: char_type
30
31
public :: collect_stdlib_chaining_maps
31
32
33
+
32
34
contains
33
35
34
36
!> Collect all exported unit tests
@@ -129,7 +131,19 @@ contains
129
131
! Use transfer to create int32 vector from generated int8 vector.
130
132
call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
131
133
call map % map_entry( key, other, conflict )
132
- call check(error, .not.conflict, "Unable to map int32 entry because of a key conflict.")
134
+ call check(error, .not.conflict, "Unable to map chaining int32 entry because of a key conflict.")
135
+
136
+ ! Test int8 key generic interface
137
+ call map % map_entry( test_8_bits( index2:index2+test_block-1, 3 ), other, conflict )
138
+ call check(error, .not.conflict, "Unable to map chaining int8 generic interface")
139
+
140
+ ! Test int32 key generic interface
141
+ call map % map_entry( transfer( test_8_bits( index2:index2+test_block-1, 4 ), [0_int32] ), other, conflict )
142
+ call check(error, .not.conflict, "Unable to map chaining int32 generic interface")
143
+
144
+ ! Test char key generic interface
145
+ call map % map_entry( transfer( test_8_bits( index2:index2+test_block-1, 5 ), char_type ), other, conflict )
146
+ call check(error, .not.conflict, "Unable to map chaining character generic interface")
133
147
134
148
if (allocated(error)) return
135
149
end do
@@ -154,6 +168,15 @@ contains
154
168
call map % key_test( key, present )
155
169
call check(error, present, "Int32 KEY not found in map KEY_TEST.")
156
170
171
+ call map % key_test( test_8_bits( index2:index2+test_block-1, 3 ), present )
172
+ call check(error, present, "Int8 KEY generic interface not found in map KEY_TEST.")
173
+
174
+ call map % key_test( transfer( test_8_bits( index2:index2+test_block-1, 4 ), [0_int32] ), present )
175
+ call check(error, present, "Int32 KEY generic interface not found in map KEY_TEST.")
176
+
177
+ call map % key_test( transfer( test_8_bits( index2:index2+test_block-1, 5 ), char_type ), present )
178
+ call check(error, present, "Char KEY generic interface not found in map KEY_TEST.")
179
+
157
180
if (allocated(error)) return
158
181
end do
159
182
@@ -177,6 +200,15 @@ contains
177
200
call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
178
201
call map % get_other_data( key, other, exists )
179
202
call check(error, exists, "Unable to get data because int32 key not found in map.")
203
+
204
+ call map % get_other_data( test_8_bits( index2:index2+test_block-1, 3 ), other, exists )
205
+ call check(error, exists, "Unable to get data because int8 generic interface key not found in map.")
206
+
207
+ call map % get_other_data( transfer( test_8_bits( index2:index2+test_block-1, 4 ), [0_int32] ) , other, exists )
208
+ call check(error, exists, "Unable to get data because int32 generic interface key not found in map.")
209
+
210
+ call map % get_other_data( transfer( test_8_bits( index2:index2+test_block-1, 5 ), char_type ) , other, exists )
211
+ call check(error, exists, "Unable to get data because character generic interface key not found in map.")
180
212
end do
181
213
182
214
end subroutine
@@ -198,6 +230,15 @@ contains
198
230
call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
199
231
call map % remove(key, existed)
200
232
call check(error, existed, "Int32 Key not found in entry removal.")
233
+
234
+ call map % remove(test_8_bits( index2:index2+test_block-1, 3 ), existed)
235
+ call check(error, existed, "Int8 Key generic interface not found in entry removal.")
236
+
237
+ call map % remove(transfer( test_8_bits( index2:index2+test_block-1, 4 ), [0_int32] ), existed)
238
+ call check(error, existed, "Int32 Key generic interface not found in entry removal.")
239
+
240
+ call map % remove(transfer( test_8_bits( index2:index2+test_block-1, 5 ), char_type ), existed)
241
+ call check(error, existed, "Character Key generic interface not found in entry removal.")
201
242
end do
202
243
203
244
end subroutine
@@ -277,9 +318,10 @@ module test_stdlib_open_maps
277
318
integer, parameter :: test_size = rand_size*4
278
319
integer, parameter :: test_16 = 2**4
279
320
integer, parameter :: test_256 = 2**8
280
- ! key_type = 2 to support int8 and int32 key types tested. Can be
321
+ ! key_type = 5 to support int8 and int32 key types tested. Can be
281
322
! increased to generate additional unique int8 vectors additional key types.
282
- integer, parameter :: key_types = 2
323
+ integer, parameter :: key_types = 5
324
+ character(len=16) :: char_type
283
325
284
326
public :: collect_stdlib_open_maps
285
327
@@ -386,6 +428,18 @@ contains
386
428
call map % map_entry( key, other, conflict )
387
429
call check(error, .not.conflict, "Unable to map int32 entry because of a key conflict.")
388
430
431
+ ! Test int8 generic key interface
432
+ call map % map_entry( test_8_bits( index2:index2+test_block-1, 3 ), other, conflict )
433
+ call check(error, .not.conflict, "Unable to map int8 generic key interface entry because of a key conflict.")
434
+
435
+ ! Test int32 key generic interface
436
+ call map % map_entry( transfer( test_8_bits( index2:index2+test_block-1, 4 ), [0_int32] ), other, conflict )
437
+ call check(error, .not.conflict, "Unable to map open int32 generic key interface entry because of a key conflict.")
438
+
439
+ ! Test character key generic interface
440
+ call map % map_entry( transfer( test_8_bits( index2:index2+test_block-1, 5 ), char_type ), other, conflict )
441
+ call check(error, .not.conflict, "Unable to map open character generic key interface entry because of a key conflict.")
442
+
389
443
if (allocated(error)) return
390
444
end do
391
445
@@ -410,6 +464,15 @@ contains
410
464
call map % key_test( key, present )
411
465
call check(error, present, "Int32 KEY not found in map KEY_TEST.")
412
466
467
+ call map % key_test( test_8_bits( index2:index2+test_block-1, 3 ), present )
468
+ call check(error, present, "Int8 KEY generic interface not found in map KEY_TEST.")
469
+
470
+ call map % key_test( transfer( test_8_bits( index2:index2+test_block-1, 4 ), [0_int32] ), present )
471
+ call check(error, present, "Int32 KEY generic interface not found in map KEY_TEST.")
472
+
473
+ call map % key_test( transfer( test_8_bits( index2:index2+test_block-1, 5 ), char_type ), present )
474
+ call check(error, present, "Character KEY generic interface not found in map KEY_TEST.")
475
+
413
476
if (allocated(error)) return
414
477
end do
415
478
@@ -433,6 +496,15 @@ contains
433
496
call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
434
497
call map % get_other_data( key, other, exists )
435
498
call check(error, exists, "Unable to get data because int32 key not found in map.")
499
+
500
+ call map % get_other_data( test_8_bits( index2:index2+test_block-1, 3 ), other, exists )
501
+ call check(error, exists, "Unable to get data because int8 generic interface key not found in map.")
502
+
503
+ call map % get_other_data( transfer( test_8_bits( index2:index2+test_block-1, 4 ), [0_int32] ), other, exists )
504
+ call check(error, exists, "Unable to get data because int32 generic interface key not found in map.")
505
+
506
+ call map % get_other_data( transfer( test_8_bits( index2:index2+test_block-1, 5 ), char_type ), other, exists )
507
+ call check(error, exists, "Unable to get data because character generic interface key not found in map.")
436
508
end do
437
509
438
510
end subroutine
@@ -454,6 +526,15 @@ contains
454
526
call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
455
527
call map % remove(key, existed)
456
528
call check(error, existed, "Int32 Key not found in entry removal.")
529
+
530
+ call map % remove( test_8_bits( index2:index2+test_block-1, 3 ), existed)
531
+ call check(error, existed, "Int8 Key generic interface not found in entry removal.")
532
+
533
+ call map % remove(transfer( test_8_bits( index2:index2+test_block-1, 4 ), [0_int32] ), existed)
534
+ call check(error, existed, "Int32 Key generic interface not found in entry removal.")
535
+
536
+ call map % remove(transfer( test_8_bits( index2:index2+test_block-1, 5 ), char_type ), existed)
537
+ call check(error, existed, "Character Key generic interface not found in entry removal.")
457
538
end do
458
539
459
540
end subroutine
0 commit comments