stdlib_strings
moduleThe stdlib_strings
module provides basic string handling and manipulation routines.
strip
Remove leading and trailing whitespace characters.
string =
strip (string)
Experimental
Pure function.
string
: Character scalar or string_type.
This argument is intent(in).The result is of the same type as string
.
program example_strip
use stdlib_ascii, only: TAB, VT, LF, CR, FF
use stdlib_strings, only: strip
implicit none
print'(a)', strip(" hello ") ! "hello"
print'(a)', strip(TAB//"goodbye"//CR//LF) ! "goodbye"
print'(a)', strip(" "//TAB//LF//VT//FF//CR) ! ""
print'(a)', strip(" ! ")//"!" ! "!!"
print'(a)', strip("Hello") ! "Hello"
end program example_strip
chomp
Remove trailing characters in set or substring from string. If no character set or substring is provided trailing whitespace is removed.
string =
chomp (string[, set|substring])
Experimental
Pure function.
string
: Character scalar or string_type.
This argument is intent(in).set
: Array of length one character. This argument is intent(in).substring
: Character scalar or string_type.
This argument is intent(in).The result is of the same type as string
.
program example_chomp
use stdlib_ascii, only: TAB, VT, LF, CR, FF
use stdlib_strings, only: chomp
implicit none
print'(a)', chomp(" hello ") ! " hello"
print'(a)', chomp(TAB//"goodbye"//CR//LF) ! "\tgoodbye"
print'(a)', chomp(" "//TAB//LF//VT//FF//CR) ! ""
print'(a)', chomp(" ! ")//"!" ! " !!"
print'(a)', chomp("Hello") ! "Hello"
print'(a)', chomp("hello", ["l", "o"]) ! "he"
print'(a)', chomp("hello", set=["l", "o"]) ! "he"
print'(a)', chomp("hello", "lo") ! "hel"
print'(a)', chomp("hello", substring="lo") ! "hel"
end program example_chomp
starts_with
Check if a string starts with a given substring.
string =
starts_with (string, substring)
Experimental
Pure function.
string
: Character scalar or string_type.
This argument is intent(in).substring
: Character scalar or string_type.
This argument is intent(in).The result is of scalar logical type.
program example_starts_with
use stdlib_strings, only: starts_with
implicit none
print'(l1)', starts_with("pattern", "pat") ! T
print'(l1)', starts_with("pattern", "ern") ! F
end program example_starts_with
ends_with
Check if a string ends with a given substring.
string =
ends_with (string, substring)
Experimental
Pure function.
string
: Character scalar or string_type.
This argument is intent(in).substring
: Character scalar or string_type.
This argument is intent(in).The result is of scalar logical type.
program example_ends_with
use stdlib_strings, only: ends_with
implicit none
print'(l1)', ends_with("pattern", "ern") ! T
print'(l1)', ends_with("pattern", "pat") ! F
end program example_ends_with
slice
Extracts the characters from the defined region of the input string by taking strides.
Argument first
and last
defines this region for extraction by function slice
.
Argument stride
defines the magnitude and direction (+/-) of stride to be taken while extraction.
stride
when given invalid value 0, is converted to +1.
Deduction Process:
Function first automatically deduces the optional arguments that are not provided by the user.
Deduced first
and last
argument take +infinity or -infinity value and deduced stride
argument
takes value +1 or -1 depending upon the actual argument(s) provided by the user.
Extraction Process:
Extraction starts only if last
is crossable from first
with stride of stride
.
Extraction starts from the first valid index in the defined region to take stride of stride
and ends when the last valid index in the defined region is crossed.
If no valid index exists in the defined region, empty string is returned.
string =
slice (string [, first, last, stride])
Experimental
Pure function.
string
: Character scalar or string_type.
This argument is intent(in).first
: integer.
This argument is intent(in) and optional.last
: integer.
This argument is intent(in) and optional.stride
: integer.
This argument is intent(in) and optional.The result is of the same type as string
.
program example_slice
use stdlib_string_type
use stdlib_strings, only: slice
implicit none
type(string_type) :: string
character(len=10) :: chars
string = "abcdefghij"
! string <-- "abcdefghij"
chars = "abcdefghij"
! chars <-- "abcdefghij"
print'(a)', slice("abcdefghij", 2, 6, 2) ! "bdf"
print'(a)', slice(chars, 2, 6, 2) ! "bdf"
string = slice(string, 2, 6, 2)
! string <-- "bdf"
end program example_slice
find
Returns the starting index of the occurrence
th occurrence of the substring pattern
in the input string string
.
Default value of occurrence
is set to 1
.
If consider_overlapping
is not provided or is set to .true.
the function counts two overlapping occurrences of substring pattern
as two different occurrences.
If occurrence
th occurrence is not found, function returns 0
.
string =
find (string, pattern [, occurrence, consider_overlapping])
Experimental
Elemental function
string
: Character scalar or string_type.
This argument is intent(in).pattern
: Character scalar or string_type.
This argument is intent(in).occurrence
: integer.
This argument is intent(in) and optional.consider_overlapping
: logical.
This argument is intent(in) and optional.The result is a scalar of integer type or an integer array of rank equal to the highest rank among all dummy arguments.
program example_find
use stdlib_string_type, only: string_type, assignment(=)
use stdlib_strings, only: find
implicit none
type(string_type) :: string
string = "needle in the character-stack"
print *, find(string, "needle") ! 1
print *, find(string, ["a", "c"], [3, 2]) ! [27, 20]
print *, find("qwqwqwq", "qwq", 3, [.false., .true.]) ! [0, 5]
end program example_find
replace_all
Replaces all occurrences of substring pattern
in the input string
with the replacement replacement
.
Occurrences overlapping on a base occurrence will not be replaced.
string =
replace_all (string, pattern, replacement)
Experimental
Pure function
string
: Character scalar or string_type.
This argument is intent(in).pattern
: Character scalar or string_type.
This argument is intent(in).replacement
: Character scalar or string_type.
This argument is intent(in).The result is of the same type as string
.
program example_replace_all
use stdlib_string_type, only: string_type, assignment(=), write (formatted)
use stdlib_strings, only: replace_all
implicit none
type(string_type) :: string
string = "hurdles here, hurdles there, hurdles everywhere"
! string <-- "hurdles here, hurdles there, hurdles everywhere"
print'(dt)', replace_all(string, "hurdles", "learn from")
! "learn from here, learn from there, learn from everywhere"
string = replace_all(string, "hurdles", "technology")
! string <-- "technology here, technology there, technology everywhere"
end program example_replace_all
padl
Returns a string of length output_length
left padded with pad_with
character if it is provided, otherwise with " "
(1 whitespace).
If output_length
is less than or equal to the length of string
, padding is not performed.
string =
padl (string, output_length [, pad_with])
Experimental
Pure function
string
: Character scalar or string_type.
This argument is intent(in).output_length
: integer.
This argument is intent(in).pad_with
: Character scalar of length 1.
This argument is intent(in) and optional.The result is of the same type as string
.
program example_padl
use stdlib_string_type, only: string_type, assignment(=), write (formatted)
use stdlib_strings, only: padl
implicit none
type(string_type) :: string
string = "left pad this string"
! string <-- "left pad this string"
print '(dt)', padl(string, 25, "$") ! "$$$$$left pad this string"
string = padl(string, 25)
! string <-- " left pad this string"
end program example_padl
padr
Returns a string of length output_length
right padded with pad_with
character if it is provided, otherwise with " "
(1 whitespace).
If output_length
is less than or equal to the length of string
, padding is not performed.
string =
padr (string, output_length [, pad_with])
Experimental
Pure function
string
: Character scalar or string_type.
This argument is intent(in).output_length
: integer.
This argument is intent(in).pad_with
: Character scalar of length 1.
This argument is intent(in) and optional.The result is of the same type as string
.
program example_padr
use stdlib_string_type, only: string_type, assignment(=), write (formatted)
use stdlib_strings, only: padr
implicit none
type(string_type) :: string
string = "right pad this string"
! string <-- "right pad this string"
print '(dt)', padr(string, 25, "$") ! "right pad this string$$$$"
string = padr(string, 25)
! string <-- "right pad this string "
end program example_padr
count
Returns the number of times the substring pattern
has occurred in the input string string
.
If consider_overlapping
is not provided or is set to .true.
the function counts two overlapping occurrences of substring pattern
as two different occurrences.
string =
count (string, pattern [, consider_overlapping])
Experimental
Elemental function
string
: Character scalar or string_type.
This argument is intent(in).pattern
: Character scalar or string_type.
This argument is intent(in).consider_overlapping
: logical.
This argument is intent(in) and optional.The result is a scalar of integer type or an integer array of rank equal to the highest rank among all dummy arguments.
program example_count
use stdlib_string_type, only: string_type, assignment(=)
use stdlib_strings, only: count
implicit none
type(string_type) :: string
string = "How much wood would a woodchuck chuck if a woodchuck could chuck wood?"
print *, count(string, "wood") ! 4
print *, count(string, ["would", "chuck", "could"]) ! [1, 4, 1]
print *, count("a long queueueueue", "ueu", [.false., .true.]) ! [2, 4]
end program example_count
zfill
Returns a string of length output_length
left-padded with zeros.
If output_length
is less than or equal to the length of string
, padding is not performed.
string =
zfill (string, output_length)
Experimental
Pure function
string
: Character scalar or string_type.
This argument is intent(in).output_length
: integer.
This argument is intent(in).The result is of the same type as string
.
program example_zfill
use stdlib_string_type, only: string_type, assignment(=), write (formatted)
use stdlib_strings, only: zfill
implicit none
type(string_type) :: string
string = "left pad this string with zeros"
! string <-- "left pad this string with zeros"
print '(dt)', zfill(string, 36) ! "00000left pad this string with zeros"
string = zfill(string, 36)
! string <-- "00000left pad this string with zeros"
end program example_zfill
to_string
Format or transfer a integer/real/complex/logical
scalar as a string.
Input a wrong format
that cause the internal-IO to fail, the result value is a string of [*]
.
string =
to_string (value [, format])
Experimental
Pure function.
value
: Shall be an integer/real/complex/logical
scalar.
This is an intent(in)
argument.format
: Shall be a character(len=*)
scalar like '(F6.2)'
or just 'F6.2'
.
This is an intent(in)
and optional
argument.value
into a string, for example '(F6.2)'
or '(f6.2)'
.
to_string
will automatically enclose format
in a set of parentheses, so passing F6.2
or f6.2
as format
is possible as well.The result is an allocatable
length character
scalar with up to 128
cached character
length.
program example_to_string
use stdlib_strings, only: to_string
implicit none
!> Example for `complex` type
print *, to_string((1, 1)) !! "(1.00000000,1.00000000)"
print *, to_string((1, 1), '(F6.2)') !! "( 1.00, 1.00)"
print *, to_string((1000, 1), '(ES0.2)'), to_string((1000, 1), '(SP,F6.3)')
!! "(1.00E+3,1.00)""(******,+1.000)"
!! Too narrow formatter for real number
!! Normal demonstration(`******` from Fortran Standard)
!> Example for `integer` type
print *, to_string(-3) !! "-3"
print *, to_string(42, '(I4)') !! " 42"
print *, to_string(1, '(I0.4)'), to_string(2, '(B4)') !! "0001"" 10"
!> Example for `real` type
print *, to_string(1.) !! "1.00000000"
print *, to_string(1., '(F6.2)') !! " 1.00"
print *, to_string(1., 'F6.2') !! " 1.00"
print *, to_string(1., '(SP,ES9.2)'), to_string(1, '(F7.3)') !! "+1.00E+00""[*]"
!! 1 wrong demonstration (`[*]` from `to_string`)
!> Example for `logical` type
print *, to_string(.true.) !! "T"
print *, to_string(.true., '(L2)') !! " T"
print *, to_string(.true., 'L2') !! " T"
print *, to_string(.false., '(I5)') !! "[*]"
!! 1 wrong demonstrations(`[*]` from `to_string`)
end program example_to_string