open_hashmap_type 派生类型

type, public, extends(hashmap_type) :: open_hashmap_type

实现“开放”哈希映射的类型


终结过程

final :: free_open_map

  • private interface free_open_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_open_keys

  • interface

    private module subroutine get_all_open_keys(map, all_keys)

    返回哈希映射中包含的所有键参数:map - 一个开放哈希映射 all_keys - 哈希映射中包含的所有键

    参数

    类型 意图可选 属性 名称
    class(open_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)

    get_other_data 函数的 Int8 键泛型接口

    参数

    类型 意图可选 属性 名称
    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)

    get_other_data 函数的 Int32 键泛型接口

    参数

    类型 意图可选 属性 名称
    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_open_map

  • interface

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

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

    参数

    类型 意图可选 属性 名称
    class(open_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)

    get_other_data 函数的 Int32 键泛型接口

    参数

    类型 意图可选 属性 名称
    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)

    get_other_data 函数的 Int8 键泛型接口

    参数

    类型 意图可选 属性 名称
    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_open_data

  • interface

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

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

    参数

    类型 意图可选 属性 名称
    class(open_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 => open_key_test

  • interface

    private module subroutine open_key_test(map, key, present)

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

    参数

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

procedure, public :: key_map_entry => map_open_entry

  • interface

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

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

    参数

    类型 意图可选 属性 名称
    class(open_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_open_entry

  • interface

    私有模块子程序 remove_open_entry(map, key, existed)

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

    参数

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

过程,公共 :: key_set_other_data => set_other_open_data

  • interface

    私有模块子程序 set_other_open_data(map, key, other, exists)

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

    参数

    类型 意图可选 属性 名称
    class(open_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 => open_loading

  • interface

    私有纯模块函数 open_loading(map)

    返回散列表中条目相对于槽的数量 参数:map - 一个开放散列表

    参数

    类型 意图可选 属性 名称
    class(open_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_open_map

  • interface

    私有模块子程序 rehash_open_map(map, hasher)

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

    参数

    类型 意图可选 属性 名称
    class(open_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_open_depth

  • interface

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

    返回散列表中槽条目相对于其槽索引的基于一的偏移量的总数 参数:map - 一个开放散列表

    参数

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

    返回值 整数(kind=int64)

源代码

    type, extends(hashmap_type) :: open_hashmap_type
!! Version: Experimental
!!
!! Type implementing an "open" hash map
        private
        integer(int_index) :: index_mask = 2_int_index**default_bits-1
!! Mask used in linear addressing
        type(open_map_entry_pool), pointer    :: cache => null()
!! Pool of allocated open_map_entry_type objects
        type(open_map_entry_list), pointer    :: free_list => null()
!! free list of map entries
        type(open_map_entry_ptr), allocatable  :: inverse(:)
!! Array of bucket lists (inverses) Note max_elts=size(inverse)
        integer(int_index), allocatable        :: slots(:)
!! Array of indices to the inverse Note # slots=size(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