哈希映射

stdlib_hashmap_wrappersstdlib_hashmaps 模块

哈希映射概述

哈希映射(哈希表)是一种数据结构,它将 *键* 映射到 *值*。它使用哈希函数根据 *键* 计算哈希码,该哈希码用作线性数组中 *槽*(桶)的索引,从中可以提取所需的 *值*。理想情况下,每个键都映射到一个唯一的槽位,但大多数哈希函数都不完美,并且可以将多个键映射到同一个 *槽位*,从而导致冲突。哈希映射在处理此类冲突的方式上有所不同。本文档讨论了 Fortran 标准库中的哈希映射。

许可证

Fortran 标准库根据 MIT 许可证发布。但是,应该评估库的组件以确定它们是否与 MIT 许可证兼容。当前的哈希映射受到 David Chase 的 [实现](http://chasewoerner.org/src/hasht/) 的启发。虽然代码已从他的实现中进行了大量修改,但他已允许无限制使用他的代码。

哈希映射模块

Fortran 标准库为实现简单的哈希映射提供了两个模块。这些映射仅接受具有单个参数(键)且产生 32 位哈希码的哈希函数。如果需要使用具有不同 API 的哈希函数,则需要修改这些模块。这两个模块是:stdlib_hashmap_wrappersstdlib_hashmaps,分别对应于文件:stdlib_hashmap_wrappers.f90stdlib_hashmaps.f90

模块 stdlib_hashmap_wrappers 提供了供 stdlib_hashmaps 使用的类型和过程。它提供了对标准库模块 stdlib_hash_32bit 的 32 位哈希函数的接口,并提供了一些哈希函数的包装器,因此不再需要为它们提供种子。它还定义了两种用于存储哈希映射中信息的类型,key_typeother_typekey_type 用于定义键,这些键反过来用于识别输入哈希映射的数据。other_type 用于包含与键关联的其他数据。

模块 stdlib_hashmaps 为父数据类型 hashmap_type 和该哈希映射类型的两个扩展定义了 API:chaining_hashmap_typeopen_hashmap_type

hashmap_type 为其两个扩展使用的过程定义了应用程序编程接口 (API)。它明确定义了五个不可覆盖的过程。它还定义了 11 个延迟过程的接口。它没有定义两种扩展类型的最终化例程,或者 open_hashmap_type 提供的一个例程。

chaining_hashmap_type 使用具有链接列表的独立链接来处理哈希索引冲突。在独立链接中,通过使用以哈希索引为根的链接列表来处理冲突索引。chaining_hashmap_type 过程在模块 stdlib_hashmap_chaining 中实现,对应于文件 stdlib_hashmap_chaining.f90

open_hashmap_type 使用线性开放寻址来处理哈希索引冲突。在线性开放寻址中,通过从初始哈希索引开始,以 1 为步长递增(模哈希映射大小)搜索开放映射槽位来处理冲突索引。open_hashmap_type 过程在子模块 stdlib_hashmap_open 中实现,对应于文件 stdlib_hashmap_open.f90

这些映射使用 2 的幂作为其槽位大小,以便可以使用 fibonacci_hash 函数将哈希码映射到映射中的索引。预计这比使用模运算的素数映射更高效,并且减少了对哈希函数需要很好地随机化其低阶位的要求。它们确实需要一个良好的随机化哈希方法才能获得良好的性能。它们都会根据哈希映射探测次数与子例程调用次数的比率来调整映射大小,以减少冲突。虽然这些映射在内部广泛使用指针,但私有的最终化子例程可以避免内存泄漏。这些映射可以接受 key_type 类型的条目键,以及 other_type 类型的其他数据。这些映射允许添加、删除和查找条目,以及包含除条目键之外的数据。

stdlib_hashmap_wrappers 模块

stdlib_hashmap_wrappers 模块提供数据类型来表示存储在模块中的键和关联数据,但也充当 stdlib_hash_32bit 模块的包装器。它允许直接访问 stdlib_hash_32bit 过程:fibonacci_hashfnv_1_hasherfnv_1a_hasher;并为哈希函数提供包装器函数 seeded_nmhash32_hasherseeded_nmhash32x_hasherseeded_water_hasher,分别对应于 nmhash32nmhash32xwater_hash。它定义了一个与接受 非标量键 的哈希函数兼容的接口 hasher_fun。它定义了一个用作种类值的整数常量 int_hash。它还定义了两种类型 key_typeother_type,以及用于存储和操作键及其关联数据的相关过程。

stdlib_hashmap_wrappers 的常量 int_hash

常量 int_hash 用于定义返回的哈希码的整数种类值以及用于访问它们的变量。它目前从 stdlib_hash_32bit 导入,其中它的值为 int32

stdlib_hashmap_wrappers 模块的派生类型

stdlib_hashmap_wrappers 模块定义了两种派生类型:key_typeother_typekey_type 旨在用于哈希表的搜索键。other_type 旨在存储与键关联的其他数据。两种类型都是不透明的。它们的当前表示如下

    type :: key_type
        private
        integer(int8), allocatable :: value(:)
    end type key_type

    type :: other_type
        private
        class(*), allocatable :: value
    end type other_type

该模块还为这些类型定义了六个过程:copy_keycopy_otherequal_keysfree_keyfree_othergetset,以及一个操作符 ==,供哈希映射使用以操作或查询这些类型的组件。

stdlib_hashmap_wrappers 过程表

stdlib_hashmap_wrappers 模块提供了几类过程:用于操作 key_type 数据的过程;用于操作 other_type 数据的过程,以及用于键的 32 位哈希函数。每类过程列出如下。它还提供了一个操作符来比较两个键类型值是否相等。

用于操作 key_type 数据的过程

  • copy_key( key_in, key_out ) - 将键 key_in 的内容复制到键 key_out 的内容中。

  • get( key, value ) - 将 key 的内容提取到 value 中,value 是一个 int8 数组、int32 数组或字符字符串。

  • free_key( key ) - 释放 key 中的内存。

  • set( key, value ) - 将 key 的内容设置为 value
    支持的键类型是 int8 数组、int32 数组和字符字符串。

用于操作 other_type 数据的过程

  • copy_other( other_in, other_out ) - 将其他数据 other_in 的内容复制到其他数据 other_out 的内容中。

  • get( other, value ) - 将 other 的内容提取到 class(*) 变量 value 中。

  • set( other, value ) - 将 other 的内容设置为 class(*) 变量 value

  • free_other( other ) - 释放 other 中的内存。

将键哈希到 32 位整数的程序

  • fnv_1_hasher( key ) - 使用 FNV-1 算法对 key 进行哈希。

  • fnv_1a_hasher( key ) - 使用 FNV-1a 算法对 key 进行哈希。

  • seeded_nmhash32_hasher( key ) - 使用 nmhash32 算法对 key 进行哈希。

  • seeded_nmhash32x_hasher( key ) - 使用 nmhash32x 算法对 key 进行哈希。

  • seeded_water_hasher( key ) - 使用 waterhash 算法对 key 进行哈希。

用于比较两个 key_type 值是否相等的运算符

  • key1 == key2 - 将 key1key2 比较以判断是否相等

stdlib_hashmap_wrappers 过程的规格

copy_key - 返回键的副本

状态

实验性

描述

返回类型为 key_type 的输入的副本。

语法

call copy_key ( old_key, new_key )

子程序。

参数

old_key: 应为类型为 key_type 的标量表达式。它是 intent(in) 参数。

new_key: 应为类型为 key_type 的标量变量。它是 intent(out) 参数。

示例
program example_copy_key
  use stdlib_hashmap_wrappers, only: &
    copy_key, operator(==), key_type, set
  use iso_fortran_env, only: int8
  implicit none
  integer(int8) :: i, value(15)
  type(key_type) :: old_key, new_key
  value = [(i, i=1, 15)]
  call set(old_key, value)
  call copy_key(old_key, new_key)
  print *, "old_key == new_key = ", old_key == new_key
end program example_copy_key

copy_other - 返回其他数据的副本

状态

实验性

描述

返回类型为 other_type 的输入的副本。

语法

call copy_other ( other_in, other_out )

子程序。

参数

other_in: 应为类型为 other_type 的标量表达式。它是 intent(in) 参数。

other_out: 应为类型为 other_type 的标量变量。它是 intent(out) 参数。

示例
program example_copy_other
  use stdlib_hashmap_wrappers, only: &
    copy_other, other_type
  use iso_fortran_env, only: int8
  implicit none
  type(other_type) :: other_in, other_out
  integer(int8) :: i
  type dummy_type
    integer(int8) :: value(15)
  end type
  type(dummy_type) :: dummy_val
  do i = 1, 15
    dummy_val%value(i) = i
  end do
  allocate (other_in%value, source=dummy_val)
  call copy_other(other_in, other_out)
  select type (out => other_out%value)
  type is (dummy_type)
    print *, "other_in == other_out = ", &
      all(dummy_val%value == out%value)
  end select
end program example_copy_other

fibonacci_hash - 将整数映射到更小的位数

状态

实验性

描述

fibonacci_hash 只是在 stdlib_hash_32bit 中实现的同名函数的重新导出。它将 32 位整数的值减少到更小的位数。

fnv_1_hasher- 从键计算哈希码

状态

实验性

描述

从类型为 key_type 的输入计算 32 位哈希码。

语法

code = fnv_1_hasher ( key )

纯函数

参数

key: 应为类型为 key_type 的标量表达式。它是 intent(in) 参数。

结果字符

结果是类型为 int32 的标量整数。

结果值

结果是使用 FNV-1 算法创建的哈希码。

注意

fnv_1_hasher 是 Glenn Fowler、Landon Curt Noll 和 Phong Vo 原始 FNV-1 哈希码的实现。此代码在短键上速度相对较快,并且足够小,以至于如果哈希是间歇性的,它通常会保留在指令缓存中。因此,它应该为典型的哈希表应用程序提供良好的性能。此代码不通过任何 SMHasher 测试,但由于其更多冲突而导致的性能下降预计会比其更快的哈希速度小。

示例
program example_fnv_1_hasher
  use stdlib_hashmap_wrappers, only: fnv_1_hasher, key_type, set
  use iso_fortran_env, only: int8, int32
  implicit none
  integer(int8), allocatable :: array1(:)
  integer(int32) :: hash
  type(key_type) :: key
  array1 = [5_int8, 4_int8, 3_int8, 1_int8, 10_int8, 4_int8]
  call set(key, array1)
  hash = fnv_1_hasher(key)
  print *, hash
end program example_fnv_1_hasher

fnv_1a_hasher- 从键计算哈希码

状态

实验性

描述

从类型为 key_type 的输入计算 32 位哈希码。

语法

code = fnv_1a_hasher ( key )

纯函数

参数

key: 应为类型为 key_type 的标量表达式。它是 intent(in) 参数。

结果字符

结果是类型为 int32 的标量整数。

结果值

结果是使用 FNV-1a 算法创建的哈希码。

注意

fnv_1a_hasher 是 Glenn Fowler、Landon Curt Noll 和 Phong Vo 原始 FNV-1A 哈希码的实现。此代码在短键上速度相对较快,并且足够小,以至于如果哈希是间歇性的,它通常会保留在指令缓存中。因此,它应该为典型的哈希表应用程序提供良好的性能。此代码不通过任何 SMHasher 测试,但由于其更多冲突而导致的性能下降预计会比其更快的哈希速度小。

示例
program example_fnv_1a_hasher
  use stdlib_hashmap_wrappers, only: &
    fnv_1a_hasher, key_type, set
  use iso_fortran_env, only: int8, int32
  implicit none
  integer(int8), allocatable :: array1(:)
  integer(int32) :: hash
  type(key_type) :: key
  array1 = [5_int8, 4_int8, 3_int8, 1_int8, 10_int8, 4_int8]
  call set(key, array1)
  hash = fnv_1a_hasher(key)
  print *, hash
end program example_fnv_1a_hasher

free_key - 释放与键关联的内存

状态

实验性

描述

释放与类型为 key_type 的变量关联的内存。

语法

call free_key ( key )

子程序。

参数

key: 应为类型为 key_type 的标量变量。它是 intent(out) 参数。

示例
program example_free_key
  use stdlib_hashmap_wrappers, only: &
    copy_key, free_key, key_type, set
  use iso_fortran_env, only: int8
  implicit none
  integer(int8) :: i, value(15)
  type(key_type) :: old_key, new_key
  value = [(i, i=1, 15)]
  call set(old_key, value)
  call copy_key(old_key, new_key)
  call free_key(old_key)
end program example_free_key

free_other - 释放与其他数据关联的内存

状态

实验性

描述

释放与类型为 other_type 的变量关联的内存。

语法

call free_other ( other )

子程序。

参数

other: 应为类型为 other_type 的标量变量。它是 intent(out) 参数。

示例
program example_free_other
  use stdlib_hashmap_wrappers, only: &
    copy_other, free_other, other_type
  use iso_fortran_env, only: int8
  implicit none
  type dummy_type
    integer(int8) :: value(15)
  end type dummy_type
  type(dummy_type) :: dummy_val
  type(other_type) :: other_in, other_out
  integer(int8) :: i
  do i = 1, 15
    dummy_val%value(i) = i
  end do
  allocate (other_in%value, source=dummy_val)
  call copy_other(other_in, other_out)
  call free_other(other_out)
end program example_free_other

get - 从派生类型中提取数据

状态

实验性

描述

key_typeother_type 中提取数据,并将其存储在变量 value 中。

语法

call get ( key, value )

call get ( other, value )

子程序。

参数

key: 应为类型为 key_type 的标量表达式。它是 intent(in) 参数。

other: 应为类型为 other_type 的标量表达式。它是 intent(in) 参数。

value: 如果第一个参数是 key_typevalue 应为可分配的默认 character 字符串变量,或类型为 integer 且种类为 int8int32 的可分配向量变量,否则第一个参数是 other_typevalue 应为 class(*) 的可分配。它是 intent(out) 参数。

示例
program example_get
  use stdlib_hashmap_wrappers, only: &
    get, key_type, set
  use iso_fortran_env, only: int8
  implicit none
  integer(int8), allocatable :: value(:), result(:)
  type(key_type) :: key
  integer(int8) :: i
  allocate (value(1:15))
  do i = 1, 15
    value(i) = i
  end do
  call set(key, value)
  call get(key, result)
  print *, 'RESULT == VALUE = ', all(value == result)
end program example_get

hasher_fun- 充当函数原型。

状态

实验性

描述

充当具有单个 key 参数的哈希函数的原型,该参数类型为 key_type,返回 int32 哈希值。

语法

type( hasher_fun ), pointer :: fun_pointer

纯函数原型

参数

key: 应为类型为 integer(int8) 的秩 1 数组表达式。它是 intent(in) 参数。

结果字符

结果是类型为 int32 的标量整数。

结果值

结果是哈希码。

注意

hasher_fun 是定义用于作为哈希表哈希函数的虚拟参数和函数指针的原型。

示例
program example_hasher_fun
  use stdlib_hashmap_wrappers, only: fnv_1a_hasher, hasher_fun, set, key_type
  use stdlib_kinds, only: int8, int32
  implicit none
  procedure(hasher_fun), pointer :: hasher_pointer
  integer(int8), allocatable :: array1(:)
  integer(int32) :: hash
  type(key_type) :: key
  hasher_pointer => fnv_1a_hasher
  array1 = [5_int8, 4_int8, 3_int8, 1_int8, 10_int8, 4_int8]
  call set(key, array1)
  hash = hasher_pointer(key)
  print *, hash
end program example_hasher_fun

operator(==) - 比较两个键是否相等

状态

实验性

描述

如果两个键相等,则返回 .true.,否则返回 .false.

语法

test = key1 == key2

纯运算符。

参数

key1: 应为类型为 key_type 的标量表达式。它是 intent(in) 参数。

key2: 应为类型为 key_type 的标量表达式。它是 intent(in) 参数。

结果字符

结果是类型为默认 logical 的值。

结果值

如果键相等,则结果为 .true.,否则为 .falss.

示例
program example_equal_keys
  use stdlib_hashmap_wrappers, only: &
    copy_key, operator(==), key_type, set
  use iso_fortran_env, only: int8
  implicit none
  integer(int8) :: i, value(15)
  type(key_type) :: old_key, new_key
  do i = 1, 15
    value(i) = i
  end do
  call set(old_key, value)
  call copy_key(old_key, new_key)
  print *, "old_key == new_key = ", old_key == new_key
end program example_equal_keys

seeded_nmhash32_hasher- 从键计算哈希码

状态

实验性

描述

从类型为 key_type 的输入计算 32 位哈希码。

语法

code = seeded_nmhash32_hasher ( key )

纯函数

参数

key: 应为类型为 key_type 的标量表达式。它是 intent(in) 参数。

结果字符

结果是类型为 int32 的标量整数。

结果值

结果是使用 nmhash32 算法创建的哈希码。

注意

seeded_nmhash32_hasher 是对模块 stdlib_hash_32bit 中的 NMHASH32_HASH 的包装,它为包装函数提供固定种子。NMHASH32 是 James Z. M. Gao 的 nmhash32 哈希码的实现。此代码在长键上具有良好的性能,但在短键上性能较差。因此,它应该为典型的哈希表应用程序提供公平的性能。此代码通过 SMHasher 测试。

示例
program example_seeded_nmhash32_hasher
  use stdlib_hashmap_wrappers, only: &
    seeded_nmhash32_hasher, key_type, set
  use iso_fortran_env, only: int8, int32
  implicit none
  integer(int8), allocatable :: array1(:)
  integer(int32) :: hash
  type(key_type) :: key
  array1 = [5_int8, 4_int8, 3_int8, 1_int8, 10_int8, 4_int8]
  call set(key, array1)
  hash = seeded_nmhash32_hasher(key)
  print *, hash
end program example_seeded_nmhash32_hasher

seeded_nmhash32x_hasher- 从键计算哈希码

状态

实验性

描述

从类型为 key_type 的输入计算 32 位哈希码。

语法

code = seeded_nmhash32x_hasher ( key )

纯函数

参数

key: 应为类型为 key_type 的标量表达式。它是 intent(in) 参数。

结果字符

结果是类型为 int32 的标量整数。

结果值

结果是使用 nmhash32x 算法创建的哈希码。

注意

seeded_nmhash32x_hasher 是对模块 stdlib_hash_32bit 中的 nmhash32x_hash 的包装,它为包装函数提供固定种子。nmhash32x 是 James Z. M. Gao 的 nmhash32x 哈希码的实现。此代码在长键上具有良好的性能,但在短键上性能较差。因此,它应该为典型的哈希表应用程序提供公平的性能。此代码通过 SMHasher 测试。

示例
program example_seeded_nmhash32x_hasher
  use stdlib_kinds, only: int8, int32
  use stdlib_hashmap_wrappers, only: &
    seeded_nmhash32x_hasher, key_type, set
  implicit none
  integer(int8), allocatable :: array1(:)
  integer(int32) :: hash
  type(key_type) :: key
  array1 = [5_int8, 4_int8, 3_int8, 1_int8, 10_int8, 4_int8]
  call set(key, array1)
  hash = seeded_nmhash32x_hasher(key)
  print *, hash
end program example_seeded_nmhash32x_hasher

seeded_water_hasher- 从键计算哈希码

状态

实验性

描述

从类型为 key_type 的输入计算 32 位哈希码。

语法

code = seeded_water_hasher ( key )

纯函数

参数

key: 应为类型为 key_type 的标量表达式。它是 intent(in) 参数。

结果字符

结果是类型为 int32 的标量整数。

结果值

结果是使用 waterhash 算法创建的哈希码。

注意

seeded_water_hasher 是对模块 stdlib_hash_32bit 中的 water_hash 的包装,它为包装函数提供固定种子。water_hash 是 Tommy Ettinger 的 waterhash 哈希码的实现。此代码在长键上具有出色的性能,在短键上也具有良好的性能。因此,它应该为典型的哈希表应用程序提供合理的性能。此代码通过 SMHasher 测试。

示例
program example_seeded_water_hasher
  use stdlib_hashmap_wrappers, only: &
    seeded_water_hasher, key_type, set
  use iso_fortran_env, only: int8, int32
  implicit none
  integer(int8), allocatable :: array1(:)
  integer(int32) :: hash
  type(key_type) :: key
  array1 = [5_int8, 4_int8, 3_int8, 1_int8, 10_int8, 4_int8]
  call set(key, array1)
  hash = seeded_water_hasher(key)
  print *, hash
end program example_seeded_water_hasher

set - 将数据放置在派生类型中

状态

实验性

描述

value 中的数据放置在 key_typeother_type 中。

语法

call set ( key, value )

call set ( other, value )

子程序。

参数

key: 应为类型为 key_type 的标量变量。它是 intent(out) 参数。

other: 应为类型为 other_type 的标量变量。它是 intent(out) 参数。

value: 如果第一个参数是 keyvalue 应为默认 character 字符串标量表达式,或类型为 integer 且种类为 int8int32 的向量表达式,而对于类型为 other 的第一个参数,value 应为 class(*) 类型。它是 intent(in) 参数。

注意

除了标量默认字符和 int8int32 向量之外的其他类型的数值可以用作 key 的基础,方法是将值传输到 int8 向量。

示例
program example_set
  use stdlib_hashmap_wrappers, only: &
    get, key_type, set
  use iso_fortran_env, only: int8
  implicit none
  integer(int8), allocatable :: value(:), result(:)
  type(key_type) :: key
  integer(int8) :: i
  allocate (value(1:15))
  do i = 1, 15
    value(i) = i
  end do
  call set(key, value)
  call get(key, result)
  print *, 'RESULT == VALUE = ', all(value == result)
end program example_set

stdlib_hashmaps 模块

stdlib_hashmaps 模块定义了三个公共数据类型,关联过程和常量,它们使用单独的链接哈希和开放寻址哈希实现了两种简单的哈希表类型。派生类型 hashmap_type 是其两个扩展的父类型:chaining_hashmap_typeopen_hashmap_type。扩展类型提供过程来操作哈希表对象的结构:initmap_entryrehashremoveset_other_data。它们还提供过程来询问哈希表中的条目:get_other_datakey_test。最后,它们提供过程来询问哈希表对象的整体结构和性能:callsentriesget_other_dataloadingslotstotal_depth。该模块还定义了许多公共常量:probe_factorload_factormap_probe_factordefault_bitsmax_bitsint_callsint_depthint_indexint_probessuccessalloc_faultarray_size_error

key_testmap_entryget_other_dataremoveset_other_data 提供通用键接口,以便支持的类型 int8 数组、int32 数组和 character 标量可以在键字段中使用,以及基本 key 类型。因此,对于 key_testkey_key_test 指定键字段的键类型,int8_key_test 是键字段的 int8 等等。除了 key_key_test 之外的过程将调用 set 函数以生成键类型并传递给 key_key_test

stdlib_hashmaps 模块的公共常量

该模块定义了几类公共常量。有些用于参数化经验插槽扩展代码。其他参数化插槽表大小。有些用于定义不同应用程序的整数种类值。最后,有些用于报告错误或成功。

常量 probe_factormap_probe_factor 用于参数化插槽扩展代码,该代码用于确定在过程调用中何时需要增加插槽数量以减少条目的搜索路径。常量 probe_factor 用于确定映射探测次数与映射调用次数的比率何时过大,需要扩展插槽。常量 map_probe_factor 用于确定在插入新条目时,映射探测次数与映射调用次数的比率何时过大,需要扩展插槽。

常量 default_bitsmax_bits 用于参数化表的插槽大小。default_bits 常量定义了默认的初始插槽数量,当前值为 6,导致初始 2**6 == 64 个插槽。这可以在创建哈希表时可选地被覆盖。max_bits 参数将最大表大小设置为 2**max_bits,其中 max_bits 的默认值为 30。表将无法用于大于 2**30 的插槽大小。

常量 int_callsint_depthint_indexint_probes 用于为各种上下文定义整型值。调用次数在 int_calls 类型的实体中报告和存储。目前 int_calls 的值为 int64。总深度,即访问表中所有元素所需的查询次数,在 int_depth 类型的实体中报告和存储。目前 int_depth 的值为 int64。表中的条目数在 int_index 类型的实体中报告和存储。目前 int_index 的值为 int32。探测次数,即哈希映射查询次数,在 int_probes 类型的实体中报告和存储。目前 int_probes 的值为 int64

常量 load_factor 仅由 open_hashmap_type 使用。它指定了在扩展发生之前可以填充的可用插槽的最大分数。当前 load_factor = 0.5625,因此 open_hashmap_type 的当前实现只能容纳超过 2**29 个条目。

最后,错误代码 successalloc_faultarray_size_error 用于报告某些过程调用的错误状态。succes 代码表示没有发现问题。alloc_fault 代码表示内存分配失败。最后,array_size_error 表示在表创建时,slots_bits 小于 default_bits 或大于 max_bits

stdlib_hashmaps 模块的派生类型

stdlib_hashmaps 模块定义了三个公共派生类型和七个私有类型,用于实现公共类型。公共类型是抽象 hashmap_type 及其扩展:chaining_hashmap_typeopen_hashmap_type。三个私有派生类型 chaining_map_entry_typechaining_map_entry_ptrchaining_map_entry_pool 用于实现 chaining_hashmap_type 公共类型。四个私有派生类型 open_map_entry_typeopen_map_entry_listopen_map_entry_ptropen_map_entry_pool 用于实现 open_hashmap_type 公共类型。下面将描述每个类型。

hashmap_type 抽象类型

hashmap_type 抽象类型充当两种类型 chaining_hashmap_typeopen_hashmap_type 的父类型。它定义了七个私有组件

  • call_count - 映射上的过程调用次数;

  • nbits - 用于寻址插槽的位数;

  • num_entries - 映射中的条目数;

  • num_free - 已删除条目的空闲列表中的条目数;

  • probe_count - 自上次调整大小或初始化以来,映射探测的次数;

  • total_probes - 直到上次调整大小或初始化为止,映射探测的总次数;以及

  • hasher - 指向映射使用的哈希函数的指针。

它还定义了五个不可覆盖的过程

  • calls - 返回映射上的过程调用次数;

  • entries - 返回映射中的条目数;

  • map_probes - 返回自初始化以来,映射探测的次数;

  • num_slots - 返回映射中的插槽数;以及

  • slots_bits - 返回用于寻址插槽的位数;

以及十个延迟过程

  • get_all_keys - 获取映射中包含的所有键;

  • get_other_data - 获取与键关联的其他映射数据;

  • init - 初始化哈希映射;

  • key_test - 返回一个逻辑标志,指示键是否在映射中定义。

  • loading - 返回条目数与插槽数的比率;

  • map_entry - 将键及其其他关联数据插入映射;

  • rehash - 使用提供的哈希函数重新散列映射;

  • remove - 删除与键关联的条目;

  • set_other_data - 替换与键关联的其他数据;

  • total_depth - 返回寻址映射中所有条目所需的探测次数;

类型的定义如下

    type, abstract :: hashmap_type

        private
        integer(int_calls) :: call_count = 0
        integer(int_calls) :: probe_count = 0
        integer(int_calls) :: total_probes = 0
        integer(int_index) :: num_entries = 0
        integer(int_index) :: num_free = 0
        integer(int32)     :: nbits = default_bits
        procedure(hasher_fun), pointer, nopass :: hasher => fnv_1_hasher

    contains

        procedure, non_overridable, pass(map) :: calls
        procedure, non_overridable, pass(map) :: entries
        procedure, non_overridable, pass(map) :: map_probes
        procedure, non_overridable, pass(map) :: num_slots
        procedure, non_overridable, pass(map) :: slots_bits
        procedure(get_all_keys), deferred, pass(map)        :: get_all_keys
        procedure(init_map), deferred, pass(map)            :: init
        procedure(loading), deferred, pass(map)             :: loading
        procedure(rehash_map), deferred, pass(map)          :: rehash
        procedure(total_depth), deferred, pass(map)         :: total_depth

        !! Generic interfaces for key types.
        procedure(key_key_test), deferred, pass(map) :: key_key_test
        procedure, non_overridable, pass(map) :: int8_key_test
        procedure, non_overridable, pass(map) :: int32_key_test
        procedure, non_overridable, pass(map) :: char_key_test

        procedure(key_map_entry), deferred, pass(map) :: key_map_entry
        procedure, non_overridable, pass(map) :: int8_map_entry
        procedure, non_overridable, pass(map) :: int32_map_entry
        procedure, non_overridable, pass(map) :: char_map_entry

        procedure(key_get_other_data), deferred, pass(map)  :: key_get_other_data
        procedure, non_overridable, pass(map) :: int8_get_other_data
        procedure, non_overridable, pass(map) :: int32_get_other_data
        procedure, non_overridable, pass(map) :: char_get_other_data

        procedure(key_remove_entry), deferred, pass(map) :: key_remove_entry
        procedure, non_overridable, pass(map) :: int8_remove_entry
        procedure, non_overridable, pass(map) :: int32_remove_entry
        procedure, non_overridable, pass(map) :: char_remove_entry

        procedure(key_set_other_data), deferred, pass(map)  :: key_set_other_data
        procedure, non_overridable, pass(map) :: int8_set_other_data
        procedure, non_overridable, pass(map) :: int32_set_other_data
        procedure, non_overridable, pass(map) :: char_set_other_data

        generic, public :: key_test => key_key_test, int8_key_test, int32_key_test, char_key_test
        generic, public :: map_entry => key_map_entry, int8_map_entry, int32_map_entry, char_map_entry
        generic, public :: get_other_data => key_get_other_data, int8_get_other_data, int32_get_other_data, char_get_other_data
        generic, public :: remove => key_remove_entry, int8_remove_entry, int32_remove_entry, char_remove_entry
        generic, public :: set_other_data => key_set_other_data, int8_set_other_data, int32_set_other_data, char_set_other_data

    end type hashmap_type

chaining_map_entry_type 派生类型

chaining_map_entry_type 类型的实体用于定义一个链表结构,该结构存储键、其其他数据、键的哈希值以及结果反向表索引。类型的定义如下

    type :: chaining_map_entry_type  ! Chaining hash map entry type
        private
        integer(int_hash)   :: hash_val ! Full hash value
        type(key_type)      :: key ! The entry's key
        type(other_type)    :: other ! Other entry data
        integer(int_index)  :: index ! Index into inverse table
        type(chaining_map_entry_type), pointer :: &
            next => null() ! Next bucket
    end type chaining_map_entry_type

目前 int_hashint_index 的值为 int32

chaining_map_entry_ptr 派生类型

chaining_map_entry_ptr 类型用于定义哈希映射的元素,这些元素要么为空,要么链接到包含表元素的链表。类型的定义如下

    type chaining_map_entry_ptr ! Wrapper for a pointer to a chaining
                                ! map entry type object
        type(chaining_map_entry_type), pointer :: target => null()
    end type chaining_map_entry_ptr

chaining_map_entry_pool 派生类型

chaining_map_entry_pool 类型用于实现一个分配的 chaining_map_entry_type 元素池,以节省分配成本。类型的定义如下

    type :: chaining_map_entry_pool
    ! Type implementing a pool of allocated
    ! `chaining_map_entry_type` objects
        private
    ! Index of next bucket
        integer(int_index)                          :: next = 0
        type(chaining_map_entry_type), allocatable :: more_map_entries(:)
        type(chaining_map_entry_pool), pointer      :: lastpool => null()
    end type chaining_map_entry_pool

chaining_hashmap_type 派生类型

chaining_hashmap_type 派生类型扩展了 hashmap_type 以实现一个独立链式哈希映射。除了 hashmap_type 的组件外,它还提供四个组件

  • cache - 用于减少分配成本的 chaining_map_entry_pool 对象池;

  • free_list - 映射条目的空闲列表;

  • inverse - 一个 chaining_map_entry_ptr 桶列表数组(反向),在条目被输入后将条目存储在固定位置;以及

  • slots - 一个用作哈希映射的桶列表数组。

它还实现了 hashmap_type 的所有延迟过程及其映射的终结器。类型的定义如下

    type, extends(hashmap_type) :: chaining_hashmap_type
        private
        type(chaining_map_entry_pool), pointer    :: cache => null()
        type(chaining_map_entry_type), pointer    :: free_list => null()
        type(chaining_map_entry_ptr), allocatable :: inverse(:)
        type(chaining_map_entry_ptr), allocatable :: slots(:)
    contains
        procedure :: get_all_keys => get_all_chaining_keys
        procedure :: key_get_other_data => get_other_chaining_data
        procedure :: init => init_chaining_map
        procedure :: loading => chaining_loading
        procedure :: key_map_entry => map_chain_entry
        procedure :: rehash => rehash_chaining_map
        procedure :: key_remove_entry => remove_chaining_entry
        procedure :: key_set_other_data => set_other_chaining_data
        procedure :: total_depth => total_chaining_depth
        procedure :: key_key_test => chaining_key_test
        final     :: free_chaining_map
    end type chaining_hashmap_type

open_map_entry_type 派生类型

open_map_entry_type 类型的实体用于定义一个链表结构,该结构存储键、其其他数据、键的哈希值以及结果反向表索引。类型的定义如下

    type :: open_map_entry_type  ! Open hash map entry type
        private
        integer(int_hash)  :: hash_val ! Full hash value
        type(key_type)     :: key ! The entry's key
        type(other_type)   :: other ! Other entry data
        integer(int_index) :: index ! Index into inverse table
    end type open_map_entry_type

目前 int_hashint_index 的值为 int32

open_map_entry_ptr 派生类型

open_map_entry_ptr 类型用于定义哈希映射的元素,这些元素要么为空,要么链接到包含表元素的链表。类型的定义如下

    type open_map_entry_ptr ! Wrapper for a pointer to a open
                            ! map entry type object
        type(open_map_entry_type), pointer :: target => null()
    end type open_map_entry_ptr

open_hashmap_type 派生类型

open_hashmap_type 派生类型扩展了 hashmap_type 以实现一个开放寻址哈希映射。除了 hashmap_type 的组件外,它还提供四个组件

  • cache - 用于减少分配成本的 open_map_entry_pool 对象池;

  • free_list - 映射条目的空闲列表;

  • index_mask - 用于线性寻址的 and 掩码;

  • inverse - 一个 open_map_entry_ptr 桶列表数组(反向),在条目被输入后将条目存储在固定位置;以及

  • slots - 一个用作哈希映射的桶列表数组。

它还实现了 hashmap_type 的所有延迟过程及其映射的终结器。类型的定义如下

    type, extends(hashmap_type) :: open_hashmap_type
        private
        integer(int_index) :: index_mask = 2_int_index**default_bits-1
        type(open_map_entry_pool), pointer    :: cache => null()
        type(open_map_entry_list), pointer    :: free_list => null()
        type(open_map_entry_ptr), allocatable  :: inverse(:)
        integer(int_index), allocatable        :: slots(:)
    contains
        procedure :: get_all_keys => get_all_open_keys
        procedure :: key_get_other_data => get_other_open_data
        procedure :: init => init_open_map
        procedure :: loading => open_loading
        procedure :: key_map_entry => map_open_entry
        procedure :: rehash => rehash_open_map
        procedure :: key_remove_entry => remove_open_entry
        procedure :: key_set_other_data => set_other_open_data
        procedure :: total_depth => total_open_depth
        procedure :: key_key_test => open_key_test
        final     :: free_open_map
    end type open_hashmap_type

stdlib_hashmap 过程表

stdlib_hashmap 模块提供了几类过程:一个过程用于初始化映射;一个过程用于修改映射的结构;过程用于修改映射的内容;过程用于报告映射的内容;以及过程用于报告映射的结构。每类过程列在下面。

初始化链式哈希映射的过程

  • map % init( hasher[, slots_bits, status] ) - 初始化链式哈希映射的例程。

修改映射结构的过程

  • map % rehash( hasher ) - 更改映射的哈希函数的例程。

修改映射内容的过程

  • map % map_entry( key, other, conflict ) - 将条目插入哈希映射。

  • map % remove( key, existed ) - 删除与 key 关联的条目(如果有)。

  • map % set_other_data( key, other, exists ) - 更改与条目关联的其他数据。

报告映射内容的过程

  • map % get_all_keys( all_keys ) - 返回映射中包含的所有键;

  • map % get_other_data( key, other, exists ) - 返回与 key 关联的其他数据;

  • map % key_test( key, present) - 返回一个标志,指示 key 是否存在于映射中。

报告映射结构的过程

  • map % calls() - 哈希映射上的子程序调用次数。

  • map % entries()- 哈希映射中的条目数。

  • map % loading() - 哈希映射中条目数相对于插槽数的比率。

  • map % map_probes() - 哈希映射上的总表探测次数。

  • map % slots() - 返回哈希映射中分配的插槽数。

  • map % total_depth() - 返回插槽条目从其插槽索引开始的基于一的偏移量的总数

stdlib_hashmaps 过程的规格

calls - 返回哈希映射上的调用次数

状态

实验性

描述

返回哈希映射上的过程调用次数。

语法

value = map % calls ()

纯函数

参数

map (pass) - 应为 hashmap_type 类的表达式。它是一个 intent(in) 参数。

结果字符

结果将是一个 int_calls 类型的整数。

结果值

结果将是哈希映射上的过程调用次数。

示例
program example_calls
  use stdlib_hashmaps, only: chaining_hashmap_type, int_calls
  use stdlib_hashmap_wrappers, only: fnv_1_hasher
  implicit none
  type(chaining_hashmap_type) :: map
  integer(int_calls) :: initial_calls
  call map%init(fnv_1_hasher)
  initial_calls = map%calls()
  print *, "INITIAL_CALLS =  ", initial_calls
end program example_calls

entries - 返回哈希映射中的条目数

状态

实验性

描述

返回哈希映射中的条目数。

语法

value = map % entries ()

纯函数

参数

map (pass) - 应为 hashmap_type 类的表达式。它是一个 intent(in) 参数。

结果字符

结果将是一个 int_index 类型的整数。

结果值

结果将是哈希映射中的条目数。

示例
program example_entries
  use stdlib_hashmaps, only: open_hashmap_type, int_index
  use stdlib_hashmap_wrappers, only: fnv_1_hasher
  implicit none
  type(open_hashmap_type) :: map
  integer(int_index) :: initial_entries
  call map%init(fnv_1_hasher)
  initial_entries = map%entries()
  print *, "INITIAL_ENTRIES =  ", initial_entries
end program example_entries

get_all_keys - 返回映射中包含的所有键

状态

实验性

描述

返回映射中包含的所有键。

语法

call map % get_all_keys ( all_keys )

子程序

参数

map (pass): 应为 chaining_hashmap_typeopen_hashmap_type 类的标量变量。它是一个 intent(in) 参数。它将是用于存储和访问其他数据的哈希映射。

all_keys: 应为 key_type 类型的秩 1 可分配数组。它是一个 intent(out) 参数。

示例
program example_hashmaps_get_all_keys
  use stdlib_kinds, only: int32
  use stdlib_hashmaps, only: chaining_hashmap_type
  use stdlib_hashmap_wrappers, only: fnv_1_hasher, get, &
                                     key_type, other_type, set
  implicit none
  type(chaining_hashmap_type) :: map
  type(key_type)   :: key
  type(other_type) :: other

  type(key_type), allocatable :: keys(:)
  integer(int32) :: i

  character(:), allocatable :: str

  call map%init(fnv_1_hasher)

  ! adding key-value pairs to the map
  call set(key, "initial key")
  call set(other, "value 1")
  call map%map_entry(key, other)

  call set(key, "second key")
  call set(other, "value 2")
  call map%map_entry(key, other)

  call set(key, "last key")
  call set(other, "value 3")
  call map%map_entry(key, other)

  ! getting all the keys in the map
  call map%get_all_keys(keys)

  print '("Number of keys in the hashmap = ", I0)', size(keys)
  !Number of keys in the hashmap = 3

  do i = 1, size(keys)
    call get( keys(i), str )  
    print '("Value of key ", I0, " = ", A)', i, str
  end do
  !Value of key 1 = initial key
  !Value of key 2 = second key
  !Value of key 3 = last key

end program example_hashmaps_get_all_keys

get_other_data - 返回与 key 关联的其他数据

状态

实验性

描述

返回与 key 关联的其他数据。

语法

value = map % get_other_data ( key, other [, exists] )

子程序

参数

map (pass): 应为 chaining_hashmap_typeopen_hashmap_type 类的标量变量。它是一个 intent(inout) 参数。它将是用于存储和访问其他数据的哈希映射。

key: 应为 key_type 类型的标量、character 类型的标量、int8 类型的数组或 int32 类型的数组。它是一个 intent(in) 参数。

other: 应为 other_data 类型的变量。它是一个 intent(out) 参数。它是与 key 关联的其他数据。

exists (可选): 应为逻辑类型变量。它是一个 intent(out) 参数。如果为 .true.,则映射中存在具有给定 key 的条目,并且 other 已定义。如果为 .false.,则 other 未定义。

示例

以下是检索与 key 关联的其他数据的示例

program example_get_other_data
  use stdlib_kinds, only: int8, int64
  use stdlib_hashmaps, only: chaining_hashmap_type, int_index
  use stdlib_hashmap_wrappers, only: fnv_1_hasher, key_type, other_type, set, get
  implicit none
  logical                     :: conflict
  type(key_type)              :: key
  type(other_type)            :: other
  type(chaining_hashmap_type) :: map
  type dummy_type
    integer                   :: value(4)
  end type dummy_type
  type(dummy_type) :: dummy
  class(*), allocatable       :: data
  integer(int8), allocatable  :: key_array(:)
  integer                     :: int_scalar

  ! Initialize hashmap
  call map%init(fnv_1_hasher)

  ! Hashmap functions are setup to store scalar value types (other).  Use a dervied
  ! type wrapper to store arrays.
  dummy%value = [4, 3, 2, 1]
  call set(other, dummy)

  ! Explicitly set key type using set function
  call set(key, [0, 1])
  call map%map_entry(key, other, conflict)
  if (.not. conflict) then
    call map%get_other_data(key, other)
  else
    error stop 'Key is already present in the map.'
  end if
  call get(other, data)
  select type (data)
  type is (dummy_type)
    print *, 'Other data % value = ', data%value
  class default
    print *, 'Invalid data type in other'
  end select

! Also can use map_entry and get_other_data generic key interfaces.   
! This is an exmple with integer arrays.  
  call map%map_entry( [2,3], other, conflict)
  if (.not. conflict) then
    call map%get_other_data( [2,3], other)
  else
    error stop 'Key is already present in the map.'
  end if
  call get(other, data)
  select type (data)
  type is (dummy_type)
    print *, 'Other data % value = ', data%value
  class default
    print *, 'Invalid data type in other'
  end select

  ! Integer scalars need to be passed as an array.   
  int_scalar = 2
  call map%map_entry( [int_scalar], other, conflict)
  if (.not. conflict) then
    call map%get_other_data( [int_scalar], other)
  else
    error stop 'Key is already present in the map.'
  end if
  call get(other, data)
  select type (data)
  type is (dummy_type)
    print *, 'Other data % value = ', data%value
  class default
    print *, 'Invalid data type in other'
  end select

  ! Example using character type key interface
  call map%map_entry( 'key_string', other, conflict)
  if (.not. conflict) then
    call map%get_other_data( 'key_string', other)
  else
    error stop 'Key is already present in the map.'
  end if
  call get(other, data)
  select type (data)
  type is (dummy_type)
    print *, 'Other data % value = ', data%value
  class default
    print *, 'Invalid data type in other'
  end select

! Transfer to int8 arrays to generate key for unsupported types.  
  key_array = transfer( [0_int64, 1_int64], [0_int8] )
  call map%map_entry( key_array, other, conflict)
  if (.not. conflict) then
    call map%get_other_data( key_array, other)
  else
    error stop 'Key is already present in the map.'
  end if
  call get(other, data)
  select type (data)
  type is (dummy_type)
    print *, 'Other data % value = ', data%value
  class default
    print *, 'Invalid data type in other'
  end select

end program example_get_other_data

init - 初始化哈希映射

状态

实验性

描述

初始化 hashmap_type 对象。

语法

call map % init ( hasher [, slots_bits, status ] )

子程序

参数

map (传递): 应为 chaining_hashmap_typeopen_hashmap_type 类的标量变量。它是一个 intent(out) 参数。它将是一个用于存储和访问条目的哈希映射。

hasher: 应为接口为 hash_fun 的过程。它是一个 intent(in) 参数。它是用于从条目键生成表哈希值的过程。

slots_bits (可选): 应为标量默认整数表达式。它是一个 intent(in) 参数。表中的初始插槽数量将为 2**slots_bits

  • slots_bits 应为小于 max_bits 的正默认整数,否则处理将以信息性错误代码停止。

  • 如果 slots_bits 缺失,则 slots_bits 的有效值为 default_bits

status (可选): 应为 int32 类型的标量整数变量。它是一个 intent(out) 参数。如果在返回时存在,它应具有错误代码值。

  • 如果映射已成功初始化,则 status 的值为 success

  • 如果为 map 数组分配内存失败,则 status 的值为 alloc_fault

  • 如果 slot_bits < 6slots_bits > max_bits,则 status 的值为 array_size_error

  • 如果 status 缺失,但 status 的值不为 success,则处理将以信息性停止代码停止。

示例
program example_init
  use stdlib_hashmaps, only: chaining_hashmap_type
  use stdlib_hashmap_wrappers, only: fnv_1_hasher
  implicit none
  type(chaining_hashmap_type) :: map
  call map%init(fnv_1_hasher, slots_bits=10)
end program example_init

key_test - 指示 key 是否存在

状态

实验性

描述

返回一个逻辑标志,指示 key 是否在映射中的条目中存在。

语法

call map % key_test ( key, present )

子程序。

参数

map (传递): 应为 chaining_hashmap_typeopen_hashmap_type 类的标量变量。它是一个 intent(inout) 参数。它是其条目将被检查的哈希映射。

key: 应为 key_type 类型标量、character 类型标量、int8 类型数组或 int32 类型数组。它是一个 intent(in) 参数。它是正在检查其在 map 中是否存在的一个 key

present (可选): 应为 logical 类型的标量变量。它是一个 intent(out) 参数。它是一个逻辑标志,其中 .true. 表示映射中存在具有该 key 的条目,而 .false. 表示没有这样的条目存在。

示例
program example_key_test
  use stdlib_kinds, only: int8
  use stdlib_hashmaps, only: chaining_hashmap_type
  use stdlib_hashmap_wrappers, only: fnv_1_hasher, key_type, set
  implicit none
  type(chaining_hashmap_type) :: map
  type(key_type) :: key
  logical :: present
  call map%init(fnv_1_hasher)
  call set(key, [0_int8, 1_int8])
  call map%key_test(key, present)
  print *, "Initial key of 10 present for empty map =  ", present
end program example_key_test

loading - 返回条目与插槽的比率

状态

实验性

描述

返回哈希映射中条目数量相对于插槽数量的比率。

语法

value = map % loading ( )

纯函数

参数

map (传递) - 应为 chaining_hashmap_typeopen_hashmap_type 类的表达式。它是一个 intent(in) 参数。

结果字符

结果将为默认实数。

结果值

结果将是条目数量相对于哈希映射中插槽数量的比率。

示例
program example_loading
  use stdlib_hashmaps, only: open_hashmap_type
  use stdlib_hashmap_wrappers, only: fnv_1_hasher
  implicit none
  type(open_hashmap_type) :: map
  real :: ratio
  call map%init(fnv_1_hasher)
  ratio = map%loading()
  print *, "Initial loading =  ", ratio
end program example_loading

map_entry - 将条目插入哈希映射中

状态

实验性

描述

如果条目不存在,则将其插入哈希映射中。

语法

call map % map_entry ( key[, other, conflict ] )

子程序

参数

map (传递): 应为 chaining_hashmap_typeopen_hashmap_type 类的标量变量。它是一个 intent(inout) 参数。它是接收条目的哈希映射。

key: 应为 key_type 类型标量、character 类型标量、int8 类型数组或 int32 类型数组。它是一个 intent(in) 参数。它是要放置在表中的条目的键。

other (可选): 应为 other_type 类型的标量表达式。它是一个 intent(in) 参数。如果存在,它是与 key 关联的其他数据。

conflict (可选): 应为 logical 类型的标量变量。它是一个 intent(out) 参数。如果存在,.true. 值表示具有 key 值的条目已经存在并且条目未进入映射,.false. 值表示 key 不存在于映射中并且条目已添加到映射中。

  • 如果 key 已经存在于 map 中,则忽略 other 的存在。
示例
program example_map_entry
  use, intrinsic:: iso_fortran_env, only: int8, int64
  use stdlib_hashmaps, only: chaining_hashmap_type
  use stdlib_hashmap_wrappers, only: fnv_1_hasher, key_type, other_type, set
  implicit none
  type(chaining_hashmap_type) :: map
  type(key_type)      :: key
  logical             :: conflict
  type(other_type)    :: other
  integer             :: int_scalar

  ! Initialize hashmap with 2^10 slots.
  ! Hashmap will dynamically increase size if needed.
  call map%init(fnv_1_hasher, slots_bits=10)
  ! Initialize other type with data to store.
  call set(other, 4)

  ! Explicitly set key using set function
  call set(key, [1, 2, 3])
  call map%map_entry(key, other, conflict)
  print *, 'CONFLICT = ', conflict

  ! Using map_entry int32 array interface
  call map%map_entry( [4, 5, 6], other, conflict)
  print *, 'CONFLICT = ', conflict

  ! Integer scalars need to be passed as an array.
  int_scalar = 1
  call map%map_entry( [int_scalar], other, conflict)
  print *, 'CONFLICT = ', conflict

  ! Using map_entry character interface
  call map%map_entry( 'key_string', other, conflict)
  print *, 'CONFLICT = ', conflict

  ! Transfer unsupported key types to int8 arrays.
  call map%map_entry( transfer( [1_int64, 2_int64, 3_int64], [0_int8] ), other, conflict)
  print *, 'CONFLICT = ', conflict

! Keys can be mapped alone without a corresponding value (other).
  call map%map_entry( [7, 8, 9], conflict=conflict)
  print *, 'CONFLICT = ', conflict
end program example_map_entry

map_probes - 返回哈希映射探测次数

状态

实验性

描述

返回哈希映射上的总探测次数。

语法

result = map % map_probes ( )

纯函数

参数

map (传递): 应为 hashmap_type 类的标量表达式。它是一个 intent(in) 参数。它是感兴趣的哈希映射。

结果字符

结果为 int_probes 类型的标量整数。

结果值

结果是 map 自初始化或重新哈希以来的探测次数。

示例
program example_probes
  use stdlib_hashmaps, only: chaining_hashmap_type
  use stdlib_hashmap_wrappers, only: fnv_1_hasher
  implicit none
  type(chaining_hashmap_type) :: map
  integer :: nprobes
  call map%init(fnv_1_hasher)
  nprobes = map%map_probes()
  print *, "Initial probes =  ", nprobes
end program example_probes

num_slots - 返回哈希映射插槽数量

状态

实验性

描述

返回哈希映射上的总插槽数量

语法

result = map % num_slots ( )

纯函数

参数

map: 应为 hashmap_type 类的标量表达式。它是一个 intent(in) 参数。它是感兴趣的哈希映射。

结果字符

结果为 int_index 类型的标量整数。

结果值

结果是 map 中的插槽数量。

示例
program example_num_slots
  use stdlib_hashmaps, only: chaining_hashmap_type, int_index
  use stdlib_hashmap_wrappers, only: fnv_1_hasher
  implicit none
  type(chaining_hashmap_type) :: map
  integer(int_index) :: initial_slots
  call map%init(fnv_1_hasher)
  initial_slots = map%num_slots()
  print *, "Initial slots =  ", initial_slots
end program example_num_slots

rehash - 更改哈希函数

状态

实验性

描述

将映射条目的哈希函数更改为 hasher 的哈希函数。

语法

call map % rehash ( hasher )

子程序

参数

map (传递): 应为 chaining_hashmap_typeopen_hashmap_type 类的标量变量。它是一个 intent(inout) 参数。它是其哈希方法要更改的哈希映射。

hasher: 应为接口为 hasher_fun 的函数。它是 map 要使用的哈希方法。

示例
program example_rehash
  use stdlib_kinds, only: int8
  use stdlib_hashmaps, only: open_hashmap_type
  use stdlib_hashmap_wrappers, only: fnv_1_hasher, fnv_1a_hasher, &
                                     key_type, other_type, set
  implicit none
  type(open_hashmap_type) :: map
  type(key_type)      :: key
  type(other_type)    :: other
  class(*), allocatable :: dummy
  allocate (dummy, source='a dummy value')
  call map%init(fnv_1_hasher, slots_bits=10)
  call set(key, [5_int8, 7_int8, 4_int8, 13_int8])
  call set(other, dummy)
  call map%map_entry(key, other)
  call map%rehash(fnv_1a_hasher)
end program example_rehash

remove - 从哈希映射中删除条目

状态

实验性

描述

从哈希映射 map 中删除条目。

语法

call map % remove ( key[, existed ])

子程序

参数

map (传递): 应为 chaining_hashmap_typeopen_hashmap_type 类的标量变量。它是一个 intent(inout) 参数。它是包含要删除元素的哈希映射。

key: 应为 key_type 类型标量、character 类型标量、int8 类型数组或 int32 类型数组。它是一个 intent(in) 参数。它是标识要删除的条目的 key

existed (可选): 应为 logical 类型的标量变量。它是一个 intent(out) 参数。如果存在,值为 .true. 表示该条目在移除之前存在于映射中,如果为 .false. 表示该条目不存在要移除,并且映射未更改。如果缺失,则该过程将返回没有具有给定键的条目。

示例
program example_remove
  use stdlib_kinds, only: int8, int64
  use stdlib_hashmaps, only: open_hashmap_type, int_index
  use stdlib_hashmap_wrappers, only: fnv_1_hasher, &
                                     fnv_1a_hasher, key_type, other_type, set
  implicit none
  type(open_hashmap_type) :: map
  type(key_type)      :: key
  type(other_type)    :: other
  logical             :: existed
  integer             :: int_scalar

  ! Initialize hashmap with 2^10 slots.
  ! Hashmap will dynamically increase size if needed.
  call map%init(fnv_1_hasher, slots_bits=10)

  ! Initialize other type with data to store.
  call set(other, 4.0)

  ! Explicitly set key type using set function
  call set(key, [1, 2, 3])
  call map%map_entry(key, other)
  call map%remove(key, existed)
  print *, "Removed key existed = ", existed

  ! Using map_entry and remove int32 generic interface.
  call map%map_entry([1, 2, 3], other)
  call map%remove([1, 2, 3], existed)
  print *, "Removed key existed = ", existed

  ! Integer scalars need to be passed as an array.
  int_scalar = 1
  call map%map_entry( [int_scalar], other)
  call map%remove( [int_scalar], existed)
  print *, "Removed key existed = ", existed

  ! Using map_entry and remove character generic interface.
  call map%map_entry('key_string', other)
  call map%remove('key_string', existed)
  print *, "Removed key existed = ", existed

  ! Use transfer to int8 arrays for unsupported key types.
  call map%map_entry( transfer( [1_int64, 2_int64], [0_int8] ), other)
  call map%remove( transfer( [1_int64,2_int64], [0_int8] ), existed)
  print *, "Removed key existed = ", existed
end program example_remove

set_other_data - 替换条目的其他数据

状态

实验性

描述

替换映射中具有键值 key 的条目的其他数据。

语法

call map % set_other_data ( key, other[, exists] )

子程序

参数

map (传递): 应为 chaining_hashmap_typeopen_hashmap_type 类的标量变量。它是一个 intent(inout) 参数。它将是一个用于存储和访问条目数据的哈希映射。

key: 应为 key_type 类型标量、character 类型标量、int8 类型数组或 int32 类型数组。它是一个 intent(in) 参数。它是其 other 数据要被替换的条目的 key

other: 应为 other_type 类型的标量表达式。它是一个 intent(in) 参数。它是要存储为具有键值 key 的条目的其他数据的數據。

exists (可选): 应为 logical 类型的标量变量。它是一个 intent(out) 参数。如果存在,值为 .true. 表示映射中存在具有该 key 的条目,并且其 other 数据已被替换,否则如果 exists.false.,则该条目不存在,并且没有任何操作。

示例
program example_set_other_data
  use stdlib_kinds, only: int8
  use stdlib_hashmaps, only: open_hashmap_type
  use stdlib_hashmap_wrappers, only: fnv_1_hasher, &
                                     fnv_1a_hasher, key_type, other_type, set
  implicit none
  logical :: exists
  type(open_hashmap_type) :: map
  type(key_type)      :: key
  type(other_type)    :: other

  ! Initialize hashmap with 2^10 slots.
  ! Hashmap will dynamically increase size if needed.
  call map%init(fnv_1_hasher, slots_bits=10)
  call set(key, [5, 7, 4, 13])
  call set(other, 'A value')
  call map%map_entry(key, other)

  call set(other, 'Another value')
  call map%set_other_data(key, other, exists)
  print *, 'The entry to have its other data replaced exists = ', exists

end program example_set_other_data

slots_bits - 返回用于寻址哈希映射插槽的位数

状态

实验性

描述

返回用于寻址哈希映射插槽的总位数。

语法

result = map % slots_bits ( )

纯函数

参数

map (传递): 应为 hashmap_type 类的标量表达式。它是一个 intent(in) 参数。它是感兴趣的哈希映射。

结果字符

结果为 int_index 类型的标量整数。

结果值

结果是 map 中用于寻址插槽的位数。

示例
program example_slots_bits
  use stdlib_hashmaps, only: chaining_hashmap_type
  use stdlib_hashmap_wrappers, only: fnv_1_hasher
  implicit none
  type(chaining_hashmap_type) :: map
  integer :: bits
  call map%init(fnv_1_hasher)
  bits = map%slots_bits()
  print *, "Initial slot bits =  ", bits
end program example_slots_bits

total_depth - 返回哈希映射条目的总深度

状态

实验性

描述

返回哈希映射中插槽条目与其插槽索引之间基于一的偏移量总数

语法

result = map % total_depth ( )

纯函数

参数

map (传递): 应为 hashmap_type 类的标量表达式。它是一个 intent(in) 参数。它是感兴趣的哈希映射。

结果字符

结果为 int_depth 类型的标量整数。

结果值

结果是映射中插槽条目与其插槽索引之间基于一的偏移量总数。

示例
program example_total_depth
  use stdlib_hashmaps, only: chaining_hashmap_type, int_depth
  use stdlib_hashmap_wrappers, only: fnv_1_hasher
  implicit none
  type(chaining_hashmap_type) :: map
  integer(int_depth) :: initial_depth
  call map%init(fnv_1_hasher)
  initial_depth = map%total_depth()
  print *, "Initial total depth =  ", initial_depth
end program example_total_depth