Type for bitsets with no more than 64 bits (Specification)
Returns .true.
if all bits in self
are 1, .false.
otherwise.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(bitset_64), | intent(in) | :: | self |
Returns .true.
if any bit in self
is 1, .false.
otherwise.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(bitset_64), | intent(in) | :: | self |
Returns the number of non-zero bits in self
.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(bitset_64), | 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 bit at pos
position in self
. If pos
is less than
zero or greater than bits(self)-1
it is ignored.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(bitset_64), | intent(inout) | :: | self | |||
integer(kind=bits_kind), | intent(in) | :: | pos |
Sets to zero all bits from the start_pos
to stop_pos
positions in self
.
If stop_pos < start_pos
then no bits are modified. Positions outside
the range 0 to bits(set)-1
are ignored.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(bitset_64), | intent(inout) | :: | self | |||
integer(kind=bits_kind), | intent(in) | :: | start_pos | |||
integer(kind=bits_kind), | intent(in) | :: | stop_pos |
Flips the bit 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.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(bitset_64), | 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_64), | 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.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(bitset_64), | 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
.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(bitset_64), | 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
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(bitset_64), | 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.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(bitset_64), | intent(in) | :: | self |
Sets the bits in self
to their logical complement.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(bitset_64), | 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.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(bitset_64), | 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 - if
bits(self)in
stringis greater
than 64 for a
bitset_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,
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(bitset_64), | 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_64), | 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.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(bitset_64), | 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_64), | 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.
.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(bitset_64), | 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
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(bitset_64), | 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.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(bitset_64), | 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_64
, 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.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(bitset_64), | 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, self
. 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, or
write_failure
if the write
statement outputting the literal failed.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
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