Skip to content

Commit 1c681d1

Browse files
committed
RC1
Update to hashmap routines to remove 'other' data derived wrapper type.
1 parent 036b091 commit 1c681d1

13 files changed

+135
-129
lines changed

example/hashmaps/example_hashmaps_copy_other.f90

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,6 @@
1+
!! This example left for reference, however 'other_type' has largely
2+
!! been depreciated in the stdlib hashmaps.
3+
14
program example_copy_other
25
use stdlib_hashmap_wrappers, only: &
36
copy_other, other_type

example/hashmaps/example_hashmaps_free_other.f90

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,6 @@
1+
!! This example left for reference, however 'other_type' has largely
2+
!! been depreciated in stdlib hashmaps.
3+
14
program example_free_other
25
use stdlib_hashmap_wrappers, only: &
36
copy_other, free_other, other_type

example/hashmaps/example_hashmaps_get_all_keys.f90

Lines changed: 3 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,6 @@ program example_hashmaps_get_all_keys
66
implicit none
77
type(chaining_hashmap_type) :: map
88
type(key_type) :: key
9-
type(other_type) :: other
109

1110
type(key_type), allocatable :: keys(:)
1211
integer(int32) :: i
@@ -17,16 +16,13 @@ program example_hashmaps_get_all_keys
1716

1817
! adding key-value pairs to the map
1918
call set(key, "initial key")
20-
call set(other, "value 1")
21-
call map%map_entry(key, other)
19+
call map%map_entry(key, "value 1")
2220

2321
call set(key, "second key")
24-
call set(other, "value 2")
25-
call map%map_entry(key, other)
22+
call map%map_entry(key, "value 2")
2623

2724
call set(key, "last key")
28-
call set(other, "value 3")
29-
call map%map_entry(key, other)
25+
call map%map_entry(key, "value 3")
3026

3127
! getting all the keys in the map
3228
call map%get_all_keys(keys)

example/hashmaps/example_hashmaps_get_other_data.f90

Lines changed: 19 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ program example_get_other_data
55
implicit none
66
logical :: conflict
77
type(key_type) :: key
8-
type(other_type) :: other
8+
99
type(chaining_hashmap_type) :: map
1010
type dummy_type
1111
integer :: value(4)
@@ -21,17 +21,18 @@ program example_get_other_data
2121
! Hashmap functions are setup to store scalar value types (other). Use a dervied
2222
! type wrapper to store arrays.
2323
dummy%value = [4, 3, 2, 1]
24-
call set(other, dummy)
2524

2625
! Explicitly set key type using set function
2726
call set(key, [0, 1])
28-
call map%map_entry(key, other, conflict)
27+
call map%map_entry(key, dummy, conflict)
2928
if (.not. conflict) then
30-
call map%get_other_data(key, other)
29+
call map%get_other_data(key, data)
3130
else
3231
error stop 'Key is already present in the map.'
3332
end if
34-
call get(other, data)
33+
34+
! Get_other_data returns data as an unlimited polymorphic scalar.
35+
! To use this type in other operations, there must be a select type operation.
3536
select type (data)
3637
type is (dummy_type)
3738
print *, 'Other data % value = ', data%value
@@ -41,29 +42,29 @@ program example_get_other_data
4142

4243
! Also can use map_entry and get_other_data generic key interfaces.
4344
! This is an exmple with integer arrays.
44-
call map%map_entry( [2,3], other, conflict)
45+
call map%map_entry( [2,3], dummy, conflict)
4546
if (.not. conflict) then
46-
call map%get_other_data( [2,3], other)
47+
call map%get_other_data( [2,3], data)
4748
else
4849
error stop 'Key is already present in the map.'
4950
end if
50-
call get(other, data)
51+
5152
select type (data)
5253
type is (dummy_type)
5354
print *, 'Other data % value = ', data%value
5455
class default
5556
print *, 'Invalid data type in other'
5657
end select
5758

58-
! Integer scalars need to be passed as an array.
59+
! Integer scalar keys need to be passed as an array.
5960
int_scalar = 2
60-
call map%map_entry( [int_scalar], other, conflict)
61+
call map%map_entry( [int_scalar], dummy, conflict)
6162
if (.not. conflict) then
62-
call map%get_other_data( [int_scalar], other)
63+
call map%get_other_data( [int_scalar], data)
6364
else
6465
error stop 'Key is already present in the map.'
6566
end if
66-
call get(other, data)
67+
6768
select type (data)
6869
type is (dummy_type)
6970
print *, 'Other data % value = ', data%value
@@ -72,13 +73,13 @@ program example_get_other_data
7273
end select
7374

7475
! Example using character type key interface
75-
call map%map_entry( 'key_string', other, conflict)
76+
call map%map_entry( 'key_string', dummy, conflict)
7677
if (.not. conflict) then
77-
call map%get_other_data( 'key_string', other)
78+
call map%get_other_data( 'key_string', data)
7879
else
7980
error stop 'Key is already present in the map.'
8081
end if
81-
call get(other, data)
82+
8283
select type (data)
8384
type is (dummy_type)
8485
print *, 'Other data % value = ', data%value
@@ -88,13 +89,13 @@ program example_get_other_data
8889

8990
! Transfer to int8 arrays to generate key for unsupported types.
9091
key_array = transfer( [0_int64, 1_int64], [0_int8] )
91-
call map%map_entry( key_array, other, conflict)
92+
call map%map_entry( key_array, dummy, conflict)
9293
if (.not. conflict) then
93-
call map%get_other_data( key_array, other)
94+
call map%get_other_data( key_array, data)
9495
else
9596
error stop 'Key is already present in the map.'
9697
end if
97-
call get(other, data)
98+
9899
select type (data)
99100
type is (dummy_type)
100101
print *, 'Other data % value = ', data%value

example/hashmaps/example_hashmaps_map_entry.f90

Lines changed: 20 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -6,38 +6,49 @@ program example_map_entry
66
type(chaining_hashmap_type) :: map
77
type(key_type) :: key
88
logical :: conflict
9-
type(other_type) :: other
109
integer :: int_scalar
1110

11+
type :: array_data_wrapper
12+
integer, allocatable :: array(:)
13+
end type
14+
15+
type(array_data_wrapper) :: array_example
16+
17+
1218
! Initialize hashmap with 2^10 slots.
1319
! Hashmap will dynamically increase size if needed.
1420
call map%init(fnv_1_hasher, slots_bits=10)
15-
! Initialize other type with data to store.
16-
call set(other, 4)
1721

1822
! Explicitly set key using set function
1923
call set(key, [1, 2, 3])
20-
call map%map_entry(key, other, conflict)
24+
call map%map_entry(key, 4, conflict)
2125
print *, 'CONFLICT = ', conflict
2226

2327
! Using map_entry int32 array interface
24-
call map%map_entry( [4, 5, 6], other, conflict)
28+
call map%map_entry( [4, 5, 6], 4, conflict)
2529
print *, 'CONFLICT = ', conflict
2630

2731
! Integer scalars need to be passed as an array.
2832
int_scalar = 1
29-
call map%map_entry( [int_scalar], other, conflict)
33+
call map%map_entry( [int_scalar], 4, conflict)
3034
print *, 'CONFLICT = ', conflict
3135

3236
! Using map_entry character interface
33-
call map%map_entry( 'key_string', other, conflict)
37+
call map%map_entry( 'key_string', 4, conflict)
3438
print *, 'CONFLICT = ', conflict
3539

3640
! Transfer unsupported key types to int8 arrays.
37-
call map%map_entry( transfer( [1_int64, 2_int64, 3_int64], [0_int8] ), other, conflict)
41+
call map%map_entry( transfer( [1_int64, 2_int64, 3_int64], [0_int8] ), 4, conflict)
3842
print *, 'CONFLICT = ', conflict
3943

40-
! Keys can be mapped alone without a corresponding value (other).
44+
! Keys can be mapped alone without a corresponding value (other) for 'Set' type functionality.
4145
call map%map_entry( [7, 8, 9], conflict=conflict)
4246
print *, 'CONFLICT = ', conflict
47+
48+
! Currently only scalar data can be mapped.
49+
! Arrays will need a wrapper.
50+
array_example % array = [1,2,3,4,5]
51+
call map % map_entry( [10,11,12], array_example, conflict=conflict )
52+
print *, 'CONFLICT = ', conflict
53+
4354
end program example_map_entry

example/hashmaps/example_hashmaps_remove.f90

Lines changed: 6 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -6,41 +6,37 @@ program example_remove
66
implicit none
77
type(open_hashmap_type) :: map
88
type(key_type) :: key
9-
type(other_type) :: other
109
logical :: existed
1110
integer :: int_scalar
1211

1312
! Initialize hashmap with 2^10 slots.
1413
! Hashmap will dynamically increase size if needed.
1514
call map%init(fnv_1_hasher, slots_bits=10)
16-
17-
! Initialize other type with data to store.
18-
call set(other, 4.0)
19-
15+
2016
! Explicitly set key type using set function
2117
call set(key, [1, 2, 3])
22-
call map%map_entry(key, other)
18+
call map%map_entry(key, 4.0)
2319
call map%remove(key, existed)
2420
print *, "Removed key existed = ", existed
2521

2622
! Using map_entry and remove int32 generic interface.
27-
call map%map_entry([1, 2, 3], other)
23+
call map%map_entry([1, 2, 3], 4.0)
2824
call map%remove([1, 2, 3], existed)
2925
print *, "Removed key existed = ", existed
3026

3127
! Integer scalars need to be passed as an array.
3228
int_scalar = 1
33-
call map%map_entry( [int_scalar], other)
29+
call map%map_entry( [int_scalar], 4.0)
3430
call map%remove( [int_scalar], existed)
3531
print *, "Removed key existed = ", existed
3632

3733
! Using map_entry and remove character generic interface.
38-
call map%map_entry('key_string', other)
34+
call map%map_entry('key_string', 4.0)
3935
call map%remove('key_string', existed)
4036
print *, "Removed key existed = ", existed
4137

4238
! Use transfer to int8 arrays for unsupported key types.
43-
call map%map_entry( transfer( [1_int64, 2_int64], [0_int8] ), other)
39+
call map%map_entry( transfer( [1_int64, 2_int64], [0_int8] ), 4.0)
4440
call map%remove( transfer( [1_int64,2_int64], [0_int8] ), existed)
4541
print *, "Removed key existed = ", existed
4642
end program example_remove

example/hashmaps/example_hashmaps_set_other_data.f90

Lines changed: 16 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -5,18 +5,27 @@ program example_set_other_data
55
implicit none
66
logical :: exists
77
type(open_hashmap_type) :: map
8-
type(key_type) :: key
9-
type(other_type) :: other
8+
class(*), allocatable :: data
109

1110
! Initialize hashmap with 2^10 slots.
1211
! Hashmap will dynamically increase size if needed.
1312
call map%init(fnv_1_hasher, slots_bits=10)
14-
call set(key, [5, 7, 4, 13])
15-
call set(other, 'A value')
16-
call map%map_entry(key, other)
13+
14+
call map%map_entry([5, 7, 4, 13], 'A value')
15+
16+
call map%set_other_data([5, 7, 4, 13], 'Another value', exists)
1717

18-
call set(other, 'Another value')
19-
call map%set_other_data(key, other, exists)
2018
print *, 'The entry to have its other data replaced exists = ', exists
2119

20+
call map%get_other_data( [5, 7, 4, 13], data)
21+
22+
! Hashmaps return an unlimited polymorphic type as other.
23+
! Must be included in a select type operation to do further operations.
24+
select type (data)
25+
type is (character(*))
26+
print *, 'Value is = ', data
27+
class default
28+
print *, 'Invalid data type in other'
29+
end select
30+
2231
end program example_set_other_data

src/stdlib_hashmap_chaining.f90

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -327,7 +327,7 @@ module subroutine get_other_chaining_data( map, key, other, exists )
327327
!
328328
class(chaining_hashmap_type), intent(inout) :: map
329329
type(key_type), intent(in) :: key
330-
type(other_type), intent(out) :: other
330+
class(*), allocatable, intent(out) :: other
331331
logical, intent(out), optional :: exists
332332

333333
integer(int_index) :: inmap
@@ -345,7 +345,7 @@ module subroutine get_other_chaining_data( map, key, other, exists )
345345
end if
346346
else if ( associated( map % inverse(inmap) % target ) ) then
347347
if (present(exists) ) exists = .true.
348-
call copy_other( map % inverse(inmap) % target % other, other )
348+
other = map % inverse(inmap) % target % other
349349
else
350350
if ( present(exists) ) then
351351
exists = .false.
@@ -535,7 +535,7 @@ module subroutine map_chain_entry(map, key, other, conflict)
535535
!
536536
class(chaining_hashmap_type), intent(inout) :: map
537537
type(key_type), intent(in) :: key
538-
type(other_type), intent(in), optional :: other
538+
class(*), intent(in), optional :: other
539539
logical, intent(out), optional :: conflict
540540

541541
integer(int_hash) :: hash_index
@@ -568,8 +568,7 @@ module subroutine map_chain_entry(map, key, other, conflict)
568568
new_ent % next => map % slots(hash_index) % target
569569
map % slots(hash_index) % target => new_ent
570570
call copy_key( key, new_ent % key )
571-
if ( present(other) ) call copy_other( other, new_ent % other )
572-
571+
if ( present(other) ) new_ent % other = other
573572
if ( new_ent % inmap == 0 ) then
574573
map % num_entries = map % num_entries + 1
575574
inmap = map % num_entries
@@ -793,7 +792,7 @@ module subroutine set_other_chaining_data( map, key, other, exists )
793792
!
794793
class(chaining_hashmap_type), intent(inout) :: map
795794
type(key_type), intent(in) :: key
796-
type(other_type), intent(in) :: other
795+
class(*), intent(in) :: other
797796
logical, intent(out), optional :: exists
798797

799798
integer(int_index) :: inmap
@@ -811,9 +810,10 @@ module subroutine set_other_chaining_data( map, key, other, exists )
811810
end if
812811
else if ( associated( map % inverse(inmap) % target ) ) then
813812
associate( target => map % inverse(inmap) % target )
814-
call copy_other( other, target % other )
815-
if ( present(exists) ) exists = .true.
816-
return
813+
814+
target % other = other
815+
if ( present(exists) ) exists = .true.
816+
return
817817
end associate
818818
else
819819
error stop submodule_name // ' % ' // procedure // ': ' // &

0 commit comments

Comments
 (0)