string_type Derived Type

type, public :: string_type
sequence

String type holding an arbitrary sequence of characters.


Constructor

public interface string_type

Constructor for new string instances

  • private elemental module function new_string(string) result(new)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in), optional :: string

    Return Value type(string_type)

  • private elemental module function new_string_from_integer_int16(val) result(new)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: val

    Return Value type(string_type)

  • private elemental module function new_string_from_integer_int32(val) result(new)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: val

    Return Value type(string_type)

  • private elemental module function new_string_from_integer_int64(val) result(new)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: val

    Return Value type(string_type)

  • private elemental module function new_string_from_integer_int8(val) result(new)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: val

    Return Value type(string_type)

  • private elemental module function new_string_from_logical_lk(val) result(new)

    Arguments

    Type IntentOptional Attributes Name
    logical(kind=lk), intent(in) :: val

    Return Value type(string_type)


Source Code

    type :: string_type
        ! Use the sequence statement below as a hack to prevent extending this type.
        ! It is not used for storage association.
        sequence
        private
        character(len=:), allocatable :: raw
    end type string_type