实现大小不超过 huge(0_int32)
的基于零的位集。当前代码使用 64 位整数来存储位,并使用所有 64 位。代码假设二进制补码整数,并将负整数视为设置了符号位。(规范)
公共过程
类型 | 可见性 | 属性 | 名称 | 初始 | |||
---|---|---|---|---|---|---|---|
integer, | public, | parameter | :: | alloc_fault | = | 1 |
表示内存分配失败的错误标志 |
integer, | public, | parameter | :: | array_size_invalid_error | = | 2 |
表示无效 bits 值的错误标志 |
integer, | public, | parameter | :: | char_string_invalid_error | = | 3 |
表示无效字符字符串的错误标志 |
integer, | public, | parameter | :: | char_string_too_large_error | = | 4 |
表示字符字符串过长的错误标志 |
integer, | public, | parameter | :: | char_string_too_small_error | = | 5 |
表示字符字符串过短的错误标志 |
integer, | public, | parameter | :: | eof_failure | = | 6 |
表示读取时出现意外文件结束的错误标志 |
integer, | public, | parameter | :: | index_invalid_error | = | 7 |
表示无效索引的错误标志 |
integer, | public, | parameter | :: | integer_overflow_error | = | 8 |
表示整数溢出的错误标志 |
integer, | public, | parameter | :: | max_digits | = | 10 | |
integer(kind=bits_kind), | public, | parameter | :: | overflow_bits | = | 2_bits_kind**30/5 | |
integer, | public, | parameter | :: | read_failure | = | 9 |
表示 READ 语句失败的错误标志 |
integer, | public, | parameter | :: | success | = | 0 |
表示没有错误的错误标志 |
integer, | public, | parameter | :: | write_failure | = | 10 |
表示 WRITE 语句失败的错误标志 |
将 set1
中的位设置为 set1
中原始位与 set2
中的位的按位与运算结果。这些集合必须具有相同的位数,否则结果未定义。(规范)
program example_and
use stdlib_bitsets
type(bitset_large) :: set0, set1
call set0 % init(166)
call set1 % init(166)
call and( set0, set1 ) ! none none
if ( none(set0) ) write(*,*) 'First test of AND worked.'
call set0 % not()
call and( set0, set1 ) ! all none
if ( none(set0) ) write(*,*) 'Second test of AND worked.'
call set1 % not()
call and( set0, set1 ) ! none all
if ( none(set0) ) write(*,*) 'Third test of AND worked.'
call set0 % not()
call and( set0, set1 ) ! all all
if ( all(set0) ) write(*,*) 'Fourth test of AND worked.'
end program example_and
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_64), | intent(inout) | :: | set1 | |||
type(bitset_64), | intent(in) | :: | set2 |
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_large), | intent(inout) | :: | set1 | |||
type(bitset_large), | intent(in) | :: | set2 |
将 set1
中的位设置为 set1
中原始位与 set2
的按位取反运算结果的按位与运算结果。这些集合必须具有相同的位数,否则结果未定义。
(规范)
program example_and_not
use stdlib_bitsets
type(bitset_large) :: set0, set1
call set0 % init(166)
call set1 % init(166)
call and_not( set0, set1 ) ! none none
if ( none(set0) ) write(*,*) 'First test of AND_NOT worked.'
call set0 % not()
call and_not( set0, set1 ) ! all none
if ( all(set0) ) write(*,*) 'Second test of AND_NOT worked.'
call set0 % not()
call set1 % not()
call and_not( set0, set1 ) ! none all
if ( none(set0) ) write(*,*) 'Third test of AND_NOT worked.'
call set0 % not()
call and_not( set0, set1 ) ! all all
if ( none(set0) ) write(*,*) 'Fourth test of AND_NOT worked.'
end program example_and_not
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_64), | intent(inout) | :: | set1 | |||
type(bitset_64), | intent(in) | :: | set2 |
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_large), | intent(inout) | :: | set1 | |||
type(bitset_large), | intent(in) | :: | set2 |
用于定义 bitset_large
的赋值。(规范)
program example_assignment
use stdlib_bitsets
logical(int8) :: logical1(64) = .true.
logical(int32), allocatable :: logical2(:)
type(bitset_64) :: set0, set1
set0 = logical1
if ( set0 % bits() /= 64 ) then
error stop procedure // &
' initialization with logical(int8) failed to set' // &
' the right size.'
else if ( .not. set0 % all() ) then
error stop procedure // ' initialization with' // &
' logical(int8) failed to set the right values.'
else
write(*,*) 'Initialization with logical(int8) succeeded.'
end if
set1 = set0
if ( set1 == set0 ) &
write(*,*) 'Initialization by assignment succeeded'
logical2 = set1
if ( all( logical2 ) ) then
write(*,*) 'Initialization of logical(int32) succeeded.'
end if
end program example_assignment
用于定义从 logical(int16)
类型数组到 bitset_large
的赋值。
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_large), | intent(out) | :: | self | |||
logical(kind=int16), | intent(in) | :: | logical_vector(:) |
用于定义从 logical(int32)
类型数组到 bitset_large
的赋值。
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_large), | intent(out) | :: | self | |||
logical(kind=int32), | intent(in) | :: | logical_vector(:) |
用于定义从 logical(int64)
类型数组到 bitset_large
的赋值。
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_large), | intent(out) | :: | self | |||
logical(kind=int64), | intent(in) | :: | logical_vector(:) |
用于定义从 logical(int8)
类型数组到 bitset_large
的赋值。
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_large), | intent(out) | :: | self | |||
logical(kind=int8), | intent(in) | :: | logical_vector(:) |
用于定义从 bitset_large
到 logical(int16)
类型数组的赋值。
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
logical(kind=int16), | intent(out), | allocatable | :: | logical_vector(:) | ||
type(bitset_large), | intent(in) | :: | set |
用于定义从 bitset_large
到 logical(int32)
类型数组的赋值。
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
logical(kind=int32), | intent(out), | allocatable | :: | logical_vector(:) | ||
type(bitset_large), | intent(in) | :: | set |
用于定义从 bitset_large
到 logical(int64)
类型数组的赋值。
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
logical(kind=int64), | intent(out), | allocatable | :: | logical_vector(:) | ||
type(bitset_large), | intent(in) | :: | set |
用于定义从 bitset_large
到 logical(int8)
类型数组的赋值。
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
logical(kind=int8), | intent(out), | allocatable | :: | logical_vector(:) | ||
type(bitset_large), | intent(in) | :: | set |
从位集 old
中的范围 start_pos
到 stop_pos
创建一个新的位集 new
。如果 start_pos
大于 stop_pos
,则新的位集为空。如果 start_pos
小于零或 stop_pos
大于 bits(old)-1
,则如果 status
存在,它具有值 index_invalid_error
并且 new
未定义,否则处理停止并显示信息性消息。(规范)
program example_extract
use stdlib_bitsets
type(bitset_large) :: set0, set1
call set0 % init(166)
call set0 % set(100,150)
call extract( set1, set0, 100, 150)
if ( set1 % bits() == 51 ) &
write(*,*) 'SET1 has the proper size.'
if ( set1 % all() ) write(*,*) 'SET1 has the proper values.'
end program example_extract
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_64), | intent(out) | :: | new | |||
type(bitset_64), | intent(in) | :: | old | |||
integer(kind=bits_kind), | intent(in) | :: | start_pos | |||
integer(kind=bits_kind), | intent(in) | :: | stop_pos | |||
integer, | intent(out), | optional | :: | status |
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_large), | intent(out) | :: | new | |||
type(bitset_large), | intent(in) | :: | old | |||
integer(kind=bits_kind), | intent(in) | :: | start_pos | |||
integer(kind=bits_kind), | intent(in) | :: | stop_pos | |||
integer, | intent(out), | optional | :: | status |
如果 set1
和 set2
中并非所有位都具有相同的值,则返回 .true.
,否则返回 .false.
。这些集合必须具有相同的位数,否则结果未定义。(规范)
program example_inequality
use stdlib_bitsets
type(bitset_64) :: set0, set1, set2
call set0 % init( 33 )
call set1 % init( 33 )
call set2 % init( 33 )
call set1 % set( 0 )
call set2 % set( 32 )
if ( set0 /= set1 .and. set0 /= set2 .and. set1 /= set2 .and. &
.not. set0 /= set0 .and. .not. set1 /= set1 .and. .not. &
set2 /= set2 ) then
write(*,*) 'Passed 64 bit inequality tests.'
else
error stop 'Failed 64 bit inequality tests.'
end if
end program example_inequality
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_64), | intent(in) | :: | set1 | |||
type(bitset_64), | intent(in) | :: | set2 |
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_large), | intent(in) | :: | set1 | |||
type(bitset_large), | intent(in) | :: | set2 |
如果 set1
和 set2
中的位不同,并且最高阶不同的位在 set1
中设置为 0,在 set2
中设置为 1,则返回 .true.
,否则返回 .false.
。这些集合必须具有相同的位数,否则结果未定义。(规范)
program example_lt
use stdlib_bitsets
type(bitset_64) :: set0, set1, set2
call set0 % init( 33 )
call set1 % init( 33 )
call set2 % init( 33 )
call set1 % set( 0 )
call set2 % set( 32 )
if ( set0 < set1 .and. set1 < set2 .and. set0 < set2 .and. &
.not. set0 < set0 .and. .not. set2 < set0 .and. .not. &
set2 < set1 ) then
write(*,*) 'Passed 64 bit less than tests.'
else
error stop 'Failed 64 bit less than tests.'
end if
end program example_lt
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_64), | intent(in) | :: | set1 | |||
type(bitset_64), | intent(in) | :: | set2 |
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_large), | intent(in) | :: | set1 | |||
type(bitset_large), | intent(in) | :: | set2 |
如果set1
和set2
中的位相同,或者最高位不同的位在set1
中设置为0,在set2
中设置为1,则返回.true.
,否则返回.false.
。两个集合的位数必须相同,否则结果未定义。(规范)
program example_le
use stdlib_bitsets
type(bitset_64) :: set0, set1, set2
call set0 % init( 33 )
call set1 % init( 33 )
call set2 % init( 33 )
call set1 % set( 0 )
call set2 % set( 32 )
if ( set0 <= set1 .and. set1 <= set2 .and. set0 <= set2 .and. &
set0 <= set0 .and. set1 <= set1 .and. set2 <= set2 .and. &
.not. set1 <= set0 .and. .not. set2 <= set0 .and. .not. &
set2 <= set1 ) then
write(*,*) 'Passed 64 bit less than or equal tests.'
else
error stop 'Failed 64 bit less than or equal tests.'
end if
end program example_le
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_64), | intent(in) | :: | set1 | |||
type(bitset_64), | intent(in) | :: | set2 |
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_large), | intent(in) | :: | set1 | |||
type(bitset_large), | intent(in) | :: | set2 |
如果set1
和set2
中的所有位都具有相同的值,则返回.true.
,否则返回.false.
。两个集合的位数必须相同,否则结果未定义。(规范)
program example_equality
use stdlib_bitsets
type(bitset_64) :: set0, set1, set2
call set0 % init( 33 )
call set1 % init( 33 )
call set2 % init( 33 )
call set1 % set( 0 )
call set2 % set( 32 )
if ( set0 == set0 .and. set1 == set1 .and. set2 == set2 .and. &
.not. set0 == set1 .and. .not. set0 == set2 .and. .not. &
set1 == set2 ) then
write(*,*) 'Passed 64 bit equality tests.'
else
error stop 'Failed 64 bit equality tests.'
end if
end program example_equality
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_64), | intent(in) | :: | set1 | |||
type(bitset_64), | intent(in) | :: | set2 |
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_large), | intent(in) | :: | set1 | |||
type(bitset_large), | intent(in) | :: | set2 |
如果set1
和set2
中的位不同,并且最高位不同的位在set1
中设置为1,在set2
中设置为0,则返回.true.
,否则返回.false.
。两个集合的位数必须相同,否则结果未定义。(规范)
program example_gt
use stdlib_bitsets
type(bitset_64) :: set0, set1, set2
call set0 % init( 33 )
call set1 % init( 33 )
call set2 % init( 33 )
call set1 % set( 0 )
call set2 % set( 32 )
if ( set1 > set0 .and. set2 > set1 .and. set2 > set0 .and. &
.not. set0 > set0 .and. .not. set0 > set1 .and. .not. &
set1 > set2 ) then
write(*,*) 'Passed 64 bit greater than tests.'
else
error stop 'Failed 64 bit greater than tests.'
end if
end program example_gt
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_64), | intent(in) | :: | set1 | |||
type(bitset_64), | intent(in) | :: | set2 |
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_large), | intent(in) | :: | set1 | |||
type(bitset_large), | intent(in) | :: | set2 |
如果set1
和set2
中的位相同,或者最高位不同的位在set1
中设置为1,在set2
中设置为0,则返回.true.
,否则返回.false.
。两个集合的位数必须相同,否则结果未定义。(规范)
program example_ge
use stdlib_bitsets
type(bitset_64) :: set0, set1, set2
call set0 % init( 33 )
call set1 % init( 33 )
call set2 % init( 33 )
call set1 % set( 0 )
call set2 % set( 32 )
if ( set1 >= set0 .and. set2 >= set1 .and. set2 >= set0 .and. &
set0 >= set0 .and. set1 >= set1 .and. set2 >= set2 .and. &
.not. set0 >= set1 .and. .not. set0 >= set2 .and. .not. &
set1 >= set2 ) then
write(*,*) 'Passed 64 bit greater than or equals tests.'
else
error stop 'Failed 64 bit greater than or equals tests.'
end if
end program example_ge
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_64), | intent(in) | :: | set1 | |||
type(bitset_64), | intent(in) | :: | set2 |
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_large), | intent(in) | :: | set1 | |||
type(bitset_large), | intent(in) | :: | set2 |
将set1
中的位设置为set1
和set2
中原始位的按位或
。两个集合的位数必须相同,否则结果未定义。(规范)
program example_or
use stdlib_bitsets
type(bitset_large) :: set0, set1
call set0 % init(166)
call set1 % init(166)
call or( set0, set1 ) ! none none
if ( none(set0) ) write(*,*) 'First test of OR worked.'
call set0 % not()
call or( set0, set1 ) ! all none
if ( all(set0) ) write(*,*) 'Second test of OR worked.'
call set0 % not()
call set1 % not()
call or( set0, set1 ) ! none all
if ( all(set0) ) write(*,*) 'Third test of OR worked.'
call set0 % not()
call or( set0, set1 ) ! all all
if ( all(set0) ) write(*,*) 'Fourth test of OR worked.'
end program example_or
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_64), | intent(inout) | :: | set1 | |||
type(bitset_64), | intent(in) | :: | set2 |
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_large), | intent(inout) | :: | set1 | |||
type(bitset_large), | intent(in) | :: | set2 |
将set1
中的位设置为set1
和set2
中原始位的按位异或
。两个集合的位数必须相同,否则结果未定义。(规范)
program example_xor
use stdlib_bitsets
type(bitset_large) :: set0, set1
call set0 % init(166)
call set1 % init(166)
call xor( set0, set1 ) ! none none
if ( none(set0) ) write(*,*) 'First test of XOR worked.'
call set0 % not()
call xor( set0, set1 ) ! all none
if ( all(set0) ) write(*,*) 'Second test of XOR worked.'
call set0 % not()
call set1 % not()
call xor( set0, set1 ) ! none all
if ( all(set0) ) write(*,*) 'Third test of XOR worked.'
call set0 % not()
call xor( set0, set1 ) ! all all
if ( none(set0) ) write(*,*) 'Fourth test of XOR worked.'
end program example_xor
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_64), | intent(inout) | :: | set1 | |||
type(bitset_64), | intent(in) | :: | set2 |
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(bitset_large), | intent(inout) | :: | set1 | |||
type(bitset_large), | intent(in) | :: | set2 |
用于位数不超过 64 位的位集的类型(规范)
procedure, public, pass(self) :: all => all_64 | |
procedure, public, pass(self) :: any => any_64 | |
procedure, public, pass(self) :: bit_count => bit_count_64 | |
procedure, public, pass(self) :: bits | |
generic, public :: clear => clear_bit, clear_range | |
procedure, public, pass(self) :: clear_bit => clear_bit_64 | |
procedure, public, pass(self) :: clear_range => clear_range_64 | |
generic, public :: flip => flip_bit, flip_range | |
procedure, public, pass(self) :: flip_bit => flip_bit_64 | |
procedure, public, pass(self) :: flip_range => flip_range_64 | |
procedure, public, pass(self) :: from_string => from_string_64 | |
generic, public :: init => init_zero | |
procedure, public, pass(self) :: init_zero => init_zero_64 | |
procedure, public, pass(self) :: input => input_64 | |
procedure, public, pass(self) :: none => none_64 | |
procedure, public, pass(self) :: not => not_64 | |
procedure, public, pass(self) :: output => output_64 | |
generic, public :: read_bitset => read_bitset_string, read_bitset_unit | |
procedure, public, pass(self) :: read_bitset_string => read_bitset_string_64 | |
procedure, public, pass(self) :: read_bitset_unit => read_bitset_unit_64 | |
generic, public :: set => set_bit, set_range | |
procedure, public, pass(self) :: set_bit => set_bit_64 | |
procedure, public, pass(self) :: set_range => set_range_64 | |
procedure, public, pass(self) :: test => test_64 | |
procedure, public, pass(self) :: to_string => to_string_64 | |
procedure, public, pass(self) :: value => value_64 | |
generic, public :: write_bitset => write_bitset_string, write_bitset_unit | |
procedure, public, pass(self) :: write_bitset_string => write_bitset_string_64 | |
procedure, public, pass(self) :: write_bitset_unit => write_bitset_unit_64 |
用于位数超过 64 位的位集的类型(规范)
procedure, public, pass(self) :: all => all_large | |
procedure, public, pass(self) :: any => any_large | |
procedure, public, pass(self) :: bit_count => bit_count_large | |
procedure, public, pass(self) :: bits | |
generic, public :: clear => clear_bit, clear_range | |
procedure, public, pass(self) :: clear_bit => clear_bit_large | |
procedure, public, pass(self) :: clear_range => clear_range_large | |
generic, public :: flip => flip_bit, flip_range | |
procedure, public, pass(self) :: flip_bit => flip_bit_large | |
procedure, public, pass(self) :: flip_range => flip_range_large | |
procedure, public, pass(self) :: from_string => from_string_large | |
generic, public :: init => init_zero | |
procedure, public, pass(self) :: init_zero => init_zero_large | |
procedure, public, pass(self) :: input => input_large | |
procedure, public, pass(self) :: none => none_large | |
procedure, public, pass(self) :: not => not_large | |
procedure, public, pass(self) :: output => output_large | |
generic, public :: read_bitset => read_bitset_string, read_bitset_unit | |
procedure, public, pass(self) :: read_bitset_string => read_bitset_string_large | |
procedure, public, pass(self) :: read_bitset_unit => read_bitset_unit_large | |
generic, public :: set => set_bit, set_range | |
procedure, public, pass(self) :: set_bit => set_bit_large | |
procedure, public, pass(self) :: set_range => set_range_large | |
procedure, public, pass(self) :: test => test_large | |
procedure, public, pass(self) :: to_string => to_string_large | |
procedure, public, pass(self) :: value => value_large | |
泛型,公用 :: write_bitset => write_bitset_string, write_bitset_unit | |
过程,公用,传递(自身) :: write_bitset_string => write_bitset_string_large | |
过程,公用,传递(自身) :: write_bitset_unit => write_bitset_unit_large |
bitset_64 和 bitset_large 的父类型 (规范)
过程(全部抽象),公用,延迟,传递(自身) :: all | |
过程(任何抽象),公用,延迟,传递(自身) :: any | |
过程(位计数抽象),公用,延迟,传递(自身) :: bit_count | |
procedure, public, pass(self) :: bits | |
泛型,公用 :: clear => clear_bit, clear_range | |
过程(清除位抽象),公用,延迟,传递(自身) :: clear_bit | |
过程(清除范围抽象),公用,延迟,传递(自身) :: clear_range | |
泛型,公用 :: flip => flip_bit, flip_range | |
过程(翻转位抽象),公用,延迟,传递(自身) :: flip_bit | |
过程(翻转范围抽象),公用,延迟,传递(自身) :: flip_range | |
过程(从字符串抽象),公用,延迟,传递(自身) :: from_string | |
泛型,公用 :: init => init_zero | |
过程(初始化零抽象),公用,延迟,传递(自身) :: init_zero | |
过程(输入抽象),公用,延迟,传递(自身) :: input | |
过程(无抽象),公用,延迟,传递(自身) :: none | |
过程(非抽象),公用,延迟,传递(自身) :: not | |
过程(输出抽象),公用,延迟,传递(自身) :: output | |
泛型,公用 :: read_bitset => read_bitset_string, read_bitset_unit | |
过程(读取位集字符串抽象),公用,延迟,传递(自身) :: read_bitset_string | |
过程(读取位集单元抽象),公用,延迟,传递(自身) :: read_bitset_unit | |
泛型,公用 :: set => set_bit, set_range | |
过程(设置位抽象),公用,延迟,传递(自身) :: set_bit | |
过程(设置范围抽象),公用,延迟,传递(自身) :: set_range | |
过程(测试抽象),公用,延迟,传递(自身) :: test | |
过程(转换为字符串抽象),公用,延迟,传递(自身) :: to_string | |
过程(值抽象),公用,延迟,传递(自身) :: value | |
泛型,公用 :: write_bitset => write_bitset_string, write_bitset_unit | |
过程(写入位集字符串抽象),公用,延迟,传递(自身) :: write_bitset_string | |
过程(写入位集单元抽象),公用,延迟,传递(自身) :: write_bitset_unit |
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
character(len=*), | intent(in) | :: | 消息 | |||
integer, | intent(in) | :: | 错误 | |||
integer, | intent(out), | optional | :: | status | ||
character(len=*), | intent(in), | optional | :: | 模块 | ||
character(len=*), | intent(in), | optional | :: | 过程 |