hashmap_type 派生类型

type, public :: hashmap_type

实现抽象哈希映射的类型 (规范)


类型绑定过程

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(get_all_keys), public, deferred, pass(map) :: get_all_keys

  • subroutine get_all_keys(map, all_keys) 原型

    返回哈希映射中包含的所有键 (规范)

    参数:map - 哈希映射 all_keys - 哈希映射中包含的所有键

    参数

    类型 意图可选 属性 名称
    class(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(init_map), public, deferred, pass(map) :: init

  • subroutine init_map(map, hasher, slots_bits, status) 原型

    例程,用于分配一个空映射,其中 HASHER 作为哈希函数,2 ** SLOTS_BITS 初始 SIZE(map % slots),SIZE(map % slots) 限制为最大 2 ** MAX_BITS,最多 LOAD_FACTOR * SIZE(map % slots),map % 反向元素。所有字段都被初始化。参数:map - 要初始化的哈希映射 hasher - 要用于将键映射到槽位的哈希函数 slots_bits - 用于映射到槽位的位数 status - 一个整数错误状态标志,允许的值:success - 没有发现问题 alloc_fault - map % slots 或 map % inverse 无法分配 array_size_error - slots_bits 或 max_bits 小于 default_bits 或大于 strict_max_bits real_value_error - load_factor 小于 0.375 或大于 0.875

    参数

    类型 意图可选 属性 名称
    class(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(key_get_other_data), public, deferred, pass(map) :: key_get_other_data

  • subroutine key_get_other_data(map, key, other, exists) 原型

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

    参数

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

procedure(key_key_test), public, deferred, pass(map) :: key_key_test

  • subroutine key_key_test(map, key, present) 原型

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

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

    参数

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

procedure(key_map_entry), public, deferred, pass(map) :: key_map_entry

  • subroutine key_map_entry(map, key, other, conflict) 原型

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

    参数

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

procedure(key_remove_entry), public, deferred, pass(map) :: key_remove_entry

  • subroutine key_remove_entry(map, key, existed) 原型

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

    参数

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

procedure(key_set_other_data), public, deferred, pass(map) :: key_set_other_data

  • subroutine key_set_other_data(map, key, other, exists) 原型

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

    参数

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

过程 (加载),公共,延迟,传递 (映射) :: 加载

  • 纯函数 加载 (映射) 原型

    返回哈希映射中条目相对于槽的数量 (规范)

    参数:映射 - 一个哈希映射

    参数

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

  • 私有纯函数 map_probes (映射)

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

    参数:map - 打开哈希映射

    参数

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

    返回值 integer(kind=int_calls)

过程,公共,不可覆盖,传递 (映射) :: num_slots

  • 私有纯函数 num_slots (映射)

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

    参数:map - 打开哈希映射

    参数

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

    返回值 integer(kind=int_index)

过程 (重新哈希映射),公共,延迟,传递 (映射) :: 重新哈希

  • 子程序 rehash_map (映射,哈希器) 原型

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

    参数

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

过程,公共,不可覆盖,传递 (映射) :: slots_bits

  • 私有纯函数 slots_bits (映射)

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

    参数:map - 打开哈希映射

    参数

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

    返回值 整数

过程 (总深度),公共,延迟,传递 (映射) :: 总深度

Key_test 过程。

  • 函数 total_depth (映射) 原型

    返回哈希映射中槽条目yy 从其槽索引的总 1 位偏移量 (规范) 参数:映射 - 一个哈希映射

    参数

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

    返回值 整数 (kind=int64)

源代码

    type, abstract :: hashmap_type
!! Version: Experimental
!!
!! Type implementing an abstract hash map
!! ([Specifications](../page/specs/stdlib_hashmaps.html#the-hashmap_type-abstract-type))
        private
        integer(int_calls) :: call_count = 0
!! Number of calls
        integer(int_calls) :: probe_count = 0
!! Number of probes since last expansion
        integer(int_calls) :: total_probes = 0
!! Cumulative number of probes
        integer(int_index) :: num_entries = 0
!! Number of entries
        integer(int_index) :: num_free = 0
!! Number of elements in the free_list
        integer(int32)     :: nbits = default_bits
!! Number of bits used to address the slots
        procedure(hasher_fun), pointer, nopass :: hasher => fnv_1_hasher
!! Hash function

    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
    
        !! Key_test procedures.
        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
        generic, public :: key_test => key_key_test, int8_key_test, int32_key_test, char_key_test
        
        ! Map_entry procedures
        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
        generic, public :: map_entry => key_map_entry, int8_map_entry, int32_map_entry, char_map_entry
        
        ! Get_other_data procedures
        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
        generic, public :: get_other_data => key_get_other_data, int8_get_other_data, int32_get_other_data, char_get_other_data
        
        ! Key_remove_entry procedures
        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
        generic, public :: remove => key_remove_entry, int8_remove_entry, int32_remove_entry, char_remove_entry
        
        ! Set_other_data procedures
        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 :: set_other_data => key_set_other_data, int8_set_other_data, int32_set_other_data, char_set_other_data
        
    end type hashmap_type