Skip to content

Commit a875ea7

Browse files
committed
Test hashmap update
Included tests in test_maps.fypp for generic key interfaces.
1 parent 3fce88e commit a875ea7

File tree

2 files changed

+91
-21
lines changed

2 files changed

+91
-21
lines changed

src/stdlib_hashmaps.f90

Lines changed: 5 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -834,7 +834,6 @@ subroutine int8_get_other_data( map, value, other, exists )
834834

835835
call set( key, value )
836836

837-
!call key_get_other_data( map, key, other, exists )
838837
call map % key_get_other_data( key, other, exists )
839838

840839
end subroutine int8_get_other_data
@@ -855,7 +854,6 @@ subroutine int32_get_other_data( map, value, other, exists )
855854

856855
call set( key, value )
857856

858-
!call key_get_other_data( map, key, other, exists )
859857
call map % key_get_other_data( key, other, exists )
860858

861859
end subroutine int32_get_other_data
@@ -876,7 +874,6 @@ subroutine char_get_other_data( map, value, other, exists )
876874

877875
call set( key, value )
878876

879-
!call key_get_other_data( map, key, other, exists )
880877
call map % key_get_other_data( key, other, exists )
881878

882879
end subroutine char_get_other_data
@@ -901,8 +898,8 @@ subroutine int8_remove_entry(map, value, existed) ! Chase's delent
901898

902899
call set( key, value )
903900

904-
!call key_remove_entry( map, key, existed )
905901
call map % key_remove_entry( key, existed )
902+
906903
end subroutine int8_remove_entry
907904

908905

@@ -925,8 +922,8 @@ subroutine int32_remove_entry(map, value, existed) ! Chase's delent
925922

926923
call set( key, value )
927924

928-
!call key_remove_entry( map, key, existed )
929925
call map % key_remove_entry( key, existed )
926+
930927
end subroutine int32_remove_entry
931928

932929

@@ -949,8 +946,8 @@ subroutine char_remove_entry(map, value, existed) ! Chase's delent
949946

950947
call set( key, value )
951948

952-
!call key_remove_entry( map, key, existed )
953949
call map % key_remove_entry( key, existed )
950+
954951
end subroutine char_remove_entry
955952

956953

@@ -969,7 +966,6 @@ subroutine int8_map_entry(map, value, other, conflict)
969966

970967
call set( key, value )
971968

972-
!call key_map_entry(map, key, other, conflict)
973969
call map % key_map_entry( key, other, conflict )
974970

975971
end subroutine int8_map_entry
@@ -991,7 +987,6 @@ subroutine int32_map_entry(map, value, other, conflict)
991987

992988
call set( key, value )
993989

994-
!call key_map_entry(map, key, other, conflict)
995990
call map % key_map_entry( key, other, conflict )
996991

997992
end subroutine int32_map_entry
@@ -1013,7 +1008,6 @@ subroutine char_map_entry(map, value, other, conflict)
10131008

10141009
call set( key, value )
10151010

1016-
!call key_map_entry(map, key, other, conflict)
10171011
call map % key_map_entry( key, other, conflict )
10181012

10191013
end subroutine char_map_entry
@@ -1039,8 +1033,8 @@ subroutine int8_key_test(map, value, present)
10391033

10401034
! Generate key from int8 array.
10411035
call set( key, value )
1036+
10421037
! Call key test procedure.
1043-
!call key_key_test(map, key, present)
10441038
call map % key_key_test( key, present )
10451039

10461040
end subroutine int8_key_test
@@ -1066,7 +1060,6 @@ subroutine int32_key_test(map, value, present)
10661060

10671061
call set( key, value )
10681062

1069-
!call key_key_test(map, key, present)
10701063
call map % key_key_test( key, present )
10711064

10721065
end subroutine int32_key_test
@@ -1091,8 +1084,7 @@ subroutine char_key_test(map, value, present)
10911084
type(key_type) :: key
10921085

10931086
call set( key, value )
1094-
1095-
!call key_key_test(map, key, present)
1087+
10961088
call map % key_key_test( key, present )
10971089

10981090
end subroutine char_key_test
@@ -1120,7 +1112,6 @@ subroutine int8_set_other_data( map, value, other, exists )
11201112

11211113
call set( key, value )
11221114

1123-
!call key_set_other_data( map, key, other, exists )
11241115
call map % key_set_other_data( key, other, exists )
11251116

11261117
end subroutine int8_set_other_data
@@ -1148,7 +1139,6 @@ subroutine int32_set_other_data( map, value, other, exists )
11481139

11491140
call set( key, value )
11501141

1151-
!call key_set_other_data( map, key, other, exists )
11521142
call map % key_set_other_data( key, other, exists )
11531143

11541144
end subroutine int32_set_other_data
@@ -1176,7 +1166,6 @@ subroutine char_set_other_data( map, value, other, exists )
11761166

11771167
call set( key, value )
11781168

1179-
!call key_set_other_data( map, key, other, exists )
11801169
call map % key_set_other_data( key, other, exists )
11811170

11821171
end subroutine char_set_other_data

test/hashmaps/test_maps.fypp

Lines changed: 86 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -24,11 +24,13 @@ module test_stdlib_chaining_maps
2424
integer, parameter :: test_size = rand_size*4
2525
integer, parameter :: test_16 = 2**4
2626
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
2828
! 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
3031
public :: collect_stdlib_chaining_maps
3132

33+
3234
contains
3335

3436
!> Collect all exported unit tests
@@ -129,7 +131,19 @@ contains
129131
! Use transfer to create int32 vector from generated int8 vector.
130132
call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
131133
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")
133147

134148
if (allocated(error)) return
135149
end do
@@ -154,6 +168,15 @@ contains
154168
call map % key_test( key, present )
155169
call check(error, present, "Int32 KEY not found in map KEY_TEST.")
156170

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+
157180
if (allocated(error)) return
158181
end do
159182

@@ -177,6 +200,15 @@ contains
177200
call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
178201
call map % get_other_data( key, other, exists )
179202
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.")
180212
end do
181213

182214
end subroutine
@@ -198,6 +230,15 @@ contains
198230
call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
199231
call map % remove(key, existed)
200232
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.")
201242
end do
202243

203244
end subroutine
@@ -277,9 +318,10 @@ module test_stdlib_open_maps
277318
integer, parameter :: test_size = rand_size*4
278319
integer, parameter :: test_16 = 2**4
279320
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
281322
! 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
283325

284326
public :: collect_stdlib_open_maps
285327

@@ -386,6 +428,18 @@ contains
386428
call map % map_entry( key, other, conflict )
387429
call check(error, .not.conflict, "Unable to map int32 entry because of a key conflict.")
388430

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+
389443
if (allocated(error)) return
390444
end do
391445

@@ -410,6 +464,15 @@ contains
410464
call map % key_test( key, present )
411465
call check(error, present, "Int32 KEY not found in map KEY_TEST.")
412466

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+
413476
if (allocated(error)) return
414477
end do
415478

@@ -433,6 +496,15 @@ contains
433496
call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
434497
call map % get_other_data( key, other, exists )
435498
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.")
436508
end do
437509

438510
end subroutine
@@ -454,6 +526,15 @@ contains
454526
call set( key, transfer( test_8_bits( index2:index2+test_block-1, 2 ), [0_int32] ) )
455527
call map % remove(key, existed)
456528
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.")
457538
end do
458539

459540
end subroutine

0 commit comments

Comments
 (0)