Type implementing the chaining_hashmap_type
types
(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 all the keys contained in a hashmap Arguments: map - an chaining hash map all_keys - all the keys contained in a hash map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(chaining_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), and SIZE(map % slots) limited to a maximum of 2MAX_BITS. All fields are initialized. Arguments: map - the chaining hash map to be initialized hasher - the hash function to be used to map keys to slots slots_bits - the bits of two used to initialize the number of 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 is less than default_bits or greater than max_bits
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(chaining_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 chaining hash table 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(chaining_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 is present in the hash map Arguments: map - the hash map of interest key - the key of interest present - a logical flag indicating whether key is present in map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(chaining_hashmap_type), | intent(inout) | :: | map | |||
type(key_type), | intent(in) | :: | key | |||
logical, | intent(out) | :: | present |
map - the hash table of interest key - the key identifying the entry other - other data associated with the key conflict - logical flag indicating whether the entry key conflicts with an existing key
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(chaining_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(chaining_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(chaining_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 Arguments: map - a chaining hash map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(chaining_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(chaining_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 |
Returns the total number of ones based offsets of slot entries from their slot index for a hash map Arguments: map - an chaining hash map
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(chaining_hashmap_type), | intent(in) | :: | map |
type, extends(hashmap_type) :: chaining_hashmap_type !! Version: Experimental !! !! Type implementing the `chaining_hashmap_type` types !! ([Specifications](../page/specs/stdlib_hashmaps.html#the-chaining_hashmap_type-derived-type)) private type(chaining_map_entry_pool), pointer :: cache => null() !! Pool of allocated chaining_map_entry_type objects type(chaining_map_entry_type), pointer :: free_list => null() !! free list of map entries type(chaining_map_entry_ptr), allocatable :: inverse(:) !! Array of bucket lists (inverses) Note max_elts=size(inverse) type(chaining_map_entry_ptr), allocatable :: slots(:) !! Array of bucket lists Note # slots=size(slots) contains procedure :: get_all_keys => get_all_chaining_keys procedure :: key_get_other_data => get_other_chaining_data procedure :: init => init_chaining_map procedure :: loading => chaining_loading procedure :: key_map_entry => map_chain_entry procedure :: rehash => rehash_chaining_map procedure :: key_remove_entry => remove_chaining_entry procedure :: key_set_other_data => set_other_chaining_data procedure :: total_depth => total_chaining_depth procedure :: key_key_test => chaining_key_test final :: free_chaining_map end type chaining_hashmap_type