stdlib_hash_32bit Module



Variables

Type Visibility Attributes Name Initial
integer, public, parameter :: int_hash = int32

The number of bits in the output hash

logical, public, parameter :: little_endian = (1==transfer([1_int8, 0_int8], 0_int16))

Interfaces

public interface fnv_1_hash

FNV_1 interfaces (Specification)

  • private elemental module function character_fnv_1(key) result(hash_code)

    FNV_1 hash function for default character string keys

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: key

    Return Value integer(kind=int_hash)

  • private pure module function int16_fnv_1(key) result(hash_code)

    FNV_1 hash function for rank 1 array keys of kind int16

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: key(:)

    Return Value integer(kind=int_hash)

  • private pure module function int32_fnv_1(key) result(hash_code)

    FNV_1 hash function for rank 1 array keys of kind int32

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: key(:)

    Return Value integer(kind=int_hash)

  • private pure module function int64_fnv_1(key) result(hash_code)

    FNV_1 hash function for rank 1 array keys of kind int64

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: key(:)

    Return Value integer(kind=int_hash)

  • private pure module function int8_fnv_1(key) result(hash_code)

    FNV_1 hash function for rank 1 array keys of kind int8

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: key(:)

    Return Value integer(kind=int_hash)

public interface fnv_1a_hash

FNV_1A interfaces (Specification)

  • private elemental module function character_fnv_1a(key) result(hash_value)

    FNV_1A hash function for default character string keys

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: key

    Return Value integer(kind=int_hash)

  • private pure module function int16_fnv_1a(key) result(hash_value)

    FNV_1A hash function for rank 1 array keys of kind int16

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: key(:)

    Return Value integer(kind=int_hash)

  • private pure module function int32_fnv_1a(key) result(hash_value)

    FNV_1A hash function for rank 1 array keys of kind int32

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: key(:)

    Return Value integer(kind=int_hash)

  • private pure module function int64_fnv_1a(key) result(hash_value)

    FNV_1A hash function for rank 1 array keys of kind int64

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: key(:)

    Return Value integer(kind=int_hash)

  • private pure module function int8_fnv_1a(key) result(hash_value)

    FNV_1A hash function for rank 1 array keys of kind int8

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: key(:)

    Return Value integer(kind=int_hash)

public interface new_nmhash32_seed

  • private module subroutine new_nmhash32_seed(seed)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(inout) :: seed

public interface new_nmhash32x_seed

  • private module subroutine new_nmhash32x_seed(seed)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(inout) :: seed

public interface new_water_hash_seed

  • private module subroutine new_water_hash_seed(seed)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(inout) :: seed

public interface nmhash32

NMHASH32 interfaces (Specification)

  • private elemental module function character_nmhash32(key, seed) result(hash_value)

    NMHASH32 hash function for default character string keys

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: key
    integer(kind=int32), intent(in) :: seed

    Return Value integer(kind=int32)

  • private pure module function int16_nmhash32(key, seed) result(hash_value)

    NMHASH32 hash function for rank 1 array keys of kind int16

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: key(0:)
    integer(kind=int32), intent(in) :: seed

    Return Value integer(kind=int32)

  • private pure module function int32_nmhash32(key, seed) result(hash_value)

    NMHASH32 hash function for rank 1 array keys of kind int32

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: key(0:)
    integer(kind=int32), intent(in) :: seed

    Return Value integer(kind=int32)

  • private pure module function int64_nmhash32(key, seed) result(hash_value)

    NMHASH32 hash function for rank 1 array keys of kind int64

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: key(0:)
    integer(kind=int32), intent(in) :: seed

    Return Value integer(kind=int32)

  • private pure module function int8_nmhash32(key, seed) result(hash_value)

    NMHASH32 hash function for rank 1 array keys of kind int8

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: key(0:)
    integer(kind=int32), intent(in) :: seed

    Return Value integer(kind=int32)

public interface nmhash32x

NMHASH32X interfaces (Specification)

  • private elemental module function character_nmhash32x(key, seed) result(hash_value)

    NMHASH32 hash function for default character string keys

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: key
    integer(kind=int32), intent(in) :: seed

    Return Value integer(kind=int32)

  • private pure module function int16_nmhash32x(key, seed) result(hash_value)

    NMHASH32 hash function for rank 1 array keys of kind int16

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: key(0:)
    integer(kind=int32), intent(in) :: seed

    Return Value integer(kind=int32)

  • private pure module function int32_nmhash32x(key, seed) result(hash_value)

    NMHASH32 hash function for rank 1 array keys of kind int32

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: key(0:)
    integer(kind=int32), intent(in) :: seed

    Return Value integer(kind=int32)

  • private pure module function int64_nmhash32x(key, seed) result(hash_value)

    NMHASH32 hash function for rank 1 array keys of kind int64

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: key(0:)
    integer(kind=int32), intent(in) :: seed

    Return Value integer(kind=int32)

  • private pure module function int8_nmhash32x(key, seed) result(hash_value)

    NMHASH32 hash function for rank 1 array keys of kind int8

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: key(0:)
    integer(kind=int32), intent(in) :: seed

    Return Value integer(kind=int32)

public interface water_hash

WATER_HASH interfaces (Specification)

  • private elemental module function character_water_hash(key, seed) result(hash_code)

    WATER hash function for default character string keys

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: key
    integer(kind=int64), intent(in) :: seed

    Return Value integer(kind=int_hash)

  • private pure module function int16_water_hash(key, seed) result(hash_code)

    WATER HASH function for rank 1 array keys of kind int16

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: key(0:)
    integer(kind=int64), intent(in) :: seed

    Return Value integer(kind=int_hash)

  • private pure module function int32_water_hash(key, seed) result(hash_code)

    WATER HASH function for rank 1 array keys of kind int32

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: key(0:)
    integer(kind=int64), intent(in) :: seed

    Return Value integer(kind=int_hash)

  • private pure module function int64_water_hash(key, seed) result(hash_code)

    WATER HASH function for rank 1 array keys of kind int64

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: key(0:)
    integer(kind=int64), intent(in) :: seed

    Return Value integer(kind=int_hash)

  • private pure module function int8_water_hash(key, seed) result(hash_code)

    WATER HASH function for rank 1 array keys of kind int8

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: key(0:)
    integer(kind=int64), intent(in) :: seed

    Return Value integer(kind=int_hash)


Functions

public elemental function fibonacci_hash(key, nbits) result(sample)

License
Creative Commons License
Version
experimental

Maps the 32 bit integer key to an unsigned integer value with only nbits bits where nbits is less than 32 (Specification)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: key
integer, intent(in) :: nbits

Return Value integer(kind=int32)

public elemental function universal_mult_hash(key, seed, nbits) result(sample)

License
Creative Commons License
Version
experimental

Uses the "random" odd 32 bit integer seed to map the 32 bit integer key to an unsigned integer value with only nbits bits where nbits is less than 32 (Specification)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(in) :: key
integer(kind=int32), intent(in) :: seed
integer, intent(in) :: nbits

Return Value integer(kind=int32)


Subroutines

public subroutine odd_random_integer(harvest)

License
Creative Commons License
Version
experimental

Returns a 32 bit pseudo random integer, harvest, distributed uniformly over the odd integers of the int32 kind. (Specification)

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(out) :: harvest