@@ -28,7 +28,7 @@ module stdlib_str2num
28
28
use, intrinsic:: ieee_arithmetic, only: ieee_value, ieee_positive_inf, ieee_quiet_nan
29
29
implicit none
30
30
private
31
- public :: to_num, to_num_p
31
+ public :: to_num, to_num_from_stream
32
32
33
33
integer(int8), parameter :: digit_0 = ichar('0',int8)
34
34
integer(int8), parameter :: period = ichar('.',int8) - digit_0
@@ -53,13 +53,13 @@ module stdlib_str2num
53
53
#:endfor
54
54
end interface
55
55
56
- interface to_num_p
56
+ interface to_num_from_stream
57
57
!! version: experimental
58
58
!!
59
59
!! Conversion of a stream of values in a string to numbers
60
60
!! ([Specification](../page/specs/stdlib_str2num.html#to-num-p-conversion-of-a-stream-of-values-in-a-strings-to-numbers))
61
61
#:for k1, t1 in (INT_KINDS_TYPES + REAL_KINDS_TYPES)
62
- module procedure to_${k1}$_p
62
+ module procedure to_${k1}$_from_stream
63
63
#:endfor
64
64
end interface
65
65
@@ -88,7 +88,7 @@ module stdlib_str2num
88
88
call to_num_base(s,v,p,stat)
89
89
end function
90
90
91
- function to_${k1}$_p (s,mold,stat) result(v)
91
+ function to_${k1}$_from_stream (s,mold,stat) result(v)
92
92
! -- In/out Variables
93
93
character(len=:), pointer :: s !> input string
94
94
${t1}$, intent(in) :: mold !> dummy argument to disambiguate at compile time the generic interface
@@ -123,13 +123,14 @@ module stdlib_str2num
123
123
stat = 23 !> initialize error status with any number > 0
124
124
!----------------------------------------------
125
125
! Find first non white space
126
- p = mvs2nwsp (s)
126
+ p = shift_to_nonwhitespace (s)
127
127
!----------------------------------------------
128
128
v = 0
129
129
do while( p<=len(s) )
130
130
val = iachar(s(p:p))-digit_0
131
131
if( val >= 0 .and. val <= 9) then
132
- v = v*10 + val ; p = p + 1
132
+ v = v*10 + val
133
+ p = p + 1
133
134
else
134
135
exit
135
136
end if
@@ -169,17 +170,20 @@ module stdlib_str2num
169
170
stat = 23 !> initialize error status with any number > 0
170
171
!----------------------------------------------
171
172
! Find first non white space
172
- p = mvs2nwsp (s)
173
+ p = shift_to_nonwhitespace (s)
173
174
!----------------------------------------------
174
175
! Verify leading negative
175
176
sign = 1
176
177
if( iachar(s(p:p)) == minus_sign+digit_0 ) then
177
- sign = -1 ; p = p + 1
178
+ sign = -1
179
+ p = p + 1
178
180
end if
179
181
if( iachar(s(p:p)) == Inf ) then
180
- v = sign*ieee_value(v, ieee_positive_inf); return
182
+ v = sign*ieee_value(v, ieee_positive_inf)
183
+ return
181
184
else if( iachar(s(p:p)) == NaN ) then
182
- v = ieee_value(v, ieee_quiet_nan); return
185
+ v = ieee_value(v, ieee_quiet_nan)
186
+ return
183
187
end if
184
188
!----------------------------------------------
185
189
! read whole and fractional number in a single integer
@@ -221,7 +225,8 @@ module stdlib_str2num
221
225
do while( p<=len(s) )
222
226
val = iachar(s(p:p))-digit_0
223
227
if( val >= 0 .and. val <= 9) then
224
- i_exp = i_exp*10_int8 + val ; p = p + 1
228
+ i_exp = i_exp*10_int8 + val
229
+ p = p + 1
225
230
else
226
231
exit
227
232
end if
@@ -263,17 +268,20 @@ module stdlib_str2num
263
268
stat = 23 !> initialize error status with any number > 0
264
269
!----------------------------------------------
265
270
! Find first non white space
266
- p = mvs2nwsp (s)
271
+ p = shift_to_nonwhitespace (s)
267
272
!----------------------------------------------
268
273
! Verify leading negative
269
274
sign = 1
270
275
if( iachar(s(p:p)) == minus_sign+digit_0 ) then
271
- sign = -1 ; p = p + 1
276
+ sign = -1
277
+ p = p + 1
272
278
end if
273
279
if( iachar(s(p:p)) == Inf ) then
274
- v = sign*ieee_value(v, ieee_positive_inf); return
280
+ v = sign*ieee_value(v, ieee_positive_inf)
281
+ return
275
282
else if( iachar(s(p:p)) == NaN ) then
276
- v = ieee_value(v, ieee_quiet_nan); return
283
+ v = ieee_value(v, ieee_quiet_nan)
284
+ return
277
285
end if
278
286
!----------------------------------------------
279
287
! read whole and fractional number in a single integer
@@ -315,7 +323,8 @@ module stdlib_str2num
315
323
do while( p<=len(s) )
316
324
val = iachar(s(p:p))-digit_0
317
325
if( val >= 0 .and. val <= 9) then
318
- i_exp = i_exp*10_int8 + val ; p = p + 1
326
+ i_exp = i_exp*10_int8 + val
327
+ p = p + 1
319
328
else
320
329
exit
321
330
end if
@@ -358,22 +367,28 @@ module stdlib_str2num
358
367
stat = 23 !> initialize error status with any number > 0
359
368
!----------------------------------------------
360
369
! Find first non white space
361
- p = mvs2nwsp (s)
370
+ p = shift_to_nonwhitespace (s)
362
371
!----------------------------------------------
363
372
! Verify leading negative
364
373
sign = 1
365
374
if( iachar(s(p:p)) == minus_sign+digit_0 ) then
366
- sign = -1 ; p = p + 1
375
+ sign = -1
376
+ p = p + 1
367
377
end if
368
378
if( iachar(s(p:p)) == Inf ) then
369
- v = sign*ieee_value(v, ieee_positive_inf); return
379
+ v = sign*ieee_value(v, ieee_positive_inf)
380
+ return
370
381
else if( iachar(s(p:p)) == NaN ) then
371
- v = ieee_value(v, ieee_quiet_nan); return
382
+ v = ieee_value(v, ieee_quiet_nan)
383
+ return
372
384
end if
373
385
!----------------------------------------------
374
386
! read whole and fractional number using two int64 values
375
387
pP = 127
376
- int_dp1 = 0; int_dp2 = 0; icount = 0; aux = 1
388
+ int_dp1 = 0
389
+ int_dp2 = 0
390
+ icount = 0
391
+ aux = 1
377
392
do i = p, min(2*maxdpt+p-1,len(s))
378
393
val = iachar(s(i:i))-digit_0
379
394
if( val >= 0 .and. val <= 9 ) then
@@ -384,7 +399,8 @@ module stdlib_str2num
384
399
int_dp2 = int_dp2*10 + val
385
400
end if
386
401
else if( val == period ) then
387
- pP = i; aux = 0
402
+ pP = i
403
+ aux = 0
388
404
else
389
405
exit
390
406
end if
@@ -415,7 +431,8 @@ module stdlib_str2num
415
431
do while( p<=len(s) )
416
432
val = iachar(s(p:p))-digit_0
417
433
if( val >= 0 .and. val <= 9) then
418
- i_exp = i_exp*10_int8 + val ; p = p + 1
434
+ i_exp = i_exp*10_int8 + val
435
+ p = p + 1
419
436
else
420
437
exit
421
438
end if
@@ -463,22 +480,28 @@ module stdlib_str2num
463
480
stat = 23 !> initialize error status with any number > 0
464
481
!----------------------------------------------
465
482
! Find first non white space
466
- p = mvs2nwsp (s)
483
+ p = shift_to_nonwhitespace (s)
467
484
!----------------------------------------------
468
485
! Verify leading negative
469
486
sign = 1
470
487
if( iachar(s(p:p)) == minus_sign+digit_0 ) then
471
- sign = -1 ; p = p + 1
488
+ sign = -1
489
+ p = p + 1
472
490
end if
473
491
if( iachar(s(p:p)) == Inf ) then
474
- v = sign*ieee_value(v, ieee_positive_inf); return
492
+ v = sign*ieee_value(v, ieee_positive_inf)
493
+ return
475
494
else if( iachar(s(p:p)) == NaN ) then
476
- v = ieee_value(v, ieee_quiet_nan); return
495
+ v = ieee_value(v, ieee_quiet_nan)
496
+ return
477
497
end if
478
498
!----------------------------------------------
479
499
! read whole and fractional number using two int64 values
480
500
pP = 127
481
- int_dp1 = 0; int_dp2 = 0; icount = 0; aux = 1
501
+ int_dp1 = 0
502
+ int_dp2 = 0
503
+ icount = 0
504
+ aux = 1
482
505
do i = p, min(2*maxdpt+p-1,len(s))
483
506
val = iachar(s(i:i))-digit_0
484
507
if( val >= 0 .and. val <= 9 ) then
@@ -489,7 +512,8 @@ module stdlib_str2num
489
512
int_dp2 = int_dp2*10 + val
490
513
end if
491
514
else if( val == period ) then
492
- pP = i; aux = 0
515
+ pP = i
516
+ aux = 0
493
517
else
494
518
exit
495
519
end if
@@ -520,7 +544,8 @@ module stdlib_str2num
520
544
do while( p<=len(s) )
521
545
val = iachar(s(p:p))-digit_0
522
546
if( val >= 0 .and. val <= 9) then
523
- i_exp = i_exp*10_int8 + val ; p = p + 1
547
+ i_exp = i_exp*10_int8 + val
548
+ p = p + 1
524
549
else
525
550
exit
526
551
end if
@@ -544,7 +569,7 @@ module stdlib_str2num
544
569
! Internal Utility functions
545
570
!---------------------------------------------
546
571
547
- elemental function mvs2nwsp (s) result(p)
572
+ elemental function shift_to_nonwhitespace (s) result(p)
548
573
!> move string to position of the next non white space character
549
574
character(*),intent(in) :: s !> character chain
550
575
integer(int8) :: p !> position
@@ -555,7 +580,7 @@ module stdlib_str2num
555
580
end do
556
581
end function
557
582
558
- elemental function mvs2wsp (s) result(p)
583
+ elemental function shift_to_whitespace (s) result(p)
559
584
!> move string to position of the next white space character
560
585
character(*),intent(in) :: s !> character chain
561
586
integer(int8) :: p !> position
0 commit comments