stdlib_strings Module

This module implements basic string handling routines.

The specification of this module is available here.


Used by


Interfaces

public interface chomp

Remove trailing characters in set from string. If no character set is provided trailing whitespace is removed.

Version: experimental

  • private pure function chomp_string(string) result(chomped_string)

    Remove trailing characters in set from string. Default character set variant where trailing whitespace is removed.

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string

    Return Value type(string_type)

  • private pure function chomp_char(string) result(chomped_string)

    Remove trailing characters in set from string. Default character set variant where trailing whitespace is removed.

    Arguments

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

    Return Value character(len=:), allocatable

  • private pure function chomp_set_string_char(string, set) result(chomped_string)

    Remove trailing characters in set from string.

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    character(len=1), intent(in) :: set(:)

    Return Value type(string_type)

  • private pure function chomp_set_char_char(string, set) result(chomped_string)

    Remove trailing characters in set from string.

    Arguments

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

    Return Value character(len=:), allocatable

  • private pure function chomp_substring_string_string(string, substring) result(chomped_string)

    Remove trailing substrings from string.

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    type(string_type), intent(in) :: substring

    Return Value type(string_type)

  • private pure function chomp_substring_char_string(string, substring) result(chomped_string)

    Remove trailing substrings from string.

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: string
    type(string_type), intent(in) :: substring

    Return Value character(len=:), allocatable

  • private pure function chomp_substring_string_char(string, substring) result(chomped_string)

    Remove trailing substrings from string.

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    character(len=*), intent(in) :: substring

    Return Value type(string_type)

  • private pure function chomp_substring_char_char(string, substring) result(chomped_string)

    Remove trailing substrings from string.

    Arguments

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

    Return Value character(len=:), allocatable

public interface count

Returns the number of times substring 'pattern' has appeared in the input string 'string' Specifications

  • private elemental function count_string_string(string, pattern, consider_overlapping) result(res)

    Returns the number of times substring 'pattern' has appeared in the input string 'string' Returns an integer

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    type(string_type), intent(in) :: pattern
    logical, intent(in), optional :: consider_overlapping

    Return Value integer

  • private elemental function count_string_char(string, pattern, consider_overlapping) result(res)

    Returns the number of times substring 'pattern' has appeared in the input string 'string' Returns an integer

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    character(len=*), intent(in) :: pattern
    logical, intent(in), optional :: consider_overlapping

    Return Value integer

  • private elemental function count_char_string(string, pattern, consider_overlapping) result(res)

    Returns the number of times substring 'pattern' has appeared in the input string 'string' Returns an integer

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: string
    type(string_type), intent(in) :: pattern
    logical, intent(in), optional :: consider_overlapping

    Return Value integer

  • private elemental function count_char_char(string, pattern, consider_overlapping) result(res)

    Returns the number of times substring 'pattern' has appeared in the input string 'string' Returns an integer

    Arguments

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

    Return Value integer

public interface ends_with

Check whether a string ends with substring or not

Version: experimental

  • private elemental function ends_with_string_string(string, substring) result(match)

    Check whether a string ends with substring or not

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    type(string_type), intent(in) :: substring

    Return Value logical

  • private elemental function ends_with_string_char(string, substring) result(match)

    Check whether a string ends with substring or not

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    character(len=*), intent(in) :: substring

    Return Value logical

  • private elemental function ends_with_char_string(string, substring) result(match)

    Check whether a string ends with substring or not

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: string
    type(string_type), intent(in) :: substring

    Return Value logical

  • private pure function ends_with_char_char(string, substring) result(match)

    Check whether a string ends with substring or not

    Arguments

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

    Return Value logical

public interface find

Finds the starting index of substring 'pattern' in the input 'string' Specifications

Version: experimental

  • private elemental function find_string_string(string, pattern, occurrence, consider_overlapping) result(res)

    Returns the starting index of the 'occurrence'th occurrence of substring 'pattern' in input 'string' Returns an integer

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    type(string_type), intent(in) :: pattern
    integer, intent(in), optional :: occurrence
    logical, intent(in), optional :: consider_overlapping

    Return Value integer

  • private elemental function find_string_char(string, pattern, occurrence, consider_overlapping) result(res)

    Returns the starting index of the 'occurrence'th occurrence of substring 'pattern' in input 'string' Returns an integer

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    character(len=*), intent(in) :: pattern
    integer, intent(in), optional :: occurrence
    logical, intent(in), optional :: consider_overlapping

    Return Value integer

  • private elemental function find_char_string(string, pattern, occurrence, consider_overlapping) result(res)

    Returns the starting index of the 'occurrence'th occurrence of substring 'pattern' in input 'string' Returns an integer

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: string
    type(string_type), intent(in) :: pattern
    integer, intent(in), optional :: occurrence
    logical, intent(in), optional :: consider_overlapping

    Return Value integer

  • private elemental function find_char_char(string, pattern, occurrence, consider_overlapping) result(res)

    Returns the starting index of the 'occurrence'th occurrence of substring 'pattern' in input 'string' Returns an integer

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: string
    character(len=*), intent(in) :: pattern
    integer, intent(in), optional :: occurrence
    logical, intent(in), optional :: consider_overlapping

    Return Value integer

public interface padl

Left pad the input string Specifications

  • private pure function padl_string_default(string, output_length) result(res)

    Left pad the input string with " " (1 whitespace)

    Returns a new string

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    integer, intent(in) :: output_length

    Return Value type(string_type)

  • private pure function padl_string_pad_with(string, output_length, pad_with) result(res)

    Left pad the input string with the 'pad_with' character

    Returns a new string

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    integer, intent(in) :: output_length
    character(len=1), intent(in) :: pad_with

    Return Value type(string_type)

  • private pure function padl_char_default(string, output_length) result(res)

    Left pad the input string with " " (1 whitespace)

    Returns a new string

    Arguments

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

    Return Value character(kind=output_length), len=max)

  • private pure function padl_char_pad_with(string, output_length, pad_with) result(res)

    Left pad the input string with the 'pad_with' character

    Returns a new string

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: string
    integer, intent(in) :: output_length
    character(len=1), intent(in) :: pad_with

    Return Value character(kind=output_length), len=max)

public interface padr

Right pad the input string Specifications

  • private pure function padr_string_default(string, output_length) result(res)

    Right pad the input string with " " (1 whitespace)

    Returns a new string

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    integer, intent(in) :: output_length

    Return Value type(string_type)

  • private pure function padr_string_pad_with(string, output_length, pad_with) result(res)

    Right pad the input string with the 'pad_with' character

    Returns a new string

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    integer, intent(in) :: output_length
    character(len=1), intent(in) :: pad_with

    Return Value type(string_type)

  • private pure function padr_char_default(string, output_length) result(res)

    Right pad the input string with " " (1 whitespace)

    Returns a new string

    Arguments

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

    Return Value character(kind=output_length), len=max)

  • private pure function padr_char_pad_with(string, output_length, pad_with) result(res)

    Right pad the input string with the 'pad_with' character

    Returns a new string

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: string
    integer, intent(in) :: output_length
    character(len=1), intent(in) :: pad_with

    Return Value character(kind=output_length), len=max)

public interface replace_all

Replaces all the occurrences of substring 'pattern' in the input 'string' with the replacement 'replacement' Version: experimental

  • private pure function replace_all_string_string_string(string, pattern, replacement) result(res)

    Replaces all occurrences of substring 'pattern' in the input 'string' with the replacement 'replacement' Returns a new string

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    type(string_type), intent(in) :: pattern
    type(string_type), intent(in) :: replacement

    Return Value type(string_type)

  • private pure function replace_all_string_string_char(string, pattern, replacement) result(res)

    Replaces all occurrences of substring 'pattern' in the input 'string' with the replacement 'replacement' Returns a new string

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    type(string_type), intent(in) :: pattern
    character(len=*), intent(in) :: replacement

    Return Value type(string_type)

  • private pure function replace_all_string_char_string(string, pattern, replacement) result(res)

    Replaces all occurrences of substring 'pattern' in the input 'string' with the replacement 'replacement' Returns a new string

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    character(len=*), intent(in) :: pattern
    type(string_type), intent(in) :: replacement

    Return Value type(string_type)

  • private pure function replace_all_char_string_string(string, pattern, replacement) result(res)

    Replaces all occurrences of substring 'pattern' in the input 'string' with the replacement 'replacement' Returns a new string

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: string
    type(string_type), intent(in) :: pattern
    type(string_type), intent(in) :: replacement

    Return Value character(len=:), allocatable

  • private pure function replace_all_string_char_char(string, pattern, replacement) result(res)

    Replaces all occurrences of substring 'pattern' in the input 'string' with the replacement 'replacement' Returns a new string

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    character(len=*), intent(in) :: pattern
    character(len=*), intent(in) :: replacement

    Return Value type(string_type)

  • private pure function replace_all_char_string_char(string, pattern, replacement) result(res)

    Replaces all occurrences of substring 'pattern' in the input 'string' with the replacement 'replacement' Returns a new string

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: string
    type(string_type), intent(in) :: pattern
    character(len=*), intent(in) :: replacement

    Return Value character(len=:), allocatable

  • private pure function replace_all_char_char_string(string, pattern, replacement) result(res)

    Replaces all occurrences of substring 'pattern' in the input 'string' with the replacement 'replacement' Returns a new string

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: string
    character(len=*), intent(in) :: pattern
    type(string_type), intent(in) :: replacement

    Return Value character(len=:), allocatable

  • private pure function replace_all_char_char_char(string, pattern, replacement) result(res)

    Replaces all the occurrences of substring 'pattern' in the input 'string' with the replacement 'replacement' Returns a new string

    Arguments

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

    Return Value character(len=:), allocatable

public interface slice

Extracts characters from the input string to return a new string

Version: experimental

  • private elemental function slice_string(string, first, last, stride) result(sliced_string)

    Extract the characters from the region between 'first' and 'last' index (both inclusive) of the input 'string' by taking strides of length 'stride' Returns a new string

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    integer, intent(in), optional :: first
    integer, intent(in), optional :: last
    integer, intent(in), optional :: stride

    Return Value type(string_type)

  • private pure function slice_char(string, first, last, stride) result(sliced_string)

    Extract the characters from the region between 'first' and 'last' index (both inclusive) of the input 'string' by taking strides of length 'stride' Returns a new string

    Arguments

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

    Return Value character(len=:), allocatable

public interface starts_with

Check whether a string starts with substring or not

Version: experimental

  • private elemental function starts_with_string_string(string, substring) result(match)

    Check whether a string starts with substring or not

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    type(string_type), intent(in) :: substring

    Return Value logical

  • private elemental function starts_with_string_char(string, substring) result(match)

    Check whether a string starts with substring or not

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    character(len=*), intent(in) :: substring

    Return Value logical

  • private elemental function starts_with_char_string(string, substring) result(match)

    Check whether a string starts with substring or not

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: string
    type(string_type), intent(in) :: substring

    Return Value logical

  • private pure function starts_with_char_char(string, substring) result(match)

    Check whether a string starts with substring or not

    Arguments

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

    Return Value logical

public interface strip

Remove leading and trailing whitespace characters.

Version: experimental

  • private pure function strip_string(string) result(stripped_string)

    Remove leading and trailing whitespace characters.

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string

    Return Value type(string_type)

  • private pure function strip_char(string) result(stripped_string)

    Remove leading and trailing whitespace characters.

    Arguments

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

    Return Value character(len=:), allocatable

public interface to_string

Format or transfer other types as a string. (Specification)

  • private pure module function to_string_1_i_int16(value) result(string)

    Arguments

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

    Return Value character(len=:), allocatable

  • private pure module function to_string_1_i_int32(value) result(string)

    Arguments

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

    Return Value character(len=:), allocatable

  • private pure module function to_string_1_i_int64(value) result(string)

    Arguments

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

    Return Value character(len=:), allocatable

  • private pure module function to_string_1_i_int8(value) result(string)

    Arguments

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

    Return Value character(len=:), allocatable

  • private pure module function to_string_1_l_lk(value) result(string)

    Arguments

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

    Return Value character(len=1)

  • private pure module function to_string_2_i_int16(value, format) result(string)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: value
    character(len=*), intent(in) :: format

    Return Value character(len=:), allocatable

  • private pure module function to_string_2_i_int32(value, format) result(string)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: value
    character(len=*), intent(in) :: format

    Return Value character(len=:), allocatable

  • private pure module function to_string_2_i_int64(value, format) result(string)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: value
    character(len=*), intent(in) :: format

    Return Value character(len=:), allocatable

  • private pure module function to_string_2_i_int8(value, format) result(string)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: value
    character(len=*), intent(in) :: format

    Return Value character(len=:), allocatable

  • private pure module function to_string_2_l_lk(value, format) result(string)

    Arguments

    Type IntentOptional Attributes Name
    logical(kind=lk), intent(in) :: value
    character(len=*), intent(in) :: format

    Return Value character(len=:), allocatable

  • private pure module function to_string_c_dp(value, format) result(string)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: value
    character(len=*), intent(in), optional :: format

    Return Value character(len=:), allocatable

  • private pure module function to_string_c_sp(value, format) result(string)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: value
    character(len=*), intent(in), optional :: format

    Return Value character(len=:), allocatable

  • private pure module function to_string_r_dp(value, format) result(string)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: value
    character(len=*), intent(in), optional :: format

    Return Value character(len=:), allocatable

  • private pure module function to_string_r_sp(value, format) result(string)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: value
    character(len=*), intent(in), optional :: format

    Return Value character(len=:), allocatable

public interface zfill

Left pad the input string with zeros. Specifications

  • private pure function zfill_string(string, output_length) result(res)

    Left pad the input string with zeros

    Returns a new string

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(in) :: string
    integer, intent(in) :: output_length

    Return Value type(string_type)

  • private pure function zfill_char(string, output_length) result(res)

    Left pad the input string with zeros

    Returns a new string

    Arguments

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

    Return Value character(kind=output_length), len=max)