@@ -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
156155Procedures 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) ` .
413412It 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
647646is 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.
651649It 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
657655value 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
686684Generic 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.
13751373It is an ` intent(inout) ` argument. It is the hash map whose entries
13761374are 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
13801378presence in the ` map ` is being examined.
13811379
13821380` present ` : shall be a scalar variable of type ` logical ` .
@@ -1456,8 +1454,8 @@ Subroutine
14561454is an ` intent(inout) ` argument. It is the hash map to receive the
14571455entry.
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
14611459to be placed in the table.
14621460
14631461` other ` (optional): shall be a scalar of any type, including derived types.
@@ -1621,8 +1619,8 @@ Subroutine
16211619It is an ` intent(inout) ` argument. It is the hash map with the element
16221620to 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
16261624the entry to be removed.
16271625
16281626` existed ` (optional): shall be a scalar variable of type default
@@ -1664,8 +1662,8 @@ Subroutine
16641662is an ` intent(inout) ` argument. It will be a hash map used to store
16651663and 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
16691667entry whose ` other ` data is to be replaced.
16701668
16711669` other ` (optional): shall be a scalar of any type, including derived types.
0 commit comments