chaining_hashmap_type Derived Type

type, public, extends(hashmap_type) :: chaining_hashmap_type

Type implementing the chaining_hashmap_type types (Specifications)


Finalization Procedures

final :: free_chaining_map

  • private interface free_chaining_map()

    Arguments

    None

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, public :: get_all_keys => get_all_chaining_keys

  • interface

    private module subroutine get_all_chaining_keys(map, all_keys)

    Returns all the keys contained in a hashmap Arguments: map - an chaining hash map all_keys - all the keys contained in a hash map

    Arguments

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

procedure, public :: get_other_data => get_other_chaining_data

  • interface

    private module subroutine get_other_chaining_data(map, key, other, 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

    Arguments

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

procedure, public :: init => init_chaining_map

  • interface

    private module subroutine init_chaining_map(map, hasher, slots_bits, status)

    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

    Arguments

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

procedure, public :: key_test => chaining_key_test

  • interface

    private module subroutine chaining_key_test(map, key, present)

    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

    Arguments

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

procedure, public :: loading => chaining_loading

  • interface

    private pure module function chaining_loading(map)

    Returns the number of entries relative to slots in a hash map Arguments: map - a chaining hash map

    Arguments

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

    Return Value real

procedure, public :: map_entry => map_chain_entry

  • interface

    private module subroutine map_chain_entry(map, key, other, conflict)

    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

    Arguments

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

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, public :: rehash => rehash_chaining_map

  • interface

    private module subroutine rehash_chaining_map(map, hasher)

    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(chaining_hashmap_type), intent(inout) :: map
    procedure(hasher_fun) :: hasher

procedure, public :: remove => remove_chaining_entry

  • interface

    private module subroutine remove_chaining_entry(map, key, 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

    Arguments

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

procedure, public :: set_other_data => set_other_chaining_data

  • interface

    private module subroutine set_other_chaining_data(map, key, other, exists)

    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(chaining_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, public :: total_depth => total_chaining_depth

  • interface

    private module function total_chaining_depth(map) result(total_depth)

    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

    Arguments

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

    Return Value integer(kind=int_depth)

Source Code

    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 :: get_other_data => get_other_chaining_data
        procedure :: init => init_chaining_map
        procedure :: loading => chaining_loading
        procedure :: map_entry => map_chain_entry
        procedure :: rehash => rehash_chaining_map
        procedure :: remove => remove_chaining_entry
        procedure :: set_other_data => set_other_chaining_data
        procedure :: total_depth => total_chaining_depth
        procedure :: key_test => chaining_key_test
        final     :: free_chaining_map
    end type chaining_hashmap_type