string_class Derived Type

type, public, abstract :: string_class

Abstract base class for string objects


Contents

Source Code


Type-Bound Procedures

procedure(assign_object_char_interface), public, deferred :: assign_object_char

  • elemental subroutine assign_object_char_interface(lhs, rhs) Prototype

    Assign a character sequence to a string object.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(inout) :: lhs
    character(len=*), intent(in) :: rhs

generic, public :: assignment(=) => assign_object_char

Assign a character sequence to a string object.

  • elemental subroutine assign_object_char_interface(lhs, rhs) Prototype

    Assign a character sequence to a string object.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(inout) :: lhs
    character(len=*), intent(in) :: rhs

generic, public :: assignment(=) => assign_object_string

Assign a string type to a string object.

  • private elemental subroutine assign_object_string(lhs, rhs)

    Assign a string type to a string object.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(inout) :: lhs
    type(string_type), intent(in) :: rhs

generic, public :: assignment(=) => assign_object_object

Assign a string type to a string object.

  • private elemental subroutine assign_object_object(lhs, rhs)

    Assign a string object to a string object.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(inout) :: lhs
    class(string_class), intent(in) :: rhs

procedure(get_char_interface), public, deferred :: get_char

Return the character sequence represented by the string.

  • pure function get_char_interface(self) result(character_string) Prototype

    Return the character sequence represented by the string.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: self

    Return Value character(len=:), allocatable

procedure(get_char_pos_interface), public, deferred :: get_char_pos

Return the character sequence represented by the string.

  • elemental function get_char_pos_interface(self, pos) result(character_string) Prototype

    Return the character sequence represented by the string.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: self
    integer, intent(in) :: pos

    Return Value character(len=1)

procedure(get_char_range_interface), public, deferred :: get_char_range

Return the character sequence represented by the string.

  • pure function get_char_range_interface(self, start, last) result(character_string) Prototype

    Return the character sequence represented by the string.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: self
    integer, intent(in) :: start
    integer, intent(in) :: last

    Return Value character(len=last-start+1)

procedure(get_int_interface), public, deferred :: get_len

Returns the length of the character sequence represented by the string.

  • elemental function get_int_interface(self) result(val) Prototype

    Return a integer value representing a property of the character sequence, like - the length of the character sequence - the character-to-integer conversion

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: self

    Return Value integer

procedure(get_int_interface), public, deferred :: get_len_trim

Returns the length of the character sequence without trailing spaces represented by the string.

  • elemental function get_int_interface(self) result(val) Prototype

    Return a integer value representing a property of the character sequence, like - the length of the character sequence - the character-to-integer conversion

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: self

    Return Value integer

generic, public :: operator(//) => concat_object_object, concat_object_string, concat_string_object, concat_object_char, concat_char_object

Compare two character sequences for inequality.

  • private elemental function concat_object_object(lhs, rhs) result(string)

    Compare two character sequences for being greater.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value type(string_type)

  • private elemental function concat_object_string(lhs, rhs) result(string)

    Compare two character sequences for being greater.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    type(string_type), intent(in) :: rhs

    Return Value type(string_type)

  • private elemental function concat_string_object(lhs, rhs) result(string)

    Compare two character sequences for being greater.

    Arguments

    Type IntentOptional AttributesName
    type(string_type), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value type(string_type)

  • private elemental function concat_object_char(lhs, rhs) result(string)

    Compare two character sequences for being greater.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    character(len=*), intent(in) :: rhs

    Return Value type(string_type)

  • private elemental function concat_char_object(lhs, rhs) result(string)

    Compare two character sequences for being greater.

    Arguments

    Type IntentOptional AttributesName
    character(len=*), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value type(string_type)

generic, public :: operator(/=) => ne_object_object, ne_object_string, ne_string_object, ne_object_char, ne_char_object

Compare two character sequences for inequality.

  • private elemental function ne_object_object(lhs, rhs) result(is_ne)

    Compare two character sequences for inequality.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value logical

  • private elemental function ne_object_string(lhs, rhs) result(is_ne)

    Compare two character sequences for inequality.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    type(string_type), intent(in) :: rhs

    Return Value logical

  • private elemental function ne_string_object(lhs, rhs) result(is_ne)

    Compare two character sequences for inequality.

    Arguments

    Type IntentOptional AttributesName
    type(string_type), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value logical

  • private elemental function ne_object_char(lhs, rhs) result(is_ne)

    Compare two character sequences for inequality.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    character(len=*), intent(in) :: rhs

    Return Value logical

  • private elemental function ne_char_object(lhs, rhs) result(is_ne)

    Compare two character sequences for inequality.

    Arguments

    Type IntentOptional AttributesName
    character(len=*), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value logical

generic, public :: operator(<) => lt_object_object, lt_object_string, lt_string_object, lt_object_char, lt_char_object

Compare two character sequences for being less.

  • private elemental function lt_object_object(lhs, rhs) result(is_lt)

    Compare two character sequences for being less.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value logical

  • private elemental function lt_object_string(lhs, rhs) result(is_lt)

    Compare two character sequences for being less.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    type(string_type), intent(in) :: rhs

    Return Value logical

  • private elemental function lt_string_object(lhs, rhs) result(is_lt)

    Compare two character sequences for being less.

    Arguments

    Type IntentOptional AttributesName
    type(string_type), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value logical

  • private elemental function lt_object_char(lhs, rhs) result(is_lt)

    Compare two character sequences for being less.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    character(len=*), intent(in) :: rhs

    Return Value logical

  • private elemental function lt_char_object(lhs, rhs) result(is_lt)

    Compare two character sequences for being less.

    Arguments

    Type IntentOptional AttributesName
    character(len=*), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value logical

generic, public :: operator(<=) => le_object_object, le_object_string, le_string_object, le_object_char, le_char_object

Compare two character sequences for being less or equal.

  • private elemental function le_object_object(lhs, rhs) result(is_le)

    Compare two character sequences for being less or equal.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value logical

  • private elemental function le_object_string(lhs, rhs) result(is_le)

    Compare two character sequences for being less or equal.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    type(string_type), intent(in) :: rhs

    Return Value logical

  • private elemental function le_string_object(lhs, rhs) result(is_le)

    Compare two character sequences for being less or equal

    Arguments

    Type IntentOptional AttributesName
    type(string_type), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value logical

  • private elemental function le_object_char(lhs, rhs) result(is_le)

    Compare two character sequences for being less or equal.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    character(len=*), intent(in) :: rhs

    Return Value logical

  • private elemental function le_char_object(lhs, rhs) result(is_le)

    Compare two character sequences for being less or equal

    Arguments

    Type IntentOptional AttributesName
    character(len=*), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value logical

generic, public :: operator(==) => eq_object_object, eq_object_string, eq_string_object, eq_object_char, eq_char_object

Compare two character sequences for equality.

  • private elemental function eq_object_object(lhs, rhs) result(is_eq)

    Compare two character sequences for equality.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value logical

  • private elemental function eq_object_string(lhs, rhs) result(is_eq)

    Compare two character sequences for equality.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    type(string_type), intent(in) :: rhs

    Return Value logical

  • private elemental function eq_string_object(lhs, rhs) result(is_eq)

    Compare two character sequences for equality.

    Arguments

    Type IntentOptional AttributesName
    type(string_type), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value logical

  • private elemental function eq_object_char(lhs, rhs) result(is_eq)

    Compare two character sequences for equality.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    character(len=*), intent(in) :: rhs

    Return Value logical

  • private elemental function eq_char_object(lhs, rhs) result(is_eq)

    Compare two character sequences for equality.

    Arguments

    Type IntentOptional AttributesName
    character(len=*), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value logical

generic, public :: operator(>) => gt_object_object, gt_object_string, gt_string_object, gt_object_char, gt_char_object

Compare two character sequences for being greater.

  • private elemental function gt_object_object(lhs, rhs) result(is_gt)

    Compare two character sequences for being greater.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value logical

  • private elemental function gt_object_string(lhs, rhs) result(is_gt)

    Compare two character sequences for being greater.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    type(string_type), intent(in) :: rhs

    Return Value logical

  • private elemental function gt_string_object(lhs, rhs) result(is_gt)

    Compare two character sequences for being greater.

    Arguments

    Type IntentOptional AttributesName
    type(string_type), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value logical

  • private elemental function gt_object_char(lhs, rhs) result(is_gt)

    Compare two character sequences for being greater.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    character(len=*), intent(in) :: rhs

    Return Value logical

  • private elemental function gt_char_object(lhs, rhs) result(is_gt)

    Compare two character sequences for being greater.

    Arguments

    Type IntentOptional AttributesName
    character(len=*), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value logical

generic, public :: operator(>=) => ge_object_object, ge_object_string, ge_string_object, ge_object_char, ge_char_object

Compare two character sequences for being greater or equal.

  • private elemental function ge_object_object(lhs, rhs) result(is_ge)

    Compare two character sequences for being greater or equal.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value logical

  • private elemental function ge_object_string(lhs, rhs) result(is_ge)

    Compare two character sequences for being greater or equal.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    type(string_type), intent(in) :: rhs

    Return Value logical

  • private elemental function ge_string_object(lhs, rhs) result(is_ge)

    Compare two character sequences for being greater or equal

    Arguments

    Type IntentOptional AttributesName
    type(string_type), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value logical

  • private elemental function ge_object_char(lhs, rhs) result(is_ge)

    Compare two character sequences for being greater or equal.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: lhs
    character(len=*), intent(in) :: rhs

    Return Value logical

  • private elemental function ge_char_object(lhs, rhs) result(is_ge)

    Compare two character sequences for being greater or equal

    Arguments

    Type IntentOptional AttributesName
    character(len=*), intent(in) :: lhs
    class(string_class), intent(in) :: rhs

    Return Value logical

generic, public :: read(formatted) => read_formatted

Read a character sequence from a connected formatted unit into the string.

  • private subroutine read_formatted(self, unit, iotype, v_list, iostat, iomsg)

    Read a character sequence from a connected formatted unit into the string.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(inout) :: self
    integer, intent(in) :: unit
    character(len=*), intent(in) :: iotype
    integer, intent(in) :: v_list(:)
    integer, intent(out) :: iostat
    character(len=*), intent(inout) :: iomsg

generic, public :: read(unformatted) => read_unformatted

Read a character sequence from a connected unformatted unit into the string.

  • private subroutine read_unformatted(self, unit, iostat, iomsg)

    Read a character sequence from a connected unformatted unit into the string.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(inout) :: self
    integer, intent(in) :: unit
    integer, intent(out) :: iostat
    character(len=*), intent(inout) :: iomsg

generic, public :: write(formatted) => write_formatted

Write the character sequence hold by the string to a connected formatted unit.

  • private subroutine write_formatted(self, unit, iotype, v_list, iostat, iomsg)

    Write the character sequence hold by the string to a connected formatted unit.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: self
    integer, intent(in) :: unit
    character(len=*), intent(in) :: iotype
    integer, intent(in) :: v_list(:)
    integer, intent(out) :: iostat
    character(len=*), intent(inout) :: iomsg

generic, public :: write(unformatted) => write_unformatted

Write the character sequence hold by the string to a connected unformatted unit.

  • private subroutine write_unformatted(self, unit, iostat, iomsg)

    Write the character sequence hold by the string to a connected unformatted unit.

    Arguments

    Type IntentOptional AttributesName
    class(string_class), intent(in) :: self
    integer, intent(in) :: unit
    integer, intent(out) :: iostat
    character(len=*), intent(inout) :: iomsg

Source Code

    type, abstract :: string_class
    contains
        private

        !> Assign a character sequence to a string object.
        generic, public :: assignment(=) => assign_object_char
        ! BUG: Intel 2021 requires deferred bindings to be public
        procedure(assign_object_char_interface), public, deferred :: assign_object_char

        !> Assign a string type to a string object.
        generic, public :: assignment(=) => assign_object_string
        procedure :: assign_object_string

        !> Assign a string type to a string object.
        generic, public :: assignment(=) => assign_object_object
        procedure :: assign_object_object

        !> Returns the length of the character sequence represented by the string.
        ! BUG: Intel 2021 requires deferred bindings to be public
        procedure(get_int_interface), public, deferred :: get_len

        !> Returns the length of the character sequence without trailing spaces
        !> represented by the string.
        ! BUG: Intel 2021 requires deferred bindings to be public
        procedure(get_int_interface), public, deferred :: get_len_trim

        !> Character-to-integer conversion function.
        procedure :: get_ichar

        !> Code in ASCII collating sequence.
        procedure :: get_iachar

        !> Return the character sequence represented by the string.
        ! BUG: Intel 2021 requires deferred bindings to be public
        procedure(get_char_interface), public, deferred :: get_char

        !> Return the character sequence represented by the string.
        ! BUG: Intel 2021 requires deferred bindings to be public
        procedure(get_char_pos_interface), public, deferred :: get_char_pos

        !> Return the character sequence represented by the string.
        ! BUG: Intel 2021 requires deferred bindings to be public
        procedure(get_char_range_interface), public, deferred :: get_char_range

        !> Left-adjust the character sequence represented by the string.
        !> The length of the character sequence remains unchanged.
        procedure :: get_trim

        !> Left-adjust the character sequence represented by the string.
        !> The length of the character sequence remains unchanged.
        procedure :: get_adjustl

        !> Right-adjust the character sequence represented by the string.
        !> The length of the character sequence remains unchanged.
        procedure :: get_adjustr

        !> Repeats the character sequence hold by the string by the number of
        !> specified copies.
        procedure :: get_repeat

        !> Scan a *string* for the presence of a *set* of characters. Scans a *string* for
        !> any of the characters in a *set* of characters.
        !>
        !> If *back* is either absent or *false*, this function returns the position
        !> of the leftmost character of *string* that is in *set*. If *back* is *true*,
        !> the rightmost position is returned. If no character of *set* is found in
        !> *string*, the result is zero.
        !>
        !> This method is elemental and returns a default integer scalar value.
        generic :: get_scan => get_scan_object, get_scan_string, get_scan_char
        !> Implementation of scanning against a set provided as string object
        procedure :: get_scan_object
        !> Implementation of scanning against a set provided as string type
        procedure :: get_scan_string
        !> Implementation of scanning against a set provided as character scalar
        procedure :: get_scan_char

        !> Scan a string for the absence of a set of characters. Verifies that all
        !> the characters in string belong to the set of characters in set.
        !>
        !> If *back* is either absent or *false*, this function returns the position
        !> of the leftmost character of *string* that is not in *set*. If *back* is *true*,
        !> the rightmost position is returned. If all characters of *string* are found
        !> in *set*, the result is zero.
        !>
        !> This method is elemental and returns a default integer scalar value.
        generic :: get_verify => get_verify_object, get_verify_string, get_verify_char
        !> Implementation of verifying against a set provided as string object
        procedure :: get_verify_object
        !> Implementation of verifying against a set provided as string type
        procedure :: get_verify_string
        !> Implementation of verifying against a set provided as character scalar
        procedure :: get_verify_char

        !> Position of a *substring* within a *string*.
        !>
        !> Returns the position of the start of the leftmost or rightmost occurrence
        !> of string *substring* in *string*, counting from one. If *substring* is not
        !> present in *string*, zero is returned.
        !>
        !> This method is elemental and returns a default integer scalar value.
        generic :: get_index => get_index_object, get_index_string, get_index_char
        !> Implementation of finding a substring provided as string object
        procedure :: get_index_object
        !> Implementation of finding a substring provided as string type
        procedure :: get_index_string
        !> Implementation of finding a substring provided as character value
        procedure :: get_index_char

        !> Lexically compare two character sequences for being greater.
        generic :: is_lgt => is_lgt_object, is_lgt_string, is_lgt_char
        !> Implementation of lexical comparison with RHS provided as string object
        procedure, pass(lhs) :: is_lgt_object
        !> Implementation of lexical comparison with RHS provided as string type
        procedure, pass(lhs) :: is_lgt_string
        !> Implementation of lexical comparison with RHS provided as character value
        procedure, pass(lhs) :: is_lgt_char

        !> Lexically compare two character sequences for being less than.
        generic :: is_llt => is_llt_object, is_llt_string, is_llt_char
        !> Implementation of lexical comparison with RHS provided as string object
        procedure, pass(lhs) :: is_llt_object
        !> Implementation of lexical comparison with RHS provided as string type
        procedure, pass(lhs) :: is_llt_string
        !> Implementation of lexical comparison with RHS provided as character value
        procedure, pass(lhs) :: is_llt_char

        !> Lexically compare two character sequences for being greater than or equal.
        generic :: is_lge => is_lge_object, is_lge_string, is_lge_char
        !> Implementation of lexical comparison with RHS provided as string object
        procedure, pass(lhs) :: is_lge_object
        !> Implementation of lexical comparison with RHS provided as string type
        procedure, pass(lhs) :: is_lge_string
        !> Implementation of lexical comparison with RHS provided as character value
        procedure, pass(lhs) :: is_lge_char

        !> Lexically compare two character sequences for being less than or equal.
        generic :: is_lle => is_lle_object, is_lle_string, is_lle_char
        !> Implementation of lexical comparison with RHS provided as string object
        procedure, pass(lhs) :: is_lle_object
        !> Implementation of lexical comparison with RHS provided as string type
        procedure, pass(lhs) :: is_lle_string
        !> Implementation of lexical comparison with RHS provided as character value
        procedure, pass(lhs) :: is_lle_char

        !> Compare two character sequences for being greater.
        generic, public :: operator(>) => gt_object_object, gt_object_string, &
            gt_string_object, gt_object_char, gt_char_object
        procedure, pass(lhs) :: gt_object_object
        procedure, pass(lhs) :: gt_object_string
        procedure, pass(rhs) :: gt_string_object
        procedure, pass(lhs) :: gt_object_char
        procedure, pass(rhs) :: gt_char_object

        !> Compare two character sequences for being less.
        generic, public :: operator(<) => lt_object_object, lt_object_string, &
            lt_string_object, lt_object_char, lt_char_object
        procedure, pass(lhs) :: lt_object_object
        procedure, pass(lhs) :: lt_object_string
        procedure, pass(rhs) :: lt_string_object
        procedure, pass(lhs) :: lt_object_char
        procedure, pass(rhs) :: lt_char_object

        !> Compare two character sequences for being greater or equal.
        generic, public :: operator(>=) => ge_object_object, ge_object_string, &
            ge_string_object, ge_object_char, ge_char_object
        procedure, pass(lhs) :: ge_object_object
        procedure, pass(lhs) :: ge_object_string
        procedure, pass(rhs) :: ge_string_object
        procedure, pass(lhs) :: ge_object_char
        procedure, pass(rhs) :: ge_char_object

        !> Compare two character sequences for being less or equal.
        generic, public :: operator(<=) => le_object_object, le_object_string, &
            le_string_object, le_object_char, le_char_object
        procedure, pass(lhs) :: le_object_object
        procedure, pass(lhs) :: le_object_string
        procedure, pass(rhs) :: le_string_object
        procedure, pass(lhs) :: le_object_char
        procedure, pass(rhs) :: le_char_object

        !> Compare two character sequences for equality.
        generic, public :: operator(==) => eq_object_object, eq_object_string, &
            eq_string_object, eq_object_char, eq_char_object
        procedure, pass(lhs) :: eq_object_object
        procedure, pass(lhs) :: eq_object_string
        procedure, pass(rhs) :: eq_string_object
        procedure, pass(lhs) :: eq_object_char
        procedure, pass(rhs) :: eq_char_object

        !> Compare two character sequences for inequality.
        generic, public :: operator(/=) => ne_object_object, ne_object_string, &
            ne_string_object, ne_object_char, ne_char_object
        procedure, pass(lhs) :: ne_object_object
        procedure, pass(lhs) :: ne_object_string
        procedure, pass(rhs) :: ne_string_object
        procedure, pass(lhs) :: ne_object_char
        procedure, pass(rhs) :: ne_char_object

        !> Compare two character sequences for inequality.
        generic, public :: operator(//) => concat_object_object, concat_object_string, &
            concat_string_object, concat_object_char, concat_char_object
        procedure, pass(lhs) :: concat_object_object
        procedure, pass(lhs) :: concat_object_string
        procedure, pass(rhs) :: concat_string_object
        procedure, pass(lhs) :: concat_object_char
        procedure, pass(rhs) :: concat_char_object

        !> Write the character sequence hold by the string to a connected unformatted
        !> unit.
        generic, public :: write(unformatted) => write_unformatted
        procedure :: write_unformatted

        !> Write the character sequence hold by the string to a connected formatted
        !> unit.
        generic, public :: write(formatted) => write_formatted
        procedure :: write_formatted

        !> Read a character sequence from a connected unformatted unit into the string.
        generic, public :: read(unformatted) => read_unformatted
        procedure :: read_unformatted

        !> Read a character sequence from a connected formatted unit into the string.
        generic, public :: read(formatted) => read_formatted
        procedure :: read_formatted

    end type string_class