Type implementing an abstract hash map (Specifications)
Returns the number of subroutine calls on an open hash map (Specifications)
Arguments: map - an open hash map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(in) | :: | map |
Character key generic interface for get_other_data function
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
character(len=*), | intent(in) | :: | value | |||
type(other_type), | intent(out) | :: | other | |||
logical, | intent(out), | optional | :: | exists |
Returns a logical flag indicating whether KEY exists in the hash map (Specifications)
Arguments:
map - the hash map of interest
value - char array that is the key to lookup.
present - a flag indicating whether key is present in the map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
character(len=*), | intent(in) | :: | value | |||
logical, | intent(out) | :: | present |
Inserts an entry into the hash table (Specifications)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
character(len=*), | intent(in) | :: | value | |||
type(other_type), | intent(in), | optional | :: | other | ||
logical, | intent(out), | optional | :: | conflict |
Remove the entry, if any, that has the key Arguments: map - the table from which the entry is to be removed key - the key to an entry existed - a logical flag indicating whether an entry with the key was present in the original map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
character(len=*), | intent(in) | :: | value | |||
logical, | intent(out), | optional | :: | existed |
Change the other data associated with the key Arguments: map - the map with the entry of interest value - the char value key to the entry inthe map other - the new data to be associated with the key exists - a logical flag indicating whether the key is already entered in the map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
character(len=*), | intent(in) | :: | value | |||
type(other_type), | intent(in) | :: | other | |||
logical, | intent(out), | optional | :: | exists |
Returns the number of entries in a hash map (Specifications)
Arguments: map - an open hash map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(in) | :: | map |
Returns the all keys contained in a hash map (Specifications)
Arguments: map - a hash map all_keys - all the keys contained in a hash map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(in) | :: | map | |||
type(key_type), | intent(out), | allocatable | :: | all_keys(:) |
Int8 key generic interface for get_other_data function
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
integer(kind=int8), | intent(in) | :: | value(:) | |||
type(other_type), | intent(out) | :: | other | |||
logical, | intent(out), | optional | :: | exists |
Int32 key generic interface for get_other_data function
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
integer(kind=int32), | intent(in) | :: | value(:) | |||
type(other_type), | intent(out) | :: | other | |||
logical, | intent(out), | optional | :: | exists |
Character key generic interface for get_other_data function
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
character(len=*), | intent(in) | :: | value | |||
type(other_type), | intent(out) | :: | other | |||
logical, | intent(out), | optional | :: | exists |
Routine to allocate an empty map with HASHER as the hash function, 2SLOTS_BITS initial SIZE(map % slots), SIZE(map % slots) limited to a maximum of 2MAX_BITS, and with up to LOAD_FACTOR * SIZE(map % slots), map % inverse elements. All fields are initialized. Arguments: map - the hash maap to be initialized hasher - the hash function to be used to map keys to slots slots_bits - the number of bits initially used to map to the slots status - an integer error status flag with the allowed values: success - no problems were found alloc_fault - map % slots or map % inverse could not be allocated array_size_error - slots_bits or max_bits is less than default_bits or greater than strict_max_bits real_value_error - load_factor is less than 0.375 or greater than 0.875
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(out) | :: | map | |||
procedure(hasher_fun) | :: | hasher | ||||
integer, | intent(in), | optional | :: | slots_bits | ||
integer(kind=int32), | intent(out), | optional | :: | status |
Int32 key generic interface for get_other_data function
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
integer(kind=int32), | intent(in) | :: | value(:) | |||
type(other_type), | intent(out) | :: | other | |||
logical, | intent(out), | optional | :: | exists |
Returns a logical flag indicating whether KEY exists in the hash map (Specifications)
Arguments:
map - the hash map of interest
value - int32 array that is the key to lookup.
present - a flag indicating whether key is present in the map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
integer(kind=int32), | intent(in) | :: | value(:) | |||
logical, | intent(out) | :: | present |
Inserts an entry into the hash table (Specifications)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
integer(kind=int32), | intent(in) | :: | value(:) | |||
type(other_type), | intent(in), | optional | :: | other | ||
logical, | intent(out), | optional | :: | conflict |
Remove the entry, if any, that has the key Arguments: map - the table from which the entry is to be removed key - the key to an entry existed - a logical flag indicating whether an entry with the key was present in the original map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
integer(kind=int32), | intent(in) | :: | value(:) | |||
logical, | intent(out), | optional | :: | existed |
Change the other data associated with the key Arguments: map - the map with the entry of interest value - the int32 array key to the entry inthe map other - the new data to be associated with the key exists - a logical flag indicating whether the key is already entered in the map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
integer(kind=int32), | intent(in) | :: | value(:) | |||
type(other_type), | intent(in) | :: | other | |||
logical, | intent(out), | optional | :: | exists |
Int8 key generic interface for get_other_data function
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
integer(kind=int8), | intent(in) | :: | value(:) | |||
type(other_type), | intent(out) | :: | other | |||
logical, | intent(out), | optional | :: | exists |
Returns a logical flag indicating whether KEY exists in the hash map (Specifications)
Arguments:
map - the hash map of interest
value - int8 array that is the key to lookup.
present - a flag indicating whether key is present in the map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
integer(kind=int8), | intent(in) | :: | value(:) | |||
logical, | intent(out) | :: | present |
Int8 generic interface for map entry (Specifications)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
integer(kind=int8), | intent(in) | :: | value(:) | |||
type(other_type), | intent(in), | optional | :: | other | ||
logical, | intent(out), | optional | :: | conflict |
Remove the entry, if any, that has the key Arguments: map - the table from which the entry is to be removed value - the int8 array key to an entry existed - a logical flag indicating whether an entry with the key was present in the original map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
integer(kind=int8), | intent(in) | :: | value(:) | |||
logical, | intent(out), | optional | :: | existed |
Change the other data associated with the key Arguments: map - the map with the entry of interest value - the int8 array key to the entry inthe map other - the new data to be associated with the key exists - a logical flag indicating whether the key is already entered in the map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
integer(kind=int8), | intent(in) | :: | value(:) | |||
type(other_type), | intent(in) | :: | other | |||
logical, | intent(out), | optional | :: | exists |
Returns the other data associated with the inverse table index Arguments: map - a hash map key - the key associated with a map entry other - the other data associated with the key exists - a logical flag indicating whether an entry with that key exists
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
type(key_type), | intent(in) | :: | key | |||
type(other_type), | intent(out) | :: | other | |||
logical, | intent(out), | optional | :: | exists |
Returns a logical flag indicating whether KEY exists in the hash map (Specifications)
Arguments: map - the hash map of interest key - the key of interest present - a flag indicating whether key is present in the map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
type(key_type), | intent(in) | :: | key | |||
logical, | intent(out) | :: | present |
Inserts an entry into the hash table (Specifications)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
type(key_type), | intent(in) | :: | key | |||
type(other_type), | intent(in), | optional | :: | other | ||
logical, | intent(out), | optional | :: | conflict |
Remove the entry, if any, that has the key Arguments: map - the table from which the entry is to be removed key - the key to an entry existed - a logical flag indicating whether an entry with the key was present in the original map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
type(key_type), | intent(in) | :: | key | |||
logical, | intent(out), | optional | :: | existed |
Change the other data associated with the key Arguments: map - the map with the entry of interest key - the key to the entry inthe map other - the new data to be associated with the key exists - a logical flag indicating whether the key is already entered in the map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
type(key_type), | intent(in) | :: | key | |||
type(other_type), | intent(in) | :: | other | |||
logical, | intent(out), | optional | :: | exists |
Returns a logical flag indicating whether KEY exists in the hash map (Specifications)
Arguments:
map - the hash map of interest
value - int8 array that is the key to lookup.
present - a flag indicating whether key is present in the map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
integer(kind=int8), | intent(in) | :: | value(:) | |||
logical, | intent(out) | :: | present |
Returns a logical flag indicating whether KEY exists in the hash map (Specifications)
Arguments:
map - the hash map of interest
value - int32 array that is the key to lookup.
present - a flag indicating whether key is present in the map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
integer(kind=int32), | intent(in) | :: | value(:) | |||
logical, | intent(out) | :: | present |
Returns a logical flag indicating whether KEY exists in the hash map (Specifications)
Arguments:
map - the hash map of interest
value - char array that is the key to lookup.
present - a flag indicating whether key is present in the map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
character(len=*), | intent(in) | :: | value | |||
logical, | intent(out) | :: | present |
Returns the number of entries relative to slots in a hash map (Specifications)
Arguments: map - a hash map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(in) | :: | map |
Int8 generic interface for map entry (Specifications)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
integer(kind=int8), | intent(in) | :: | value(:) | |||
type(other_type), | intent(in), | optional | :: | other | ||
logical, | intent(out), | optional | :: | conflict |
Inserts an entry into the hash table (Specifications)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
integer(kind=int32), | intent(in) | :: | value(:) | |||
type(other_type), | intent(in), | optional | :: | other | ||
logical, | intent(out), | optional | :: | conflict |
Inserts an entry into the hash table (Specifications)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
character(len=*), | intent(in) | :: | value | |||
type(other_type), | intent(in), | optional | :: | other | ||
logical, | intent(out), | optional | :: | conflict |
Returns the total number of table probes on a hash map (Specifications)
Arguments: map - an open hash map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(in) | :: | map |
Returns the number of allocated slots in a hash map (Specifications)
Arguments: map - an open hash map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(in) | :: | map |
Changes the hashing method of the table entries to that of HASHER. Arguments: map the table to be rehashed hasher the hasher function to be used for the table
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
procedure(hasher_fun) | :: | hasher |
Remove the entry, if any, that has the key Arguments: map - the table from which the entry is to be removed value - the int8 array key to an entry existed - a logical flag indicating whether an entry with the key was present in the original map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
integer(kind=int8), | intent(in) | :: | value(:) | |||
logical, | intent(out), | optional | :: | existed |
Remove the entry, if any, that has the key Arguments: map - the table from which the entry is to be removed key - the key to an entry existed - a logical flag indicating whether an entry with the key was present in the original map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
integer(kind=int32), | intent(in) | :: | value(:) | |||
logical, | intent(out), | optional | :: | existed |
Remove the entry, if any, that has the key Arguments: map - the table from which the entry is to be removed key - the key to an entry existed - a logical flag indicating whether an entry with the key was present in the original map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
character(len=*), | intent(in) | :: | value | |||
logical, | intent(out), | optional | :: | existed |
Change the other data associated with the key Arguments: map - the map with the entry of interest value - the int8 array key to the entry inthe map other - the new data to be associated with the key exists - a logical flag indicating whether the key is already entered in the map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
integer(kind=int8), | intent(in) | :: | value(:) | |||
type(other_type), | intent(in) | :: | other | |||
logical, | intent(out), | optional | :: | exists |
Change the other data associated with the key Arguments: map - the map with the entry of interest value - the int32 array key to the entry inthe map other - the new data to be associated with the key exists - a logical flag indicating whether the key is already entered in the map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
integer(kind=int32), | intent(in) | :: | value(:) | |||
type(other_type), | intent(in) | :: | other | |||
logical, | intent(out), | optional | :: | exists |
Change the other data associated with the key Arguments: map - the map with the entry of interest value - the char value key to the entry inthe map other - the new data to be associated with the key exists - a logical flag indicating whether the key is already entered in the map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(inout) | :: | map | |||
character(len=*), | intent(in) | :: | value | |||
type(other_type), | intent(in) | :: | other | |||
logical, | intent(out), | optional | :: | exists |
Returns the number of bits used to specify the number of allocated slots in a hash map (Specifications)
Arguments: map - an open hash map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(in) | :: | map |
Key_test procedures.
Returns the total number of ones based offsets of slot entriesyy from their slot index for a hash map (Specifications) Arguments: map - a hash map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(hashmap_type), | intent(in) | :: | map |
type, abstract :: hashmap_type !! Version: Experimental !! !! Type implementing an abstract hash map !! ([Specifications](../page/specs/stdlib_hashmaps.html#the-hashmap_type-abstract-type)) private integer(int_calls) :: call_count = 0 !! Number of calls integer(int_calls) :: probe_count = 0 !! Number of probes since last expansion integer(int_calls) :: total_probes = 0 !! Cumulative number of probes integer(int_index) :: num_entries = 0 !! Number of entries integer(int_index) :: num_free = 0 !! Number of elements in the free_list integer(int32) :: nbits = default_bits !! Number of bits used to address the slots procedure(hasher_fun), pointer, nopass :: hasher => fnv_1_hasher !! Hash function contains procedure, non_overridable, pass(map) :: calls procedure, non_overridable, pass(map) :: entries procedure, non_overridable, pass(map) :: map_probes procedure, non_overridable, pass(map) :: num_slots procedure, non_overridable, pass(map) :: slots_bits procedure(get_all_keys), deferred, pass(map) :: get_all_keys procedure(init_map), deferred, pass(map) :: init procedure(loading), deferred, pass(map) :: loading procedure(rehash_map), deferred, pass(map) :: rehash procedure(total_depth), deferred, pass(map) :: total_depth !! Key_test procedures. procedure(key_key_test), deferred, pass(map) :: key_key_test procedure, non_overridable, pass(map) :: int8_key_test procedure, non_overridable, pass(map) :: int32_key_test procedure, non_overridable, pass(map) :: char_key_test generic, public :: key_test => key_key_test, int8_key_test, int32_key_test, char_key_test ! Map_entry procedures procedure(key_map_entry), deferred, pass(map) :: key_map_entry procedure, non_overridable, pass(map) :: int8_map_entry procedure, non_overridable, pass(map) :: int32_map_entry procedure, non_overridable, pass(map) :: char_map_entry generic, public :: map_entry => key_map_entry, int8_map_entry, int32_map_entry, char_map_entry ! Get_other_data procedures procedure(key_get_other_data), deferred, pass(map) :: key_get_other_data procedure, non_overridable, pass(map) :: int8_get_other_data procedure, non_overridable, pass(map) :: int32_get_other_data procedure, non_overridable, pass(map) :: char_get_other_data generic, public :: get_other_data => key_get_other_data, int8_get_other_data, int32_get_other_data, char_get_other_data ! Key_remove_entry procedures procedure(key_remove_entry), deferred, pass(map) :: key_remove_entry procedure, non_overridable, pass(map) :: int8_remove_entry procedure, non_overridable, pass(map) :: int32_remove_entry procedure, non_overridable, pass(map) :: char_remove_entry generic, public :: remove => key_remove_entry, int8_remove_entry, int32_remove_entry, char_remove_entry ! Set_other_data procedures procedure(key_set_other_data), deferred, pass(map) :: key_set_other_data procedure, non_overridable, pass(map) :: int8_set_other_data procedure, non_overridable, pass(map) :: int32_set_other_data procedure, non_overridable, pass(map) :: char_set_other_data generic, public :: set_other_data => key_set_other_data, int8_set_other_data, int32_set_other_data, char_set_other_data end type hashmap_type