shared_rhash Module



Contents


Interfaces

public interface initialise_shared_rht

  • private subroutine initialise_shared_rht_impl(ilut_list, space_size, hash_table, ht_size)

    Default initializer for shared read-only hash-tables, that defaults the determinant size to the number of electrons. This sets up a hash table storing the position of iluts in a given list, such that lookup is done with the shared_rht_lookup function that supports iluts @param[in] ilut_list list of iluts to be indexed by the hash table @param[in] space_size size of the index space @param[out] hash_table shared read-only hashtable to index the ilut_list @param[out] ht_size optional, the size of the hash table. Defaults to space_size

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=n_int), intent(in) :: ilut_list(0:,:)
    integer, intent(in) :: space_size
    type(shared_rhash_t), intent(out) :: hash_table
    integer, intent(in), optional :: ht_size
  • private subroutine initialise_shared_rht_expl(ilut_list, space_size, hash_table, det_size, ht_size)

    Explicit initializer for shared read-only hash-tables that allows to set the determinant size @param[in] ilut_list list of iluts to be indexed by the hash table @param[in] space_size size of the index space @param[out] hash_table shared read-only hashtable to index the ilut_list @param[in] det_size size of the determinants encoded in ilut_list (for convenience) @param[out] ht_size the size of the hash table, has to be specified herer!

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=n_int), intent(in) :: ilut_list(0:,:)
    integer, intent(in) :: space_size
    type(shared_rhash_t), intent(out) :: hash_table
    integer, intent(in) :: det_size
    integer, intent(in) :: ht_size

Derived Types

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.

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 Subroutine
procedure , public , :: dealloc Subroutine
procedure , public , :: count_value Subroutine
procedure , public , :: add_value Subroutine
procedure , public , :: finalize_setup Subroutine
procedure , public , :: setup_offsets Subroutine
procedure , public , :: direct_lookup Subroutine
procedure , public , :: callback_lookup Subroutine
procedure , public , :: known_conflicts Function
procedure , public , :: val_range Function
procedure , public , :: sync Subroutine

Functions

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

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)


Subroutines

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

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

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

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

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

private subroutine finalize_setup(this)

Dealloates temporary arrays used for initialisation

Arguments

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

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

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

private subroutine sync(this)

Synchronize the shared resource

Arguments

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

private subroutine initialise_shared_rht_impl(ilut_list, space_size, hash_table, ht_size)

Default initializer for shared read-only hash-tables, that defaults the determinant size to the number of electrons. This sets up a hash table storing the position of iluts in a given list, such that lookup is done with the shared_rht_lookup function that supports iluts @param[in] ilut_list list of iluts to be indexed by the hash table @param[in] space_size size of the index space @param[out] hash_table shared read-only hashtable to index the ilut_list @param[out] ht_size optional, the size of the hash table. Defaults to space_size

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: ilut_list(0:,:)
integer, intent(in) :: space_size
type(shared_rhash_t), intent(out) :: hash_table
integer, intent(in), optional :: ht_size

private subroutine initialise_shared_rht_expl(ilut_list, space_size, hash_table, det_size, ht_size)

Explicit initializer for shared read-only hash-tables that allows to set the determinant size @param[in] ilut_list list of iluts to be indexed by the hash table @param[in] space_size size of the index space @param[out] hash_table shared read-only hashtable to index the ilut_list @param[in] det_size size of the determinants encoded in ilut_list (for convenience) @param[out] ht_size the size of the hash table, has to be specified herer!

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: ilut_list(0:,:)
integer, intent(in) :: space_size
type(shared_rhash_t), intent(out) :: hash_table
integer, intent(in) :: det_size
integer, intent(in) :: ht_size

public subroutine shared_rht_lookup(core_ht, ilut, nI, tgt_space, i, core_state)

Lookup a value in a shared-read-only hashtable. Returns the position of a given ilut in the target space used for setting up this hash table @param[in] core_ht hashtable used for the lookup @param[in] ilut the ilut for which we want to get the position in tgt_space @param[in] nI decoded determinant corresponding to ilut (usually already available, so no need to decode again @param[in] tgt_space ilut_list used to initialise core_ht, this is where we want to search for the given ilut @param[out] i on return, position of ilut in tgt_space if found, 0 else @param[out] core_state on return, true if ilut is found, false else

Arguments

Type IntentOptional Attributes Name
type(shared_rhash_t), intent(in) :: core_ht
integer(kind=n_int), intent(in) :: ilut(0:NIfTot)
integer, intent(in) :: nI(:)
integer(kind=int64), intent(in) :: tgt_space(0:,1:)
integer, intent(out) :: i
logical, intent(out) :: core_state