bitset_64 派生类型

type, public, extends(bitset_type) :: bitset_64

位集类型,不超过 64 位 (规范)


类型绑定过程

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

  • interface

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

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

    参数

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

    返回值 logical

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

  • interface

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

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

    参数

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

    返回值 logical

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

  • interface

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

    返回 self 中非零位的数量。

    参数

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

  • interface

    private elemental module subroutine clear_bit_64(self, pos)

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

    参数

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

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

  • interface

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

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

    参数

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

  • interface

    private elemental module subroutine flip_bit_64(self, pos)

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

    参数

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

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

  • interface

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

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

    参数

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

  • interface

    private module subroutine from_string_64(self, string, status)

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

    参数

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

  • interface

    private module subroutine init_zero_64(self, bits, status)

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

    参数

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

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

  • interface

    private module subroutine input_64(self, unit, status)

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

    参数

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

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

  • interface

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

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

    参数

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

    返回值 logical

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

  • interface

    private elemental module subroutine not_64(self)

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

    参数

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

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

  • interface

    private module subroutine output_64(self, unit, status)

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

    参数

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

  • interface

    private module subroutine read_bitset_string_64(self, string, status)

    使用默认字符 string 中的位集字面量来定义位集 self。字面量之前可能有一系列任意空白字符。如果 status 缺失,则错误将导致错误停止,并显示信息性停止代码。如果 status 存在,则其具有以下值之一:* success - 如果没有发生问题,* alloc_fault - 如果为 SELF 分配内存失败,* array_size_invalid_error - 如果bits(self)string中大于 64(对于bitset_64),*char_string_invalid_error- 如果位集字面量包含无效字符,*char_string_too_small_error - 如果字符串在读取所有位之前结束。* integer_overflow_error - 如果位集字面量具有大于其表示范围的 bits(self) 值,

    参数

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

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

  • interface

    private module subroutine read_bitset_unit_64(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) 大于 64(对于 bitset_64),* char_string_invalid_error - 如果读取位集字面量时发现无效字符,* eof_failure - 如果 read 语句在完成位集字面量读取之前到达文件末尾,* integer_overflow_error - 如果位集字面量具有大于其表示范围的 bits(self) 值,* read_failure - 如果 read 语句失败,

    参数

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

  • interface

    private elemental module subroutine set_bit_64(self, pos)

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

    参数

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

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

  • interface

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

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

    参数

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

procedure, public, pass(self) :: test => test_64

  • interface

    private elemental module function test_64(self, pos) result(test)

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

    参数

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

    返回值 logical

procedure, public, pass(self) :: to_string => to_string_64

  • interface

    private module subroutine to_string_64(self, string, status)

    self 的值表示为 string 中的二进制字面量。状态可以具有 successalloc_fault 值。

    参数

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

procedure, public, pass(self) :: value => value_64

  • interface

    private elemental module function value_64(self, pos) result(value)

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

    参数

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

    返回值 integer

generic, public :: write_bitset => write_bitset_string, write_bitset_unit

  • private interface write_bitset_string_large()

    参数

  • private interface write_bitset_unit_large()

    参数

procedure, public, pass(self) :: write_bitset_string => write_bitset_string_64

  • interface

    private module subroutine write_bitset_string_64(self, string, status)

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

    参数

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

procedure, public, pass(self) :: write_bitset_unit => write_bitset_unit_64

  • interface

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

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

    参数

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

源代码

    type, extends(bitset_type) :: bitset_64
!! Version: experimental
!!
!! Type for bitsets with no more than 64 bits ([Specification](../page/specs/stdlib_bitsets.html#the-stdlib_bitsets-derived-types))
        private
        integer(block_kind), private :: block = 0

    contains

        procedure, pass(self)  :: all => all_64
        procedure, pass(self)  :: any => any_64
        procedure, pass(self)  :: bit_count => bit_count_64
        procedure, pass(self)  :: clear_bit => clear_bit_64
        procedure, pass(self)  :: clear_range => clear_range_64
        procedure, pass(self)  :: flip_bit => flip_bit_64
        procedure, pass(self)  :: flip_range => flip_range_64
        procedure, pass(self)  :: from_string => from_string_64
        procedure, pass(self)  :: init_zero => init_zero_64
        procedure, pass(self)  :: input => input_64
        procedure, pass(self)  :: none => none_64
        procedure, pass(self)  :: not => not_64
        procedure, pass(self)  :: output => output_64
        procedure, pass(self)  :: read_bitset_string => read_bitset_string_64
        procedure, pass(self)  :: read_bitset_unit => read_bitset_unit_64
        procedure, pass(self)  :: set_bit => set_bit_64
        procedure, pass(self)  :: set_range => set_range_64
        procedure, pass(self)  :: test => test_64
        procedure, pass(self)  :: to_string => to_string_64
        procedure, pass(self)  :: value => value_64
        procedure, pass(self)  :: write_bitset_string => write_bitset_string_64
        procedure, pass(self)  :: write_bitset_unit => write_bitset_unit_64

    end type bitset_64