Skip to content

Commit 7ae89fb

Browse files
authored
Merge pull request #2 from Aman-Godara/format_string
improved aesthetics to make code consistent with stdlib's format make & cmake passed with msys2-gfortran-10.
2 parents e7ce1e7 + 34fa3cd commit 7ae89fb

7 files changed

+148
-109
lines changed

Diff for: doc/specs/stdlib_strings.md

+9-6
Original file line numberDiff line numberDiff line change
@@ -283,7 +283,6 @@ Default value of `occurrence` is set to `1`.
283283
If `consider_overlapping` is not provided or is set to `.true.` the function counts two overlapping occurrences of substring as two different occurrences.
284284
If `occurrence`th occurrence is not found, function returns `0`.
285285

286-
287286
#### Syntax
288287

289288
`string = [[stdlib_strings(module):find(interface)]] (string, pattern [, occurrence, consider_overlapping])`
@@ -336,10 +335,9 @@ end program demo_find
336335

337336
Format or transfer a integer/real/complex/logical variable as a character sequence.
338337

339-
340338
#### Syntax
341339

342-
`format_string = [[stdlib_strings(module):format_string(interface)]] (value [, format])`
340+
`format_string = [[stdlib_strings(module):format_string(interface)]] (val [, fmt])`
343341

344342
#### Status
345343

@@ -358,33 +356,38 @@ Pure function
358356

359357
#### Result value
360358

361-
The result is a allocatable length Character scalar.
359+
The result is an allocatable length Character scalar.
362360

363361
#### Example
364362

365363
```fortran
366-
program demo_strings_format_string
364+
program demo_format_string
367365
use, non_intrinsic :: stdlib_strings, only: format_string
368366
implicit none
367+
369368
print *, 'format_string(complex) : '
370369
print *, format_string((1, 1)) ! (1.00000000,1.00000000)
371370
print *, format_string((1, 1), '(F6.2)') ! ( 1.00, 1.00)
372371
print *, format_string((1000, 1), '(ES0.2)'), format_string((1000, 1), '(SP,F6.3)') ! (1.00E+3,1.00)(******,+1.000)
373372
!! Too narrow formatter for real number
374373
!! Normal demonstration(`******` from Fortran Standard)
374+
375375
print *, 'format_string(integer) : '
376376
print *, format_string(1) ! 1
377377
print *, format_string(1, '(I4)') ! 1
378378
print *, format_string(1, '(I0.4)'), format_string(2, '(B4)') ! 0001 10
379+
379380
print *, 'format_string(real) : '
380381
print *, format_string(1.) ! 1.00000000
381382
print *, format_string(1., '(F6.2)') ! 1.00
382383
print *, format_string(1., '(SP,ES9.2)'), format_string(1, '(F7.3)') ! +1.00E+00*
383384
!! 1 wrong demonstration(`*` from `format_string`)
385+
384386
print *, 'format_string(logical) : '
385387
print *, format_string(.true.) ! T
386388
print *, format_string(.true., '(L2)') ! T
387389
print *, format_string(.true., 'L2'), format_string(.false., '(I5)') ! **
388390
!! 2 wrong demonstrations(`*` from `format_string`)
389-
end program demo_strings_format_string
391+
392+
end program demo_format_string
390393
```

Diff for: src/stdlib_strings.fypp

+8-7
Original file line numberDiff line numberDiff line change
@@ -18,17 +18,18 @@ module stdlib_strings
1818
public :: starts_with, ends_with
1919
public :: slice, find
2020

21+
!> Format other types as character sequence.
22+
!> ([Specification](../page/specs/stdlib_strings.html#description))
23+
!> Version: experimental
2124
interface format_string
22-
!! version: experimental
23-
!!
24-
!! Format other types as character sequence.
25-
!! ([Specification](../page/specs/stdlib_strings.html#description))
2625
#:for kind, type in KINDS_TYPES
27-
pure module function format_string_${type[0]}$${kind}$(val, fmt) result(string)
28-
character(len=:), allocatable :: string
26+
!> Format ${type}$ variable as character sequence
27+
pure module function format_string_${type[0]}$_${kind}$(val, fmt) result(string)
2928
${type}$, intent(in) :: val
3029
character(len=*), intent(in), optional :: fmt
31-
end function format_string_${type[0]}$${kind}$
30+
character(len=:), allocatable :: string
31+
end function format_string_${type[0]}$_${kind}$
32+
3233
#:endfor
3334
end interface format_string
3435

Diff for: src/stdlib_strings_format_string.fypp

+16-12
Original file line numberDiff line numberDiff line change
@@ -7,9 +7,11 @@ submodule (stdlib_strings) stdlib_strings_format_string
77

88
contains
99

10-
#:for kind, type in RIL_KINDS_TYPES
11-
module procedure format_string_${type[0]}$${kind}$
12-
!! Format ${type}$ variable as character sequence
10+
11+
#:for kind, type in RIL_KINDS_TYPES
12+
!> Format ${type}$ variable as character sequence
13+
module procedure format_string_${type[0]}$_${kind}$
14+
1315
character(len=buffer_len) :: buffer
1416
integer :: stat
1517

@@ -21,17 +23,19 @@ contains
2123
!!\TODO: *?
2224
end if
2325

24-
end procedure format_string_${type[0]}$${kind}$
25-
#:endfor
26+
end procedure format_string_${type[0]}$_${kind}$
27+
28+
#:endfor
29+
30+
#:for kind, type in CMPLX_KINDS_TYPES
31+
!> Format ${type}$ variable as character sequence
32+
module procedure format_string_${type[0]}$_${kind}$
2633

27-
#:for kind, type in CMPLX_KINDS_TYPES
28-
module procedure format_string_${type[0]}$${kind}$
29-
!! Format ${type}$ variable as character sequence
34+
string = '(' // format_string_r_${kind}$(val%re, fmt) // ',' // &
35+
& format_string_r_${kind}$(val%im, fmt) // ')'
3036

31-
string = '('//format_string_r${kind}$(val%re, fmt)//','// &
32-
format_string_r${kind}$(val%im, fmt)//')'
37+
end procedure format_string_${type[0]}$_${kind}$
3338

34-
end procedure format_string_${type[0]}$${kind}$
35-
#:endfor
39+
#:endfor
3640

3741
end submodule stdlib_strings_format_string

Diff for: src/tests/string/CMakeLists.txt

+1-1
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(strings_format_string)
8+
ADDTEST(string_format_string)

Diff for: src/tests/string/Makefile.manual

+1-1
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_strings_format_string.f90
8+
test_string_format_string.f90
99

1010

1111
include ../Makefile.manual.test.mk

Diff for: src/tests/string/test_string_format_string.f90

+113
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,113 @@
1+
! SPDX-Identifier: MIT
2+
module test_string_format_string
3+
use stdlib_strings, only: format_string, starts_with
4+
use stdlib_error, only: check
5+
use stdlib_optval, only: optval
6+
implicit none
7+
8+
contains
9+
10+
11+
subroutine check_formatter(actual, expected, description, partial)
12+
character(len=*), intent(in) :: actual, expected, description
13+
logical, intent(in), optional :: partial
14+
logical :: stat
15+
character(len=:), allocatable :: msg
16+
17+
if (optval(partial, .false.)) then
18+
stat = starts_with(actual, expected)
19+
else
20+
stat = actual == expected
21+
end if
22+
23+
if (.not. stat) then
24+
msg = description // new_line("a") // &
25+
& "Expected: '" // expected // "' but got '" // actual // "'"
26+
else
27+
print '(" - ", a, /, " Result: ''", a, "''")', description, actual
28+
end if
29+
30+
call check(stat, msg)
31+
32+
end subroutine check_formatter
33+
34+
subroutine test_format_string_complex
35+
call check_formatter(format_string((1, 1)), "(1.0", &
36+
& "Default formatter for complex number", partial=.true.)
37+
call check_formatter(format_string((1, 1), '(F6.2)'), "( 1.00, 1.00)", &
38+
& "Formatter for complex number")
39+
call check_formatter(format_string((-1, -1), '(F6.2)'), "( -1.00, -1.00)", &
40+
& "Formatter for negative complex number")
41+
call check_formatter(format_string((1, 1), '(SP,F6.2)'), "( +1.00, +1.00)", &
42+
& "Formatter with sign control descriptor for complex number")
43+
call check_formatter(format_string((1, 1), '(F6.2)') // format_string((2, 2), '(F7.3)'), &
44+
& "( 1.00, 1.00)( 2.000, 2.000)", &
45+
& "Multiple formatters for complex numbers")
46+
47+
end subroutine test_format_string_complex
48+
49+
subroutine test_format_string_integer
50+
call check_formatter(format_string(100), "100", &
51+
& "Default formatter for integer number")
52+
call check_formatter(format_string(100, '(I6)'), " 100", &
53+
& "Formatter for integer number")
54+
call check_formatter(format_string(100, '(I0.6)'), "000100", &
55+
& "Formatter with zero padding for integer number")
56+
call check_formatter(format_string(100, '(I6)') // format_string(1000, '(I7)'), &
57+
& " 100 1000", "Multiple formatters for integers")
58+
call check_formatter(format_string(34, '(B8)'), " 100010", &
59+
& "Binary formatter for integer number")
60+
call check_formatter(format_string(34, '(O0.3)'), "042", &
61+
& "Octal formatter with zero padding for integer number")
62+
call check_formatter(format_string(34, '(Z3)'), " 22", &
63+
& "Hexadecimal formatter for integer number")
64+
65+
end subroutine test_format_string_integer
66+
67+
subroutine test_format_string_real
68+
call check_formatter(format_string(100.), "100.0", &
69+
& "Default formatter for real number", partial=.true.)
70+
call check_formatter(format_string(100., '(F6.2)'), "100.00", &
71+
& "Formatter for real number")
72+
call check_formatter(format_string(289., '(E7.2)'), ".29E+03", &
73+
& "Exponential formatter with rounding for real number")
74+
call check_formatter(format_string(128., '(ES8.2)'), "1.28E+02", &
75+
& "Exponential formatter for real number")
76+
77+
! Wrong demonstration
78+
call check_formatter(format_string(-100., '(F6.2)'), "*", &
79+
& "Too narrow formatter for signed real number", partial=.true.)
80+
call check_formatter(format_string(1000., '(F6.3)'), "*", &
81+
& "Too narrow formatter for real number", partial=.true.)
82+
call check_formatter(format_string(1000., '(7.3)'), "*", &
83+
& "Invalid formatter for real number", partial=.true.)
84+
85+
end subroutine test_format_string_real
86+
87+
subroutine test_format_string_logical
88+
call check_formatter(format_string(.true.), "T", &
89+
& "Default formatter for logcal value")
90+
call check_formatter(format_string(.true., '(L2)'), " T", &
91+
& "Formatter for logical value")
92+
call check_formatter(format_string(.false., '(L2)') // format_string(.true., '(L5)'), &
93+
& " F T", "Multiple formatters for logical values")
94+
95+
! Wrong demonstration
96+
call check_formatter(format_string(.false., '(1x)'), "*", &
97+
& "Invalid formatter for logical value", partial=.true.)
98+
99+
end subroutine test_format_string_logical
100+
101+
102+
end module test_string_format_string
103+
104+
program tester
105+
use test_string_format_string
106+
implicit none
107+
108+
call test_format_string_complex
109+
call test_format_string_integer
110+
call test_format_string_logical
111+
call test_format_string_real
112+
113+
end program tester

Diff for: src/tests/string/test_strings_format_string.f90

-82
This file was deleted.

0 commit comments

Comments
 (0)