chaining_hashmap_type 派生类型

type, public, extends(hashmap_type) :: chaining_hashmap_type

实现 chaining_hashmap_type 类型的类型 (规范)


终结过程

final :: free_chaining_map

  • private interface free_chaining_map()

    参数


类型绑定过程

procedure, public, non_overridable, pass(map) :: calls

  • private pure function calls(map)

    返回打开哈希表上的子程序调用次数 (规范)

    参数:map - 打开的哈希表

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(in) :: map

    返回值 integer(kind=int_calls)

procedure, public, non_overridable, pass(map) :: char_get_other_data

  • private subroutine char_get_other_data(map, value, other, exists)

    字符键通用接口,用于 get_other_data 函数

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    character(len=*), intent(in) :: value
    type(other_type), intent(out) :: other
    logical, intent(out), optional :: exists

procedure, public, non_overridable, pass(map) :: char_key_test

  • private subroutine char_key_test(map, value, present)

    返回一个逻辑标志,指示 KEY 是否存在于哈希表中 (规范)

    参数:map - 感兴趣的哈希表 value - 字符数组,是查找的键。
    present - 一个标志,指示键是否出现在表中

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    character(len=*), intent(in) :: value
    logical, intent(out) :: present

procedure, public, non_overridable, pass(map) :: char_map_entry

  • private subroutine char_map_entry(map, value, other, conflict)

    将条目插入哈希表中 (规范)

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    character(len=*), intent(in) :: value
    type(other_type), intent(in), optional :: other
    logical, intent(out), optional :: conflict

procedure, public, non_overridable, pass(map) :: char_remove_entry

  • private subroutine char_remove_entry(map, value, existed)

    删除具有键的条目(如果有) 参数:map - 要从中删除条目的表 key - 条目的键 existed - 一个逻辑标志,指示具有键的条目是否出现在原始表中

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    character(len=*), intent(in) :: value
    logical, intent(out), optional :: existed

procedure, public, non_overridable, pass(map) :: char_set_other_data

  • private subroutine char_set_other_data(map, value, other, exists)

    更改与键关联的其他数据 参数:map - 包含感兴趣条目的表 value - 条目在表中的字符值键 other - 与键关联的新数据 exists - 一个逻辑标志,指示键是否已在表中输入

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    character(len=*), intent(in) :: value
    type(other_type), intent(in) :: other
    logical, intent(out), optional :: exists

procedure, public, non_overridable, pass(map) :: entries

  • private pure function entries(map)

    返回哈希表中的条目数 (规范)

    参数:map - 打开的哈希表

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(in) :: map

    返回值 integer(kind=int_index)

procedure, public :: get_all_keys => get_all_chaining_keys

  • interface

    private module subroutine get_all_chaining_keys(map, all_keys)

    返回哈希表中包含的所有键 参数:map - 链式哈希表 all_keys - 哈希表中包含的所有键

    参数

    类型 意图可选 属性 名称
    class(chaining_hashmap_type), intent(in) :: map
    type(key_type), intent(out), allocatable :: all_keys(:)
  • private interface get_other_open_data()

    参数

  • private subroutine int8_get_other_data(map, value, other, exists)

    Int8 键通用接口,用于 get_other_data 函数

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    integer(kind=int8), intent(in) :: value(:)
    type(other_type), intent(out) :: other
    logical, intent(out), optional :: exists
  • private subroutine int32_get_other_data(map, value, other, exists)

    Int32 键通用接口,用于 get_other_data 函数

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    integer(kind=int32), intent(in) :: value(:)
    type(other_type), intent(out) :: other
    logical, intent(out), optional :: exists
  • private subroutine char_get_other_data(map, value, other, exists)

    字符键通用接口,用于 get_other_data 函数

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    character(len=*), intent(in) :: value
    type(other_type), intent(out) :: other
    logical, intent(out), optional :: exists

procedure, public :: init => init_chaining_map

  • interface

    private module subroutine init_chaining_map(map, hasher, slots_bits, status)

    例程用于分配一个空表,其中 HASHER 为哈希函数,2SLOTS_BITS 为初始 SIZE(map % slots),并且 SIZE(map % slots) 限制为不超过 2MAX_BITS。所有字段都被初始化。参数:map - 要初始化的链式哈希表 hasher - 用于将键映射到槽的哈希函数 slots_bits - 用于初始化槽数的 2 的幂 status - 整数错误状态标志,允许的值为:success - 未发现任何问题 alloc_fault - 无法分配 map % slots 或 map % inverse array_size_error - slots_bits 小于 default_bits 或大于 max_bits

    参数

    类型 意图可选 属性 名称
    class(chaining_hashmap_type), intent(out) :: map
    procedure(hasher_fun) :: hasher
    integer, intent(in), optional :: slots_bits
    integer(kind=int32), intent(out), optional :: status

procedure, public, non_overridable, pass(map) :: int32_get_other_data

  • private subroutine int32_get_other_data(map, value, other, exists)

    Int32 键通用接口,用于 get_other_data 函数

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    integer(kind=int32), intent(in) :: value(:)
    type(other_type), intent(out) :: other
    logical, intent(out), optional :: exists

procedure, public, non_overridable, pass(map) :: int32_key_test

  • private subroutine int32_key_test(map, value, present)

    返回一个逻辑标志,指示 KEY 是否存在于哈希表中 (规范)

    参数:map - 感兴趣的哈希表 value - int32 数组,是查找的键。
    present - 一个标志,指示键是否出现在表中

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    integer(kind=int32), intent(in) :: value(:)
    logical, intent(out) :: present

procedure, public, non_overridable, pass(map) :: int32_map_entry

  • private subroutine int32_map_entry(map, value, other, conflict)

    将条目插入哈希表中 (规范)

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    integer(kind=int32), intent(in) :: value(:)
    type(other_type), intent(in), optional :: other
    logical, intent(out), optional :: conflict

procedure, public, non_overridable, pass(map) :: int32_remove_entry

  • private subroutine int32_remove_entry(map, value, existed)

    删除具有键的条目(如果有) 参数:map - 要从中删除条目的表 key - 条目的键 existed - 一个逻辑标志,指示具有键的条目是否出现在原始表中

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    integer(kind=int32), intent(in) :: value(:)
    logical, intent(out), optional :: existed

procedure, public, non_overridable, pass(map) :: int32_set_other_data

  • private subroutine int32_set_other_data(map, value, other, exists)

    更改与键关联的其他数据 参数:map - 包含感兴趣条目的表 value - 条目在表中的 int32 数组键 other - 与键关联的新数据 exists - 一个逻辑标志,指示键是否已在表中输入

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    integer(kind=int32), intent(in) :: value(:)
    type(other_type), intent(in) :: other
    logical, intent(out), optional :: exists

procedure, public, non_overridable, pass(map) :: int8_get_other_data

  • private subroutine int8_get_other_data(map, value, other, exists)

    Int8 键通用接口,用于 get_other_data 函数

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    integer(kind=int8), intent(in) :: value(:)
    type(other_type), intent(out) :: other
    logical, intent(out), optional :: exists

procedure, public, non_overridable, pass(map) :: int8_key_test

  • private subroutine int8_key_test(map, value, present)

    返回一个逻辑标志,指示 KEY 是否存在于哈希表中 (规范)

    参数:map - 感兴趣的哈希表 value - int8 数组,是查找的键。
    present - 一个标志,指示键是否出现在表中

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    integer(kind=int8), intent(in) :: value(:)
    logical, intent(out) :: present

procedure, public, non_overridable, pass(map) :: int8_map_entry

  • private subroutine int8_map_entry(map, value, other, conflict)

    Int8 通用接口,用于映射条目 (规范)

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    integer(kind=int8), intent(in) :: value(:)
    type(other_type), intent(in), optional :: other
    logical, intent(out), optional :: conflict

procedure, public, non_overridable, pass(map) :: int8_remove_entry

  • private subroutine int8_remove_entry(map, value, existed)

    删除具有键的条目(如果有) 参数:map - 要从中删除条目的表 value - int8 数组键,指向条目 existed - 一个逻辑标志,指示具有键的条目是否出现在原始表中

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    integer(kind=int8), intent(in) :: value(:)
    logical, intent(out), optional :: existed

procedure, public, non_overridable, pass(map) :: int8_set_other_data

  • private subroutine int8_set_other_data(map, value, other, exists)

    更改与键关联的其他数据 参数:map - 包含感兴趣条目的表 value - 条目在表中的 int8 数组键 other - 与键关联的新数据 exists - 一个逻辑标志,指示键是否已在表中输入

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    integer(kind=int8), intent(in) :: value(:)
    type(other_type), intent(in) :: other
    logical, intent(out), optional :: exists

procedure, public :: key_get_other_data => get_other_chaining_data

  • interface

    private module subroutine get_other_chaining_data(map, key, other, exists)

    返回与反向表索引关联的其他数据 参数:map - 链式哈希表 key - 与映射条目关联的键 other - 与键关联的其他数据 exists - 一个逻辑标志,指示是否有一个具有该键的条目存在

    参数

    类型 意图可选 属性 名称
    class(chaining_hashmap_type), intent(inout) :: map
    type(key_type), intent(in) :: key
    type(other_type), intent(out) :: other
    logical, intent(out), optional :: exists

procedure, public :: key_key_test => chaining_key_test

  • interface

    private module subroutine chaining_key_test(map, key, present)

    返回一个逻辑标志,指示 KEY 是否出现在哈希表中 参数:map - 感兴趣的哈希表 key - 感兴趣的键 present - 一个逻辑标志,指示键是否出现在表中

    参数

    类型 意图可选 属性 名称
    class(chaining_hashmap_type), intent(inout) :: map
    type(key_type), intent(in) :: key
    logical, intent(out) :: present

procedure, public :: key_map_entry => map_chain_entry

  • interface

    private module subroutine map_chain_entry(map, key, other, conflict)

    map - 感兴趣的哈希表 key - 标识条目的键 other - 与键关联的其他数据 conflict - 逻辑标志,指示条目键是否与现有键冲突

    参数

    类型 意图可选 属性 名称
    class(chaining_hashmap_type), intent(inout) :: map
    type(key_type), intent(in) :: key
    type(other_type), intent(in), optional :: other
    logical, intent(out), optional :: conflict

procedure, public :: key_remove_entry => remove_chaining_entry

  • interface

    private module subroutine remove_chaining_entry(map, key, existed)

    删除具有键的条目(如果有) 参数:map - 要从中删除条目的表 key - 条目的键 existed - 一个逻辑标志,指示具有键的条目是否出现在原始表中

    参数

    类型 意图可选 属性 名称
    class(chaining_hashmap_type), intent(inout) :: map
    type(key_type), intent(in) :: key
    logical, intent(out), optional :: existed

procedure, public :: key_set_other_data => set_other_chaining_data

  • interface

    private module subroutine set_other_chaining_data(map, key, other, exists)

    更改与键关联的其他数据 参数:map - 包含感兴趣条目的表 key - 条目在表中的键 other - 与键关联的新数据 exists - 一个逻辑标志,指示键是否已在表中输入

    参数

    类型 意图可选 属性 名称
    class(chaining_hashmap_type), intent(inout) :: map
    type(key_type), intent(in) :: key
    type(other_type), intent(in) :: other
    logical, intent(out), optional :: exists

通用,公共 :: key_test => key_key_testint8_key_testint32_key_testchar_key_test

  • 私有接口 open_key_test()

    参数

  • private subroutine int8_key_test(map, value, present)

    返回一个逻辑标志,指示 KEY 是否存在于哈希表中 (规范)

    参数:map - 感兴趣的哈希表 value - int8 数组,是查找的键。
    present - 一个标志,指示键是否出现在表中

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    integer(kind=int8), intent(in) :: value(:)
    logical, intent(out) :: present
  • private subroutine int32_key_test(map, value, present)

    返回一个逻辑标志,指示 KEY 是否存在于哈希表中 (规范)

    参数:map - 感兴趣的哈希表 value - int32 数组,是查找的键。
    present - 一个标志,指示键是否出现在表中

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    integer(kind=int32), intent(in) :: value(:)
    logical, intent(out) :: present
  • private subroutine char_key_test(map, value, present)

    返回一个逻辑标志,指示 KEY 是否存在于哈希表中 (规范)

    参数:map - 感兴趣的哈希表 value - 字符数组,是查找的键。
    present - 一个标志,指示键是否出现在表中

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    character(len=*), intent(in) :: value
    logical, intent(out) :: present

过程,公共 :: loading => chaining_loading

  • interface

    私有纯模块函数 chaining_loading(map)

    返回哈希映射中条目相对于槽位的数量 参数:map - 链式哈希映射

    参数

    类型 意图可选 属性 名称
    class(chaining_hashmap_type), intent(in) :: map

    返回值 实数

通用,公共 :: map_entry => key_map_entryint8_map_entryint32_map_entrychar_map_entry

  • 私有接口 map_open_entry()

    参数

  • private subroutine int8_map_entry(map, value, other, conflict)

    Int8 通用接口,用于映射条目 (规范)

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    integer(kind=int8), intent(in) :: value(:)
    type(other_type), intent(in), optional :: other
    logical, intent(out), optional :: conflict
  • private subroutine int32_map_entry(map, value, other, conflict)

    将条目插入哈希表中 (规范)

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    integer(kind=int32), intent(in) :: value(:)
    type(other_type), intent(in), optional :: other
    logical, intent(out), optional :: conflict
  • private subroutine char_map_entry(map, value, other, conflict)

    将条目插入哈希表中 (规范)

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    character(len=*), intent(in) :: value
    type(other_type), intent(in), optional :: other
    logical, intent(out), optional :: conflict

过程,公共,不可重写,传递(map) :: map_probes

  • 私有纯函数 map_probes(map)

    返回哈希映射上的探测总数 (规格)

    参数:map - 打开的哈希表

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(in) :: map

    返回值 integer(kind=int_calls)

过程,公共,不可重写,传递(map) :: num_slots

  • 私有纯函数 num_slots(map)

    返回哈希映射中分配的槽位数 (规格)

    参数:map - 打开的哈希表

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(in) :: map

    返回值 integer(kind=int_index)

过程,公共 :: rehash => rehash_chaining_map

  • interface

    私有模块子例程 rehash_chaining_map(map, hasher)

    将表条目的哈希方法更改为 HASHER 的方法。参数:map 要重新哈希的表 hasher 要用于表的哈希函数

    参数

    类型 意图可选 属性 名称
    class(chaining_hashmap_type), intent(inout) :: map
    procedure(hasher_fun) :: hasher
  • 私有接口 remove_open_entry()

    参数

  • private subroutine int8_remove_entry(map, value, existed)

    删除具有键的条目(如果有) 参数:map - 要从中删除条目的表 value - int8 数组键,指向条目 existed - 一个逻辑标志,指示具有键的条目是否出现在原始表中

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    integer(kind=int8), intent(in) :: value(:)
    logical, intent(out), optional :: existed
  • private subroutine int32_remove_entry(map, value, existed)

    删除具有键的条目(如果有) 参数:map - 要从中删除条目的表 key - 条目的键 existed - 一个逻辑标志,指示具有键的条目是否出现在原始表中

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    integer(kind=int32), intent(in) :: value(:)
    logical, intent(out), optional :: existed
  • private subroutine char_remove_entry(map, value, existed)

    删除具有键的条目(如果有) 参数:map - 要从中删除条目的表 key - 条目的键 existed - 一个逻辑标志,指示具有键的条目是否出现在原始表中

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    character(len=*), intent(in) :: value
    logical, intent(out), optional :: existed
  • 私有接口 set_other_open_data()

    参数

  • private subroutine int8_set_other_data(map, value, other, exists)

    更改与键关联的其他数据 参数:map - 包含感兴趣条目的表 value - 条目在表中的 int8 数组键 other - 与键关联的新数据 exists - 一个逻辑标志,指示键是否已在表中输入

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    integer(kind=int8), intent(in) :: value(:)
    type(other_type), intent(in) :: other
    logical, intent(out), optional :: exists
  • private subroutine int32_set_other_data(map, value, other, exists)

    更改与键关联的其他数据 参数:map - 包含感兴趣条目的表 value - 条目在表中的 int32 数组键 other - 与键关联的新数据 exists - 一个逻辑标志,指示键是否已在表中输入

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    integer(kind=int32), intent(in) :: value(:)
    type(other_type), intent(in) :: other
    logical, intent(out), optional :: exists
  • private subroutine char_set_other_data(map, value, other, exists)

    更改与键关联的其他数据 参数:map - 包含感兴趣条目的表 value - 条目在表中的字符值键 other - 与键关联的新数据 exists - 一个逻辑标志,指示键是否已在表中输入

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(inout) :: map
    character(len=*), intent(in) :: value
    type(other_type), intent(in) :: other
    logical, intent(out), optional :: exists

过程,公共,不可重写,传递(map) :: slots_bits

  • 私有纯函数 slots_bits(map)

    返回用于指定哈希映射中分配的槽位数量的位数 (规格)

    参数:map - 打开的哈希表

    参数

    类型 意图可选 属性 名称
    class(hashmap_type), intent(in) :: map

    返回值 整数

过程,公共 :: total_depth => total_chaining_depth

  • interface

    私有模块函数 total_chaining_depth(map) 结果(total_depth)

    返回哈希映射中槽位条目与其槽位索引之间的基于一的偏移量的总数 参数:map - 链式哈希映射

    参数

    类型 意图可选 属性 名称
    class(chaining_hashmap_type), intent(in) :: map

    返回值 整数(kind=int_depth)

源代码

    type, extends(hashmap_type) :: chaining_hashmap_type
!! Version: Experimental
!!
!! Type implementing the `chaining_hashmap_type` types
!! ([Specifications](../page/specs/stdlib_hashmaps.html#the-chaining_hashmap_type-derived-type))
        private
        type(chaining_map_entry_pool), pointer    :: cache => null()
!! Pool of allocated chaining_map_entry_type objects
        type(chaining_map_entry_type), pointer    :: free_list => null()
!! free list of map entries
        type(chaining_map_entry_ptr), allocatable :: inverse(:)
!! Array of bucket lists (inverses) Note max_elts=size(inverse)
        type(chaining_map_entry_ptr), allocatable :: slots(:)
!! Array of bucket lists Note # slots=size(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