Skip to content

Commit d9ece9c

Browse files
authored
Merge pull request #1 from jvdp1/fypp_qp
Addition of some fypp directives
2 parents ea6560b + 17d3dae commit d9ece9c

File tree

4 files changed

+50
-22
lines changed

4 files changed

+50
-22
lines changed

src/CMakeLists.txt

+1-1
Original file line numberDiff line numberDiff line change
@@ -55,6 +55,7 @@ set(fppFiles
5555
stdlib_math_is_close.fypp
5656
stdlib_math_all_close.fypp
5757
stdlib_math_diff.fypp
58+
stdlib_str2num.fypp
5859
stdlib_string_type.fypp
5960
stdlib_string_type_constructor.fypp
6061
stdlib_strings_to_string.fypp
@@ -82,7 +83,6 @@ set(SRC
8283
stdlib_specialfunctions_legendre.f90
8384
stdlib_quadrature_gauss.f90
8485
stdlib_stringlist_type.f90
85-
stdlib_str2num.f90
8686
${outFiles}
8787
)
8888

src/stdlib_str2num.f90 src/stdlib_str2num.fypp

+40-19
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
#:include "common.fypp"
12
!> The `stdlib_str2num` module provides procedures and interfaces for conversion
23
!> of characters to numerical types. Currently supported: int32, real32 and real64
34
!>
@@ -22,7 +23,7 @@
2223
!> difference rel : 0.3300E-029%
2324

2425
module stdlib_str2num
25-
use iso_fortran_env, only: sp => real32, dp => real64, qp => real128
26+
use stdlib_kinds, only: sp, dp, qp, int8, int16, int32, int64
2627
use ieee_arithmetic
2728
implicit none
2829
private
@@ -43,24 +44,36 @@ module stdlib_str2num
4344
integer(kind=ikind), parameter :: LF = 10, CR = 13, WS = 32
4445

4546
interface to_num
46-
module procedure to_int
47+
#:for k1, t1 in INT_KINDS_TYPES
48+
module procedure to_${k1}$
49+
#:endfor
4750
module procedure to_float
4851
module procedure to_double
52+
#:if WITH_QP
4953
module procedure to_quad
54+
#:endif
5055
end interface
5156

5257
interface to_num_p
53-
module procedure to_int_p
58+
#:for k1, t1 in INT_KINDS_TYPES
59+
module procedure to_${k1}$_p
60+
#:endfor
5461
module procedure to_float_p
5562
module procedure to_double_p
63+
#:if WITH_QP
5664
module procedure to_quad_p
65+
#:endif
5766
end interface
5867

5968
interface to_num_base
60-
module procedure to_int_32
69+
#:for k1, t1 in INT_KINDS_TYPES
70+
module procedure to_int_${k1}$
71+
#:endfor
6172
module procedure to_real_sp
6273
module procedure to_real_dp
74+
#:if WITH_QP
6375
module procedure to_real_qp
76+
#:endif
6477
end interface
6578

6679
contains
@@ -69,33 +82,35 @@ module stdlib_str2num
6982
! String To Number interfaces
7083
!---------------------------------------------
7184

72-
elemental function to_int(s,mold) result(v)
85+
#:for k1, t1 in INT_KINDS_TYPES
86+
elemental function to_${k1}$(s,mold) result(v)
7387
! -- In/out Variables
7488
character(*), intent(in) :: s !> input string
75-
integer, intent(in) :: mold !> dummy argument to disambiguate at compile time the generic interface
76-
integer :: v !> Output integer 32 value
89+
${t1}$, intent(in) :: mold !> dummy argument to disambiguate at compile time the generic interface
90+
${t1}$ :: v !> Output integer 32 value
7791
! -- Internal Variables
78-
integer(1) :: p !> position within the number
79-
integer(1) :: stat !> error status
92+
integer(int8) :: p !> position within the number
93+
integer(int8) :: stat !> error status
8094
!----------------------------------------------
8195
call to_num_base(s,v,p,stat)
8296
end function
8397

84-
function to_int_p(s,mold,stat) result(v)
98+
function to_${k1}$_p(s,mold,stat) result(v)
8599
! -- In/out Variables
86100
character(len=:), pointer :: s !> input string
87-
integer, intent(in) :: mold !> dummy argument to disambiguate at compile time the generic interface
88-
integer :: v !> Output integer 32 value
89-
integer(1),intent(inout), optional :: stat
101+
${t1}$, intent(in) :: mold !> dummy argument to disambiguate at compile time the generic interface
102+
${t1}$ :: v !> Output ${t1}$ value
103+
integer(int8),intent(inout), optional :: stat
90104
! -- Internal Variables
91-
integer(1) :: p !> position within the number
92-
integer(1) :: err
105+
integer(int8) :: p !> position within the number
106+
integer(int8) :: err
93107
!----------------------------------------------
94108
call to_num_base(s,v,p,err)
95109
p = min( p , len(s) )
96110
s => s(p:)
97111
if(present(stat)) stat = err
98112
end function
113+
#:endfor
99114

100115
elemental function to_float(s,mold) result(r)
101116
! -- In/out Variables
@@ -153,6 +168,7 @@ function to_double_p(s,mold,stat) result(r)
153168
if(present(stat)) stat = err
154169
end function
155170

171+
#:if WITH_QP
156172
function to_quad(s,mold) result(r)
157173
! -- In/out Variables
158174
character(*), intent(in) :: s !> input string
@@ -180,16 +196,18 @@ function to_quad_p(s,mold,stat) result(r)
180196
s => s(p:)
181197
if(present(stat)) stat = err
182198
end function
199+
#:endif
183200

184201
!---------------------------------------------
185202
! String To Number Implementations
186203
!---------------------------------------------
187204

188-
elemental subroutine to_int_32(s,v,p,stat)
205+
#:for k1, t1 in INT_KINDS_TYPES
206+
elemental subroutine to_int_${k1}$(s,v,p,stat)
189207
!> Return an unsigned 32-bit integer
190208
! -- In/out Variables
191209
character(*), intent(in) :: s !> input string
192-
integer(int32), intent(inout) :: v !> Output real value
210+
${t1}$, intent(out) :: v !> Output real value
193211
integer(int8), intent(out) :: p !> position within the number
194212
integer(int8), intent(out) :: stat !> status upon succes or failure to read
195213
! -- Internal Variables
@@ -211,6 +229,7 @@ elemental subroutine to_int_32(s,v,p,stat)
211229
end do
212230
stat = 0
213231
end subroutine
232+
#:endfor
214233

215234
elemental subroutine to_real_sp(s,v,p,stat)
216235
integer, parameter :: wp = sp
@@ -400,6 +419,7 @@ elemental subroutine to_real_dp(s,v,p,stat)
400419
stat = 0
401420
end subroutine
402421

422+
#:if WITH_QP
403423
subroutine to_real_qp(s,v,p,stat)
404424
integer, parameter :: wp = qp
405425
!> Sequentially unroll the character and get the sub integers composing the whole number, fraction and exponent
@@ -502,6 +522,7 @@ subroutine to_real_qp(s,v,p,stat)
502522
end if
503523
stat = 0
504524
end subroutine
525+
#:endif
505526

506527
!---------------------------------------------
507528
! Internal Utility functions
@@ -510,7 +531,7 @@ subroutine to_real_qp(s,v,p,stat)
510531
elemental function mvs2nwsp(s) result(p)
511532
!> move string to position of the next non white space character
512533
character(*),intent(in) :: s !> character chain
513-
integer(1) :: p !> position
534+
integer(int8) :: p !> position
514535
!----------------------------------------------
515536
p = 1
516537
do while( p<len(s) .and. (iachar(s(p:p))==WS.or.iachar(s(p:p))==LF.or.iachar(s(p:p))==CR) )
@@ -529,4 +550,4 @@ elemental function mvs2wsp(s) result(p)
529550
end do
530551
end function
531552

532-
end module stdlib_str2num
553+
end module stdlib_str2num

test/string/CMakeLists.txt

+2
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
# Create a list of the files to be preprocessed
44
set(fppFiles
55
test_string_assignment.fypp
6+
test_string_to_number.fypp
67
)
78

89
fypp_f90("${fyppFlags}" "${fppFiles}" outFiles)
@@ -14,4 +15,5 @@ ADDTEST(string_match)
1415
ADDTEST(string_derivedtype_io)
1516
ADDTEST(string_functions)
1617
ADDTEST(string_strip_chomp)
18+
ADDTEST(string_to_number)
1719
ADDTEST(string_to_string)

test/string/test_string_to_number.f90 test/string/test_string_to_number.fypp

+7-2
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
module test_string_to_number
2-
use iso_fortran_env, only: sp=>real32, dp=>real64, qp=>real128
2+
use stdlib_kinds, only: sp, dp, qp
33
use stdlib_str2num
44
use testdrive, only : new_unittest, unittest_type, error_type, check
55
implicit none
@@ -14,6 +14,9 @@ subroutine collect_string_to_number(testsuite)
1414
testsuite = [ &
1515
new_unittest("to_float", test_to_float), &
1616
new_unittest("to_double", test_to_double) &
17+
#:if WITH_QP
18+
, new_unittest("to_quadruple", test_to_quadruple) &
19+
#:endif
1720
]
1821
end subroutine collect_string_to_number
1922

@@ -215,6 +218,7 @@ logical function ucheck(s)
215218
end function
216219
end subroutine
217220

221+
#:if WITH_QP
218222
subroutine test_to_quadruple(error)
219223
use stdlib_str2num
220224
type(error_type), allocatable, intent(out) :: error
@@ -313,6 +317,7 @@ logical function ucheck(s)
313317
end if
314318
end function
315319
end subroutine
320+
#:endif
316321

317322
end module test_string_to_number
318323

@@ -340,4 +345,4 @@ program tester
340345
write(error_unit, '(i0, 1x, a)') stat, "test(s) failed!"
341346
error stop
342347
end if
343-
end program
348+
end program

0 commit comments

Comments
 (0)