Skip to content

Commit 7fcc8e4

Browse files
committed
Initial commit
1 parent 6aa5177 commit 7fcc8e4

File tree

6 files changed

+198
-314
lines changed

6 files changed

+198
-314
lines changed

doc/specs/stdlib_hashmaps.md

Lines changed: 46 additions & 48 deletions
Original file line numberDiff line numberDiff line change
@@ -145,13 +145,12 @@ Procedures to manipulate `key_type` data:
145145
`key_in`, to contents of the key, `key_out`.
146146

147147
* `get( key, value )` - extracts the contents of `key` into `value`,
148-
an `int8` array, `int32` array, or character string.
148+
an `int8` array, `int32` array, or `character` string.
149149

150150
* `free_key( key )` - frees the memory in `key`.
151151

152-
* `set( key, value )` - sets the content of `key` to `value`.
153-
Supported key types are `int8` array, `int32` array, and character
154-
string.
152+
* `set( key, value )` - sets key type `key` based on `value`.
153+
Value may be a scalar or rank-1 array of any type.
155154

156155
Procedures to hash keys to 32 bit integers:
157156

@@ -409,7 +408,7 @@ Pure function prototype
409408

410409
##### Argument
411410

412-
`key`: Shall be a rank one array expression of type `integer(int8)`.
411+
`key`: Shall be a rank-1 array expression of type `integer(int8)`.
413412
It is an `intent(in)` argument.
414413

415414
##### Result character
@@ -646,14 +645,13 @@ Subroutine.
646645
`key`: shall be a scalar variable of type `key_type`. It
647646
is an `intent(out)` argument.
648647

649-
`value`: shall be a default `character` string scalar expression,
650-
or a vector expression of type `integer`and kind `int8` or `int32`.
648+
`value`: shall be a scalar or rank-1 array of any type.
651649
It is an `intent(in)` argument.
652650

653651
##### Note
654652

655-
Values of types other than a scalar default character or and
656-
`int8` or `int32` vector can be used as the basis of a `key` by transferring the
653+
Values of types not supported such as rank-2 or higher arrays
654+
can be used as the basis of a `key` by transferring the
657655
value to an `int8` vector.
658656

659657
##### Example
@@ -684,12 +682,14 @@ overall structure and performance of the hash map object:`calls`,
684682
`int_probes`, `success`, `alloc_fault`, and `array_size_error`.
685683

686684
Generic key interfaces for `key_test`, `map_entry`, `get_other_data`,
687-
`remove`, and `set_other_data` are povided so that the supported types
688-
of `int8` arrays, `int32` arrays and `character` scalars can be used in the
689-
key field as well as the base `key` type. So for `key_test`,
690-
`key_key_test` specifies key type for the key field, `int8_key_test` is `int8`
691-
for the key field and so on. Procedures other than `key_key_test` will call
692-
the `set` function to generate a key type and pass to `key_key_test`.
685+
`remove`, and `set_other_data` are povided so that scalar and rank-1
686+
values of any type can be provided as well as the base `key` type.
687+
So for `key_test`, `scalar_key_test` and `rank_one_key_test` are the generic
688+
interfaces for scalar and rank-1 values. A `key_type` will be generated
689+
based on those values and passed to `key_key_test`. If a key_type already
690+
is available, then `key_key_test` can be used instead of the generic `key_test`
691+
interface and may have slightly better performance since there is no
692+
select type construct used.
693693

694694
### The `stdlib_hashmaps` module's public constants
695695

@@ -850,37 +850,35 @@ The type's definition is below:
850850
procedure(rehash_map), deferred, pass(map) :: rehash
851851
procedure(total_depth), deferred, pass(map) :: total_depth
852852
853-
!! Generic interfaces for key types.
853+
!! Key_test procedures.
854854
procedure(key_key_test), deferred, pass(map) :: key_key_test
855-
procedure, non_overridable, pass(map) :: int8_key_test
856-
procedure, non_overridable, pass(map) :: int32_key_test
857-
procedure, non_overridable, pass(map) :: char_key_test
855+
procedure, non_overridable, pass(map) :: scalar_key_test
856+
procedure, non_overridable, pass(map) :: rank_one_key_test
857+
generic, public :: key_test => scalar_key_test, rank_one_key_test
858858
859+
! Map_entry procedures
859860
procedure(key_map_entry), deferred, pass(map) :: key_map_entry
860-
procedure, non_overridable, pass(map) :: int8_map_entry
861-
procedure, non_overridable, pass(map) :: int32_map_entry
862-
procedure, non_overridable, pass(map) :: char_map_entry
861+
procedure, non_overridable, pass(map) :: scalar_map_entry
862+
procedure, non_overridable, pass(map) :: rank_one_map_entry
863+
generic, public :: map_entry => scalar_map_entry, rank_one_map_entry
863864
864-
procedure(key_get_other_data), deferred, pass(map) :: key_get_other_data
865-
procedure, non_overridable, pass(map) :: int8_get_other_data
866-
procedure, non_overridable, pass(map) :: int32_get_other_data
867-
procedure, non_overridable, pass(map) :: char_get_other_data
865+
! Get_other_data procedures
866+
procedure(key_get_other_data), deferred, pass(map) :: key_get_other_data
867+
procedure, non_overridable, pass(map) :: scalar_get_other_data
868+
procedure, non_overridable, pass(map) :: rank_one_get_other_data
869+
generic, public :: get_other_data => scalar_get_other_data, rank_one_get_other_data
868870
871+
! Key_remove_entry procedures
869872
procedure(key_remove_entry), deferred, pass(map) :: key_remove_entry
870-
procedure, non_overridable, pass(map) :: int8_remove_entry
871-
procedure, non_overridable, pass(map) :: int32_remove_entry
872-
procedure, non_overridable, pass(map) :: char_remove_entry
873+
procedure, non_overridable, pass(map) :: scalar_remove_entry
874+
procedure, non_overridable, pass(map) :: rank_one_remove_entry
875+
generic, public :: remove => scalar_remove_entry, rank_one_remove_entry
873876
877+
! Set_other_data procedures
874878
procedure(key_set_other_data), deferred, pass(map) :: key_set_other_data
875-
procedure, non_overridable, pass(map) :: int8_set_other_data
876-
procedure, non_overridable, pass(map) :: int32_set_other_data
877-
procedure, non_overridable, pass(map) :: char_set_other_data
878-
879-
generic, public :: key_test => key_key_test, int8_key_test, int32_key_test, char_key_test
880-
generic, public :: map_entry => key_map_entry, int8_map_entry, int32_map_entry, char_map_entry
881-
generic, public :: get_other_data => key_get_other_data, int8_get_other_data, int32_get_other_data, char_get_other_data
882-
generic, public :: remove => key_remove_entry, int8_remove_entry, int32_remove_entry, char_remove_entry
883-
generic, public :: set_other_data => key_set_other_data, int8_set_other_data, int32_set_other_data, char_set_other_data
879+
procedure, non_overridable, pass(map) :: scalar_set_other_data
880+
procedure, non_overridable, pass(map) :: rank_one_set_other_data
881+
generic, public :: set_other_data => scalar_set_other_data, rank_one_set_other_data
884882
885883
end type hashmap_type
886884
```
@@ -1263,8 +1261,8 @@ Subroutine
12631261
`intent(inout)` argument. It will be
12641262
the hash map used to store and access the other data.
12651263

1266-
`key`: shall be a of type `key_type` scalar, `character` scalar, `int8` array
1267-
or `int32` array. It is an `intent(in)` argument.
1264+
`key`: shall be a scalar or rank-1 array of any type.
1265+
It is an `intent(in)` argument.
12681266

12691267
`other`: shall be a allocatable unlimited polymorphic scalar.
12701268
(class(*), allocatable) It is an `intent(out)` argument.
@@ -1375,8 +1373,8 @@ Subroutine.
13751373
It is an `intent(inout)` argument. It is the hash map whose entries
13761374
are examined.
13771375

1378-
`key`: shall be a of type `key_type` scalar, `character` scalar, `int8` array
1379-
or `int32` array. It is an `intent(in)` argument. It is a `key` whose
1376+
`key`: shall be a scalar or rank-1 array of any type.
1377+
It is an `intent(in)` argument. It is a `key` whose
13801378
presence in the `map` is being examined.
13811379

13821380
`present`: shall be a scalar variable of type `logical`.
@@ -1456,8 +1454,8 @@ Subroutine
14561454
is an `intent(inout)` argument. It is the hash map to receive the
14571455
entry.
14581456

1459-
`key`: shall be a of type `key_type` scalar, `character` scalar, `int8` array
1460-
or `int32` array. It is an `intent(in)` argument. It is the key for the entry
1457+
`key`: shall be a scalar or rank-1 array of any type.
1458+
It is an `intent(in)` argument. It is the key for the entry
14611459
to be placed in the table.
14621460

14631461
`other` (optional): shall be a scalar of any type, including derived types.
@@ -1621,8 +1619,8 @@ Subroutine
16211619
It is an `intent(inout)` argument. It is the hash map with the element
16221620
to be removed.
16231621

1624-
`key`: shall be a of type `key_type` scalar, `character` scalar, `int8` array
1625-
or `int32` array. It is an `intent(in)` argument. It is the `key` identifying
1622+
`key`: shall be a scalar or rank-1 array of any type.
1623+
It is an `intent(in)` argument. It is the `key` identifying
16261624
the entry to be removed.
16271625

16281626
`existed` (optional): shall be a scalar variable of type default
@@ -1664,8 +1662,8 @@ Subroutine
16641662
is an `intent(inout)` argument. It will be a hash map used to store
16651663
and access the entry's data.
16661664

1667-
`key`: shall be a of type `key_type` scalar, `character` scalar, `int8` array
1668-
or `int32` array. It is an `intent(in)` argument. It is the `key` to the
1665+
`key`: shall be a scalar or rank-1 array of any type.
1666+
It is an `intent(in)` argument. It is the `key` to the
16691667
entry whose `other` data is to be replaced.
16701668

16711669
`other` (optional): shall be a scalar of any type, including derived types.

example/hashmaps/example_hashmaps_get_all_keys.f90

Lines changed: 3 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -12,14 +12,11 @@ program example_hashmaps_get_all_keys
1212
character(:), allocatable :: str
1313

1414
! adding key-value pairs to the map
15-
call set(key, "initial key")
16-
call map%map_entry(key, "value 1")
15+
call map%map_entry("initial key", "value 1")
1716

18-
call set(key, "second key")
19-
call map%map_entry(key, "value 2")
17+
call map%map_entry("second key", "value 2")
2018

21-
call set(key, "last key")
22-
call map%map_entry(key, "value 3")
19+
call map%map_entry("last key", "value 3")
2320

2421
! getting all the keys in the map
2522
call map%get_all_keys(keys)

example/hashmaps/example_hashmaps_get_other_data.f90

Lines changed: 25 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@ program example_get_other_data
1212
type(dummy_type) :: dummy
1313
class(*), allocatable :: data
1414
integer(int8), allocatable :: key_array(:)
15-
integer :: int_scalar
15+
integer :: int_scalar, unsupported_key(3,3)
1616

1717
! Hashmap functions are setup to store scalar value types (other). Use a dervied
1818
! type wrapper to store arrays.
@@ -36,8 +36,7 @@ program example_get_other_data
3636
print *, 'Invalid data type in other'
3737
end select
3838

39-
! Also can use map_entry and get_other_data generic key interfaces.
40-
! This is an exmple with integer arrays.
39+
! Can also just provide key values direct to most hashmap routines.
4140
call map%map_entry( [2,3], dummy, conflict)
4241
if (.not. conflict) then
4342
call map%get_other_data( [2,3], data)
@@ -46,26 +45,26 @@ program example_get_other_data
4645
end if
4746

4847
select type (data)
49-
type is (dummy_type)
50-
print *, 'Other data % value = ', data%value
51-
class default
52-
print *, 'Invalid data type in other'
48+
type is (dummy_type)
49+
print *, 'Other data % value = ', data%value
50+
class default
51+
print *, 'Invalid data type in other'
5352
end select
5453

55-
! Integer scalar keys need to be passed as an array.
54+
! Scalar and rank one objects of any type can be used as keys.
5655
int_scalar = 2
57-
call map%map_entry( [int_scalar], dummy, conflict)
56+
call map%map_entry( int_scalar, dummy, conflict)
5857
if (.not. conflict) then
59-
call map%get_other_data( [int_scalar], data)
58+
call map%get_other_data( int_scalar, data)
6059
else
6160
error stop 'Key is already present in the map.'
6261
end if
6362

6463
select type (data)
65-
type is (dummy_type)
66-
print *, 'Other data % value = ', data%value
67-
class default
68-
print *, 'Invalid data type in other'
64+
type is (dummy_type)
65+
print *, 'Other data % value = ', data%value
66+
class default
67+
print *, 'Invalid data type in other'
6968
end select
7069

7170
! Example using character type key interface
@@ -77,26 +76,26 @@ program example_get_other_data
7776
end if
7877

7978
select type (data)
80-
type is (dummy_type)
81-
print *, 'Other data % value = ', data%value
82-
class default
83-
print *, 'Invalid data type in other'
79+
type is (dummy_type)
80+
print *, 'Other data % value = ', data%value
81+
class default
82+
print *, 'Invalid data type in other'
8483
end select
8584

86-
! Transfer to int8 arrays to generate key for unsupported types.
87-
key_array = transfer( [0_int64, 1_int64], [0_int8] )
88-
call map%map_entry( key_array, dummy, conflict)
85+
! Rank 2 or higher keys not directly supported. Transfer to int8 arrays to generate keys.
86+
call set(key, transfer(unsupported_key,[0_int8]))
87+
call map%map_entry( key, dummy, conflict)
8988
if (.not. conflict) then
90-
call map%get_other_data( key_array, data)
89+
call map%get_other_data( key, data)
9190
else
9291
error stop 'Key is already present in the map.'
9392
end if
9493

9594
select type (data)
96-
type is (dummy_type)
97-
print *, 'Other data % value = ', data%value
98-
class default
99-
print *, 'Invalid data type in other'
95+
type is (dummy_type)
96+
print *, 'Other data % value = ', data%value
97+
class default
98+
print *, 'Invalid data type in other'
10099
end select
101100

102101
end program example_get_other_data

example/hashmaps/example_hashmaps_map_entry.f90

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -6,14 +6,15 @@ program example_map_entry
66
type(chaining_hashmap_type) :: map
77
type(key_type) :: key
88
logical :: conflict
9-
integer :: int_scalar
109

1110
type :: array_data_wrapper
1211
integer, allocatable :: array(:)
1312
end type
1413

1514
type(array_data_wrapper) :: array_example
1615

16+
integer :: unsupported_key(3,3)
17+
1718
! Initialize hashmap with 2^10 slots.
1819
! Hashmap will dynamically increase size if needed.
1920
call map%init(slots_bits=10)
@@ -23,21 +24,20 @@ program example_map_entry
2324
call map%map_entry(key, 4, conflict)
2425
print *, 'CONFLICT = ', conflict
2526

26-
! Using map_entry int32 array interface
27+
! Using the set function is not required. Can input key into the map_entry key fied.
2728
call map%map_entry( [4, 5, 6], 4, conflict)
2829
print *, 'CONFLICT = ', conflict
2930

30-
! Integer scalars need to be passed as an array.
31-
int_scalar = 1
32-
call map%map_entry( [int_scalar], 4, conflict)
31+
! Scalars can also be used as keys.
32+
call map%map_entry( 1, 4, conflict)
3333
print *, 'CONFLICT = ', conflict
3434

35-
! Using map_entry character interface
35+
! Any type of scalar or rank 1 array can be used as a key.
3636
call map%map_entry( 'key_string', 4, conflict)
3737
print *, 'CONFLICT = ', conflict
3838

39-
! Transfer unsupported key types to int8 arrays.
40-
call map%map_entry( transfer( [1_int64, 2_int64, 3_int64], [0_int8] ), 4, conflict)
39+
! A rank 2 or higher array can used as a key by transfering to an int8 array.
40+
call map%map_entry( transfer( unsupported_key, [0_int8] ), 4, conflict)
4141
print *, 'CONFLICT = ', conflict
4242

4343
! Keys can be mapped alone without a corresponding value (other) for 'Set' type functionality.

0 commit comments

Comments
 (0)