stdlib_string_type
moduleThe stdlib_string_type
provides a derived type holding an arbitrary sequence
of characters compatible with most Fortran intrinsic character procedures as
well as operators for working with character variables and constants.
string_type
derived typeThe string_type
is defined as a non-extendible derived type representing a
sequence of characters. The internal representation of the character sequence
is implementation dependent and not visible for the user of the module.
Experimental
Procedures returning string_type
instances can usually be used in elemental
context, while procedures returning scalar character values can only be
used in a pure way.
Experimental
The module defines a constructor to create an empty string type.
Creates a string instance representing an empty string.
res =
string_type ()
Elemental function.
None.
The result is an instance of string_type
with zero length.
program example_constructor_empty
use stdlib_string_type
implicit none
type(string_type) :: string
string = string_type()
! len(string) == 0
end program example_constructor_empty
Experimental
The module defines a constructor to create a string type from a character scalar.
Creates a string instance representing the input character scalar value. The constructor shall create an empty string if an unallocated deferred-length character variable is passed.
res =
string_type (string)
Elemental function.
string
: shall be a scalar character value. It is an intent(in)
argument.
The result is an instance of string_type
.
program example_constructor_scalar
use stdlib_string_type
implicit none
type(string_type) :: string
string = string_type("Sequence")
! len(string) == 8
string = string_type(" S p a c e d ")
! len(string) == 13
end program example_constructor_scalar
Experimental
The module defines a constructor to create a string type from an integer scalar.
res =
string_type (string)
Elemental function.
val
: shall be a scalar integer value. It is an intent(in)
argument.
The result is an instance of string_type
.
program example_constructor_integer
use stdlib_string_type
implicit none
type(string_type) :: string
string = string_type(42)
! len(string) == 2
string = string_type(-289)
! len(string) == 4
end program example_constructor_integer
Experimental
The module defines a constructor to create a string type from a logical scalar.
res =
string_type (string)
Elemental function.
val
: shall be a scalar logical value. It is an intent(in)
argument.
The result is an instance of string_type
.
program example_constructor_logical
use stdlib_string_type
implicit none
type(string_type) :: string
string = string_type(.true.)
! len(string) == 1
string = string_type(.false.)
! len(string) == 1
end program example_constructor_logical
Experimental
The module defines an assignment operations, =
, to create a string type
from a character scalar.
Creates a string instance representing the right-hand-side character scalar value.
lhs = rhs
Elemental subroutine, assignment(=)
.
program example_constructor_character
use stdlib_string_type
implicit none
type(string_type) :: string
! len(string) == 0
string = "Sequence"
! len(string) == 8
end program example_constructor_character
Experimental
Returns the length of the string.
res =
len (string)
Elemental function.
string
: Instance of a string_type
. This argument is intent(in)
.
The result is a default integer scalar value.
program example_len
use stdlib_string_type
implicit none
type(string_type) :: string
integer :: length
string = "Some longer sentence for this example."
length = len(string)
! length == 38
string = "Whitespace "
length = len(string)
! length == 38
end program example_len
Experimental
Returns the length of the character sequence without trailing spaces represented by the string.
res =
len_trim (string)
Elemental function.
string
: Instance of a string_type
. This argument is intent(in)
.
The result is a default integer scalar value.
program example_len_trim
use stdlib_string_type
implicit none
type(string_type) :: string
integer :: length
string = "Some longer sentence for this example."
length = len_trim(string)
! length == 38
string = "Whitespace "
length = len_trim(string)
! length == 10
end program example_len_trim
Experimental
Returns the character sequence hold by the string without trailing spaces
represented by a string_type
.
res =
trim (string)
Elemental function.
string
: Instance of a string_type
. This argument is intent(in)
.The result is a scalar string_type
value.
program example_trim
use stdlib_string_type
implicit none
type(string_type) :: string
string = "Whitespace "
string = trim(string)
! len(string) == 10
end program example_trim
Experimental
Left-adjust the character sequence represented by the string. The length of the character sequence remains unchanged.
res =
adjustl (string)
Elemental function.
string
: Instance of a string_type
. This argument is intent(in)
.The result is a scalar string_type
value.
program example_adjustl
use stdlib_string_type
implicit none
type(string_type) :: string
string = " Whitespace"
string = adjustl(string)
! char(string) == "Whitespace "
end program example_adjustl
Experimental
Right-adjust the character sequence represented by the string. The length of the character sequence remains unchanged.
res =
adjustr (string)
Elemental function.
string
: Instance of a string_type
. This argument is intent(in)
.The result is a scalar string_type
value.
program example_adjustr
use stdlib_string_type
implicit none
type(string_type) :: string
string = "Whitespace "
string = adjustr(string)
! char(string) == " Whitespace"
end program example_adjustr
Experimental
Repeats the character sequence hold by the string by the number of specified copies.
res =
repeat (string, ncopies)
Elemental function.
string
: Instance of a string_type
. This argument is intent(in)
.ncopies
: Integer of default type. This argument is intent(in)
.The result is a scalar string_type
value.
program example_repeat
use stdlib_string_type
implicit none
type(string_type) :: string
string = "What? "
string = repeat(string, 3)
! string == "What? What? What? "
end program example_repeat
Experimental
Return the character sequence represented by the string.
res =
char (string)
Pure function.
string
: Instance of a string_type
. This argument is intent(in)
.The result is a scalar character value.
program example_char
use stdlib_string_type
implicit none
type(string_type) :: string
character(len=:), allocatable :: dlc
string = "Character sequence"
dlc = char(string)
! dlc == "Character sequence"
end program example_char
Experimental
Return the character at a certain position in the string.
res =
char (string, pos)
Elemental function.
string
: Instance of a string_type
. This argument is intent(in)
.pos
: Integer of default type. This argument is intent(in)
.The result is a scalar character value.
program example_char_position
use stdlib_string_type
implicit none
type(string_type) :: string
character(len=:), allocatable :: dlc
character(len=1), allocatable :: chars(:)
string = "Character sequence"
dlc = char(string, 3)
! dlc == "a"
chars = char(string, [3, 5, 8, 12, 14, 15, 18])
! chars == ["a", "a", "e", "e", "u", "e", "e"]
end program example_char_position
Experimental
Return a substring from the character sequence of the string.
res =
char (string, start, last)
Pure function.
string
: Instance of a string_type
. This argument is intent(in)
.start
: Integer of default type. This argument is intent(in)
.last
: Integer of default type. This argument is intent(in)
.The result is a scalar character value.
program example_char_range
use stdlib_string_type
implicit none
type(string_type) :: string
character(len=:), allocatable :: dlc
string = "Fortran"
dlc = char(string, 1, 4)
! dlc == "Fort"
end program example_char_range
Experimental
Character-to-integer conversion function.
Returns the code for the character in the first character position of the character sequence in the system's native character set.
res =
ichar (string)
Elemental function.
string
: Instance of a string_type
. This argument is intent(in)
.The result is a default integer scalar value.
program example_ichar
use stdlib_string_type
implicit none
type(string_type) :: string
integer :: code
string = "Fortran"
code = ichar(string)
end program example_ichar
Experimental
Code in ASCII collating sequence.
Returns the code for the ASCII character in the first character position of the character sequences represent by the string.
res =
iachar (string)
Elemental function.
string
: Instance of a string_type
. This argument is intent(in)
.The result is a default integer scalar value.
program example_iachar
use stdlib_string_type
implicit none
type(string_type) :: string
integer :: code
string = "Fortran"
code = iachar(string)
end program example_iachar
Experimental
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.
res =
index (string, substring[, back])
Elemental function.
string
: Either scalar character value or string type. This argument is intent(in)
.substring
: Either scalar character value or string type. This argument is intent(in)
.back
: Either absent or a scalar logical value. This argument is intent(in)
.The result is a default integer scalar value.
program example_index
use stdlib_string_type
implicit none
type(string_type) :: string
integer :: pos
string = "Search this string for this expression"
pos = index(string, "this")
! pos == 8
pos = index(string, "this", back=.true.)
! pos == 24
pos = index(string, "This")
! pos == 0
end program example_index
Experimental
Scans a string for the presence 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.
res =
scan (string, set[, back])
Elemental function.
string
: Either scalar character value or string type. This argument is intent(in)
.set
: Either scalar character value or string type. This argument is intent(in)
.back
: Either absent or a scalar logical value. This argument is intent(in)
.The result is a default integer scalar value.
program example_scan
use stdlib_string_type
implicit none
type(string_type) :: string
integer :: pos
string = "fortran"
pos = scan(string, "ao")
! pos == 2
pos = scan(string, "ao", .true.)
! pos == 6
pos = scan(string, "c++")
! pos == 0
end program example_scan
Experimental
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.
res =
verify (string, set[, back])
Elemental function.
string
: Either scalar character value or string type. This argument is intent(in)
.set
: Either scalar character value or string type. This argument is intent(in)
.back
: Either absent or a scalar logical value. This argument is intent(in)
.The result is a default integer scalar value.
program example_verify
use stdlib_string_type
implicit none
type(string_type) :: string
integer :: pos
string = "fortran"
pos = verify(string, "ao")
! pos == 1
pos = verify(string, "fo")
! pos == 3
pos = verify(string, "c++")
! pos == 1
pos = verify(string, "c++", back=.true.)
! pos == 7
pos = verify(string, string)
! pos == 0
end program example_verify
Experimental
Lexically compare the order of two character sequences being greater than.
The left-hand side, the right-hand side or both character sequences can
be represented by a string type.
This defines three procedures overloading the intrinsic lgt
procedure.
res =
lgt (lhs, rhs)
Elemental function.
lhs
: Either scalar character value or string type. This argument is intent(in)
.rhs
: Either scalar character value or string type. This argument is intent(in)
.The result is a default logical scalar value.
program example_lgt
use stdlib_string_type
implicit none
type(string_type) :: string
logical :: res
string = "bcd"
res = lgt(string, "abc")
! res .eqv. .true.
res = lgt(string, "bcd")
! res .eqv. .false.
res = lgt(string, "cde")
! res .eqv. .false.
end program example_lgt
Experimental
Lexically compare the order of two character sequences being less than.
The left-hand side, the right-hand side or both character sequences can
be represented by a string type.
This defines three procedures overloading the intrinsic llt
procedure.
res =
llt (lhs, rhs)
Elemental function.
lhs
: Either scalar character value or string type. This argument is intent(in)
.rhs
: Either scalar character value or string type. This argument is intent(in)
.The result is a default logical scalar value.
program example_llt
use stdlib_string_type
implicit none
type(string_type) :: string
logical :: res
string = "bcd"
res = llt(string, "abc")
! res .eqv. .false.
res = llt(string, "bcd")
! res .eqv. .false.
res = llt(string, "cde")
! res .eqv. .true.
end program example_llt
Experimental
Lexically compare the order of two character sequences being greater than or equal.
The left-hand side, the right-hand side or both character sequences can
be represented by a string type.
This defines three procedures overloading the intrinsic lge
procedure.
res =
lge (lhs, rhs)
Elemental function.
lhs
: Either scalar character value or string type. This argument is intent(in)
.rhs
: Either scalar character value or string type. This argument is intent(in)
.The result is a default logical scalar value.
program example_lge
use stdlib_string_type
implicit none
type(string_type) :: string
logical :: res
string = "bcd"
res = lge(string, "abc")
! res .eqv. .true.
res = lge(string, "bcd")
! res .eqv. .true.
res = lge(string, "cde")
! res .eqv. .false.
end program example_lge
Experimental
Lexically compare the order of two character sequences being less than or equal.
The left-hand side, the right-hand side or both character sequences can
be represented by a string type.
This defines three procedures overloading the intrinsic lle
procedure.
res =
lle (lhs, rhs)
Elemental function.
lhs
: Either scalar character value or string type. This argument is intent(in)
.rhs
: Either scalar character value or string type. This argument is intent(in)
.The result is a default logical scalar value.
program example_lle
use stdlib_string_type
implicit none
type(string_type) :: string
logical :: res
string = "bcd"
res = lle(string, "abc")
! res .eqv. .false.
res = lle(string, "bcd")
! res .eqv. .true.
res = lle(string, "cde")
! res .eqv. .true.
end program example_lle
Experimental
Returns a new string_type instance which holds the lowercase version of the character sequence hold by the input string.
lowercase_string =
to_lower (string)
Elemental function.
string
: Instance of string_type
. This argument is intent(in)
.
The result is a scalar string_type
value.
program example_to_lower
use stdlib_string_type
implicit none
type(string_type) :: string, lowercase_string
string = "Lowercase This String"
! string <-- "Lowercase This String"
lowercase_string = to_lower(string)
! string <-- "Lowercase This String"
! lowercase_string <-- "lowercase this string"
end program example_to_lower
Experimental
Returns a new string_type instance which holds the uppercase version of the character sequence hold by the input string.
uppercase_string =
to_upper (string)
Elemental function.
string
: Instance of string_type
. This argument is intent(in)
.
The result is a scalar string_type
value.
program example_to_upper
use stdlib_string_type
implicit none
type(string_type) :: string, uppercase_string
string = "Uppercase This String"
! string <-- "Uppercase This String"
uppercase_string = to_upper(string)
! string <-- "Uppercase This String"
! uppercase_string <-- "UPPERCASE THIS STRING"
end program example_to_upper
Experimental
Returns a new string_type instance which holds the titlecase version of the character sequence hold by the input string. Title case: First character of every word in the sentence is converted to uppercase and the rest of the characters are converted to lowercase. A word is a contiguous sequence of character(s) which consists of alphabetical character(s) and numeral(s) only and doesn't exclude any alphabetical character or numeral present next to either of its 2 ends.
titlecase_string =
to_title (string)
Elemental function.
string
: Instance of string_type
. This argument is intent(in)
.
The result is a scalar string_type
value.
program example_to_title
use stdlib_string_type
implicit none
type(string_type) :: string, titlecase_string
string = "titlecase this string."
! string <-- "titlecase this string."
titlecase_string = to_title(string)
! string <-- "titlecase this string."
! titlecase_string <-- "Titlecase This String."
end program example_to_title
Experimental
Returns a new string_type instance which holds the sentencecase version of the character sequence hold by the input string. Sentencecase version: The first alphabetical character of the input character sequence is transformed to uppercase unless it follows a numeral and the rest of the characters in the sequence are transformed to lowercase.
sentencecase_string =
to_sentence (string)
Elemental function.
string
: Instance of string_type
. This argument is intent(in)
.
The result is a scalar string_type
value.
program example_to_sentence
use stdlib_string_type
implicit none
type(string_type) :: string, sentencecase_string
string = "sentencecase this string."
! string <-- "sentencecase this string."
sentencecase_string = to_sentence(string)
! string <-- "sentencecase this string."
! sentencecase_string <-- "Sentencecase this string."
end program example_to_sentence
Experimental
Returns a new string_type instance which holds the reversed version of the character sequence hold by the input string.
reverse_string =
reverse (string)
Elemental function.
string
: Instance of string_type
. This argument is intent(in)
.
The result is a scalar string_type
value.
program example_reverse
use stdlib_string_type
implicit none
type(string_type) :: string, reverse_string
string = "Reverse This String"
! string <-- "Reverse This String"
reverse_string = reverse(string)
! string <-- "Reverse This String"
! reverse_string <-- "gnirtS sihT esreveR"
end program example_reverse
Experimental
Compare the order of two character sequences being greater.
The left-hand side, the right-hand side or both character sequences can
be represented by a string type.
This defines three procedures overloading the intrinsic operator(>)
and operator(.gt.)
.
res = lhs > rhs
res = lhs .gt. rhs
Elemental function, operator(>)
and operator(.gt.)
.
lhs
: Either scalar character value or string type. This argument is intent(in)
.rhs
: Either scalar character value or string type. This argument is intent(in)
.The result is a default logical scalar value.
program example_gt
use stdlib_string_type
implicit none
type(string_type) :: string
logical :: res
string = "bcd"
res = string > "abc"
! res .eqv. .true.
res = string > "bcd"
! res .eqv. .false.
res = string > "cde"
! res .eqv. .false.
end program example_gt
Experimental
Compare the order of two character sequences being less.
The left-hand side, the right-hand side or both character sequences can
be represented by a string type.
This defines three procedures overloading the intrinsic operator(<)
and operator(.lt.)
.
res = lhs < rhs
res = lhs .lt. rhs
Elemental function, operator(<)
and operator(.lt.)
.
lhs
: Either scalar character value or string type. This argument is intent(in)
.rhs
: Either scalar character value or string type. This argument is intent(in)
.The result is a default logical scalar value.
program example_lt
use stdlib_string_type
implicit none
type(string_type) :: string
logical :: res
string = "bcd"
res = string < "abc"
! res .eqv. .false.
res = string < "bcd"
! res .eqv. .false.
res = string < "cde"
! res .eqv. .true.
end program example_lt
Experimental
Compare the order of two character sequences being greater or equal.
The left-hand side, the right-hand side or both character sequences can
be represented by a string type.
This defines three procedures overloading the intrinsic operator(>=)
and operator(.ge.)
.
res = lhs >= rhs
res = lhs .ge. rhs
Elemental function, operator(>=)
and operator(.ge.)
.
lhs
: Either scalar character value or string type. This argument is intent(in)
.rhs
: Either scalar character value or string type. This argument is intent(in)
.The result is a default logical scalar value.
program example_ge
use stdlib_string_type
implicit none
type(string_type) :: string
logical :: res
string = "bcd"
res = string >= "abc"
! res .eqv. .true.
res = string >= "bcd"
! res .eqv. .true.
res = string >= "cde"
! res .eqv. .false.
end program example_ge
Experimental
Compare the order of two character sequences being less or equal.
The left-hand side, the right-hand side or both character sequences can
be represented by a string type.
This defines three procedures overloading the intrinsic operator(<=)
and operator(.le.)
.
res = lhs <= rhs
res = lhs .le. rhs
Elemental function, operator(<=)
and operator(.le.)
.
lhs
: Either scalar character value or string type. This argument is intent(in)
.rhs
: Either scalar character value or string type. This argument is intent(in)
.The result is a default logical scalar value.
program example_le
use stdlib_string_type
implicit none
type(string_type) :: string
logical :: res
string = "bcd"
res = string <= "abc"
! res .eqv. .false.
res = string <= "bcd"
! res .eqv. .true.
res = string <= "cde"
! res .eqv. .true.
end program example_le
Experimental
Compare two character sequences for equality.
The left-hand side, the right-hand side or both character sequences can
be represented by a string type.
This defines three procedures overloading the intrinsic operator(==)
and operator(.eq.)
.
res = lhs == rhs
res = lhs .eq. rhs
Elemental function, operator(==)
and operator(.eq.)
.
lhs
: Either scalar character value or string type. This argument is intent(in)
.rhs
: Either scalar character value or string type. This argument is intent(in)
.The result is a default logical scalar value.
program example_eq
use stdlib_string_type
implicit none
type(string_type) :: string
logical :: res
string = "bcd"
res = string == "abc"
! res .eqv. .false.
res = string == "bcd"
! res .eqv. .true.
res = string == "cde"
! res .eqv. .false.
end program example_eq
Experimental
Compare two character sequences for inequality.
The left-hand side, the right-hand side or both character sequences can
be represented by a string type.
This defines three procedures overloading the intrinsic operator(/=)
and operator(.ne.)
.
res = lhs /= rhs
res = lhs .ne. rhs
Elemental function, operator(/=)
and operator(.ne.)
.
lhs
: Either scalar character value or string type. This argument is intent(in)
.rhs
: Either scalar character value or string type. This argument is intent(in)
.The result is a default logical scalar value.
program example_ne
use stdlib_string_type
implicit none
type(string_type) :: string
logical :: res
string = "bcd"
res = string /= "abc"
! res .eqv. .true.
res = string /= "bcd"
! res .eqv. .false.
res = string /= "cde"
! res .eqv. .true.
end program example_ne
Experimental
Concatenate two character sequences.
The left-hand side, the right-hand side or both character sequences can
be represented by a string type.
This defines three procedures overloading the intrinsic operator(//)
.
res = lhs // rhs
Elemental function, operator(//)
.
lhs
: Either scalar character value or string type. This argument is intent(in)
.rhs
: Either scalar character value or string type. This argument is intent(in)
.The result is an instance of string_type
.
program example_cont
use stdlib_string_type
implicit none
type(string_type) :: string
string = "Hello, "
string = string//"World!"
! len(string) == 13
end program example_cont
Experimental
Write the character sequence hold by the string to a connected unformatted unit. The character sequences is represented by an 64 bit signed integer record, holding the length of the following character record.
write(unit, iostat=iostat, iomsg=iomsg) string
Unformatted user defined derived type output.
string
: Instance of the string type to read. This argument is intent(inout)
.unit
: Formatted unit for output. This argument is intent(in)
.iostat
: Status identifier to indicate success of output operation.
This argument is intent(out)
.iomsg
: Buffer to return error message in case of failing output operation.
This argument is intent(inout)
.program example_uwrite
use stdlib_string_type
implicit none
type(string_type) :: string
integer :: io
string = "Important saved value"
open (newunit=io, form="unformatted", status="scratch")
write (io) string
rewind (io)
read (io) string
close (io)
end program example_uwrite
Experimental
Write the character sequence hold by the string to a connected formatted unit.
The current implementation is limited to list directed output and dt
formatted
output. Requesting namelist output will raise an error.
write(unit, fmt, iostat=iostat, iomsg=iomsg) string
Formatted user defined derived type output.
string
: Instance of the string type to read. This argument is intent(inout)
.unit
: Formatted unit for output. This argument is intent(in)
.iotype
: Type of formatted data transfer, has the value "LISTDIRECTED"
for fmt=*
,
"NAMELIST"
for namelist output or starts with "DT"
for derived type output.
This argument is intent(in)
.v_list
: Rank one array of default integer type containing the edit descriptors for
derived type output.
This argument is intent(in)
.iostat
: Status identifier to indicate success of output operation.
This argument is intent(out)
.iomsg
: Buffer to return error message in case of failing output operation.
This argument is intent(inout)
.program example_fwrite
use stdlib_string_type
implicit none
type(string_type) :: string
integer :: io
string = "Important saved value"
open (newunit=io, form="formatted", status="scratch")
write (io, *) string
write (io, *)
rewind (io)
read (io, *) string
close (io)
end program example_fwrite
Experimental
Read a character sequence from a connected unformatted unit into the string. The character sequences is represented by an 64 bit signed integer record, holding the length of the following character record.
On failure the state the read variable is undefined and implementation dependent.
read(unit, iostat=iostat, iomsg=iomsg) string
Unformatted derived type input.
string
: Instance of the string type to read. This argument is intent(inout)
.unit
: Formatted unit for input. This argument is intent(in)
.iostat
: Status identifier to indicate success of input operation.
This argument is intent(out)
.iomsg
: Buffer to return error message in case of failing input operation.
This argument is intent(inout)
.program example_uread
use stdlib_string_type
implicit none
type(string_type) :: string
integer :: io
string = "Important saved value"
open (newunit=io, form="unformatted", status="scratch")
write (io) string
rewind (io)
read (io) string
close (io)
end program example_uread
Experimental
Read a character sequence from a connected formatted unit into the string. List-directed input will retrieve the complete record into the string.
On failure the state the read variable is undefined and implementation dependent.
The current implementation is limited to list directed input.
Requesting dt
formatted input or namelist output will raise an error.
read(unit, fmt, iostat=iostat, iomsg=iomsg) string
Formatted derived type input.
string
: Instance of the string type to read. This argument is intent(inout)
.unit
: Formatted unit for input. This argument is intent(in)
.iotype
: Type of formatted data transfer, has the value "LISTDIRECTED"
for fmt=*
,
"NAMELIST"
for namelist input or starts with "DT"
for derived type input.
This argument is intent(in)
.v_list
: Rank one array of default integer type containing the edit descriptors for
derived type input.
This argument is intent(in)
.iostat
: Status identifier to indicate success of input operation.
This argument is intent(out)
.iomsg
: Buffer to return error message in case of failing input operation.
This argument is intent(inout)
.program example_fread
use stdlib_string_type
implicit none
type(string_type) :: string
integer :: io
string = "Important saved value"
open (newunit=io, form="formatted", status="scratch")
write (io, *) string
write (io, *)
rewind (io)
read (io, *) string
close (io)
end program example_fread
Experimental
Moves the allocation from from
to to
, consequently deallocating from
in this process.
If from
is not allocated before execution, to
gets deallocated by the process.
An unallocated string_type
instance is equivalent to an empty string.
If from
and to
are the same variable, then from
remains unchanged.
call
move (from, to)
Pure subroutine (Elemental subroutine, only when both from
and to
are type(string_type)
)
from
: Character scalar or string_type.
This argument is intent(inout)
.to
: Character scalar or string_type.
This argument is intent(inout)
when both from
and to
are type(string_type)
,
otherwise intent(out)
.program example_move
use stdlib_string_type, only: string_type, assignment(=), move
implicit none
type(string_type) :: from_string
character(len=:), allocatable :: from_char, to_char
from_string = "move this string"
from_char = "move this char"
! from_string <-- "move this string"
! from_char <-- "move this char"
! to_char <-- (unallocated)
call move(from_string, to_char)
! from_string <-- ""
! to_char <-- "move this string"
call move(from_char, to_char)
! from_char <-- (unallocated)
! to_string <-- "move this char"
end program example_move