Skip to content

Commit b05cbae

Browse files
committed
rename format_string to format_to_string;
rename `format_to_string` input arg: val -> value; fmt -> format. modify `format_to_string` failure output string as `[*]`; update `format_to_string` doc.
1 parent 835de22 commit b05cbae

9 files changed

+127
-124
lines changed

doc/specs/stdlib_strings.md

Lines changed: 30 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -329,15 +329,16 @@ end program demo_find
329329
```
330330

331331
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
332-
### `format_string`
332+
### `format_to_string`
333333

334334
#### Description
335335

336-
Format or transfer a integer/real/complex/logical variable as a character sequence.
336+
Format or transfer a `integer/real/complex/logical` scalar as a string.
337+
Input a wrong `format` that cause the internal-IO to fail, the result value is a string of `[*]`.
337338

338339
#### Syntax
339340

340-
`format_string = [[stdlib_strings(module):format_string(interface)]] (val [, fmt])`
341+
`format_to_string = [[stdlib_strings(module):format_to_string(interface)]] (value [, format])`
341342

342343
#### Status
343344

@@ -349,45 +350,45 @@ Pure function
349350

350351
#### Argument
351352

352-
- `value`: Integer/real/complex/logical scalar.
353-
This argument is intent(in).
354-
- `format`: Character scalar like `'(F6.2)'`.
355-
This argument is intent(in) and optional.
353+
- `value`: Shall be an `integer/real/complex/logical` scalar.
354+
This is an `intent(in)` argument.
355+
- `format`: Shall be a `character` scalar like `'(F6.2)'`.
356+
This is an `intent(in)` and `optional` argument.
356357

357358
#### Result value
358359

359-
The result is an allocatable length Character scalar.
360+
The result is an allocatable length `character` scalar with up to 512 `character` length.
360361

361362
#### Example
362363

363364
```fortran
364-
program demo_format_string
365-
use, non_intrinsic :: stdlib_strings, only: format_string
365+
program demo_format_to_string
366+
use :: stdlib_strings, only: format_to_string
366367
implicit none
367368
368-
print *, 'format_string(complex) : '
369-
print *, format_string((1, 1)) ! (1.00000000,1.00000000)
370-
print *, format_string((1, 1), '(F6.2)') ! ( 1.00, 1.00)
371-
print *, format_string((1000, 1), '(ES0.2)'), format_string((1000, 1), '(SP,F6.3)') ! (1.00E+3,1.00)(******,+1.000)
369+
print *, 'format_to_string(complex) : '
370+
print *, format_to_string((1, 1)) ! (1.00000000,1.00000000)
371+
print *, format_to_string((1, 1), '(F6.2)') ! ( 1.00, 1.00)
372+
print *, format_to_string((1000, 1), '(ES0.2)'), format_to_string((1000, 1), '(SP,F6.3)') ! (1.00E+3,1.00)(******,+1.000)
372373
!! Too narrow formatter for real number
373374
!! Normal demonstration(`******` from Fortran Standard)
374375
375-
print *, 'format_string(integer) : '
376-
print *, format_string(1) ! 1
377-
print *, format_string(1, '(I4)') ! 1
378-
print *, format_string(1, '(I0.4)'), format_string(2, '(B4)') ! 0001 10
376+
print *, 'format_to_string(integer) : '
377+
print *, format_to_string(1) ! 1
378+
print *, format_to_string(1, '(I4)') ! 1
379+
print *, format_to_string(1, '(I0.4)'), format_to_string(2, '(B4)') ! 0001 10
379380
380-
print *, 'format_string(real) : '
381-
print *, format_string(1.) ! 1.00000000
382-
print *, format_string(1., '(F6.2)') ! 1.00
383-
print *, format_string(1., '(SP,ES9.2)'), format_string(1, '(F7.3)') ! +1.00E+00*
384-
!! 1 wrong demonstration(`*` from `format_string`)
381+
print *, 'format_to_string(real) : '
382+
print *, format_to_string(1.) ! 1.00000000
383+
print *, format_to_string(1., '(F6.2)') ! 1.00
384+
print *, format_to_string(1., '(SP,ES9.2)'), format_to_string(1, '(F7.3)') ! +1.00E+00[*]
385+
!! 1 wrong demonstration(`*` from `format_to_string`)
385386
386-
print *, 'format_string(logical) : '
387-
print *, format_string(.true.) ! T
388-
print *, format_string(.true., '(L2)') ! T
389-
print *, format_string(.true., 'L2'), format_string(.false., '(I5)') ! **
390-
!! 2 wrong demonstrations(`*` from `format_string`)
387+
print *, 'format_to_string(logical) : '
388+
print *, format_to_string(.true.) ! T
389+
print *, format_to_string(.true., '(L2)') ! T
390+
print *, format_to_string(.true., 'L2'), format_to_string(.false., '(I5)') ! [*][*]
391+
!! 2 wrong demonstrations(`*` from `format_to_string`)
391392
392-
end program demo_format_string
393+
end program demo_format_to_string
393394
```

src/CMakeLists.txt

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,7 @@ set(fppFiles
3030
stdlib_stats_distribution_PRNG.fypp
3131
stdlib_math.fypp
3232
stdlib_string_type.fypp
33-
stdlib_string_format_string.fypp
33+
stdlib_string_format_to_string.fypp
3434
stdlib_strings.fypp
3535
)
3636

src/Makefile.manual

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ SRCFYPP =\
2828
stdlib_stats_distribution_PRNG.fypp \
2929
stdlib_string_type.fypp \
3030
stdlib_strings.fypp \
31-
stdlib_string_format_string.fypp
31+
stdlib_string_format_to_string.fypp
3232

3333
SRC = f18estop.f90 \
3434
stdlib_error.f90 \
@@ -76,7 +76,8 @@ stdlib_specialfunctions_legendre.o: stdlib_kinds.o stdlib_specialfunctions.o
7676
stdlib_io.o: \
7777
stdlib_error.o \
7878
stdlib_optval.o \
79-
stdlib_kinds.o
79+
stdlib_kinds.o \
80+
stdlib_ascii.o
8081
stdlib_linalg.o: \
8182
stdlib_kinds.o
8283
stdlib_linalg_diag.o: \
@@ -143,5 +144,5 @@ stdlib_strings.o: stdlib_ascii.o \
143144
stdlib_optval.o \
144145
stdlib_kinds.o
145146
stdlib_math.o: stdlib_kinds.o
146-
stdlib_string_format_string.o: stdlib_strings.o
147+
stdlib_string_format_to_string.o: stdlib_strings.o
147148
stdlib_linalg_outer_product.o: stdlib_linalg.o

src/stdlib_string_format_string.fypp

Lines changed: 0 additions & 41 deletions
This file was deleted.
Lines changed: 41 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,41 @@
1+
#:include "common.fypp"
2+
#:set RIL_KINDS_TYPES = REAL_KINDS_TYPES + INT_KINDS_TYPES + LOG_KINDS_TYPES
3+
submodule (stdlib_strings) stdlib_strings_format_to_string
4+
5+
implicit none
6+
integer, parameter :: buffer_len = 512
7+
8+
contains
9+
10+
11+
#:for kind, type in RIL_KINDS_TYPES
12+
!> Format or transfer a ${type}$ scalar as a string.
13+
module procedure format_to_string_${type[0]}$_${kind}$
14+
15+
character(len=buffer_len) :: buffer
16+
integer :: stat
17+
18+
write(buffer, optval(format, "(g0)"), iostat=stat) value
19+
if (stat == 0) then
20+
string = trim(buffer)
21+
else
22+
string = '[*]'
23+
!!\TODO: [*]?
24+
end if
25+
26+
end procedure format_to_string_${type[0]}$_${kind}$
27+
28+
#:endfor
29+
30+
#:for kind, type in CMPLX_KINDS_TYPES
31+
!> Format or transfer a ${type}$ scalar as a string.
32+
module procedure format_to_string_${type[0]}$_${kind}$
33+
34+
string = '(' // format_to_string_r_${kind}$(value%re, format) // ',' // &
35+
& format_to_string_r_${kind}$(value%im, format) // ')'
36+
37+
end procedure format_to_string_${type[0]}$_${kind}$
38+
39+
#:endfor
40+
41+
end submodule stdlib_strings_format_to_string

src/stdlib_strings.fypp

Lines changed: 10 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -13,25 +13,26 @@ module stdlib_strings
1313
implicit none
1414
private
1515

16-
public :: format_string
16+
public :: format_to_string
1717
public :: strip, chomp
1818
public :: starts_with, ends_with
1919
public :: slice, find
2020

21-
!> Format other types as character sequence.
21+
!> Format or transfer other types as a string.
2222
!> ([Specification](../page/specs/stdlib_strings.html#description))
23+
!>
2324
!> Version: experimental
24-
interface format_string
25+
interface format_to_string
2526
#:for kind, type in KINDS_TYPES
26-
!> Format ${type}$ variable as character sequence
27-
pure module function format_string_${type[0]}$_${kind}$(val, fmt) result(string)
28-
${type}$, intent(in) :: val
29-
character(len=*), intent(in), optional :: fmt
27+
!> Format or transfer a ${type}$ scalar as a string.
28+
pure module function format_to_string_${type[0]}$_${kind}$(value, format) result(string)
29+
${type}$, intent(in) :: value
30+
character(len=*), intent(in), optional :: format
3031
character(len=:), allocatable :: string
31-
end function format_string_${type[0]}$_${kind}$
32+
end function format_to_string_${type[0]}$_${kind}$
3233

3334
#:endfor
34-
end interface format_string
35+
end interface format_to_string
3536

3637
!> Remove leading and trailing whitespace characters.
3738
!>

src/tests/string/CMakeLists.txt

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,4 +5,4 @@ ADDTEST(string_match)
55
ADDTEST(string_derivedtype_io)
66
ADDTEST(string_functions)
77
ADDTEST(string_strip_chomp)
8-
ADDTEST(string_format_string)
8+
ADDTEST(string_format_to_string)

src/tests/string/Makefile.manual

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ PROGS_SRC = test_string_assignment.f90 \
55
test_string_match.f90 \
66
test_string_operator.f90 \
77
test_string_strip_chomp.f90 \
8-
test_string_format_string.f90
8+
test_string_format_to_string.f90
99

1010

1111
include ../Makefile.manual.test.mk
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
! SPDX-Identifier: MIT
2-
module test_string_format_string
3-
use stdlib_strings, only: format_string, starts_with
2+
module test_string_format_to_string
3+
use stdlib_strings, only: format_to_string, starts_with
44
use stdlib_error, only: check
55
use stdlib_optval, only: optval
66
implicit none
@@ -31,83 +31,83 @@ subroutine check_formatter(actual, expected, description, partial)
3131

3232
end subroutine check_formatter
3333

34-
subroutine test_format_string_complex
35-
call check_formatter(format_string((1, 1)), "(1.0", &
34+
subroutine test_format_to_string_complex
35+
call check_formatter(format_to_string((1, 1)), "(1.0", &
3636
& "Default formatter for complex number", partial=.true.)
37-
call check_formatter(format_string((1, 1), '(F6.2)'), "( 1.00, 1.00)", &
37+
call check_formatter(format_to_string((1, 1), '(F6.2)'), "( 1.00, 1.00)", &
3838
& "Formatter for complex number")
39-
call check_formatter(format_string((-1, -1), '(F6.2)'), "( -1.00, -1.00)", &
39+
call check_formatter(format_to_string((-1, -1), '(F6.2)'), "( -1.00, -1.00)", &
4040
& "Formatter for negative complex number")
41-
call check_formatter(format_string((1, 1), '(SP,F6.2)'), "( +1.00, +1.00)", &
41+
call check_formatter(format_to_string((1, 1), '(SP,F6.2)'), "( +1.00, +1.00)", &
4242
& "Formatter with sign control descriptor for complex number")
43-
call check_formatter(format_string((1, 1), '(F6.2)') // format_string((2, 2), '(F7.3)'), &
43+
call check_formatter(format_to_string((1, 1), '(F6.2)') // format_to_string((2, 2), '(F7.3)'), &
4444
& "( 1.00, 1.00)( 2.000, 2.000)", &
4545
& "Multiple formatters for complex numbers")
4646

47-
end subroutine test_format_string_complex
47+
end subroutine test_format_to_string_complex
4848

49-
subroutine test_format_string_integer
50-
call check_formatter(format_string(100), "100", &
49+
subroutine test_format_to_string_integer
50+
call check_formatter(format_to_string(100), "100", &
5151
& "Default formatter for integer number")
52-
call check_formatter(format_string(100, '(I6)'), " 100", &
52+
call check_formatter(format_to_string(100, '(I6)'), " 100", &
5353
& "Formatter for integer number")
54-
call check_formatter(format_string(100, '(I0.6)'), "000100", &
54+
call check_formatter(format_to_string(100, '(I0.6)'), "000100", &
5555
& "Formatter with zero padding for integer number")
56-
call check_formatter(format_string(100, '(I6)') // format_string(1000, '(I7)'), &
56+
call check_formatter(format_to_string(100, '(I6)') // format_to_string(1000, '(I7)'), &
5757
& " 100 1000", "Multiple formatters for integers")
58-
call check_formatter(format_string(34, '(B8)'), " 100010", &
58+
call check_formatter(format_to_string(34, '(B8)'), " 100010", &
5959
& "Binary formatter for integer number")
60-
call check_formatter(format_string(34, '(O0.3)'), "042", &
60+
call check_formatter(format_to_string(34, '(O0.3)'), "042", &
6161
& "Octal formatter with zero padding for integer number")
62-
call check_formatter(format_string(34, '(Z3)'), " 22", &
62+
call check_formatter(format_to_string(34, '(Z3)'), " 22", &
6363
& "Hexadecimal formatter for integer number")
6464

65-
end subroutine test_format_string_integer
65+
end subroutine test_format_to_string_integer
6666

67-
subroutine test_format_string_real
68-
call check_formatter(format_string(100.), "100.0", &
67+
subroutine test_format_to_string_real
68+
call check_formatter(format_to_string(100.), "100.0", &
6969
& "Default formatter for real number", partial=.true.)
70-
call check_formatter(format_string(100., '(F6.2)'), "100.00", &
70+
call check_formatter(format_to_string(100., '(F6.2)'), "100.00", &
7171
& "Formatter for real number")
72-
call check_formatter(format_string(289., '(E7.2)'), ".29E+03", &
72+
call check_formatter(format_to_string(289., '(E7.2)'), ".29E+03", &
7373
& "Exponential formatter with rounding for real number")
74-
call check_formatter(format_string(128., '(ES8.2)'), "1.28E+02", &
74+
call check_formatter(format_to_string(128., '(ES8.2)'), "1.28E+02", &
7575
& "Exponential formatter for real number")
7676

7777
! Wrong demonstration
78-
call check_formatter(format_string(-100., '(F6.2)'), "*", &
78+
call check_formatter(format_to_string(-100., '(F6.2)'), "*", &
7979
& "Too narrow formatter for signed real number", partial=.true.)
80-
call check_formatter(format_string(1000., '(F6.3)'), "*", &
80+
call check_formatter(format_to_string(1000., '(F6.3)'), "*", &
8181
& "Too narrow formatter for real number", partial=.true.)
82-
call check_formatter(format_string(1000., '(7.3)'), "*", &
82+
call check_formatter(format_to_string(1000., '(7.3)'), "[*]", &
8383
& "Invalid formatter for real number", partial=.true.)
8484

85-
end subroutine test_format_string_real
85+
end subroutine test_format_to_string_real
8686

87-
subroutine test_format_string_logical
88-
call check_formatter(format_string(.true.), "T", &
87+
subroutine test_format_to_string_logical
88+
call check_formatter(format_to_string(.true.), "T", &
8989
& "Default formatter for logcal value")
90-
call check_formatter(format_string(.true., '(L2)'), " T", &
90+
call check_formatter(format_to_string(.true., '(L2)'), " T", &
9191
& "Formatter for logical value")
92-
call check_formatter(format_string(.false., '(L2)') // format_string(.true., '(L5)'), &
92+
call check_formatter(format_to_string(.false., '(L2)') // format_to_string(.true., '(L5)'), &
9393
& " F T", "Multiple formatters for logical values")
9494

9595
! Wrong demonstration
96-
call check_formatter(format_string(.false., '(1x)'), "*", &
96+
call check_formatter(format_to_string(.false., '(1x)'), "[*]", &
9797
& "Invalid formatter for logical value", partial=.true.)
9898

99-
end subroutine test_format_string_logical
99+
end subroutine test_format_to_string_logical
100100

101101

102-
end module test_string_format_string
102+
end module test_string_format_to_string
103103

104104
program tester
105-
use test_string_format_string
105+
use test_string_format_to_string
106106
implicit none
107107

108-
call test_format_string_complex
109-
call test_format_string_integer
110-
call test_format_string_logical
111-
call test_format_string_real
108+
call test_format_to_string_complex
109+
call test_format_to_string_integer
110+
call test_format_to_string_logical
111+
call test_format_to_string_real
112112

113113
end program tester

0 commit comments

Comments
 (0)