1
+ #:include "common.fypp"
1
2
!> The `stdlib_str2num` module provides procedures and interfaces for conversion
2
3
!> of characters to numerical types. Currently supported: int32, real32 and real64
3
4
!>
22
23
!> difference rel : 0.3300E-029%
23
24
24
25
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
26
27
use ieee_arithmetic
27
28
implicit none
28
29
private
@@ -43,24 +44,36 @@ module stdlib_str2num
43
44
integer(kind=ikind), parameter :: LF = 10, CR = 13, WS = 32
44
45
45
46
interface to_num
46
- module procedure to_int
47
+ #:for k1, t1 in INT_KINDS_TYPES
48
+ module procedure to_${k1}$
49
+ #:endfor
47
50
module procedure to_float
48
51
module procedure to_double
52
+ #:if WITH_QP
49
53
module procedure to_quad
54
+ #:endif
50
55
end interface
51
56
52
57
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
54
61
module procedure to_float_p
55
62
module procedure to_double_p
63
+ #:if WITH_QP
56
64
module procedure to_quad_p
65
+ #:endif
57
66
end interface
58
67
59
68
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
61
72
module procedure to_real_sp
62
73
module procedure to_real_dp
74
+ #:if WITH_QP
63
75
module procedure to_real_qp
76
+ #:endif
64
77
end interface
65
78
66
79
contains
@@ -69,33 +82,35 @@ module stdlib_str2num
69
82
! String To Number interfaces
70
83
!---------------------------------------------
71
84
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)
73
87
! -- In/out Variables
74
88
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
77
91
! -- 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
80
94
!----------------------------------------------
81
95
call to_num_base(s,v,p,stat)
82
96
end function
83
97
84
- function to_int_p (s ,mold ,stat ) result(v)
98
+ function to_${k1}$_p (s,mold,stat) result(v)
85
99
! -- In/out Variables
86
100
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
90
104
! -- 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
93
107
!----------------------------------------------
94
108
call to_num_base(s,v,p,err)
95
109
p = min( p , len(s) )
96
110
s => s(p:)
97
111
if(present(stat)) stat = err
98
112
end function
113
+ #:endfor
99
114
100
115
elemental function to_float(s,mold) result(r)
101
116
! -- In/out Variables
@@ -153,6 +168,7 @@ function to_double_p(s,mold,stat) result(r)
153
168
if(present(stat)) stat = err
154
169
end function
155
170
171
+ #:if WITH_QP
156
172
function to_quad(s,mold) result(r)
157
173
! -- In/out Variables
158
174
character(*), intent(in) :: s !> input string
@@ -180,16 +196,18 @@ function to_quad_p(s,mold,stat) result(r)
180
196
s => s(p:)
181
197
if(present(stat)) stat = err
182
198
end function
199
+ #:endif
183
200
184
201
!---------------------------------------------
185
202
! String To Number Implementations
186
203
!---------------------------------------------
187
204
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)
189
207
!> Return an unsigned 32-bit integer
190
208
! -- In/out Variables
191
209
character(*), intent(in) :: s !> input string
192
- integer (int32) , intent (inout ) :: v ! > Output real value
210
+ ${t1}$ , intent(out ) :: v !> Output real value
193
211
integer(int8), intent(out) :: p !> position within the number
194
212
integer(int8), intent(out) :: stat !> status upon succes or failure to read
195
213
! -- Internal Variables
@@ -211,6 +229,7 @@ elemental subroutine to_int_32(s,v,p,stat)
211
229
end do
212
230
stat = 0
213
231
end subroutine
232
+ #:endfor
214
233
215
234
elemental subroutine to_real_sp(s,v,p,stat)
216
235
integer, parameter :: wp = sp
@@ -400,6 +419,7 @@ elemental subroutine to_real_dp(s,v,p,stat)
400
419
stat = 0
401
420
end subroutine
402
421
422
+ #:if WITH_QP
403
423
subroutine to_real_qp(s,v,p,stat)
404
424
integer, parameter :: wp = qp
405
425
!> 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)
502
522
end if
503
523
stat = 0
504
524
end subroutine
525
+ #:endif
505
526
506
527
!---------------------------------------------
507
528
! Internal Utility functions
@@ -510,7 +531,7 @@ subroutine to_real_qp(s,v,p,stat)
510
531
elemental function mvs2nwsp(s) result(p)
511
532
!> move string to position of the next non white space character
512
533
character(*),intent(in) :: s !> character chain
513
- integer (1 ) :: p ! > position
534
+ integer(int8 ) :: p !> position
514
535
!----------------------------------------------
515
536
p = 1
516
537
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)
529
550
end do
530
551
end function
531
552
532
- end module stdlib_str2num
553
+ end module stdlib_str2num
0 commit comments