stdlib_hashmap_wrappers Module

Public procedures Public types Public integers



Interfaces

public interface get

  • private subroutine get_char_key(key, value)

    Gets the contents of the key as a CHARACTER string Arguments: key - the input key value - the contents of key mapped to a CHARACTER string

    Arguments

    Type IntentOptional Attributes Name
    type(key_type), intent(in) :: key
    character(len=:), intent(out), allocatable :: value
  • private subroutine get_int8_key(key, value)

    Gets the contents of the key as an INTEGER(INT8) vector Arguments: key - the input key value - the contents of key mapped to an INTEGER(INT8) vector

    Arguments

    Type IntentOptional Attributes Name
    type(key_type), intent(in) :: key
    integer(kind=int8), intent(out), allocatable :: value(:)
  • private pure subroutine get_int32_key(key, value)

    Gets the contents of the key as an INTEGER(INT32) vector Arguments: key - the input key value - the contents of key mapped to an INTEGER(INT32) vector

    Arguments

    Type IntentOptional Attributes Name
    type(key_type), intent(in) :: key
    integer(kind=int32), intent(out), allocatable :: value(:)

public interface operator(==)

  • private function equal_keys(key1, key2) result(test)

    Compares two keys for equality (Specifications)

    Arguments: key1 - the first key key2 - the second key

    Arguments

    Type IntentOptional Attributes Name
    type(key_type), intent(in) :: key1
    type(key_type), intent(in) :: key2

    Return Value logical

public interface set

  • private subroutine set_char_key(key, value)

    Sets the contents of the key from a CHARACTER string Arguments: key - the output key value - the input CHARACTER string

    Arguments

    Type IntentOptional Attributes Name
    type(key_type), intent(out) :: key
    character(len=*), intent(in) :: value
  • private subroutine set_int8_key(key, value)

    Sets the contents of the key from an INTEGER(INT8) vector Arguments: key - the output key value - the input INTEGER(INT8) vector

    Arguments

    Type IntentOptional Attributes Name
    type(key_type), intent(out) :: key
    integer(kind=int8), intent(in) :: value(:)
  • private pure subroutine set_int32_key(key, value)

    Sets the contents of the key from an INTEGER(INT32) vector Arguments: key - the output key value - the input INTEGER(INT32) vector

    Arguments

    Type IntentOptional Attributes Name
    type(key_type), intent(out) :: key
    integer(kind=int32), intent(in) :: value(:)

Abstract Interfaces

abstract interface

Abstract interface to a 64 bit hash function operating on a KEY_TYPE

  • public pure function hasher_fun(key) result(hash_value)

    Arguments

    Type IntentOptional Attributes Name
    type(key_type), intent(in) :: key

    Return Value integer(kind=int_hash)


Derived Types

type, public ::  key_type

A wrapper type for the key's true type

Components

Type Visibility Attributes Name Initial
integer(kind=int8), public, allocatable :: value(:)

Functions

public pure function fnv_1_hasher(key)

License
Creative Commons License
Version
Experimental

Hashes a key with the FNV_1 algorithm Arguments: key - the key to be hashed

Arguments

Type IntentOptional Attributes Name
type(key_type), intent(in) :: key

Return Value integer(kind=int_hash)

public pure function fnv_1a_hasher(key)

License
Creative Commons License
Version
Experimental

Hashes a key with the FNV_1a algorithm (Specifications)

Read more…

Arguments

Type IntentOptional Attributes Name
type(key_type), intent(in) :: key

Return Value integer(kind=int_hash)

public pure function seeded_nmhash32_hasher(key)

License
Creative Commons License
Version
Experimental

Hashes a key with the NMHASH32 hash algorithm (Specifications)

Read more…

Arguments

Type IntentOptional Attributes Name
type(key_type), intent(in) :: key

Return Value integer(kind=int_hash)

public pure function seeded_nmhash32x_hasher(key)

License
Creative Commons License
Version
Experimental

Hashes a key with the NMHASH32X hash algorithm (Specifications) Arguments: key - the key to be hashed seed - the seed (unused) for the hashing algorithm

Arguments

Type IntentOptional Attributes Name
type(key_type), intent(in) :: key

Return Value integer(kind=int_hash)

public pure function seeded_water_hasher(key)

License
Creative Commons License
Version
Experimental

Hashes a key with the waterhash algorithm (Specifications)

Read more…

Arguments

Type IntentOptional Attributes Name
type(key_type), intent(in) :: key

Return Value integer(kind=int_hash)


Subroutines

public pure subroutine copy_key(old_key, new_key)

License
Creative Commons License
Version
Experimental

Copies the contents of the key, old_key, to the key, new_key (Specifications)

Read more…

Arguments

Type IntentOptional Attributes Name
type(key_type), intent(in) :: old_key
type(key_type), intent(out) :: new_key

public subroutine free_key(key)

License
Creative Commons License
Version
Experimental

Frees the memory in a key (Specifications)

Read more…

Arguments

Type IntentOptional Attributes Name
type(key_type), intent(inout) :: key