string_type

stdlib_string_type 模块

简介

stdlib_string_type 提供了一个派生类型,该类型保存任意字符序列,与大多数 Fortran 内置字符过程以及用于处理字符变量和常量的运算符兼容。

提供的派生类型

string_type 派生类型

string_type 定义为不可扩展的派生类型,表示字符序列。字符序列的内部表示依赖于实现,对模块用户不可见。

状态

实验性

提供的过程和方法

返回 string_type 实例的过程通常可以在元素上下文中使用,而返回标量字符值的过程只能以纯方式使用。

空字符串构造函数

状态

实验性

描述

该模块定义了一个构造函数来创建空字符串类型。

创建一个表示空字符串的字符串实例。

语法

res = string_type ()

元素函数。

参数

无。

结果值

结果是长度为零的 string_type 实例。

示例

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

从字符标量构造

状态

实验性

描述

该模块定义了一个构造函数,用于从字符标量创建字符串类型。

创建一个表示输入字符标量值的字符串实例。如果传递未分配的延迟长度字符变量,则构造函数应创建空字符串。

语法

res = string_type (string)

元素函数。

参数

string:应为标量字符值。它是一个 intent(in) 参数。

结果值

结果是 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

从整数标量构造

状态

实验性

描述

该模块定义了一个构造函数,用于从整数标量创建字符串类型。

语法

res = string_type (string)

元素函数。

参数

val:应为标量整数值。它是一个 intent(in) 参数。

结果值

结果是 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

从逻辑标量构造

状态

实验性

描述

该模块定义了一个构造函数,用于从逻辑标量创建字符串类型。

语法

res = string_type (string)

元素函数。

参数

val:应为标量逻辑值。它是一个 intent(in) 参数。

结果值

结果是 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

字符标量赋值

状态

实验性

描述

该模块定义了一个赋值运算 =,用于从字符标量创建字符串类型。

创建一个表示右侧字符标量值的字符串实例。

语法

lhs = rhs

元素子程序,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

Len 函数

状态

实验性

描述

返回字符串的长度。

语法

res = len (string)

元素函数。

参数

stringstring_type 的实例。此参数为 intent(in)

结果值

结果是默认整数标量值。

示例

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 函数

状态

实验性

描述

返回字符串表示的字符序列的长度,不包括尾随空格。

语法

res = len_trim (string)

元素函数。

参数

stringstring_type 的实例。此参数为 intent(in)

结果值

结果是默认整数标量值。

示例

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 函数

状态

实验性

描述

返回字符串持有的字符序列,不包括由 string_type 表示的尾随空格。

语法

res = trim (string)

元素函数。

参数

  • stringstring_type 的实例。此参数为 intent(in)

结果值

结果是标量 string_type 值。

示例

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 函数

状态

实验性

描述

左对齐字符串表示的字符序列。字符序列的长度保持不变。

语法

res = adjustl (string)

元素函数。

参数

  • stringstring_type 的实例。此参数为 intent(in)

结果值

结果是标量 string_type 值。

示例

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 函数

状态

实验性

描述

右对齐字符串表示的字符序列。字符序列的长度保持不变。

语法

res = adjustr (string)

元素函数。

参数

  • stringstring_type 的实例。此参数为 intent(in)

结果值

结果是标量 string_type 值。

示例

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 函数

状态

实验性

描述

将字符串持有的字符序列重复指定副本数。

语法

res = repeat (string, ncopies)

元素函数。

参数

  • stringstring_type 的实例。此参数为 intent(in)
  • ncopies:默认类型的整数。此参数为 intent(in)

结果值

结果是标量 string_type 值。

示例

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 函数

状态

实验性

描述

返回字符串表示的字符序列。

语法

res = char (string)

纯函数。

参数

  • stringstring_type 的实例。此参数为 intent(in)

结果值

结果是标量字符值。

示例

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 函数(位置变体)

状态

实验性

描述

返回字符串中特定位置的字符。

语法

res = char (string, pos)

元素函数。

参数

  • stringstring_type 的实例。此参数为 intent(in)
  • pos:默认类型的整数。此参数为 intent(in)

结果值

结果是标量字符值。

示例

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 函数(范围变体)

状态

实验性

描述

返回字符串字符序列的子字符串。

语法

res = char (string, start, last)

纯函数。

参数

  • stringstring_type 的实例。此参数为 intent(in)
  • start:默认类型的整数。此参数为 intent(in)
  • last:默认类型的整数。此参数为 intent(in)

结果值

结果是标量字符值。

示例

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 函数

状态

实验性

描述

字符到整数转换函数。

返回系统本机字符集中字符序列第一个字符位置的字符代码。

语法

res = ichar (string)

元素函数。

参数

  • stringstring_type 的实例。此参数为 intent(in)

结果值

结果是默认整数标量值。

示例

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 函数

状态

实验性

描述

ASCII 排序序列中的代码。

返回字符串表示的字符序列第一个字符位置的 ASCII 字符的代码。

语法

res = iachar (string)

元素函数。

参数

  • stringstring_type 的实例。此参数为 intent(in)

结果值

结果是默认整数标量值。

示例

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 函数

状态

实验性

描述

字符串子字符串的位置。

返回字符串子字符串最左边或最右边出现的起始位置,从 1 开始计数。如果子字符串不存在于字符串中,则返回 0。

语法

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

元素函数。

参数

  • string:标量字符值或字符串类型。此参数为 intent(in)
  • substring:标量字符值或字符串类型。此参数为 intent(in)
  • back:不存在或标量逻辑值。此参数为 intent(in)

结果值

结果是默认整数标量值。

示例

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 函数

状态

实验性

描述

扫描字符串中是否存在一组字符中的任何字符。如果back不存在或为false,则此函数返回字符串中最左边字符的位置,该字符位于set中。如果backtrue,则返回最右边位置。如果在字符串中找不到set的任何字符,则结果为 0。

语法

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

元素函数。

参数

  • string:标量字符值或字符串类型。此参数为 intent(in)
  • set:标量字符值或字符串类型。此参数为 intent(in)
  • back:不存在或标量逻辑值。此参数为 intent(in)

结果值

结果是默认整数标量值。

示例

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 函数

状态

实验性

描述

验证字符串中的所有字符是否都属于set中的一组字符。如果back不存在或为false,则此函数返回字符串中最左边字符的位置,该字符不在set中。如果backtrue,则返回最右边位置。如果在set中找到字符串的所有字符,则结果为 0。

语法

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

元素函数。

参数

  • string:标量字符值或字符串类型。此参数为 intent(in)
  • set:标量字符值或字符串类型。此参数为 intent(in)
  • back:不存在或标量逻辑值。此参数为 intent(in)

结果值

结果是默认整数标量值。

示例

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 函数(词法大于)

状态

实验性

描述

词法比较两个字符序列的顺序是否大于。

左侧、右侧或两个字符序列都可以由字符串类型表示。这定义了三个重载内置 lgt 过程的过程。

语法

res = lgt (lhs, rhs)

元素函数。

参数

  • lhs:标量字符值或字符串类型。此参数为 intent(in)
  • rhs:标量字符值或字符串类型。此参数为 intent(in)

结果值

结果是默认逻辑标量值。

示例

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 函数(词法小于)

状态

实验性

描述

词法比较两个字符序列的顺序是否小于。

左侧、右侧或两个字符序列都可以由字符串类型表示。这定义了三个重载内置 llt 过程的过程。

语法

res = llt (lhs, rhs)

元素函数。

参数

  • lhs:标量字符值或字符串类型。此参数为 intent(in)
  • rhs:标量字符值或字符串类型。此参数为 intent(in)

结果值

结果是默认逻辑标量值。

示例

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 函数(词法大于或等于)

状态

实验性

描述

词法比较两个字符序列的顺序是否大于或等于。

左侧、右侧或两个字符序列都可以由字符串类型表示。这定义了三个重载内置 lge 过程的过程。

语法

res = lge (lhs, rhs)

元素函数。

参数

  • lhs:标量字符值或字符串类型。此参数为 intent(in)
  • rhs:标量字符值或字符串类型。此参数为 intent(in)

结果值

结果是默认逻辑标量值。

示例

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 函数(词法小于或等于)

状态

实验性

描述

词法比较两个字符序列的顺序是否小于或等于。

左侧、右侧或两个字符序列都可以由字符串类型表示。这定义了三个重载内置 lle 过程的过程。

语法

res = lle (lhs, rhs)

元素函数。

参数

  • lhs:标量字符值或字符串类型。此参数为 intent(in)
  • rhs:标量字符值或字符串类型。此参数为 intent(in)

结果值

结果是默认逻辑标量值。

示例

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 函数

状态

实验性

描述

返回一个新的 string_type 实例,该实例保存输入字符串持有的字符序列的小写版本。

语法

lowercase_string = to_lower (string)

元素函数。

参数

stringstring_type 的实例。此参数为 intent(in)

结果值

结果是标量 string_type 值。

示例

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 函数

状态

实验性

描述

返回一个新的 string_type 实例,该实例保存输入字符串持有的字符序列的大写版本。

语法

uppercase_string = to_upper (string)

元素函数。

参数

stringstring_type 的实例。此参数为 intent(in)

结果值

结果是标量 string_type 值。

示例

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 函数

状态

实验性

描述

返回一个新的 string_type 实例,该实例保存输入字符串持有的字符序列的标题大小写版本。标题大小写:句中每个单词的第一个字符转换为大写,其余字符转换为小写。单词是仅由字母字符和数字组成的连续字符序列,并且不排除其两端任一侧的任何字母字符或数字。

语法

titlecase_string = to_title (string)

元素函数。

参数

stringstring_type 的实例。此参数为 intent(in)

结果值

结果是标量 string_type 值。

示例

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 函数

状态

实验性

描述

返回一个新的 string_type 实例,其中包含输入字符串所持有的字符序列的句子大小写版本。句子大小写版本:输入字符序列的第一个字母字符将转换为大写,除非它紧跟在一个数字后面,并且序列中的其余字符将转换为小写。

语法

sentencecase_string = to_sentence (string)

元素函数。

参数

stringstring_type 的实例。此参数为 intent(in)

结果值

结果是标量 string_type 值。

示例

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 函数

状态

实验性

描述

返回一个新的 string_type 实例,其中包含输入字符串所持有的字符序列的反转版本。

语法

reverse_string = reverse (string)

元素函数。

参数

stringstring_type 的实例。此参数为 intent(in)

结果值

结果是标量 string_type 值。

示例

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

比较运算符大于

状态

实验性

描述

比较两个字符序列的顺序是否大于。

左侧、右侧或两个字符序列都可以由字符串类型表示。这定义了三个过程,重载了内在的 operator(>)operator(.gt.)

语法

res = lhs > rhs

res = lhs .gt. rhs

元素函数,operator(>)operator(.gt.)

参数

  • lhs:标量字符值或字符串类型。此参数为 intent(in)
  • rhs:标量字符值或字符串类型。此参数为 intent(in)

结果值

结果是默认逻辑标量值。

示例

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

比较运算符小于

状态

实验性

描述

比较两个字符序列的顺序是否小于。

左侧、右侧或两个字符序列都可以由字符串类型表示。这定义了三个过程,重载了内在的 operator(<)operator(.lt.)

语法

res = lhs < rhs

res = lhs .lt. rhs

元素函数,operator(<)operator(.lt.)

参数

  • lhs:标量字符值或字符串类型。此参数为 intent(in)
  • rhs:标量字符值或字符串类型。此参数为 intent(in)

结果值

结果是默认逻辑标量值。

示例

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

比较运算符大于或等于

状态

实验性

描述

比较两个字符序列的顺序是否大于或等于。

左侧、右侧或两个字符序列都可以由字符串类型表示。这定义了三个过程,重载了内在的 operator(>=)operator(.ge.)

语法

res = lhs >= rhs

res = lhs .ge. rhs

元素函数,operator(>=)operator(.ge.)

参数

  • lhs:标量字符值或字符串类型。此参数为 intent(in)
  • rhs:标量字符值或字符串类型。此参数为 intent(in)

结果值

结果是默认逻辑标量值。

示例

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

比较运算符小于或等于

状态

实验性

描述

比较两个字符序列的顺序是否小于或等于。

左侧、右侧或两个字符序列都可以由字符串类型表示。这定义了三个过程,重载了内在的 operator(<=)operator(.le.)

语法

res = lhs <= rhs

res = lhs .le. rhs

元素函数,operator(<=)operator(.le.)

参数

  • lhs:标量字符值或字符串类型。此参数为 intent(in)
  • rhs:标量字符值或字符串类型。此参数为 intent(in)

结果值

结果是默认逻辑标量值。

示例

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

比较运算符等于

状态

实验性

描述

比较两个字符序列是否相等。

左侧、右侧或两个字符序列都可以由字符串类型表示。这定义了三个过程,重载了内在的 operator(==)operator(.eq.)

语法

res = lhs == rhs

res = lhs .eq. rhs

元素函数,operator(==)operator(.eq.)

参数

  • lhs:标量字符值或字符串类型。此参数为 intent(in)
  • rhs:标量字符值或字符串类型。此参数为 intent(in)

结果值

结果是默认逻辑标量值。

示例

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

比较运算符不等于

状态

实验性

描述

比较两个字符序列是否不相等。

左侧、右侧或两个字符序列都可以由字符串类型表示。这定义了三个过程,重载了内在的 operator(/=)operator(.ne.)

语法

res = lhs /= rhs

res = lhs .ne. rhs

元素函数,operator(/=)operator(.ne.)

参数

  • lhs:标量字符值或字符串类型。此参数为 intent(in)
  • rhs:标量字符值或字符串类型。此参数为 intent(in)

结果值

结果是默认逻辑标量值。

示例

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

连接运算符

状态

实验性

描述

连接两个字符序列。

左侧、右侧或两个字符序列都可以由字符串类型表示。这定义了三个过程,重载了内在的 operator(//)

语法

res = lhs // rhs

元素函数,operator(//)

参数

  • lhs:标量字符值或字符串类型。此参数为 intent(in)
  • rhs:标量字符值或字符串类型。此参数为 intent(in)

结果值

结果是 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

无格式写入

状态

实验性

描述

将字符串所持有的字符序列写入已连接的无格式单元。字符序列由一个 64 位有符号整数记录表示,其中包含后续字符记录的长度。

语法

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

无格式用户定义派生类型输出。

参数

  • string:要读取的字符串类型的实例。此参数为 intent(inout)
  • unit:输出的格式化单元。此参数为 intent(in)
  • iostat:状态标识符,指示输出操作是否成功。此参数为 intent(out)
  • iomsg:在输出操作失败的情况下返回错误消息的缓冲区。此参数为 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

格式化写入

状态

实验性

描述

将字符串所持有的字符序列写入已连接的格式化单元。

当前实现仅限于列表定向输出和 dt 格式化输出。请求名称列表输出将引发错误。

语法

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

格式化用户定义派生类型输出。

参数

  • string:要读取的字符串类型的实例。此参数为 intent(inout)
  • unit:输出的格式化单元。此参数为 intent(in)
  • iotype:格式化数据传输的类型,对于 fmt=* 的值为 "LISTDIRECTED",对于名称列表输出的值为 "NAMELIST",或者对于派生类型输出的值以 "DT" 开头。此参数为 intent(in)
  • v_list:秩为 1 的默认整数类型数组,包含派生类型输出的编辑描述符。此参数为 intent(in)
  • iostat:状态标识符,指示输出操作是否成功。此参数为 intent(out)
  • iomsg:在输出操作失败的情况下返回错误消息的缓冲区。此参数为 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

无格式读取

状态

实验性

描述

从已连接的无格式单元读取字符序列到字符串中。字符序列由一个 64 位有符号整数记录表示,其中包含后续字符记录的长度。

如果失败,则读取变量的状态未定义且取决于实现。

语法

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

无格式派生类型输入。

参数

  • string:要读取的字符串类型的实例。此参数为 intent(inout)
  • unit:输入的格式化单元。此参数为 intent(in)
  • iostat:状态标识符,指示输入操作是否成功。此参数为 intent(out)
  • iomsg:在输入操作失败的情况下返回错误消息的缓冲区。此参数为 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

格式化读取

状态

实验性

描述

从已连接的格式化单元读取字符序列到字符串中。列表定向输入将检索完整记录到字符串中。

如果失败,则读取变量的状态未定义且取决于实现。

当前实现仅限于列表定向输入。请求 dt 格式化输入或名称列表输出将引发错误。

语法

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

格式化派生类型输入。

参数

  • string:要读取的字符串类型的实例。此参数为 intent(inout)
  • unit:输入的格式化单元。此参数为 intent(in)
  • iotype:格式化数据传输的类型,对于 fmt=* 的值为 "LISTDIRECTED",对于名称列表输入的值为 "NAMELIST",或者对于派生类型输入的值以 "DT" 开头。此参数为 intent(in)
  • v_list:秩为 1 的默认整数类型数组,包含派生类型输入的编辑描述符。此参数为 intent(in)
  • iostat:状态标识符,指示输入操作是否成功。此参数为 intent(out)
  • iomsg:在输入操作失败的情况下返回错误消息的缓冲区。此参数为 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

移动

状态

实验性

描述

将分配从 from 移动到 to,因此在此过程中释放 from 的分配。如果 from 在执行之前未分配,则 to 将在此过程中被释放分配。未分配的 string_type 实例等效于空字符串。如果 fromto 是同一个变量,则 from 保持不变。

语法

call move (from, to)

纯子程序(元素子程序,仅当 fromto 均为 type(string_type) 时)

参数

  • from:字符标量或 string_type。此参数为 intent(inout)
  • to:字符标量或 string_type。当 fromto 均为 type(string_type) 时,此参数为 intent(inout),否则为 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