
Parent type for bitset_64 and bitset_large (Specification)
Returns .true. if all bits in self are 1, .false. otherwise.
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
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(in) | :: | self |
Returns .true. if any bit in self is 1, .false. otherwise.
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
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(in) | :: | self |
Returns the number of non-zero bits in 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
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(in) | :: | self |
Returns the number of bit positions in self.
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(in) | :: | self |
Sets to zero the pos position in self. If pos is less than zero or
greater than bits(self)-1 it is ignored.
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
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(inout) | :: | self | |||
| integer(kind=bits_kind), | intent(in) | :: | pos |
Sets to zero all bits from the start_pos to stop_pos positions in set.
If stop_pos < start_pos then no bits are modified. Positions outside
the range 0 to bits(self)-1 are ignored.
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(inout) | :: | self | |||
| integer(kind=bits_kind), | intent(in) | :: | start_pos | |||
| integer(kind=bits_kind), | intent(in) | :: | stop_pos |
Flips the value at the pos position in self, provided the position is
valid. If pos is less than 0 or greater than bits(self)-1, no value is
changed.
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
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(inout) | :: | self | |||
| integer(kind=bits_kind), | intent(in) | :: | pos |
Flips all valid bits from the start_pos to the stop_pos positions in
self. If stop_pos < start_pos no bits are flipped. Positions less than
0 or greater than bits(self)-1 are ignored.
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(inout) | :: | self | |||
| integer(kind=bits_kind), | intent(in) | :: | start_pos | |||
| integer(kind=bits_kind), | intent(in) | :: | stop_pos |
Initializes the bitset self treating string as a binary literal
status may have the values:
* success - if no problems were found,
* alloc_fault - if allocation of the bitset failed
* char_string_too_large_error - if string was too large, or
* char_string_invalid_error - if string had an invalid character.
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
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(out) | :: | self | |||
| character(len=*), | intent(in) | :: | string | |||
| integer, | intent(out), | optional | :: | status |
Creates the bitset, self, of size bits, with all bits initialized to
zero. bits must be non-negative. If an error occurs and status is
absent then processing stops with an informative stop code. status
will have one of the values;
* success - if no problems were found,
* alloc_fault - if memory allocation failed
* array_size_invalid_error - if bits is either negative or larger
than 64 with self of class bitset_64, or
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
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(out) | :: | self | |||
| integer(kind=bits_kind), | intent(in) | :: | bits | |||
| integer, | intent(out), | optional | :: | status |
Reads the components of the bitset, self, from the unformatted I/O
unit, unit, assuming that the components were written using output.
If an error occurs and status is absent then processing stops with
an informative stop code. status has one of the values:
* success - if no problem was found
* alloc_fault - if it failed allocating memory for self, or
* array_size_invalid_error if the bits(self) in unit is negative
or greater than 64 for a bitset_64 input.
* read_failure - if it failed during the reads from 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
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(out) | :: | self | |||
| integer, | intent(in) | :: | unit | |||
| integer, | intent(out), | optional | :: | status |
Returns .true. if none of the bits in self have the value 1.
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
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(in) | :: | self |
Sets the bits in self to their logical complement
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
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(inout) | :: | self |
Writes the components of the bitset, self, to the unformatted I/O
unit, unit, in a unformatted sequence compatible with input. If
status is absent an error results in an error stop with an
informative stop code. If status is present it has the default
value of success, or the value write_failure if the write failed.
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
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(in) | :: | self | |||
| integer, | intent(in) | :: | unit | |||
| integer, | intent(out), | optional | :: | status |
Uses the bitset literal in the default character string, to define
the bitset, self. The literal may be preceded by an an arbitrary
sequence of blank characters. If status is absent an error results
in an error stop with an informative stop code. If status
is present it has one of the values
* success - if no problems occurred,
* alloc_fault - if allocation of memory for SELF failed,
* array_size_invalid_error - ifbits(self)instringis greater
than 64 for abitset_64,
*char_string_invalid_error- if the bitset literal has an invalid
character,
*char_string_too_small_error - if the string ends before all the bits
are read.
* integer_overflow_error - if the bitset literal has a bits(self)
value too large to be represented,
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
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(out) | :: | self | |||
| character(len=*), | intent(in) | :: | string | |||
| integer, | intent(out), | optional | :: | status |
Uses the bitset literal at the current position in the formatted
file with I/O unit, unit, to define the bitset, self. The literal
may be preceded by an an arbitrary sequence of blank characters.
If advance is present it must be either 'YES' or 'NO'. If absent
it has the default value of 'YES' to determine whether advancing
I/O occurs. If status is absent an error results in an error stop
with an informative stop code. If status is present it has one of
the values:
* success - if no problem occurred,
* alloc_fault - if allocation of self failed,
* array_size_invalid_error - if bits(self) in the bitset literal
is greater than 64 for a bitset_64,
* char_string_invalid_error - if the read of the bitset literal found
an invalid character,
* eof_failure - if a read statement reached an end-of-file before
completing the read of the bitset literal,
* integer_overflow_error - if the bitset literal has a bits(self)
value too large to be represented,
* read_failure - if a read statement fails,
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(out) | :: | self | |||
| integer, | intent(in) | :: | unit | |||
| character(len=*), | intent(in), | optional | :: | advance | ||
| integer, | intent(out), | optional | :: | status |
Sets the value at the pos position in self, provided the position is
valid. If the position is less than 0 or greater than bits(self)-1
then self is unchanged.
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
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(inout) | :: | self | |||
| integer(kind=bits_kind), | intent(in) | :: | pos |
Sets all valid bits to 1 from the start_pos to the stop_pos positions
in self. If stop_pos < start_pos no bits are changed. Positions outside
the range 0 to bits(self)-1 are ignored.
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(inout) | :: | self | |||
| integer(kind=bits_kind), | intent(in) | :: | start_pos | |||
| integer(kind=bits_kind), | intent(in) | :: | stop_pos |
Returns .true. if the pos position is set, .false. otherwise. If pos
is negative or greater than bits(self) - 1 the result is .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
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(in) | :: | self | |||
| integer(kind=bits_kind), | intent(in) | :: | pos |
Represents the value of self as a binary literal in string
Status may have the values success or 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
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(in) | :: | self | |||
| character(len=:), | intent(out), | allocatable | :: | string | ||
| integer, | intent(out), | optional | :: | status |
Returns 1 if the pos position is set, 0 otherwise. If pos is negative
or greater than bits(set) - 1 the result is 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
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(in) | :: | self | |||
| integer(kind=bits_kind), | intent(in) | :: | pos |
Writes a bitset literal to the allocatable default character string,
representing the individual bit values in the bitset_type, self.
If status is absent an error results in an error stop with an
informative stop code. If status is present it has the default
value of success, or the value alloc_fault if allocation of
the output string failed.
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
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| class(bitset_type), | intent(in) | :: | self | |||
| character(len=:), | intent(out), | allocatable | :: | string | ||
| integer, | intent(out), | optional | :: | status |
Writes a bitset literal to the I/O unit, unit, representing the
individual bit values in the bitset_t, self. If an error occurs then
processing stops with a message to error_unit. By default or if
advance is present with the value 'YES', advancing output is used.
If advance is present with the value 'NO', then the current record
is not advanced by the write. If status is absent, an error results
in an error stop with an informative stop code. If status is
present it has the default value of success, the value
alloc_fault if allocation of the output string failed,
write_failure if the write statement outputting the literal failed.
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| 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