Faster string to double

The issue is of course the accuracy and all the edge cases one has to keep in mind. If one were willing to tolerate around 10 epsilon and not want to indulge in bit-processing and not support everything C stdlib strtod does, then some simple options are amenable with a decent speed improvement over C strtod. Shown below is one such example setup as a subroutine subprogram in order to allow easier procedure overloading for single precision and possibly extended precision (80-bit) floating-point values.

Click for code

Simple Fortran String to Double

module F_strtod_m
! Simple Fortran string to double
   use, intrinsic :: iso_fortran_env, only : I8 => int64
   integer, parameter :: DP = selected_real_kind( p=12 )
   ! FP constants
   real(DP), parameter :: TEN = 10.0_dp
   ! Integer constants
   integer, parameter :: ASCII_NEGATIVE = 45
   integer, parameter :: ASCII_PERIOD = 46
   integer, parameter :: ASCII_0 = 48
   integer, parameter :: ASCII_9 = 57
   integer(I8), parameter :: TEN_INT = 10_i8
contains
   elemental subroutine F_strtod( str, r )
      character(len=*), intent(in) :: str
      real(DP), intent(out) :: r
      ! Local variables
      integer(I8) :: n, n_exp
      integer :: lens, pos_exp, expnt
      r = 0.0_dp
      n_exp = 0
      lens = len_trim( str )
      pos_exp = index( str, "E", back=.true. )
      if ( pos_exp == 0 ) then
         pos_exp = index( str, "e", back=.true. )
      end if
      if ( pos_exp > 0 ) then
         call str2dec( str(pos_exp+1:lens), n_exp ) 
      else
         pos_exp = lens + 1
      end if
      call str2dec( str(1:pos_exp-1), n, expnt )
      r = real( n, kind=DP ) * (TEN**(n_exp + expnt)) 
      return
   end subroutine
   elemental subroutine str2dec( s, n, expnt )
      character(len=*), intent(in)   :: s
      integer(I8), intent(out)       :: n 
      integer, intent(out), optional :: expnt
      integer :: ipos, ic, pos_period, exponent
      n = 0_i8
      pos_period = 0
      exponent = -1
      if ( present(expnt) ) exponent = 0 
      do ipos = len(s), 1, -1
         ic = ichar( s(ipos:ipos) )
         if ( present(expnt) ) then 
            if ( ic == ASCII_PERIOD ) then
               pos_period = ipos
               cycle
            end if
         end if 
         if ( ic == ASCII_NEGATIVE ) then
            n = -n
            exit
         end if 
         if ( (ic < ASCII_0).or.(ic > ASCII_9) ) exit
         exponent = exponent + 1 
         n = n + TEN_INT**(exponent)*(ic - 48)
      end do
      if ( present(expnt) ) expnt = -len(s) + pos_period - 1
      return
   end subroutine 
end module

Block 1: formatted read toward string to double
time * : 0.7490 seconds

Block 2: C strtod
time * : 0.2980 seconds

Block 3: Fortran strtod
time * : 0.1410 seconds
Values match within 10 epsilon.

1 Like