@@ -28,7 +28,7 @@ module stdlib_str2num
2828 use, intrinsic:: ieee_arithmetic, only: ieee_value, ieee_positive_inf, ieee_quiet_nan
2929 implicit none
3030 private
31- public :: to_num, to_num_p
31+ public :: to_num, to_num_from_stream
3232
3333 integer(int8), parameter :: digit_0 = ichar('0',int8)
3434 integer(int8), parameter :: period = ichar('.',int8) - digit_0
@@ -53,13 +53,13 @@ module stdlib_str2num
5353 #:endfor
5454 end interface
5555
56- interface to_num_p
56+ interface to_num_from_stream
5757 !! version: experimental
5858 !!
5959 !! Conversion of a stream of values in a string to numbers
6060 !! ([Specification](../page/specs/stdlib_str2num.html#to-num-p-conversion-of-a-stream-of-values-in-a-strings-to-numbers))
6161 #:for k1, t1 in (INT_KINDS_TYPES + REAL_KINDS_TYPES)
62- module procedure to_${k1}$_p
62+ module procedure to_${k1}$_from_stream
6363 #:endfor
6464 end interface
6565
@@ -88,7 +88,7 @@ module stdlib_str2num
8888 call to_num_base(s,v,p,stat)
8989 end function
9090
91- function to_${k1}$_p (s,mold,stat) result(v)
91+ function to_${k1}$_from_stream (s,mold,stat) result(v)
9292 ! -- In/out Variables
9393 character(len=:), pointer :: s !> input string
9494 ${t1}$, intent(in) :: mold !> dummy argument to disambiguate at compile time the generic interface
@@ -123,13 +123,14 @@ module stdlib_str2num
123123 stat = 23 !> initialize error status with any number > 0
124124 !----------------------------------------------
125125 ! Find first non white space
126- p = mvs2nwsp (s)
126+ p = shift_to_nonwhitespace (s)
127127 !----------------------------------------------
128128 v = 0
129129 do while( p<=len(s) )
130130 val = iachar(s(p:p))-digit_0
131131 if( val >= 0 .and. val <= 9) then
132- v = v*10 + val ; p = p + 1
132+ v = v*10 + val
133+ p = p + 1
133134 else
134135 exit
135136 end if
@@ -169,17 +170,20 @@ module stdlib_str2num
169170 stat = 23 !> initialize error status with any number > 0
170171 !----------------------------------------------
171172 ! Find first non white space
172- p = mvs2nwsp (s)
173+ p = shift_to_nonwhitespace (s)
173174 !----------------------------------------------
174175 ! Verify leading negative
175176 sign = 1
176177 if( iachar(s(p:p)) == minus_sign+digit_0 ) then
177- sign = -1 ; p = p + 1
178+ sign = -1
179+ p = p + 1
178180 end if
179181 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
181184 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
183187 end if
184188 !----------------------------------------------
185189 ! read whole and fractional number in a single integer
@@ -221,7 +225,8 @@ module stdlib_str2num
221225 do while( p<=len(s) )
222226 val = iachar(s(p:p))-digit_0
223227 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
225230 else
226231 exit
227232 end if
@@ -263,17 +268,20 @@ module stdlib_str2num
263268 stat = 23 !> initialize error status with any number > 0
264269 !----------------------------------------------
265270 ! Find first non white space
266- p = mvs2nwsp (s)
271+ p = shift_to_nonwhitespace (s)
267272 !----------------------------------------------
268273 ! Verify leading negative
269274 sign = 1
270275 if( iachar(s(p:p)) == minus_sign+digit_0 ) then
271- sign = -1 ; p = p + 1
276+ sign = -1
277+ p = p + 1
272278 end if
273279 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
275282 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
277285 end if
278286 !----------------------------------------------
279287 ! read whole and fractional number in a single integer
@@ -315,7 +323,8 @@ module stdlib_str2num
315323 do while( p<=len(s) )
316324 val = iachar(s(p:p))-digit_0
317325 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
319328 else
320329 exit
321330 end if
@@ -358,22 +367,28 @@ module stdlib_str2num
358367 stat = 23 !> initialize error status with any number > 0
359368 !----------------------------------------------
360369 ! Find first non white space
361- p = mvs2nwsp (s)
370+ p = shift_to_nonwhitespace (s)
362371 !----------------------------------------------
363372 ! Verify leading negative
364373 sign = 1
365374 if( iachar(s(p:p)) == minus_sign+digit_0 ) then
366- sign = -1 ; p = p + 1
375+ sign = -1
376+ p = p + 1
367377 end if
368378 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
370381 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
372384 end if
373385 !----------------------------------------------
374386 ! read whole and fractional number using two int64 values
375387 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
377392 do i = p, min(2*maxdpt+p-1,len(s))
378393 val = iachar(s(i:i))-digit_0
379394 if( val >= 0 .and. val <= 9 ) then
@@ -384,7 +399,8 @@ module stdlib_str2num
384399 int_dp2 = int_dp2*10 + val
385400 end if
386401 else if( val == period ) then
387- pP = i; aux = 0
402+ pP = i
403+ aux = 0
388404 else
389405 exit
390406 end if
@@ -415,7 +431,8 @@ module stdlib_str2num
415431 do while( p<=len(s) )
416432 val = iachar(s(p:p))-digit_0
417433 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
419436 else
420437 exit
421438 end if
@@ -463,22 +480,28 @@ module stdlib_str2num
463480 stat = 23 !> initialize error status with any number > 0
464481 !----------------------------------------------
465482 ! Find first non white space
466- p = mvs2nwsp (s)
483+ p = shift_to_nonwhitespace (s)
467484 !----------------------------------------------
468485 ! Verify leading negative
469486 sign = 1
470487 if( iachar(s(p:p)) == minus_sign+digit_0 ) then
471- sign = -1 ; p = p + 1
488+ sign = -1
489+ p = p + 1
472490 end if
473491 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
475494 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
477497 end if
478498 !----------------------------------------------
479499 ! read whole and fractional number using two int64 values
480500 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
482505 do i = p, min(2*maxdpt+p-1,len(s))
483506 val = iachar(s(i:i))-digit_0
484507 if( val >= 0 .and. val <= 9 ) then
@@ -489,7 +512,8 @@ module stdlib_str2num
489512 int_dp2 = int_dp2*10 + val
490513 end if
491514 else if( val == period ) then
492- pP = i; aux = 0
515+ pP = i
516+ aux = 0
493517 else
494518 exit
495519 end if
@@ -520,7 +544,8 @@ module stdlib_str2num
520544 do while( p<=len(s) )
521545 val = iachar(s(p:p))-digit_0
522546 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
524549 else
525550 exit
526551 end if
@@ -544,7 +569,7 @@ module stdlib_str2num
544569 ! Internal Utility functions
545570 !---------------------------------------------
546571
547- elemental function mvs2nwsp (s) result(p)
572+ elemental function shift_to_nonwhitespace (s) result(p)
548573 !> move string to position of the next non white space character
549574 character(*),intent(in) :: s !> character chain
550575 integer(int8) :: p !> position
@@ -555,7 +580,7 @@ module stdlib_str2num
555580 end do
556581 end function
557582
558- elemental function mvs2wsp (s) result(p)
583+ elemental function shift_to_whitespace (s) result(p)
559584 !> move string to position of the next white space character
560585 character(*),intent(in) :: s !> character chain
561586 integer(int8) :: p !> position
0 commit comments