string_type

The stdlib_string_type module

Introduction

The 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.

Derived types provided

The string_type derived type

The 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.

Status

Experimental

Procedures and methods provided

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.

Constructor for empty string

Status

Experimental

Description

The module defines a constructor to create an empty string type.

Creates a string instance representing an empty string.

Syntax

res = string_type ()

Class

Elemental function.

Argument

None.

Result value

The result is an instance of string_type with zero length.

Example

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

Constructor from character scalar

Status

Experimental

Description

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.

Syntax

res = string_type (string)

Class

Elemental function.

Argument

string: shall be a scalar character value. It is an intent(in) argument.

Result value

The result is an instance of string_type.

Example

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

Constructor from integer scalar

Status

Experimental

Description

The module defines a constructor to create a string type from an integer scalar.

Syntax

res = string_type (string)

Class

Elemental function.

Argument

val: shall be a scalar integer value. It is an intent(in) argument.

Result value

The result is an instance of string_type.

Example

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

Constructor from logical scalar

Status

Experimental

Description

The module defines a constructor to create a string type from a logical scalar.

Syntax

res = string_type (string)

Class

Elemental function.

Argument

val: shall be a scalar logical value. It is an intent(in) argument.

Result value

The result is an instance of string_type.

Example

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

Assignment of character scalar

Status

Experimental

Description

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.

Syntax

lhs = rhs

Class

Elemental subroutine, assignment(=).

Example

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

Len function

Status

Experimental

Description

Returns the length of the string.

Syntax

res = len (string)

Class

Elemental function.

Argument

string: Instance of a string_type. This argument is intent(in).

Result value

The result is a default integer scalar value.

Example

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

Len_trim function

Status

Experimental

Description

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

Syntax

res = len_trim (string)

Class

Elemental function.

Argument

string: Instance of a string_type. This argument is intent(in).

Result value

The result is a default integer scalar value.

Example

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

Trim function

Status

Experimental

Description

Returns the character sequence hold by the string without trailing spaces represented by a string_type.

Syntax

res = trim (string)

Class

Elemental function.

Argument

  • string: Instance of a string_type. This argument is intent(in).

Result value

The result is a scalar string_type value.

Example

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

Adjustl function

Status

Experimental

Description

Left-adjust the character sequence represented by the string. The length of the character sequence remains unchanged.

Syntax

res = adjustl (string)

Class

Elemental function.

Argument

  • string: Instance of a string_type. This argument is intent(in).

Result value

The result is a scalar string_type value.

Example

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

Adjustr function

Status

Experimental

Description

Right-adjust the character sequence represented by the string. The length of the character sequence remains unchanged.

Syntax

res = adjustr (string)

Class

Elemental function.

Argument

  • string: Instance of a string_type. This argument is intent(in).

Result value

The result is a scalar string_type value.

Example

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

Repeat function

Status

Experimental

Description

Repeats the character sequence hold by the string by the number of specified copies.

Syntax

res = repeat (string, ncopies)

Class

Elemental function.

Argument

  • string: Instance of a string_type. This argument is intent(in).
  • ncopies: Integer of default type. This argument is intent(in).

Result value

The result is a scalar string_type value.

Example

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

Char function

Status

Experimental

Description

Return the character sequence represented by the string.

Syntax

res = char (string)

Class

Pure function.

Argument

  • string: Instance of a string_type. This argument is intent(in).

Result value

The result is a scalar character value.

Example

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

Char function (position variant)

Status

Experimental

Description

Return the character at a certain position in the string.

Syntax

res = char (string, pos)

Class

Elemental function.

Argument

  • string: Instance of a string_type. This argument is intent(in).
  • pos: Integer of default type. This argument is intent(in).

Result value

The result is a scalar character value.

Example

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

Char function (range variant)

Status

Experimental

Description

Return a substring from the character sequence of the string.

Syntax

res = char (string, start, last)

Class

Pure function.

Argument

  • 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).

Result value

The result is a scalar character value.

Example

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

Ichar function

Status

Experimental

Description

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.

Syntax

res = ichar (string)

Class

Elemental function.

Argument

  • string: Instance of a string_type. This argument is intent(in).

Result value

The result is a default integer scalar value.

Example

program example_ichar
  use stdlib_string_type
  implicit none
  type(string_type) :: string
  integer :: code

  string = "Fortran"
  code = ichar(string)
end program example_ichar

Iachar function

Status

Experimental

Description

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.

Syntax

res = iachar (string)

Class

Elemental function.

Argument

  • string: Instance of a string_type. This argument is intent(in).

Result value

The result is a default integer scalar value.

Example

program example_iachar
  use stdlib_string_type
  implicit none
  type(string_type) :: string
  integer :: code

  string = "Fortran"
  code = iachar(string)
end program example_iachar

Index function

Status

Experimental

Description

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.

Syntax

res = index (string, substring[, back])

Class

Elemental function.

Argument

  • 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).

Result value

The result is a default integer scalar value.

Example

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

Scan function

Status

Experimental

Description

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.

Syntax

res = scan (string, set[, back])

Class

Elemental function.

Argument

  • 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).

Result value

The result is a default integer scalar value.

Example

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

Verify function

Status

Experimental

Description

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.

Syntax

res = verify (string, set[, back])

Class

Elemental function.

Argument

  • 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).

Result value

The result is a default integer scalar value.

Example

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

Lgt function (lexical greater than)

Status

Experimental

Description

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.

Syntax

res = lgt (lhs, rhs)

Class

Elemental function.

Argument

  • 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).

Result value

The result is a default logical scalar value.

Example

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

Llt function (lexical less than)

Status

Experimental

Description

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.

Syntax

res = llt (lhs, rhs)

Class

Elemental function.

Argument

  • 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).

Result value

The result is a default logical scalar value.

Example

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

Lge function (lexical greater than or equal)

Status

Experimental

Description

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.

Syntax

res = lge (lhs, rhs)

Class

Elemental function.

Argument

  • 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).

Result value

The result is a default logical scalar value.

Example

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

Lle function (lexical less than or equal)

Status

Experimental

Description

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.

Syntax

res = lle (lhs, rhs)

Class

Elemental function.

Argument

  • 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).

Result value

The result is a default logical scalar value.

Example

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

To_lower function

Status

Experimental

Description

Returns a new string_type instance which holds the lowercase version of the character sequence hold by the input string.

Syntax

lowercase_string = to_lower (string)

Class

Elemental function.

Argument

string: Instance of string_type. This argument is intent(in).

Result Value

The result is a scalar string_type value.

Example

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

To_upper function

Status

Experimental

Description

Returns a new string_type instance which holds the uppercase version of the character sequence hold by the input string.

Syntax

uppercase_string = to_upper (string)

Class

Elemental function.

Argument

string: Instance of string_type. This argument is intent(in).

Result Value

The result is a scalar string_type value.

Example

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

To_title function

Status

Experimental

Description

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.

Syntax

titlecase_string = to_title (string)

Class

Elemental function.

Argument

string: Instance of string_type. This argument is intent(in).

Result Value

The result is a scalar string_type value.

Example

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

To_sentence function

Status

Experimental

Description

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.

Syntax

sentencecase_string = to_sentence (string)

Class

Elemental function.

Argument

string: Instance of string_type. This argument is intent(in).

Result Value

The result is a scalar string_type value.

Example

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

Reverse function

Status

Experimental

Description

Returns a new string_type instance which holds the reversed version of the character sequence hold by the input string.

Syntax

reverse_string = reverse (string)

Class

Elemental function.

Argument

string: Instance of string_type. This argument is intent(in).

Result Value

The result is a scalar string_type value.

Example

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

Comparison operator greater

Status

Experimental

Description

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.).

Syntax

res = lhs > rhs

res = lhs .gt. rhs

Class

Elemental function, operator(>) and operator(.gt.).

Argument

  • 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).

Result value

The result is a default logical scalar value.

Example

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

Comparison operator less

Status

Experimental

Description

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.).

Syntax

res = lhs < rhs

res = lhs .lt. rhs

Class

Elemental function, operator(<) and operator(.lt.).

Argument

  • 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).

Result value

The result is a default logical scalar value.

Example

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

Comparison operator greater or equal

Status

Experimental

Description

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.).

Syntax

res = lhs >= rhs

res = lhs .ge. rhs

Class

Elemental function, operator(>=) and operator(.ge.).

Argument

  • 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).

Result value

The result is a default logical scalar value.

Example

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

Comparison operator less or equal

Status

Experimental

Description

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.).

Syntax

res = lhs <= rhs

res = lhs .le. rhs

Class

Elemental function, operator(<=) and operator(.le.).

Argument

  • 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).

Result value

The result is a default logical scalar value.

Example

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

Comparison operator equal

Status

Experimental

Description

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.).

Syntax

res = lhs == rhs

res = lhs .eq. rhs

Class

Elemental function, operator(==) and operator(.eq.).

Argument

  • 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).

Result value

The result is a default logical scalar value.

Example

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

Comparison operator not equal

Status

Experimental

Description

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.).

Syntax

res = lhs /= rhs

res = lhs .ne. rhs

Class

Elemental function, operator(/=) and operator(.ne.).

Argument

  • 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).

Result value

The result is a default logical scalar value.

Example

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

Concatenation operator

Status

Experimental

Description

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(//).

Syntax

res = lhs // rhs

Class

Elemental function, operator(//).

Argument

  • 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).

Result value

The result is an instance of string_type.

Example

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

Unformatted write

Status

Experimental

Description

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.

Syntax

write(unit, iostat=iostat, iomsg=iomsg) string

Class

Unformatted user defined derived type output.

Argument

  • 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).

Example

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

Formatted write

Status

Experimental

Description

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.

Syntax

write(unit, fmt, iostat=iostat, iomsg=iomsg) string

Class

Formatted user defined derived type output.

Argument

  • 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).

Example

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

Unformatted read

Status

Experimental

Description

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.

Syntax

read(unit, iostat=iostat, iomsg=iomsg) string

Class

Unformatted derived type input.

Argument

  • 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).

Example

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

Formatted read

Status

Experimental

Description

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.

Syntax

read(unit, fmt, iostat=iostat, iomsg=iomsg) string

Class

Formatted derived type input.

Argument

  • 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).

Example

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

move

Status

Experimental

Description

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.

Syntax

call move (from, to)

Class

Pure subroutine (Elemental subroutine, only when both from and to are type(string_type))

Argument

  • 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).

Example

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