@@ -157,7 +157,7 @@ Procedures to manipulate `key_type` data:
157157 ` key_in ` , to contents of the key, ` key_out ` .
158158
159159* ` get( key, value ) ` - extracts the contents of ` key ` into ` value ` ,
160- an ` int8 ` array, ' int32' array, or character string.
160+ an ` int8 ` array, ` int32 ` array, or character string.
161161
162162* ` free_key( key ) ` - frees the memory in ` key ` .
163163
@@ -474,9 +474,9 @@ is an `intent(in)` argument.
474474` other ` : shall be a scalar expression of type ` other_type ` . It
475475is an ` intent(in) ` argument.
476476
477- ` value ` : if the the first argument is of ` key_type ` ` value ` shall be
478- an allocatable default character string variable, or
479- an allocatable vector variable of type integer and kind ` int8 ` or
477+ ` value ` : if the the first argument is of ` key_type ` , ` value ` shall be
478+ an allocatable default ` character ` string variable, or
479+ an allocatable vector variable of type ` integer ` and kind ` int8 ` or
480480` int32 ` , otherwise the first argument is of ` other_type ` and ` value `
481481shall be an allocatable of ` class(*) ` . It is an ` intent(out) ` argument.
482482
@@ -751,8 +751,8 @@ is an `intent(out)` argument.
751751` other ` : shall be a scalar variable of type ` other_type ` . It
752752is an ` intent(out) ` argument.
753753
754- ` value ` : if the first argument is ` key ` ` value ` shall be a default
755- character string scalar expression, or a vector expression of type integer
754+ ` value ` : if the first argument is ` key ` , ` value ` shall be a default
755+ ` character ` string scalar expression, or a vector expression of type ` integer `
756756and kind ` int8 ` or ` int32 ` , while for a first argument of type
757757` other ` ` value ` shall be of type ` class(*) ` . It is an ` intent(in) `
758758argument.
@@ -790,6 +790,14 @@ overall structure and performance of the hash map object:`calls`,
790790` max_bits ` , ` int_calls ` , ` int_depth ` , ` int_index ` ,
791791` int_probes ` , ` success ` , ` alloc_fault ` , and ` array_size_error ` .
792792
793+ Generic key interfaces for ` key_test ` , ` map_entry ` , ` get_other_data ` ,
794+ ` remove ` , and ` set_other_data ` are povided so that the supported types
795+ of ` int8 ` arrays, ` int32 ` arrays and ` character ` scalars can be used in the
796+ key field as well as the base ` key ` type. So for ` key_test ` ,
797+ ` key_key_test ` specifies key type for the key field, ` int8_key_test ` is ` int8 `
798+ for the key field and so on. Procedures other than ` key_key_test ` will call
799+ the ` set ` function to generate a key type and pass to ` key_key_test ` .
800+
793801### The ` stdlib_hashmaps ` module's public constants
794802
795803The module defines several categories of public constants. Some are
@@ -924,6 +932,7 @@ The type's definition is below:
924932
925933``` fortran
926934 type, abstract :: hashmap_type
935+
927936 private
928937 integer(int_calls) :: call_count = 0
929938 integer(int_calls) :: probe_count = 0
@@ -932,22 +941,52 @@ The type's definition is below:
932941 integer(int_index) :: num_free = 0
933942 integer(int32) :: nbits = default_bits
934943 procedure(hasher_fun), pointer, nopass :: hasher => fnv_1_hasher
944+
935945 contains
946+
936947 procedure, non_overridable, pass(map) :: calls
937948 procedure, non_overridable, pass(map) :: entries
938949 procedure, non_overridable, pass(map) :: map_probes
939- procedure, non_overridable, pass(map) :: slots_bits
940950 procedure, non_overridable, pass(map) :: num_slots
941- procedure(get_all_keys), deferred, pass(map) :: get_all_keys
942- procedure(get_other), deferred, pass(map) :: get_other_data
943- procedure(init_map), deferred, pass(map) :: init
944- procedure(key_test), deferred, pass(map) :: key_test
945- procedure(loading), deferred, pass(map) :: loading
946- procedure(map_entry), deferred, pass(map) :: map_entry
947- procedure(rehash_map), deferred, pass(map) :: rehash
948- procedure(remove_entry), deferred, pass(map) :: remove
949- procedure(set_other), deferred, pass(map) :: set_other_data
950- procedure(total_depth), deferred, pass(map) :: total_depth
951+ procedure, non_overridable, pass(map) :: slots_bits
952+ procedure(get_all_keys), deferred, pass(map) :: get_all_keys
953+ procedure(init_map), deferred, pass(map) :: init
954+ procedure(loading), deferred, pass(map) :: loading
955+ procedure(rehash_map), deferred, pass(map) :: rehash
956+ procedure(total_depth), deferred, pass(map) :: total_depth
957+
958+ !! Generic interfaces for key types.
959+ procedure(key_key_test), deferred, pass(map) :: key_key_test
960+ procedure, non_overridable, pass(map) :: int8_key_test
961+ procedure, non_overridable, pass(map) :: int32_key_test
962+ procedure, non_overridable, pass(map) :: char_key_test
963+
964+ procedure(key_map_entry), deferred, pass(map) :: key_map_entry
965+ procedure, non_overridable, pass(map) :: int8_map_entry
966+ procedure, non_overridable, pass(map) :: int32_map_entry
967+ procedure, non_overridable, pass(map) :: char_map_entry
968+
969+ procedure(key_get_other_data), deferred, pass(map) :: key_get_other_data
970+ procedure, non_overridable, pass(map) :: int8_get_other_data
971+ procedure, non_overridable, pass(map) :: int32_get_other_data
972+ procedure, non_overridable, pass(map) :: char_get_other_data
973+
974+ procedure(key_remove_entry), deferred, pass(map) :: key_remove_entry
975+ procedure, non_overridable, pass(map) :: int8_remove_entry
976+ procedure, non_overridable, pass(map) :: int32_remove_entry
977+ procedure, non_overridable, pass(map) :: char_remove_entry
978+
979+ procedure(key_set_other_data), deferred, pass(map) :: key_set_other_data
980+ procedure, non_overridable, pass(map) :: int8_set_other_data
981+ procedure, non_overridable, pass(map) :: int32_set_other_data
982+ procedure, non_overridable, pass(map) :: char_set_other_data
983+
984+ generic, public :: key_test => key_key_test, int8_key_test, int32_key_test, char_key_test
985+ generic, public :: map_entry => key_map_entry, int8_map_entry, int32_map_entry, char_map_entry
986+ generic, public :: get_other_data => key_get_other_data, int8_get_other_data, int32_get_other_data, char_get_other_data
987+ generic, public :: remove => key_remove_entry, int8_remove_entry, int32_remove_entry, char_remove_entry
988+ generic, public :: set_other_data => key_set_other_data, int8_set_other_data, int32_set_other_data, char_set_other_data
989+
951990 end type hashmap_type
952991```
953992
@@ -1028,21 +1067,21 @@ as follows:
10281067``` fortran
10291068 type, extends(hashmap_type) :: chaining_hashmap_type
10301069 private
1031- type(chaining_map_entry_pool), pointer :: cache => null()
1032- type(chaining_map_entry_type), pointer :: free_list => null()
1033- type(chaining_map_entry_ptr), allocatable :: inverse(:)
1070+ type(chaining_map_entry_pool), pointer :: cache => null()
1071+ type(chaining_map_entry_type), pointer :: free_list => null()
1072+ type(chaining_map_entry_ptr), allocatable :: inverse(:)
10341073 type(chaining_map_entry_ptr), allocatable :: slots(:)
10351074 contains
10361075 procedure :: get_all_keys => get_all_chaining_keys
1037- procedure :: get_other_data => get_other_chaining_data
1076+ procedure :: key_get_other_data => get_other_chaining_data
10381077 procedure :: init => init_chaining_map
1039- procedure :: key => chaining_key_test
10401078 procedure :: loading => chaining_loading
1041- procedure :: map_entry => map_chain_entry
1079+ procedure :: key_map_entry => map_chain_entry
10421080 procedure :: rehash => rehash_chaining_map
1043- procedure :: remove => remove_chaining_entry
1044- procedure :: set_other_data => set_other_chaining_data
1081+ procedure :: key_remove_entry => remove_chaining_entry
1082+ procedure :: key_set_other_data => set_other_chaining_data
10451083 procedure :: total_depth => total_chaining_depth
1084+ procedure :: key_key_test => chaining_key_test
10461085 final :: free_chaining_map
10471086 end type chaining_hashmap_type
10481087```
@@ -1103,24 +1142,24 @@ It also implements all of the deferred procedures of the
11031142as follows:
11041143
11051144``` fortran
1106- type, extends(hashmap_type) :: open_hashmap_type
1107- private
1145+ type, extends(hashmap_type) :: open_hashmap_type
1146+ private
11081147 integer(int_index) :: index_mask = 2_int_index**default_bits-1
11091148 type(open_map_entry_pool), pointer :: cache => null()
1110- type(open_map_entry_list), pointer :: free_list => null()
1111- type(open_map_entry_ptr), allocatable :: inverse(:)
1112- integer(int_index), allocatable :: slots(:)
1149+ type(open_map_entry_list), pointer :: free_list => null()
1150+ type(open_map_entry_ptr), allocatable :: inverse(:)
1151+ integer(int_index), allocatable :: slots(:)
11131152 contains
11141153 procedure :: get_all_keys => get_all_open_keys
1115- procedure :: get_other_data => get_other_open_data
1154+ procedure :: key_get_other_data => get_other_open_data
11161155 procedure :: init => init_open_map
1117- procedure :: key_test => open_key_test
11181156 procedure :: loading => open_loading
1119- procedure :: map_entry => map_open_entry
1157+ procedure :: key_map_entry => map_open_entry
11201158 procedure :: rehash => rehash_open_map
1121- procedure :: remove => remove_open_entry
1122- procedure :: set_other_data => set_other_open_data
1159+ procedure :: key_remove_entry => remove_open_entry
1160+ procedure :: key_set_other_data => set_other_open_data
11231161 procedure :: total_depth => total_open_depth
1162+ procedure :: key_key_test => open_key_test
11241163 final :: free_open_map
11251164 end type open_hashmap_type
11261165```
@@ -1323,8 +1362,8 @@ Subroutine
13231362 ` intent(inout) ` argument. It will be
13241363 the hash map used to store and access the other data.
13251364
1326- ` key ` : shall be a scalar expression of type ` key_type ` . It
1327- is an ` intent(in) ` argument.
1365+ ` key ` : shall be a of type ` key_type ` scalar, ` character ` scalar, ` int8 ` array
1366+ or ` int32 ` array. It is an ` intent(in) ` argument.
13281367
13291368` other ` : shall be a variable of type ` other_data ` .
13301369 It is an ` intent(out) ` argument. It is the other data associated
@@ -1435,9 +1474,9 @@ Subroutine.
14351474It is an ` intent(inout) ` argument. It is the hash map whose entries
14361475are examined.
14371476
1438- ` key ` : shall be a scalar expression of type ` key_type ` . It
1439- is an ` intent(in) ` argument. It is a ` key ` whose presence in the ` map `
1440- is being examined.
1477+ ` key ` : shall be a of type ` key_type ` scalar, ` character ` scalar, ` int8 ` array
1478+ or ` int32 ` array. It is an ` intent(in) ` argument. It is a ` key ` whose
1479+ presence in the ` map ` is being examined.
14411480
14421481` present ` (optional): shall be a scalar variable of type default
14431482` logical ` . It is an intent(out) argument. It is a logical flag where
@@ -1516,9 +1555,9 @@ Subroutine
15161555is an ` intent(inout) ` argument. It is the hash map to receive the
15171556entry.
15181557
1519- ` key ` : shall be a scalar expression of type ` key_type ` .
1520- It is an ` intent(in) ` argument. It is the key for the entry to be
1521- placed in the table.
1558+ ` key ` : shall be a of type ` key_type ` scalar, ` character ` scalar, ` int8 ` array
1559+ or ` int32 ` array. It is an ` intent(in) ` argument. It is the key for the entry
1560+ to be placed in the table.
15221561
15231562` other ` (optional): shall be a scalar expression of type ` other_type ` .
15241563 It is an ` intent(in) ` argument. If present it is the other data to be
@@ -1677,9 +1716,9 @@ Subroutine
16771716It is an ` intent(inout) ` argument. It is the hash map with the element
16781717to be removed.
16791718
1680- ` key ` : shall be a scalar expression of type ` key_type ` . It
1681- is an ` intent(in) ` argument. It is the ` key ` identifying the entry
1682- to be removed.
1719+ ` key ` : shall be a of type ` key_type ` scalar, ` character ` scalar, ` int8 ` array
1720+ or ` int32 ` array. It is an ` intent(in) ` argument. It is the ` key ` identifying
1721+ the entry to be removed.
16831722
16841723` existed ` (optional): shall be a scalar variable of type default
16851724logical. It is an ` intent(out) ` argument. If present with the value
@@ -1719,9 +1758,9 @@ Subroutine
17191758is an ` intent(inout) ` argument. It will be a hash map used to store
17201759and access the entry's data.
17211760
1722- ` key ` : shall be a scalar expression of type ` key_type ` . It
1723- is an ` intent(in) ` argument. It is the ` key ` to the entry whose
1724- ` other ` data is to be replaced.
1761+ ` key ` : shall be a of type ` key_type ` scalar, ` character ` scalar, ` int8 ` array
1762+ or ` int32 ` array. It is an ` intent(in) ` argument. It is the ` key ` to the
1763+ entry whose ` other ` data is to be replaced.
17251764
17261765` other ` : shall be a scalar expression of type ` other_type ` .
17271766It is an ` intent(in) ` argument. It is the data to be stored as
0 commit comments