Below is a simple enough Julia script in Fortran style that does about the same as the Fortran code in the original post - note the timing measurement is restricted to parsing:
using Parsers
const N = 10_000_000
n = rand(-500_000:499_999, N)
str = string.(n, base=10)
@time n_parsed = Parsers.parse.(Int, str)
@assert n_parsed == n
println(minimum(n,dims=1))
println(maximum(n,dims=1))
On a given workstation the response by Julia is as follows:
C:\temp>Julia parse.jl
0.190575 seconds (160.08 k allocations: 85.959 MiB, 28.57% compilation time)
[-500000]
[499999]
C:\temp>Julia parse.jl
0.192144 seconds (160.08 k allocations: 85.959 MiB, 28.82% compilation time)
[-500000]
[499999]
C:\temp>Julia parse.jl
0.192366 seconds (160.08 k allocations: 85.959 MiB, 28.57% compilation time)
[-500000]
[499999]
Thus it’s around 0.192 seconds. Now note the above script sets up a jagged array of strings such that the leading and trailing blanks are removed.
On the same workstation, using gfortran and doing the same i.e., parsing strings which are left and right adjusted, the timing results are around 0.121 seconds, about 60% faster.
Click to see the Fortran code used with gfortran
! main program
program p
use timer_m
use num_m
integer, parameter :: N = 10**7
type(num_t), allocatable :: nums(:)
integer, allocatable :: ints(:)
type(timer_t) :: timer
integer :: i
allocate( nums(N) )
allocate( ints(N) )
call generate( nums )
call timer%start()
do i = 1, N
ints(i) = parse_int( nums(i)%digits )
end do
call timer%stop()
print "(g0,f0.4,g0)", "Parsing time: ", timer%t(), " seconds."
call assert( nums, ints )
print *, "First: ", ints(1), nums(1)%n
print *, "Last: ", ints(N), nums(N)%n
print *, "Min: ", minval(ints, dim=1), nums(minloc(ints, dim=1))%n
print *, "Max: ", maxval(ints, dim=1), nums(maxloc(ints, dim=1))%n
end program
! Helper module
module num_m
type :: num_t
integer :: n
character(len=:), allocatable :: digits
end type
contains
impure elemental subroutine generate( num )
type(num_t), intent(inout) :: num
real :: x
call random_number( x )
num%n = 10**6*(x - 0.5 ) ! random integer
num%digits = repeat(' ', ncopies=10)
write( num%digits, fmt="(i0)" ) num%n
num%digits = adjustl( trim(num%digits) )
end subroutine
impure elemental subroutine assert( num, n )
type(num_t), intent(in) :: num
integer, intent(in) :: n
if ( n /= num%n ) then
print *, num%n, n
error stop "num /= n"
end if
end subroutine
! Simple variant for base 10 of function by @lkedward toward Julia microbenchmark
elemental function parse_int(s) result(n)
! Argument list
character(len=*), intent(in) :: s
! Function result
integer :: n
! Local variables
integer :: i, d, sign
n = 0
sign = 1
loop_digits: do i = 1, len(s)
d = ichar(s(i:i))
select case ( d )
case ( ichar('0'):ichar('9') )
d = d - ichar('0')
case ( ichar('-') )
sign = -1
cycle loop_digits
case ( ichar('+'), ichar(' ') )
cycle loop_digits
case default
error stop "parse error"
end select
n = n*10 + d
end do loop_digits
n = sign*n
end function
end module
! Timer module
module kinds_m
use, intrinsic :: iso_fortran_env, only : I8 => int64
integer, parameter :: P12 = selected_real_kind( p=12 )
end module
module timer_m
use kinds_m, only : I8, WP => P12
private
real(WP), parameter :: ZERO = 0.0_wp
type, public :: timer_t
private
integer(I8) :: start_tick = 0
integer(I8) :: end_tick = 0
integer(I8) :: rate = 0
contains
procedure, pass(this) :: start => start_time
procedure, pass(this) :: stop => end_time
procedure, pass(this) :: t => get_time
end type
contains
impure elemental subroutine start_time( this )
class(timer_t), intent(inout) :: this
call system_clock( this%start_tick, this%rate )
end subroutine
impure elemental subroutine end_time( this )
class(timer_t), intent(inout) :: this
call system_clock( this%end_tick )
end subroutine
elemental function get_time( this ) result(time)
class(timer_t), intent(in) :: this
real(WP) :: time
time = real(this%end_tick-this%start_tick, kind=kind(time) ) / &
real(this%rate, kind=kind(time) )
end function
end module
C:\temp>gfortran -O3 -funroll-loops -march=native p.f90 -o p.exe
C:\temp>p.exe
Parsing time: .1207 seconds.
First: -256765 -256765
Last: 488620 488620
Min: -500000 -500000
Max: 499999 499999
C:\temp>p.exe
Parsing time: .1225 seconds.
First: 461273 461273
Last: -258333 -258333
Min: -499999 -499999
Max: 499999 499999
C:\temp>p.exe
Parsing time: .1212 seconds.
First: -179684 -179684
Last: -327573 -327573
Min: -499999 -499999
Max: 499999 499999