字符串

stdlib_strings 模块

简介

stdlib_strings 模块提供基本的字符串处理和操作例程。

提供的过程和方法

strip

描述

删除前导和尾随空格字符。

语法

string = strip (string)

状态

实验性

纯函数。

参数

  • string: 字符标量或 string_type。此参数意图 (intent) 为入参。

结果值

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

描述

string 中删除尾随的 setsubstring 中的字符。如果没有提供字符 setsubstring,则删除尾随空格。

语法

string = chomp (string[, set|substring])

状态

实验性

纯函数。

参数

  • string: 字符标量或 string_type。此参数意图 (intent) 为入参。
  • set: 长度为 1 个字符的数组。此参数意图 (intent) 为入参。
  • substring: 字符标量或 string_type。此参数意图 (intent) 为入参。

结果值

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

描述

检查 string 是否以给定的 substring 开头。

语法

string = starts_with (string, substring)

状态

实验性

纯函数。

参数

  • string: 字符标量或 string_type。此参数意图 (intent) 为入参。
  • substring: 字符标量或 string_type。此参数意图 (intent) 为入参。

结果值

结果为标量逻辑类型。

示例

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

描述

检查 string 是否以给定的 substring 结尾。

语法

string = ends_with (string, substring)

状态

实验性

纯函数。

参数

  • string: 字符标量或 string_type。此参数意图 (intent) 为入参。
  • substring: 字符标量或 string_type。此参数意图 (intent) 为入参。

结果值

结果为标量逻辑类型。

示例

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

描述

通过采用步长,从输入字符串的定义区域提取字符。
参数 firstlast 通过函数 slice 定义此提取区域。
参数 stride 定义在提取时要采取的步长的幅度和方向 (+/-)。如果给定无效值 0,则 stride 将转换为 +1。

推断过程
函数首先自动推断用户未提供的可选参数。
推断的 firstlast 参数取 +infinity 或 -infinity 值,推断的 stride 参数取 +1 或 -1 值,具体取决于用户提供的实际参数。

提取过程
只有当 last 可以用 stride 步长从 first 穿越时,才会开始提取。
提取从定义区域中的第一个有效索引开始,采用 stride 步长,并在穿过定义区域中的最后一个有效索引时结束。
如果定义区域中不存在有效索引,则返回空字符串。

语法

string = slice (string [, first, last, stride])

状态

实验性

纯函数。

参数

  • string: 字符标量或 string_type。此参数意图 (intent) 为入参。
  • first: 整数。此参数意图 (intent) 为入参且可选。
  • last: 整数。此参数意图 (intent) 为入参且可选。
  • stride: 整数。此参数意图 (intent) 为入参且可选。

结果值

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

描述

返回 occurrencepattern 子字符串在输入字符串 string 中出现的起始索引。
occurrence 的默认值为 1。如果未提供 consider_overlapping 或将其设置为 .true.,则该函数将两个重叠的 pattern 子字符串出现视为两次不同的出现。
如果未找到 occurrence 次出现,则函数返回 0

语法

string = find (string, pattern [, occurrence, consider_overlapping])

状态

实验性

元素函数

参数

  • string: 字符标量或 string_type。此参数意图 (intent) 为入参。
  • pattern: 字符标量或 string_type。此参数意图 (intent) 为入参。
  • occurrence: 整数。此参数意图 (intent) 为入参且可选。
  • consider_overlapping: 逻辑。此参数意图 (intent) 为入参且可选。

结果值

结果为整数类型的标量或秩等于所有虚拟参数中最高秩的整数数组。

示例

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

描述

用替换 replacement 替换输入 stringpattern 子字符串的所有出现。
在基础出现上重叠的出现将不会被替换。

语法

string = replace_all (string, pattern, replacement)

状态

实验性

纯函数

参数

  • string: 字符标量或 string_type。此参数意图 (intent) 为入参。
  • pattern: 字符标量或 string_type。此参数意图 (intent) 为入参。
  • replacement: 字符标量或 string_type。此参数意图 (intent) 为入参。

结果值

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

描述

返回长度为 output_length 的字符串,如果提供了 pad_with 字符,则用该字符进行左填充,否则用 " "(1 个空格)进行填充。
如果 output_length 小于或等于 string 的长度,则不执行填充。

语法

string = padl (string, output_length [, pad_with])

状态

实验性

纯函数

参数

  • string: 字符标量或 string_type。此参数意图 (intent) 为入参。
  • output_length: 整数。此参数意图 (intent) 为入参。
  • pad_with: 长度为 1 的字符标量。此参数意图 (intent) 为入参且可选。

结果值

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

描述

返回长度为 output_length 的字符串,如果提供了 pad_with 字符,则用该字符进行右填充,否则用 " "(1 个空格)进行填充。
如果 output_length 小于或等于 string 的长度,则不执行填充。

语法

string = padr (string, output_length [, pad_with])

状态

实验性

纯函数

参数

  • string: 字符标量或 string_type。此参数意图 (intent) 为入参。
  • output_length: 整数。此参数意图 (intent) 为入参。
  • pad_with: 长度为 1 的字符标量。此参数意图 (intent) 为入参且可选。

结果值

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

描述

返回 pattern 子字符串在输入字符串 string 中出现的次数。
如果未提供 consider_overlapping 或将其设置为 .true.,则该函数将两个重叠的 pattern 子字符串出现视为两次不同的出现。

语法

string = count (string, pattern [, consider_overlapping])

状态

实验性

元素函数

参数

  • string: 字符标量或 string_type。此参数意图 (intent) 为入参。
  • pattern: 字符标量或 string_type。此参数意图 (intent) 为入参。
  • consider_overlapping: 逻辑。此参数意图 (intent) 为入参且可选。

结果值

结果为整数类型的标量或秩等于所有虚拟参数中最高秩的整数数组。

示例

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

描述

返回长度为 output_length 的字符串,用零进行左填充。如果 output_length 小于或等于 string 的长度,则不执行填充。

语法

string = zfill (string, output_length)

状态

实验性

纯函数

参数

  • string: 字符标量或 string_type。此参数意图 (intent) 为入参。
  • output_length: 整数。此参数意图 (intent) 为入参。

结果值

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

描述

integer/real/complex/logical 标量格式化或转换为字符串。
输入错误的 format 导致内部 IO 失败,结果值为 [*] 字符串。

语法

string = to_string (value [, format])

状态

实验性

纯函数。

参数

  • value: 应为 integer/real/complex/logical 标量。这是一个 intent(in) 参数。
  • format: 应为 character(len=*) 标量,例如 '(F6.2)''F6.2'。这是一个 intent(in)optional 参数。
    包含用于将 value 格式化为字符串的编辑描述符,例如 '(F6.2)''(f6.2)'to_string 会自动将 format 括在括号中,因此将 F6.2f6.2 作为 format 传递也是可能的。

结果值

结果是一个 allocatable 长度 character 标量,具有最多 128 个缓存 character 长度。

示例

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