shared_rhash_t Derived Type

type, public :: shared_rhash_t

The shared read-only hash table stores a given number of arbitrary input values in one contiguous array and addresses this contiguous array using a hashtable The input values are stored in order of ascending hash value, with conflicts stored adjacently. For each hash value, the position of the first value with that hash value is stored. The lookup then searches for a given value between the first and the last stored value with the same hash value.


Contents

Source Code


Components

Type Visibility Attributes Name Initial
type(shared_array_int64_t), private :: indices
type(shared_array_int64_t), private :: hval_offsets
integer(kind=int64), private :: hval_range
integer, private, allocatable :: mult(:)
logical, private :: t_conflicts_known = .false.

Type-Bound Procedures

procedure, public, :: alloc

  • private subroutine alloc(this, n_elem, htsize)

    Allocate the internal (shared) memory @param[in] n_elem number of distinct values to store @param[in] htsize range of the hash function

    Arguments

    Type IntentOptional Attributes Name
    class(shared_rhash_t), intent(inout) :: this
    integer(kind=int64), intent(in) :: n_elem
    integer(kind=int64), intent(in) :: htsize

procedure, public, :: dealloc

  • private subroutine dealloc(this)

    Deallocate all arrays associated with this hash table object

    Arguments

    Type IntentOptional Attributes Name
    class(shared_rhash_t), intent(inout) :: this

procedure, public, :: count_value

  • private subroutine count_value(this, hval)

    Log the occurence of this hash value in the set of values to be stored Does not add it, only updates the offsets @param[in] hval hash value to be logged

    Arguments

    Type IntentOptional Attributes Name
    class(shared_rhash_t), intent(inout) :: this
    integer(kind=int64), intent(in) :: hval

procedure, public, :: add_value

  • private subroutine add_value(this, hval, index, pos)

    Add an input value to the stored values, assuming we already know the offsets @param[in] hval value to be stored @param[in] index index belonging to this value @param[out] pos on return, the position where this value was stored

    Arguments

    Type IntentOptional Attributes Name
    class(shared_rhash_t), intent(inout) :: this
    integer(kind=int64), intent(in) :: hval
    integer(kind=int64), intent(in) :: index
    integer(kind=int64), intent(out) :: pos

procedure, public, :: finalize_setup

  • private subroutine finalize_setup(this)

    Dealloates temporary arrays used for initialisation

    Arguments

    Type IntentOptional Attributes Name
    class(shared_rhash_t), intent(inout) :: this

procedure, public, :: setup_offsets

  • private subroutine setup_offsets(this)

    For performance reasons, we cannot directly calculate the offsets, but instead first count the number of conflicts per hash value. Then, we sum these up cumulatively Directly counting the offsets is horrifically slow

    Arguments

    Type IntentOptional Attributes Name
    class(shared_rhash_t), intent(inout) :: this

procedure, public, :: direct_lookup

  • private subroutine direct_lookup(this, hval, index, pos, t_found)

    Look up a value in this hash table. Returns whether the value is stored and if yes, where @param[in] hval hash value of the index to look up @param[in] index value to be looked up @param[out] pos on return, the position of index if found, else 0 @param[out] t_found on return, true if and only if index was found

    Arguments

    Type IntentOptional Attributes Name
    class(shared_rhash_t), intent(in) :: this
    integer(kind=int64), intent(in) :: hval
    integer(kind=int64), intent(in) :: index
    integer(kind=int64), intent(out) :: pos
    logical, intent(out) :: t_found

procedure, public, :: callback_lookup

  • private subroutine callback_lookup(this, hval, pos, t_found, loc_verify)

    Generic lookup routine, using an external routine for verification DOES NOT TO THE SAME AS direct_lookup @param[in] hval hash value of the index to look up @param[out] pos on return, the matching entry @param[out] t_found on return, true if and only if index was found @param[in] verify function to check if an entry matches

    Arguments

    Type IntentOptional Attributes Name
    class(shared_rhash_t), intent(in) :: this
    integer(kind=int64), intent(in) :: hval
    integer(kind=int64), intent(out) :: pos
    logical, intent(out) :: t_found
    private function loc_verify(i) result(match)
    Arguments
    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: i
    Return Value logical

procedure, public, :: known_conflicts

  • private function known_conflicts(this) result(t_kc)

    During initialisation, we can only start writing values once the offsets are known. This requires knowledge about the number of conflicts per hash value. This function tells us whether the conflicts have already been counted. @return t_kc true if and only if the conflicts have already been counted.

    Arguments

    Type IntentOptional Attributes Name
    class(shared_rhash_t), intent(in) :: this

    Return Value logical

procedure, public, :: val_range

  • private function val_range(this) result(h_range)

    Get the range of hash table values of this ht @return h_range maximum possible hash value of this ht

    Arguments

    Type IntentOptional Attributes Name
    class(shared_rhash_t), intent(in) :: this

    Return Value integer(kind=int64)

procedure, public, :: sync

  • private subroutine sync(this)

    Synchronize the shared resource

    Arguments

    Type IntentOptional Attributes Name
    class(shared_rhash_t), intent(in) :: this

Source Code

    type :: shared_rhash_t
        ! All arrays here are mpi-3 shared memory
        private
        ! The hashed data is stored in one contiguous array
        ! Typically, we will be storing indices of some array
        type(shared_array_int64_t) :: indices

        ! Alongside, we store the offset of the hash values - the position of the first
        ! index for each hash value
        type(shared_array_int64_t) :: hval_offsets
        ! The range of the hash function
        integer(int64) :: hval_range

        ! auxiliary array for initialisation. This stores how many input values we already
        ! added for each hash value
        integer, allocatable :: mult(:)

        ! are the conflicts of the hashtable already counted (have the offsets been set?)
        logical :: t_conflicts_known = .false.

    contains

        ! Allocate the memory
        procedure :: alloc
        procedure :: dealloc
        ! Fill up the indices - since this is memory critical, we allow direct write to them
        procedure :: count_value
        procedure :: add_value
        ! Set up the table. It is read-only, so this is the only way to set it up
        procedure :: finalize_setup
        ! After counting the indices, we have to get the offsets (doing so on the fly is
        ! horiffically slow)
        procedure :: setup_offsets

        ! Look up an index. Returns the position in the contiguous array
        procedure :: direct_lookup
        procedure :: callback_lookup

        ! Tell if the conflicts have been counted
        procedure :: known_conflicts
        ! Check how large the hash table shall be
        procedure :: val_range

        ! Synchronize between tasks
        procedure :: sync
    end type shared_rhash_t