I am now tweeting about C interoperability. It’s nice that one can call functions in the C standard library just by providing an interface. I may present an example of using the C atoi function to read an integer from a string instead of an internal read. I am finding atoi to be 3 to 15 times faster than a Fortran internal read of an integer, depending on the compiler, and atof to be 1.7 to 5.3 times faster than a Fortran internal read of a double.
program main
use, intrinsic :: iso_c_binding, only: c_char, c_null_char
implicit none
interface
function atoi(in) bind(c)
use, intrinsic :: iso_c_binding
integer(c_int) :: atoi
character(c_char) :: in(*)
end function
end interface
integer :: j,iran
integer, parameter :: nread = 10**7, nt = 3
character(len=10,kind=c_char), allocatable :: digits(:), cdigits(:)
real :: times(nt),dt(nt-1),xran
integer, allocatable :: iran_c(:),iran_f(:)
allocate (digits(nread),cdigits(nread),iran_c(nread),iran_f(nread))
do j=1,nread
call random_number(xran)
iran = 10**6*(xran-0.5) ! random integer
write (digits(j),"(i0)") iran ! write integer to string
cdigits(j) = trim(digits(j)) // c_null_char ! create C string
end do
call cpu_time(times(1))
do j=1,nread ! read integers from C strings using C atoi
iran_c(j) = atoi(cdigits(j))
end do
call cpu_time(times(2))
do j=1,nread ! read integers from strings using internal read
read (digits(j),*) iran_f(j)
end do
call cpu_time(times(3))
dt = times(2:nt)-times(1:nt-1)
print "(4a8)","","C","Fortran","ratio"
print "(a8,3f8.4,/)","times",dt,dt(2)/dt(1)
print "(/,*(a8))","#","mean","min","max","first","last","maxdiff"
print "(i8,f8.1,*(i8))",nread,sum(dble(iran_c))/nread,minval(iran_c),maxval(iran_c), &
iran_c(1),iran_c(nread),maxval(abs(iran_c-iran_f))
end program main
using on WSL2 the script
#!/bin/bash
# compile and run a program composed of one or more source files with the .f90 extension, using several compilers
# usage: ./cmpl_all.sh mod1.f90 mod2.f90 main.f90
exec=a.out
declare compilers=("gfortran -O3" "ifort -O3" "nvfortran -O3" "flang -O3")
declare sources=("$@")
declare objs=("${sources[@]/.f90/.o}")
print_version=false # print compiler version
for FC in "${compilers[@]}"; do # loop over compilers
echo && echo $FC
if [ "$print_version" = true ]; then
$FC --version
fi
rm -f *.o $exec # cleanup
for src in "${sources[@]}"; do
$FC -c $src
done
$FC -o $exec "${objs[@]}"
time ./$exec
done
I get results
gfortran -O3
C Fortran ratio
times 0.2395 3.7085 15.4877
# mean min max first last maxdiff
10000000 -132.2 -499999 499999 75306 -450799 0
real 0m8.783s
user 0m8.737s
sys 0m0.040s
ifort -O3
C Fortran ratio
times 0.2385 2.7406 11.4902
# mean min max first last maxdiff
10000000 44.4 -499999 499999 -499999 -6839 0
real 0m5.650s
user 0m5.614s
sys 0m0.020s
nvfortran -O3
C Fortran ratio
times 0.2415 0.7409 3.0679
# mean min max first last maxdiff
10000000 -88.2 -499999 499999 407922 -293367 0
real 0m3.054s
user 0m2.964s
sys 0m0.080s
flang -O3
C Fortran ratio
times 0.2422 0.9240 3.8145
# mean min max first last maxdiff
10000000 -88.2 -499999 499999 407923 -293367 0
real 0m3.350s
user 0m3.301s
sys 0m0.040s
and for a code comparing C atof with an internal read of a double
program main
use, intrinsic :: iso_c_binding, only: c_char, c_null_char, c_double
implicit none
interface
function atof(in) bind(c)
use, intrinsic :: iso_c_binding
real(c_double) :: atof
character(c_char) :: in(*)
end function
end interface
integer :: j
integer, parameter :: nread = 10**7, nt = 3, dp = c_double
character(len=20,kind=c_char), allocatable :: digits(:), cdigits(:)
real(kind=dp) :: times(nt),dt(nt-1),xran
real(kind=dp), allocatable :: xran_c(:),xran_f(:)
allocate (digits(nread),cdigits(nread),xran_c(nread),xran_f(nread))
do j=1,nread
call random_number(xran)
xran = xran - 0.5
write (digits(j),"(f0.6)") xran ! write real to string
cdigits(j) = trim(digits(j)) // c_null_char ! create C string
end do
call cpu_time(times(1))
do j=1,nread ! read reals from C strings using C atof
xran_c(j) = atof(cdigits(j))
end do
call cpu_time(times(2))
do j=1,nread ! read reals from strings using internal read
read (digits(j),*) xran_f(j)
end do
call cpu_time(times(3))
dt = times(2:nt)-times(1:nt-1)
print "(4a8)","","C","Fortran","ratio"
print "(a8,3f8.4,/)","times",dt,dt(2)/dt(1)
print "(/,*(a8))","#","mean","min","max","first","last","maxdiff"
print "(i8,*(f8.4))",nread,sum(xran_c)/nread,minval(xran_c),maxval(xran_c), &
xran_c(1),xran_c(nread),maxval(abs(xran_c-xran_f))
end program main
I get
gfortran -O3
C Fortran ratio
times 0.9669 5.0880 5.2620
# mean min max first last maxdiff
10000000 0.0001 -0.5000 0.5000 -0.4798 -0.1218 0.0000
real 0m13.807s
user 0m13.771s
sys 0m0.030s
ifort -O3
C Fortran ratio
times 0.9708 3.0744 3.1670
# mean min max first last maxdiff
10000000 0.0000 -0.5000 0.5000 -0.5000 -0.0068 0.0000
real 0m9.775s
user 0m9.653s
sys 0m0.090s
nvfortran -O3
C Fortran ratio
times 0.9870 1.6308 1.6523
# mean min max first last maxdiff
10000000 -0.0001 -0.5000 0.5000 0.4079 -0.2934 0.0000
real 0m5.243s
user 0m5.108s
sys 0m0.110s
flang -O3
C Fortran ratio
times 0.9753 1.7878 1.8330
# mean min max first last maxdiff
10000000 -0.0001 -0.5000 0.5000 0.4079 -0.2934 0.0000
real 0m5.480s
user 0m5.359s
sys 0m0.110s