bitset_large 派生类型

type, public, extends(bitset_type) :: bitset_large

用于超过 64 位的位集的类型 (规范)


类型绑定过程

procedure, public, pass(self) :: all => all_large

  • interface

    private elemental module function all_large(self) result(all)

    如果 self 中的所有位都为 1,则返回 .true.,否则返回 .false.

    参数

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

    返回值 逻辑型

procedure, public, pass(self) :: any => any_large

  • interface

    private elemental module function any_large(self) result(any)

    如果 self 中的任何一位为 1,则返回 .true.,否则返回 .false.

    参数

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

    返回值 逻辑型

procedure, public, pass(self) :: bit_count => bit_count_large

  • interface

    private elemental module function bit_count_large(self) result(bit_count)

    返回 self 中非零位的数量。

    参数

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

    返回值 integer(kind=bits_kind)

procedure, public, pass(self) :: bits

  • public elemental function bits(self)

    许可证
    Creative Commons License
    版本
    实验性

    返回 self 中的位数。

    参数

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

    返回值 integer(kind=bits_kind)

generic, public :: clear => clear_bit, clear_range

  • private interface clear_bit_large()

    参数

  • private interface clear_range_large()

    参数

procedure, public, pass(self) :: clear_bit => clear_bit_large

  • interface

    private elemental module subroutine clear_bit_large(self, pos)

    selfpos 位置处的位设置为零。如果 pos 小于零或大于 bits(self)-1,则忽略。

    参数

    类型 意图可选 属性 名称
    class(bitset_large), intent(inout) :: self
    integer(kind=bits_kind), intent(in) :: pos

procedure, public, pass(self) :: clear_range => clear_range_large

  • interface

    private pure module subroutine clear_range_large(self, start_pos, stop_pos)

    self 中从 start_posstop_pos 位置的所有位设置为零。如果 stop_pos < start_pos,则不修改任何位。超出范围 0 到 bits(set)-1 的位置将被忽略。

    参数

    类型 意图可选 属性 名称
    class(bitset_large), intent(inout) :: self
    integer(kind=bits_kind), intent(in) :: start_pos
    integer(kind=bits_kind), intent(in) :: stop_pos

generic, public :: flip => flip_bit, flip_range

  • private interface flip_bit_large()

    参数

  • private interface flip_range_large()

    参数

procedure, public, pass(self) :: flip_bit => flip_bit_large

  • interface

    private elemental module subroutine flip_bit_large(self, pos)

    翻转 selfpos 位置处的位值,前提是该位置有效。如果 pos 小于 0 或大于 bits(self)-1,则不更改任何值。

    参数

    类型 意图可选 属性 名称
    class(bitset_large), intent(inout) :: self
    integer(kind=bits_kind), intent(in) :: pos

procedure, public, pass(self) :: flip_range => flip_range_large

  • interface

    private pure module subroutine flip_range_large(self, start_pos, stop_pos)

    翻转 self 中从 start_posstop_pos 位置的所有有效位。如果 stop_pos < start_pos,则不翻转任何位。小于 0 或大于 bits(self)-1 的位置将被忽略。

    参数

    类型 意图可选 属性 名称
    class(bitset_large), intent(inout) :: self
    integer(kind=bits_kind), intent(in) :: start_pos
    integer(kind=bits_kind), intent(in) :: stop_pos

procedure, public, pass(self) :: from_string => from_string_large

  • interface

    private module subroutine from_string_large(self, string, status)

    初始化位集 self,将 string 视为二进制字面量 status 可能具有以下值:* success - 如果未发现任何问题,* alloc_fault - 如果位集分配失败 * char_string_too_large_error - 如果 string 太大,或 * char_string_invalid_error - 如果字符串包含无效字符。

    参数

    类型 意图可选 属性 名称
    class(bitset_large), intent(out) :: self
    character(len=*), intent(in) :: string
    integer, intent(out), optional :: status

generic, public :: init => init_zero

  • private interface init_zero_large()

    参数

procedure, public, pass(self) :: init_zero => init_zero_large

  • interface

    private module subroutine init_zero_large(self, bits, status)

    创建大小为 bits 的位集 self,所有位都初始化为零。bits 必须是非负数。如果发生错误且 status 缺失,则处理将停止并显示信息性停止代码。status 将具有以下值之一;* success - 如果未发现任何问题,* alloc_fault - 如果内存分配失败 * array_size_invalid_error - 如果 bits 为负数或大于 64 且 self 的类为 bitset_64,或者

    参数

    类型 意图可选 属性 名称
    class(bitset_large), intent(out) :: self
    integer(kind=bits_kind), intent(in) :: bits
    integer, intent(out), optional :: status

procedure, public, pass(self) :: input => input_large

  • interface

    private module subroutine input_large(self, unit, status)

    从非格式化 I/O 单位 unit 读取位集 self 的组件,假设这些组件是使用 output 编写的。如果发生错误且 status 缺失,则处理将停止并显示信息性停止代码。status 具有以下值之一:* success - 如果未发现任何问题 * alloc_fault - 如果为 self 分配内存失败,或 * array_size_invalid_error 如果 unit 中的 bits(self) 为负数或对于 bitset_64 输入大于 64。* read_failure - 如果从 unit 读取失败

    参数

    类型 意图可选 属性 名称
    class(bitset_large), intent(out) :: self
    integer, intent(in) :: unit
    integer, intent(out), optional :: status

procedure, public, pass(self) :: none => none_large

  • interface

    private elemental module function none_large(self) result(none)

    如果 self 中的任何位都不为 1,则返回 .true.

    参数

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

    返回值 逻辑型

procedure, public, pass(self) :: not => not_large

  • interface

    private elemental module subroutine not_large(self)

    self 中的位设置为其逻辑补码

    参数

    类型 意图可选 属性 名称
    class(bitset_large), intent(inout) :: self

procedure, public, pass(self) :: output => output_large

  • interface

    private module subroutine output_large(self, unit, status)

    将位集 self 的组件写入非格式化 I/O 单位 unit,以与 input 兼容的非格式化序列。如果 status 缺失,则错误将导致错误停止并显示信息性停止代码。如果 status 存在,则其默认值为 success,或者如果写入失败,则值为 write_failure

    参数

    类型 意图可选 属性 名称
    class(bitset_large), intent(in) :: self
    integer, intent(in) :: unit
    integer, intent(out), optional :: status

generic, public :: read_bitset => read_bitset_string, read_bitset_unit

  • private interface read_bitset_string_large()

    参数

  • private interface read_bitset_unit_large()

    参数

procedure, public, pass(self) :: read_bitset_string => read_bitset_string_large

  • interface

    private module subroutine read_bitset_string_large(self, string, status)

    使用默认字符 string 中的位集字面量来定义位集 self。字面量前面可以是任意数量的空格字符。如果 status 缺失,则错误将导致错误停止并显示信息性停止代码。如果 status 存在,则其具有以下值之一 * success - 如果未发生任何问题,* alloc_fault - 如果为 SELF 分配内存失败,* array_size_invalid_error - ifbits(self)instringis greater than 64 for abitset_64, *char_string_invalid_error- 如果位集字面量包含无效字符,*char_string_too_small_error - 如果字符串在读取所有位之前结束。* integer_overflow_error - 如果位集字面量的 bits(self) 值太大而无法表示,

    参数

    类型 意图可选 属性 名称
    class(bitset_large), intent(out) :: self
    character(len=*), intent(in) :: string
    integer, intent(out), optional :: status

procedure, public, pass(self) :: read_bitset_unit => read_bitset_unit_large

  • interface

    private module subroutine read_bitset_unit_large(self, unit, advance, status)

    使用 I/O 单位 unit 的格式化文件中当前位置处的位集字面量来定义位集 self。字面量前面可以是任意数量的空格字符。如果 advance 存在,则它必须是 'YES' 或 'NO'。如果不存在,则其默认值为 'YES',以确定是否发生 I/O 提前。如果 status 缺失,则错误将导致错误停止并显示信息性停止代码。如果 status 存在,则其具有以下值之一:* success - 如果未发生任何问题,* alloc_fault - 如果 self 的分配失败,* array_size_invalid_error - 如果位集字面量中的 bits(self) 对于 bitset_64 大于 64,* char_string_invalid_error - 如果读取位集字面量时发现无效字符,* eof_failure - 如果 read 语句在完成读取位集字面量之前到达文件末尾,* integer_overflow_error - 如果位集字面量的 bits(self) 值太大而无法表示,* read_failure - 如果 read 语句失败,

    参数

    类型 意图可选 属性 名称
    class(bitset_large), intent(out) :: self
    integer, intent(in) :: unit
    character(len=*), intent(in), optional :: advance
    integer, intent(out), optional :: status

generic, public :: set => set_bit, set_range

  • private interface set_bit_large()

    参数

  • private interface set_range_large()

    参数

procedure, public, pass(self) :: set_bit => set_bit_large

  • interface

    private elemental module subroutine set_bit_large(self, pos)

    设置 selfpos 位置处的值,前提是该位置有效。如果位置小于 0 或大于 bits(self)-1,则 self 保持不变。

    参数

    类型 意图可选 属性 名称
    class(bitset_large), intent(inout) :: self
    integer(kind=bits_kind), intent(in) :: pos

procedure, public, pass(self) :: set_range => set_range_large

  • interface

    private pure module subroutine set_range_large(self, start_pos, stop_pos)

    self中从start_posstop_pos位置的所有有效位设置为1。如果stop_pos < start_pos,则不更改任何位。超出0到bits(self)-1范围的位置将被忽略。

    参数

    类型 意图可选 属性 名称
    class(bitset_large), intent(inout) :: self
    integer(kind=bits_kind), intent(in) :: start_pos
    integer(kind=bits_kind), intent(in) :: stop_pos

过程,公共,传递(self) :: test => test_large

  • interface

    私有元素模块函数 test_large(self, pos) 结果(test)

    如果pos位置被设置,则返回.true.,否则返回.false.。如果pos为负数或大于bits(self) - 1,则结果为.false.

    参数

    类型 意图可选 属性 名称
    class(bitset_large), intent(in) :: self
    integer(kind=bits_kind), intent(in) :: pos

    返回值 逻辑型

过程,公共,传递(self) :: to_string => to_string_large

  • interface

    私有模块子程序 to_string_large(self, string, status)

    self的值表示为string中的二进制字面量。Status可能具有值successalloc_fault

    参数

    类型 意图可选 属性 名称
    class(bitset_large), intent(in) :: self
    字符(len=:), intent(out), 可分配的 :: string
    integer, intent(out), optional :: status

过程,公共,传递(self) :: value => value_large

  • interface

    私有元素模块函数 value_large(self, pos) 结果(value)

    如果pos位置被设置,则返回1,否则返回0。如果pos为负数或大于bits(set) - 1,则结果为0。

    参数

    类型 意图可选 属性 名称
    class(bitset_large), intent(in) :: self
    integer(kind=bits_kind), intent(in) :: pos

    返回值 整数

泛型,公共 :: write_bitset => write_bitset_stringwrite_bitset_unit

  • 私有接口 write_bitset_string_large()

    参数

  • 私有接口 write_bitset_unit_large()

    参数

过程,公共,传递(self) :: write_bitset_string => write_bitset_string_large

  • interface

    私有模块子程序 write_bitset_string_large(self, string, status)

    将位集字面量写入可分配的默认字符string,表示bitset_large中各个位的值,self。如果status不存在,则导致错误停止并显示信息性停止代码。如果status存在,则其默认值为success,如果输出字符串分配失败,则值为alloc_fault

    参数

    类型 意图可选 属性 名称
    class(bitset_large), intent(in) :: self
    字符(len=:), intent(out), 可分配的 :: string
    integer, intent(out), optional :: status

过程,公共,传递(self) :: write_bitset_unit => write_bitset_unit_large

  • interface

    私有模块子程序 write_bitset_unit_large(self, unit, advance, status)

    将位集字面量写入I/O单元unit,表示位集中各个位的值,self。默认情况下或如果advance存在且值为'YES',则使用前进输出。如果advance存在且值为'NO',则写入不会使当前记录前进。如果status不存在,则导致错误停止并显示信息性停止代码。如果status存在,则其默认值为success,如果输出字符串分配失败,则值为alloc_fault,如果输出字面量的write语句失败,则值为write_failure

    参数

    类型 意图可选 属性 名称
    class(bitset_large), intent(in) :: self
    integer, intent(in) :: unit
    character(len=*), intent(in), optional :: advance
    integer, intent(out), optional :: status

源代码

    type, extends(bitset_type) :: bitset_large
!! Version: experimental
!!
!! Type for bitsets with more than 64 bits ([Specification](../page/specs/stdlib_bitsets.html#the-stdlib_bitsets-derived-types))

        private
        integer(block_kind), private, allocatable :: blocks(:)

    contains

        procedure, pass(self)  :: all => all_large
        procedure, pass(self)  :: any => any_large
        procedure, pass(self)  :: bit_count => bit_count_large
        procedure, pass(self)  :: clear_bit => clear_bit_large
        procedure, pass(self)  :: clear_range => clear_range_large
        procedure, pass(self)  :: flip_bit => flip_bit_large
        procedure, pass(self)  :: flip_range => flip_range_large
        procedure, pass(self)  :: from_string => from_string_large
        procedure, pass(self)  :: init_zero => init_zero_large
        procedure, pass(self)  :: input => input_large
        procedure, pass(self)  :: none => none_large
        procedure, pass(self)  :: not => not_large
        procedure, pass(self)  :: output => output_large
        procedure, pass(self)  :: &
            read_bitset_string => read_bitset_string_large
        procedure, pass(self)  :: read_bitset_unit => read_bitset_unit_large
        procedure, pass(self)  :: set_bit => set_bit_large
        procedure, pass(self)  :: set_range => set_range_large
        procedure, pass(self)  :: test => test_large
        procedure, pass(self)  :: to_string => to_string_large
        procedure, pass(self)  :: value => value_large
        procedure, pass(self)  :: &
            write_bitset_string => write_bitset_string_large
        procedure, pass(self)  :: write_bitset_unit => write_bitset_unit_large

    end type bitset_large