bitset_64 和 bitset_large 的父类型 (规范)
如果self
中的所有位都为1,则返回.true.
,否则返回.false.
。
program example_all
use stdlib_bitsets
character(*), parameter :: &
bits_all = '111111111111111111111111111111111'
type(bitset_64) :: set0
call set0 % from_string( bits_all )
if ( bits(set0) /= 33 ) then
error stop "FROM_STRING failed to interpret " // &
'BITS_ALL's size properly."
else if ( .not. set0 % all() ) then
error stop "FROM_STRING failed to interpret" // &
"BITS_ALL's value properly."
else
write(*,*) "FROM_STRING transferred BITS_ALL properly" // &
" into set0."
end if
end program example_all
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(in) | :: | self |
如果self
中的任何一位为1,则返回.true.
,否则返回.false.
。
program example_any
use stdlib_bitsets
character(*), parameter :: &
bits_0 = '0000000000000000000'
type(bitset_64) :: set0
call set0 % from_string( bits_0 )
if ( .not. set0 % any() ) then
write(*,*) "FROM_STRING interpreted " // &
"BITS_0's value properly."
end if
call set0 % set(5)
if ( set0 % any() ) then
write(*,*) "ANY interpreted SET0's value properly."
end if
end program example_any
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(in) | :: | self |
返回self
中非零位的数量。
program example_bit_count
use stdlib_bitsets
character(*), parameter :: &
bits_0 = '0000000000000000000'
type(bitset_64) :: set0
call set0 % from_string( bits_0 )
if ( set0 % bit_count() == 0 ) then
write(*,*) "FROM_STRING interpreted " // &
"BITS_0's value properly."
end if
call set0 % set(5)
if ( set0 % bit_count() == 1 ) then
write(*,*) "BIT_COUNT interpreted SET0's value properly."
end if
end program example_bit_count
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(in) | :: | self |
返回self
中的位数。
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(in) | :: | self |
将self
中的第pos
位置为零。如果pos
小于零或大于bits(self)-1
,则忽略它。
program example_clear
use stdlib_bitsets
type(bitset_large) :: set0
call set0 % init(166)
call set0 % not()
if ( set0 % all() ) write(*,*) 'SET0 is properly initialized.'
call set0 % clear(165)
if ( .not. set0 % test(165) ) write(*,*) 'Bit 165 is cleared.'
call set0 % clear(0,164)
if ( set0 % none() ) write(*,*) 'All bits are cleared.'
end program example_clear
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(inout) | :: | self | |||
integer(kind=bits_kind), | intent(in) | :: | pos |
将set
中从start_pos
到stop_pos
位置的所有位设置为零。如果stop_pos < start_pos
,则不修改任何位。超出0到bits(self)-1
范围的位置将被忽略。
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(inout) | :: | self | |||
integer(kind=bits_kind), | intent(in) | :: | start_pos | |||
integer(kind=bits_kind), | intent(in) | :: | stop_pos |
翻转self
中第pos
位置的值,前提是位置有效。如果pos
小于0或大于bits(self)-1
,则不更改任何值。
program example_flip
use stdlib_bitsets
type(bitset_large) :: set0
call set0 % init(166)
if ( set0 % none() ) write(*,*) 'SET0 is properly initialized.'
call set0 % flip(165)
if ( set0 % test(165) ) write(*,*) 'Bit 165 is flipped.'
call set0 % flip(0,164)
if ( set0 % all() ) write(*,*) 'All bits are flipped.'
end program example_flip
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(inout) | :: | self | |||
integer(kind=bits_kind), | intent(in) | :: | pos |
翻转self
中从start_pos
到stop_pos
位置的所有有效位。如果stop_pos < start_pos
,则不翻转任何位。小于0或大于bits(self)-1
的位置将被忽略。
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(inout) | :: | self | |||
integer(kind=bits_kind), | intent(in) | :: | start_pos | |||
integer(kind=bits_kind), | intent(in) | :: | stop_pos |
初始化位集self
,将string
视为二进制文本status
可能具有以下值:* success
- 如果未发现任何问题,* alloc_fault
- 如果位集分配失败 * char_string_too_large_error
- 如果string
太大,或 * char_string_invalid_error
- 如果字符串包含无效字符。
program example_from_string
use stdlib_bitsets
character(*), parameter :: &
bits_all = '111111111111111111111111111111111'
type(bitset_64) :: set0
call set0 % from_string( bits_all )
if ( bits(set0) /= 33 ) then
error stop "FROM_STRING failed to interpret " // &
'BITS_ALL's size properly."
else if ( .not. set0 % all() ) then
error stop "FROM_STRING failed to interpret" // &
"BITS_ALL's value properly."
else
write(*,*) "FROM_STRING transferred BITS_ALL properly" // &
" into set0."
end if
end program example_from_string
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(out) | :: | self | |||
character(len=*), | intent(in) | :: | string | |||
integer, | intent(out), | optional | :: | status |
创建大小为bits
的位集self
,所有位都初始化为零。bits
必须是非负数。如果发生错误并且缺少status
,则处理将停止并显示信息性停止代码。status
将具有以下值之一;* success
- 如果未发现任何问题,* alloc_fault
- 如果内存分配失败 * array_size_invalid_error
- 如果bits
为负数或对于类为bitset_64
的self
大于64,或者
program example_init
use stdlib_bitsets
type(bitset_large) :: set0
call set0 % init(166)
if ( set0 % bits() == 166 ) &
write(*,*) `SET0 has the proper size.'
if ( set0 % none() ) write(*,*) 'SET0 is properly initialized.'
end program example_init
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(out) | :: | self | |||
integer(kind=bits_kind), | intent(in) | :: | bits | |||
integer, | intent(out), | optional | :: | 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
读取失败
program example_input
character(*), parameter :: &
bits_0 = '000000000000000000000000000000000', &
bits_1 = '000000000000000000000000000000001', &
bits_33 = '100000000000000000000000000000000'
integer :: unit
type(bitset_64) :: set0, set1, set2, set3, set4, set5
call set0 % from_string( bits_0 )
call set1 % from_string( bits_1 )
call set2 % from_string( bits_33 )
open( newunit=unit, file='test.bin', status='replace', &
form='unformatted', action='write' )
call set2 % output(unit)
call set1 % output(unit)
call set0 % output(unit)
close( unit )
open( newunit=unit, file='test.bin', status='old', &
form='unformatted', action='read' )
call set5 % input(unit)
call set4 % input(unit)
call set3 % input(unit)
close( unit )
if ( set3 /= set0 .or. set4 /= set1 .or. set5 /= set2 ) then
error stop 'Transfer to and from units using ' // &
' output and input failed.'
else
write(*,*) 'Transfer to and from units using ' // &
'output and input succeeded.'
end if
end program example_input
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(out) | :: | self | |||
integer, | intent(in) | :: | unit | |||
integer, | intent(out), | optional | :: | status |
如果self
中没有任何位的值为1,则返回.true.
。
program example_none
use stdlib_bitsets
character(*), parameter :: &
bits_0 = '0000000000000000000'
type(bitset_large) :: set0
call set0 % from_string( bits_0 )
if ( set0 % none() ) then
write(*,*) "FROM_STRING interpreted " // &
"BITS_0's value properly."
end if
call set0 % set(5)
if ( .not. set0 % none() ) then
write(*,*) "NONE interpreted SET0's value properly."
end if
end program example_none
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(in) | :: | self |
将self
中的位设置为其逻辑补码
program example_not
use stdlib_bitsets
type(bitset_large) :: set0
call set0 % init( 155 )
if ( set0 % none() ) then
write(*,*) "FROM_STRING interpreted " // &
"BITS_0's value properly."
end if
call set0 % not()
if ( set0 % all() ) then
write(*,*) "ALL interpreted SET0's value properly."
end if
end program example_not
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(inout) | :: | self |
将位集self
的组件写入非格式化I/O单元unit
,以与input
兼容的非格式化序列。如果缺少status
,则错误将导致错误停止并显示信息性停止代码。如果存在status
,则其默认值为success
,或者如果写入失败,则值为write_failure
。
program example_output
character(*), parameter :: &
bits_0 = '000000000000000000000000000000000', &
bits_1 = '000000000000000000000000000000001', &
bits_33 = '100000000000000000000000000000000'
integer :: unit
type(bitset_64) :: set0, set1, set2, set3, set4, set5
call set0 % from_string( bits_0 )
call set1 % from_string( bits_1 )
call set2 % from_string( bits_33 )
open( newunit=unit, file='test.bin', status='replace', &
form='unformatted', action='write' )
call set2 % output(unit)
call set1 % output(unit)
call set0 % output(unit)
close( unit )
open( newunit=unit, file='test.bin', status='old', &
form='unformatted', action='read' )
call set5 % input(unit)
call set4 % input(unit)
call set3 % input(unit)
close( unit )
if ( set3 /= set0 .or. set4 /= set1 .or. set5 /= set2 ) then
error stop 'Transfer to and from units using ' // &
' output and input failed.'
else
write(*,*) 'Transfer to and from units using ' // &
'output and input succeeded.'
end if
end program example_output
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(in) | :: | self | |||
integer, | intent(in) | :: | unit | |||
integer, | intent(out), | optional | :: | status |
使用默认字符string
中的位集文本定义位集self
。文本前面可以是任意数量的空格字符。如果缺少status
,则错误将导致错误停止并显示信息性停止代码。如果存在status
,则它具有以下值之一 * success
- 如果没有发生问题,* alloc_fault
- 如果为SELF分配内存失败,* array_size_invalid_error - 如果
string中的
bits(self)对于
bitset_64大于64,*
char_string_invalid_error- 如果位集文本包含无效字符,*
char_string_too_small_error - 如果字符串在读取所有位之前结束。 * integer_overflow_error
- 如果位集文本的bits(self)
值过大而无法表示,
program example_read_bitset
character(*), parameter :: &
bits_0 = 'S33B000000000000000000000000000000000', &
bits_1 = 'S33B000000000000000000000000000000001', &
bits_33 = 'S33B100000000000000000000000000000000'
character(:), allocatable :: test_0, test_1, test_2
integer :: unit
type(bitset_64) :: set0, set1, set2, set3, set4, set5
call set0 % read_bitset( bits_0, status )
call set1 % read_bitset( bits_1, status )
call set2 % read_bitset( bits_2, status )
call set0 % write_bitset( test_0, status )
call set1 % write_bitset( test_1, status )
call set2 % write_bitset( test_2, status )
if ( bits_0 == test_0 .and. bits_1 == test_1 .and. &
bits_2 == test_2 ) then
write(*,*) 'READ_BITSET to WRITE_BITSET strings worked.'
end if
open( newunit=unit, file='test.txt', status='replace', &
form='formatted', action='write' )
call set2 % write_bitset(unit, advance='no')
call set1 % write_bitset(unit, advance='no')
call set0 % write_bitset(unit)
close( unit )
open( newunit=unit, file='test.txt', status='old', &
form='formatted', action='read' )
call set3 % read_bitset(unit, advance='no')
call set4 % read_bitset(unit, advance='no')
call set5 % read_bitset(unit)
if ( set3 == set0 .and. set4 == set1 .and. set5 == set2 ) then
write(*,*) WRITE_BITSET to READ_BITSET through unit worked.'
end if
end program example_read_bitset
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(out) | :: | self | |||
character(len=*), | intent(in) | :: | string | |||
integer, | intent(out), | optional | :: | 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_type), | intent(out) | :: | self | |||
integer, | intent(in) | :: | unit | |||
character(len=*), | intent(in), | optional | :: | advance | ||
integer, | intent(out), | optional | :: | status |
设置self
中第pos
位置的值,前提是位置有效。如果位置小于0或大于bits(self)-1
,则self
保持不变。
program example_set
use stdlib_bitsets
type(bitset_large) :: set0
call set0 % init(166)
if ( set0 % none() ) write(*,*) 'SET0 is properly initialized.'
call set0 % set(165)
if ( set0 % test(165) ) write(*,*) 'Bit 165 is set.'
call set0 % set(0,164)
if ( set0 % all() ) write(*,*) 'All bits are set.'
end program example_set
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(inout) | :: | self | |||
integer(kind=bits_kind), | intent(in) | :: | pos |
将 self
中从 start_pos
到 stop_pos
位置的所有有效位设置为 1。如果 stop_pos < start_pos
,则不更改任何位。超出 0 到 bits(self)-1
范围的位置将被忽略。
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(inout) | :: | self | |||
integer(kind=bits_kind), | intent(in) | :: | start_pos | |||
integer(kind=bits_kind), | intent(in) | :: | stop_pos |
如果 pos
位置已设置,则返回 .true.
,否则返回 .false.
。如果 pos
为负数或大于 bits(self) - 1
,则结果为 .false.
。
program example_test
use stdlib_bitsets
type(bitset_large) :: set0
call set0 % init(166)
call set0 % not()
if ( set0 % all() ) write(*,*) 'SET0 is properly initialized.'
call set0 % clear(165)
if ( .not. set0 % test(165) ) write(*,*) 'Bit 165 is cleared.'
call set0 % set(165)
if ( set0 % test(165) ) write(*,*) 'Bit 165 is set.'
end program example_test
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(in) | :: | self | |||
integer(kind=bits_kind), | intent(in) | :: | pos |
将 self
的值表示为 string
中的二进制字面量。状态可以是 success
或 alloc_fault
。
program example_to_string
use stdlib_bitsets
character(*), parameter :: &
bits_all = '111111111111111111111111111111111'
type(bitset_64) :: set0
character(:), allocatable :: new_string
call set0 % init(33)
call set0 % not()
call set0 % to_string( new_string )
if ( new_string == bits_all ) then
write(*,*) "TO_STRING transferred BITS0 properly" // &
" into NEW_STRING."
end if
end program example_to_string
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(in) | :: | self | |||
字符(len=:), | intent(out), | 可分配 | :: | string | ||
integer, | intent(out), | optional | :: | status |
如果 pos
位置已设置,则返回 1,否则返回 0。如果 pos
为负数或大于 bits(set) - 1
,则结果为 0。
program example_value
use stdlib_bitsets
type(bitset_large) :: set0
call set0 % init(166)
call set0 % not()
if ( set0 % all() ) write(*,*) 'SET0 is properly initialized.'
call set0 % clear(165)
if ( set0 % value(165) == 0 ) write(*,*) 'Bit 165 is cleared.'
call set0 % set(165)
if ( set0 % value(165) == 1 ) write(*,*) 'Bit 165 is set.'
end program example_value
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(in) | :: | self | |||
integer(kind=bits_kind), | intent(in) | :: | pos |
将位集字面量写入可分配的默认字符 string
,表示 bitset_type
中的各个位值,self
。如果 status
缺失,则会导致错误停止,并显示信息性停止代码。如果 status
存在,则其默认值为 success
,如果输出字符串分配失败,则值为 alloc_fault
。
program example_write_bitset
character(*), parameter :: &
bits_0 = 'S33B000000000000000000000000000000000', &
bits_1 = 'S33B000000000000000000000000000000001', &
bits_33 = 'S33B100000000000000000000000000000000'
character(:), allocatable :: test_0, test_1, test_2
integer :: unit
type(bitset_64) :: set0, set1, set2, set3, set4, set5
call set0 % read_bitset( bits_0, status )
call set1 % read_bitset( bits_1, status )
call set2 % read_bitset( bits_2, status )
call set0 % write_bitset( test_0, status )
call set1 % write_bitset( test_1, status )
call set2 % write_bitset( test_2, status )
if ( bits_0 == test_0 .and. bits_1 == test_1 .and. &
bits_2 == test_2 ) then
write(*,*) 'READ_BITSET to WRITE_BITSET strings worked.'
end if
open( newunit=unit, file='test.txt', status='replace', &
form='formatted', action='write' )
call set2 % write_bitset(unit, advance='no')
call set1 % write_bitset(unit, advance='no')
call set0 % write_bitset(unit)
close( unit )
open( newunit=unit, file='test.txt', status='old', &
form='formatted', action='read' )
call set3 % read_bitset(unit, advance='no')
call set4 % read_bitset(unit, advance='no')
call set5 % read_bitset(unit)
if ( set3 == set0 .and. set4 == set1 .and. set5 == set2 ) then
write(*,*) WRITE_BITSET to READ_BITSET through unit worked.'
end if
end program example_write_bitset
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(in) | :: | self | |||
字符(len=:), | intent(out), | 可分配 | :: | string | ||
integer, | intent(out), | optional | :: | status |
将位集字面量写入 I/O 单位 unit
,表示 bitset_t
中的各个位值,self
。如果发生错误,则处理将停止,并向 error_unit
发送消息。默认情况下或如果 advance
存在且值为 'YES',则使用前进输出。如果 advance
存在且值为 'NO',则写入不会前进当前记录。如果 status
缺失,则会导致错误停止,并显示信息性停止代码。如果 status
存在,则其默认值为 success
,如果输出字符串分配失败,则值为 alloc_fault
,如果 write
语句输出字面量失败,则值为 write_failure
。
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(bitset_type), | intent(in) | :: | self | |||
integer, | intent(in) | :: | unit | |||
character(len=*), | intent(in), | optional | :: | advance | ||
integer, | intent(out), | optional | :: | status |
type, abstract :: bitset_type !! version: experimental !! !! Parent type for bitset_64 and bitset_large ([Specification](../page/specs/stdlib_bitsets.html#the-stdlib_bitsets-derived-types)) private integer(bits_kind) :: num_bits = 0_bits_kind contains procedure(all_abstract), deferred, pass(self) :: all procedure(any_abstract), deferred, pass(self) :: any procedure(bit_count_abstract), deferred, pass(self) :: bit_count procedure, pass(self) :: bits procedure(clear_bit_abstract), deferred, pass(self) :: clear_bit procedure(clear_range_abstract), deferred, pass(self) :: clear_range generic :: clear => clear_bit, clear_range procedure(flip_bit_abstract), deferred, pass(self) :: flip_bit procedure(flip_range_abstract), deferred, pass(self) :: flip_range generic :: flip => flip_bit, flip_range procedure(from_string_abstract), deferred, pass(self) :: from_string procedure(init_zero_abstract), deferred, pass(self) :: init_zero generic :: init => init_zero procedure(input_abstract), deferred, pass(self) :: input procedure(none_abstract), deferred, pass(self) :: none procedure(not_abstract), deferred, pass(self) :: not procedure(output_abstract), deferred, pass(self) :: output procedure(read_bitset_string_abstract), deferred, pass(self) :: & read_bitset_string procedure(read_bitset_unit_abstract), deferred, pass(self) :: & read_bitset_unit generic :: read_bitset => read_bitset_string, read_bitset_unit procedure(set_bit_abstract), deferred, pass(self) :: set_bit procedure(set_range_abstract), deferred, pass(self) :: set_range generic :: set => set_bit, set_range procedure(test_abstract), deferred, pass(self) :: test procedure(to_string_abstract), deferred, pass(self) :: to_string procedure(value_abstract), deferred, pass(self) :: value procedure(write_bitset_string_abstract), deferred, pass(self) :: & write_bitset_string procedure(write_bitset_unit_abstract), deferred, pass(self) :: & write_bitset_unit generic :: write_bitset => write_bitset_string, write_bitset_unit end type bitset_type