hashmap_type Derived Type

type, public :: hashmap_type

Type implementing an abstract hash map (Specifications)


Type-Bound Procedures

procedure, public, non_overridable, pass(map) :: calls

  • private pure function calls(map)

    Returns the number of subroutine calls on an open hash map (Specifications)

    Arguments: map - an open hash map

    Arguments

    Type IntentOptional Attributes Name
    class(hashmap_type), intent(in) :: map

    Return Value integer(kind=int_calls)

procedure, public, non_overridable, pass(map) :: entries

  • private pure function entries(map)

    Returns the number of entries in a hash map (Specifications)

    Arguments: map - an open hash map

    Arguments

    Type IntentOptional Attributes Name
    class(hashmap_type), intent(in) :: map

    Return Value integer(kind=int_index)

procedure(get_all_keys), public, deferred, pass(map) :: get_all_keys

  • subroutine get_all_keys(map, all_keys) Prototype

    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

    Arguments

    Type IntentOptional Attributes Name
    class(hashmap_type), intent(in) :: map
    type(key_type), intent(out), allocatable :: all_keys(:)

procedure(get_other), public, deferred, pass(map) :: get_other_data

  • subroutine get_other(map, key, other, exists) Prototype

    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

    Arguments

    Type IntentOptional 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

procedure(init_map), public, deferred, pass(map) :: init

  • subroutine init_map(map, hasher, slots_bits, status) Prototype

    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

    Arguments

    Type IntentOptional 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

procedure(key_test), public, deferred, pass(map) :: key_test

  • subroutine key_test(map, key, present) Prototype

    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

    Arguments

    Type IntentOptional Attributes Name
    class(hashmap_type), intent(inout) :: map
    type(key_type), intent(in) :: key
    logical, intent(out) :: present

procedure(loading), public, deferred, pass(map) :: loading

  • pure function loading(map) Prototype

    Returns the number of entries relative to slots in a hash map (Specifications)

    Arguments: map - a hash map

    Arguments

    Type IntentOptional Attributes Name
    class(hashmap_type), intent(in) :: map

    Return Value real

procedure(map_entry), public, deferred, pass(map) :: map_entry

  • subroutine map_entry(map, key, other, conflict) Prototype

    Inserts an entry into the hash table (Specifications)

    Arguments

    Type IntentOptional 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

procedure, public, non_overridable, pass(map) :: map_probes

  • private pure function map_probes(map)

    Returns the total number of table probes on a hash map (Specifications)

    Arguments: map - an open hash map

    Arguments

    Type IntentOptional Attributes Name
    class(hashmap_type), intent(in) :: map

    Return Value integer(kind=int_calls)

procedure, public, non_overridable, pass(map) :: num_slots

  • private pure function num_slots(map)

    Returns the number of allocated slots in a hash map (Specifications)

    Arguments: map - an open hash map

    Arguments

    Type IntentOptional Attributes Name
    class(hashmap_type), intent(in) :: map

    Return Value integer(kind=int_index)

procedure(rehash_map), public, deferred, pass(map) :: rehash

  • subroutine rehash_map(map, hasher) Prototype

    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

    Arguments

    Type IntentOptional Attributes Name
    class(hashmap_type), intent(inout) :: map
    procedure(hasher_fun) :: hasher

procedure(remove_entry), public, deferred, pass(map) :: remove

  • subroutine remove_entry(map, key, existed) Prototype

    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

    Arguments

    Type IntentOptional Attributes Name
    class(hashmap_type), intent(inout) :: map
    type(key_type), intent(in) :: key
    logical, intent(out), optional :: existed

procedure(set_other), public, deferred, pass(map) :: set_other_data

  • subroutine set_other(map, key, other, exists) Prototype

    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

    Arguments

    Type IntentOptional 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

procedure, public, non_overridable, pass(map) :: slots_bits

  • private pure function slots_bits(map)

    Returns the number of bits used to specify the number of allocated slots in a hash map (Specifications)

    Arguments: map - an open hash map

    Arguments

    Type IntentOptional Attributes Name
    class(hashmap_type), intent(in) :: map

    Return Value integer

procedure(total_depth), public, deferred, pass(map) :: total_depth

  • function total_depth(map) Prototype

    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

    Arguments

    Type IntentOptional Attributes Name
    class(hashmap_type), intent(in) :: map

    Return Value integer(kind=int64)

Source Code

    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(get_other), deferred, pass(map)    :: get_other_data
        procedure(init_map), deferred, pass(map)     :: init
        procedure(key_test), deferred, pass(map)     :: key_test
        procedure(loading), deferred, pass(map)      :: loading
        procedure(map_entry), deferred, pass(map)    :: map_entry
        procedure(rehash_map), deferred, pass(map)   :: rehash
        procedure(remove_entry), deferred, pass(map) :: remove
        procedure(set_other), deferred, pass(map)    :: set_other_data
        procedure(total_depth), deferred, pass(map)  :: total_depth

    end type hashmap_type