bitset_large Derived Type

type, public, extends(bitset_type) :: bitset_large

Type for bitsets with more than 64 bits (Specification)


Type-Bound Procedures

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

  • interface

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

    Returns .true. if all bits in self are 1, .false. otherwise.

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), intent(in) :: self

    Return Value logical

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

  • interface

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

    Returns .true. if any bit in self is 1, .false. otherwise.

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), intent(in) :: self

    Return Value logical

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

  • interface

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

    Returns the number of non-zero bits in self.

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), intent(in) :: self

    Return Value integer(kind=bits_kind)

procedure, public, pass(self) :: bits

  • public elemental function bits(self)

    License
    Creative Commons License
    Version
    experimental

    Returns the number of bit positions in self.

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_type), intent(in) :: self

    Return Value integer(kind=bits_kind)

generic, public :: clear => clear_bit, clear_range

  • private interface clear_bit_large()

    Arguments

    None
  • private interface clear_range_large()

    Arguments

    None

procedure, public, pass(self) :: clear_bit => clear_bit_large

  • interface

    private elemental module subroutine clear_bit_large(self, pos)

    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.

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), intent(inout) :: self
    integer(kind=bits_kind), intent(in) :: pos

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

  • interface

    private pure module subroutine clear_range_large(self, start_pos, stop_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.

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), 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()

    Arguments

    None
  • private interface flip_range_large()

    Arguments

    None

procedure, public, pass(self) :: flip_bit => flip_bit_large

  • interface

    private elemental module subroutine flip_bit_large(self, 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.

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), intent(inout) :: self
    integer(kind=bits_kind), intent(in) :: pos

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

  • interface

    private pure module subroutine flip_range_large(self, start_pos, stop_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.

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), 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_large

  • interface

    private module subroutine from_string_large(self, string, status)

    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.

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), intent(out) :: self
    character(len=*), intent(in) :: string
    integer, intent(out), optional :: status

generic, public :: init => init_zero

  • private interface init_zero_large()

    Arguments

    None

procedure, public, pass(self) :: init_zero => init_zero_large

  • interface

    private module subroutine init_zero_large(self, bits, 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

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), intent(out) :: self
    integer(kind=bits_kind), intent(in) :: bits
    integer, intent(out), optional :: status

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

  • interface

    private module subroutine input_large(self, unit, 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

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), intent(out) :: self
    integer, intent(in) :: unit
    integer, intent(out), optional :: status

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

  • interface

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

    Returns .true. if none of the bits in self have the value 1.

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), intent(in) :: self

    Return Value logical

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

  • interface

    private elemental module subroutine not_large(self)

    Sets the bits in self to their logical complement

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), intent(inout) :: self

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

  • interface

    private module subroutine output_large(self, unit, status)

    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.

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), 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()

    Arguments

    None
  • private interface read_bitset_unit_large()

    Arguments

    None

procedure, public, pass(self) :: read_bitset_string => read_bitset_string_large

  • interface

    private module subroutine read_bitset_string_large(self, string, 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,

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), intent(out) :: self
    character(len=*), intent(in) :: string
    integer, intent(out), optional :: status

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

  • interface

    private module subroutine read_bitset_unit_large(self, unit, advance, 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,

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), 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()

    Arguments

    None
  • private interface set_range_large()

    Arguments

    None

procedure, public, pass(self) :: set_bit => set_bit_large

  • interface

    private elemental module subroutine set_bit_large(self, pos)

    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.

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), intent(inout) :: self
    integer(kind=bits_kind), intent(in) :: pos

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

  • interface

    private pure module subroutine set_range_large(self, start_pos, stop_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.

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), 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_large

  • interface

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

    Returns .true. if the pos position is set, .false. otherwise. If pos is negative or greater than bits(self) - 1 the result is .false..

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), intent(in) :: self
    integer(kind=bits_kind), intent(in) :: pos

    Return Value logical

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

  • interface

    private module subroutine to_string_large(self, string, status)

    Represents the value of self as a binary literal in string Status may have the values success or alloc_fault.

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), intent(in) :: self
    character(len=:), intent(out), allocatable :: string
    integer, intent(out), optional :: status

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

  • interface

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

    Returns 1 if the pos position is set, 0 otherwise. If pos is negative or greater than bits(set) - 1 the result is 0.

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), intent(in) :: self
    integer(kind=bits_kind), intent(in) :: pos

    Return Value integer

generic, public :: write_bitset => write_bitset_string, write_bitset_unit

  • private interface write_bitset_string_large()

    Arguments

    None
  • private interface write_bitset_unit_large()

    Arguments

    None

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

  • interface

    private module subroutine write_bitset_string_large(self, string, status)

    Writes a bitset literal to the allocatable default character string, representing the individual bit values in the bitset_large, 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 valuealloc_fault` if allocation of the output string failed.

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), intent(in) :: self
    character(len=:), intent(out), allocatable :: string
    integer, intent(out), optional :: status

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

  • interface

    private module subroutine write_bitset_unit_large(self, unit, advance, 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.

    Arguments

    Type IntentOptional Attributes Name
    class(bitset_large), intent(in) :: self
    integer, intent(in) :: unit
    character(len=*), intent(in), optional :: advance
    integer, intent(out), optional :: status

Source Code

    type, extends(bitset_type) :: bitset_large
!! Version: experimental
!!
!! Type for bitsets with more than 64 bits ([Specification](../page/specs/stdlib_bitsets.html#the-stdlib_bitsets-derived-types))

        private
        integer(block_kind), private, allocatable :: blocks(:)

    contains

        procedure, pass(self)  :: all => all_large
        procedure, pass(self)  :: any => any_large
        procedure, pass(self)  :: bit_count => bit_count_large
        procedure, pass(self)  :: clear_bit => clear_bit_large
        procedure, pass(self)  :: clear_range => clear_range_large
        procedure, pass(self)  :: flip_bit => flip_bit_large
        procedure, pass(self)  :: flip_range => flip_range_large
        procedure, pass(self)  :: from_string => from_string_large
        procedure, pass(self)  :: init_zero => init_zero_large
        procedure, pass(self)  :: input => input_large
        procedure, pass(self)  :: none => none_large
        procedure, pass(self)  :: not => not_large
        procedure, pass(self)  :: output => output_large
        procedure, pass(self)  :: &
            read_bitset_string => read_bitset_string_large
        procedure, pass(self)  :: read_bitset_unit => read_bitset_unit_large
        procedure, pass(self)  :: set_bit => set_bit_large
        procedure, pass(self)  :: set_range => set_range_large
        procedure, pass(self)  :: test => test_large
        procedure, pass(self)  :: to_string => to_string_large
        procedure, pass(self)  :: value => value_large
        procedure, pass(self)  :: &
            write_bitset_string => write_bitset_string_large
        procedure, pass(self)  :: write_bitset_unit => write_bitset_unit_large

    end type bitset_large