Lately I have been reading many discussions here about fortran intrinsic procedures, their performance, correctness, etc. I have known for a while about some odd behavior across gfortran, ifort, and ifx. For instance, consider the following program:
program main
use, intrinsic :: iso_fortran_env, sp=>real32, dp=>real64
implicit none
real(sp), allocatable :: xsp(:)
real(sp) :: xsp_sum
real(dp), allocatable :: xdp(:)
real(dp) :: xdp_sum, xdp_xsp_difference
integer :: i, j, n
write(*,*) 'COMPILER: ',compiler_version()
write(*,*) 'OPTIONS: ',compiler_options()
write(*,*) ''
do i=0,7
do j=1,9
n = j*(10**i)
if (allocated(xsp)) deallocate(xsp)
if (allocated(xdp)) deallocate(xdp)
allocate(xsp(n), xdp(n))
xsp = 1.0
xsp_sum = sum(xsp)
xdp = 1.0
xdp_sum = sum(xdp)
xdp_xsp_difference = xdp_sum - real(xsp_sum, dp)
if (xdp_xsp_difference.gt.0.001) then
write(*,'(a,i8,a,e13.6,2(a,e22.15))') 'n: ',n, &
', xsp_sum: ',xsp_sum, &
', xdp_sum: ',xdp_sum, &
', xdp_xsp_difference: ',xdp_xsp_difference
end if
end do
end do
end program main
Depending on the compiler and optimization options you use, different results can be obtained. To summarize, this is what I got using “debugging,” “normal optimization,” and “aggressive optimization” sets of flags.
Debugging:
fpm: Entering directory '/home/tyranids/projects/some-sums'
Project is up to date
COMPILER: GCC version 11.3.0
OPTIONS: -I build/gfortran_020AF3609BFD7C6D -mtune=generic -march=x86-64 -g -Wall -Wextra -Werror=implicit-interface -fPIC -fmax-errors=1 -fcheck=bounds -fcheck=array-temps -fbacktrace -fcoarray=single -fimplicit-none -ffree-form -J build/gfortran_020AF3609BFD7C6D -fpre-include=/usr/include/finclude/math-vector-fortran.h
n: 20000000, xsp_sum: 0.167772E+08, xdp_sum: 0.200000000000000E+08, xdp_xsp_difference: 0.322278400000000E+07
n: 30000000, xsp_sum: 0.167772E+08, xdp_sum: 0.300000000000000E+08, xdp_xsp_difference: 0.132227840000000E+08
n: 40000000, xsp_sum: 0.167772E+08, xdp_sum: 0.400000000000000E+08, xdp_xsp_difference: 0.232227840000000E+08
n: 50000000, xsp_sum: 0.167772E+08, xdp_sum: 0.500000000000000E+08, xdp_xsp_difference: 0.332227840000000E+08
n: 60000000, xsp_sum: 0.167772E+08, xdp_sum: 0.600000000000000E+08, xdp_xsp_difference: 0.432227840000000E+08
n: 70000000, xsp_sum: 0.167772E+08, xdp_sum: 0.700000000000000E+08, xdp_xsp_difference: 0.532227840000000E+08
n: 80000000, xsp_sum: 0.167772E+08, xdp_sum: 0.800000000000000E+08, xdp_xsp_difference: 0.632227840000000E+08
n: 90000000, xsp_sum: 0.167772E+08, xdp_sum: 0.900000000000000E+08, xdp_xsp_difference: 0.732227840000000E+08
fpm: Leaving directory '/home/tyranids/projects/some-sums'
fpm: Entering directory '/home/tyranids/projects/some-sums'
Project is up to date
COMPILER:
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel
(R) 64, Version 2021.9.0 Build 20230302_000000
OPTIONS:
-Ibuild/ifort_64365A593998FE80 -c -warn all -check all -error-limit 1 -O0 -g -a
ssume byterecl -traceback -free -module build/ifort_64365A593998FE80 -o build/i
fort_64365A593998FE80/some-sums/app_main.f90.o
n: 20000000, xsp_sum: 0.167772E+08, xdp_sum: 0.200000000000000E+08, xdp_xsp_difference: 0.322278400000000E+07
n: 30000000, xsp_sum: 0.167772E+08, xdp_sum: 0.300000000000000E+08, xdp_xsp_difference: 0.132227840000000E+08
n: 40000000, xsp_sum: 0.167772E+08, xdp_sum: 0.400000000000000E+08, xdp_xsp_difference: 0.232227840000000E+08
n: 50000000, xsp_sum: 0.167772E+08, xdp_sum: 0.500000000000000E+08, xdp_xsp_difference: 0.332227840000000E+08
n: 60000000, xsp_sum: 0.167772E+08, xdp_sum: 0.600000000000000E+08, xdp_xsp_difference: 0.432227840000000E+08
n: 70000000, xsp_sum: 0.167772E+08, xdp_sum: 0.700000000000000E+08, xdp_xsp_difference: 0.532227840000000E+08
n: 80000000, xsp_sum: 0.167772E+08, xdp_sum: 0.800000000000000E+08, xdp_xsp_difference: 0.632227840000000E+08
n: 90000000, xsp_sum: 0.167772E+08, xdp_sum: 0.900000000000000E+08, xdp_xsp_difference: 0.732227840000000E+08
fpm: Leaving directory '/home/tyranids/projects/some-sums'
fpm: Entering directory '/home/tyranids/projects/some-sums'
Project is up to date
COMPILER:
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2023
.1.0 Build 20230320
OPTIONS:
-Ibuild/ifx_64365A593998FE80 -c -warn all -check all -error-limit 1 -O0 -g -ass
ume byterecl -traceback -free -module build/ifx_64365A593998FE80 -o build/ifx_6
4365A593998FE80/some-sums/app_main.f90.o
n: 20000000, xsp_sum: 0.167772E+08, xdp_sum: 0.200000000000000E+08, xdp_xsp_difference: 0.322278400000000E+07
n: 30000000, xsp_sum: 0.167772E+08, xdp_sum: 0.300000000000000E+08, xdp_xsp_difference: 0.132227840000000E+08
n: 40000000, xsp_sum: 0.167772E+08, xdp_sum: 0.400000000000000E+08, xdp_xsp_difference: 0.232227840000000E+08
n: 50000000, xsp_sum: 0.167772E+08, xdp_sum: 0.500000000000000E+08, xdp_xsp_difference: 0.332227840000000E+08
n: 60000000, xsp_sum: 0.167772E+08, xdp_sum: 0.600000000000000E+08, xdp_xsp_difference: 0.432227840000000E+08
n: 70000000, xsp_sum: 0.167772E+08, xdp_sum: 0.700000000000000E+08, xdp_xsp_difference: 0.532227840000000E+08
n: 80000000, xsp_sum: 0.167772E+08, xdp_sum: 0.800000000000000E+08, xdp_xsp_difference: 0.632227840000000E+08
n: 90000000, xsp_sum: 0.167772E+08, xdp_sum: 0.900000000000000E+08, xdp_xsp_difference: 0.732227840000000E+08
fpm: Leaving directory '/home/tyranids/projects/some-sums'
Under debugging flags, all 3 compilers seem to encounter errors due to precision after 2**24
. This is surprising to me, as it indicates that the intrinsic SUM function is implemented as nothing more than a naive loop. I will update this post with some timings I have done in another program that leads me to this conclusion.
EDIT:
Click to see timing and algorithm comparisons.
Here is the timing code. It compares results and timing information for the intrinsic sum, a naive do-loop, and a pairwise reduction with cutoff at 8192 elements.
program timings
use, intrinsic :: iso_fortran_env, sp=>real32, dp=>real64, i64=>int64
implicit none
integer, parameter :: n = 2**27, i_max = 128
real(sp) :: xsp(n), xsp_sum
real(dp) :: xdp(n), xdp_sum, xdp_xsp_difference
integer(i64) :: c1, c2, cr
integer :: i
write(*,*) 'COMPILER: ',compiler_version()
write(*,*) 'OPTIONS: ',compiler_options()
write(*,*) ''
write(*,*) 'n: ',n,', i_max: ',i_max
xsp = 1.0
xdp = 1.0
xdp_sum = sum(xdp)
write(*,*) '"correct" answer (xdp_sum): ',xdp_sum
call system_clock(c1, cr)
do i=1,i_max
xsp_sum = sum(xsp)
end do
call system_clock(c2)
xdp_xsp_difference = xdp_sum - real(xsp_sum, dp)
write(*,'(a32,e13.6,a,e22.15,a,e13.6)') 'intrinsic sum ',xsp_sum, &
' diff: ',xdp_xsp_difference, &
', time per call: ',(real(max(c2 - c1, 1_i64))/cr)/i_max
call system_clock(c1, cr)
do i=1,i_max
xsp_sum = s0(xsp)
end do
call system_clock(c2)
xdp_xsp_difference = xdp_sum - real(xsp_sum, dp)
write(*,'(a32,e13.6,a,e22.15,a,e13.6)') 'naive do loop ',xsp_sum, &
' diff: ',xdp_xsp_difference, &
', time per call: ',(real(max(c2 - c1, 1_i64))/cr)/i_max
call system_clock(c1, cr)
do i=1,i_max
xsp_sum = s1(xsp)
end do
call system_clock(c2)
xdp_xsp_difference = xdp_sum - real(xsp_sum, dp)
write(*,'(a32,e13.6,a,e22.15,a,e13.6)') 'pairwise sum, cutoff 8192 ',xsp_sum, &
' diff: ',xdp_xsp_difference, &
', time per call: ',(real(max(c2 - c1, 1_i64))/cr)/i_max
contains
pure function s0(xin) result(xout)
real(sp), intent(in) :: xin(:)
real(sp) :: xout
integer :: i
xout = 0.0
do i=1,size(xin)
xout = xout + xin(i)
end do
end function s0
pure recursive function s1(xin) result(xout)
real(sp), intent(in) :: xin(:)
real(sp) :: xout
integer :: n
n = size(xin)
if (n.gt.8192) then
xout = s1(xin(1:n/2)) + s1(xin(n/2+1:n))
else
xout = sum(xin)
end if
end function s1
end program timings
I compile and run with the “aggressive otimization” options. Results follow:
fpm: Entering directory '/home/tyranids/projects/some-sums'
Project is up to date
COMPILER: GCC version 11.3.0
OPTIONS: -I build/gfortran_75FF7B055CBF6CA1 -march=core2 -mmmx -mno-popcnt -msse -msse2 -msse3 -mssse3 -msse4.1 -mno-sse4.2 -mno-avx -mno-avx2 -mno-sse4a -mno-fma4 -mno-xop -mno-fma -mno-avx512f -mno-bmi -mno-bmi2 -mno-aes -mno-pclmul -mno-avx512vl -mno-avx512bw -mno-avx512dq -mno-avx512cd -mno-avx512er -mno-avx512pf -mno-avx512vbmi -mno-avx512ifma -mno-avx5124vnniw -mno-avx5124fmaps -mno-avx512vpopcntdq -mno-avx512vbmi2 -mno-gfni -mno-vpclmulqdq -mno-avx512vnni -mno-avx512bitalg -mno-avx512bf16 -mno-avx512vp2intersect -mno-3dnow -mno-adx -mno-abm -mno-cldemote -mno-clflushopt -mno-clwb -mno-clzero -mcx16 -mno-enqcmd -mno-f16c -mno-fsgsbase -mfxsr -mno-hle -msahf -mno-lwp -mno-lzcnt -mno-movbe -mno-movdir64b -mno-movdiri -mno-mwaitx -mno-pconfig -mno-pku -mno-prefetchwt1 -mno-prfchw -mno-ptwrite -mno-rdpid -mno-rdrnd -mno-rdseed -mno-rtm -mno-serialize -mno-sgx -mno-sha -mno-shstk -mno-tbm -mno-tsxldtrk -mno-vaes -mno-waitpkg -mno-wbnoinvd -mno-xsave -mno-xsavec -mno-xsaveopt -mno-xsaves -mno-amx-tile -mno-amx-int8 -mno-amx-bf16 -mno-uintr -mno-hreset -mno-kl -mno-widekl -mno-avxvnni --param=l1-cache-size=32 --param=l1-cache-line-size=64 --param=l2-cache-size=3072 -mtune=core2 -Ofast -Werror=implicit-interface -flto -fwhole-program -fimplicit-none -ffree-form -J build/gfortran_75FF7B055CBF6CA1 -fpre-include=/usr/include/finclude/math-vector-fortran.h
n: 134217728 , i_max: 128
"correct" answer (xdp_sum): 134217728.00000000
intrinsic sum 0.671089E+08 diff: 0.671088640000000E+08, time per call: 0.983408E-01
naive do loop 0.671089E+08 diff: 0.671088640000000E+08, time per call: 0.984338E-01
pairwise sum, cutoff 8192 0.134218E+09 diff: 0.000000000000000E+00, time per call: 0.104085E+00
fpm: Leaving directory '/home/tyranids/projects/some-sums'
fpm: Entering directory '/home/tyranids/projects/some-sums'
Project is up to date
COMPILER:
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel
(R) 64, Version 2021.9.0 Build 20230302_000000
OPTIONS:
-Ibuild/ifort_83E883136EE047D1 -c -fast -free -module build/ifort_83E883136EE04
7D1 -o build/ifort_83E883136EE047D1/some-sums/app_timings.f90.o
n: 134217728 , i_max: 128
"correct" answer (xdp_sum): 134217728.000000
intrinsic sum 0.671089E+08 diff: 0.671088640000000E+08, time per call: 0.498731E-01
naive do loop 0.134218E+09 diff: 0.000000000000000E+00, time per call: 0.970180E-01
pairwise sum, cutoff 8192 0.134218E+09 diff: 0.000000000000000E+00, time per call: 0.996574E-01
fpm: Leaving directory '/home/tyranids/projects/some-sums'
fpm: Entering directory '/home/tyranids/projects/some-sums'
Project is up to date
COMPILER:
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2023
.1.0 Build 20230320
OPTIONS:
-Ibuild/ifx_83E883136EE047D1 -c -fast -free -module build/ifx_83E883136EE047D1
-o build/ifx_83E883136EE047D1/some-sums/app_timings.f90.o
n: 134217728 , i_max: 128
"correct" answer (xdp_sum): 134217728.000000
intrinsic sum 0.134218E+09 diff: 0.000000000000000E+00, time per call: 0.108797E+00
naive do loop 0.134218E+09 diff: 0.000000000000000E+00, time per call: 0.109057E+00
pairwise sum, cutoff 8192 0.134218E+09 diff: 0.000000000000000E+00, time per call: 0.120868E+00
fpm: Leaving directory '/home/tyranids/projects/some-sums'
We can see that gfortran arrives at the same wrong answer (with nearly identical computation times between methods) as below, stopping at 2**26
for both intrinsic sum and do-loop. Pairwise reduction yields the correct result although is slightly slower on my machine. Perhaps most surprising to me is that whatever optimizations ifort is doing allow it to get the correct result using a simple do-loop. However, the intrinsic sum fails for ifort specifically at this power of 2, when it has no issues with larger sums as shown below. Ifx is simultaneously wrong for intrinsic and do-loop, while being the slowest for all 3 algorithms as well.
Normal Optimization
fpm: Entering directory '/home/tyranids/projects/some-sums'
Project is up to date
COMPILER: GCC version 11.3.0
OPTIONS: -I build/gfortran_776EBCE5331A33CA -march=core2 -mmmx -mno-popcnt -msse -msse2 -msse3 -mssse3 -msse4.1 -mno-sse4.2 -mno-avx -mno-avx2 -mno-sse4a -mno-fma4 -mno-xop -mno-fma -mno-avx512f -mno-bmi -mno-bmi2 -mno-aes -mno-pclmul -mno-avx512vl -mno-avx512bw -mno-avx512dq -mno-avx512cd -mno-avx512er -mno-avx512pf -mno-avx512vbmi -mno-avx512ifma -mno-avx5124vnniw -mno-avx5124fmaps -mno-avx512vpopcntdq -mno-avx512vbmi2 -mno-gfni -mno-vpclmulqdq -mno-avx512vnni -mno-avx512bitalg -mno-avx512bf16 -mno-avx512vp2intersect -mno-3dnow -mno-adx -mno-abm -mno-cldemote -mno-clflushopt -mno-clwb -mno-clzero -mcx16 -mno-enqcmd -mno-f16c -mno-fsgsbase -mfxsr -mno-hle -msahf -mno-lwp -mno-lzcnt -mno-movbe -mno-movdir64b -mno-movdiri -mno-mwaitx -mno-pconfig -mno-pku -mno-prefetchwt1 -mno-prfchw -mno-ptwrite -mno-rdpid -mno-rdrnd -mno-rdseed -mno-rtm -mno-serialize -mno-sgx -mno-sha -mno-shstk -mno-tbm -mno-tsxldtrk -mno-vaes -mno-waitpkg -mno-wbnoinvd -mno-xsave -mno-xsavec -mno-xsaveopt -mno-xsaves -mno-amx-tile -mno-amx-int8 -mno-amx-bf16 -mno-uintr -mno-hreset -mno-kl -mno-widekl -mno-avxvnni --param=l1-cache-size=32 --param=l1-cache-line-size=64 --param=l2-cache-size=3072 -mtune=core2 -O2 -Werror=implicit-interface -fimplicit-none -ffree-form -J build/gfortran_776EBCE5331A33CA -fpre-include=/usr/include/finclude/math-vector-fortran.h
n: 20000000, xsp_sum: 0.167772E+08, xdp_sum: 0.200000000000000E+08, xdp_xsp_difference: 0.322278400000000E+07
n: 30000000, xsp_sum: 0.167772E+08, xdp_sum: 0.300000000000000E+08, xdp_xsp_difference: 0.132227840000000E+08
n: 40000000, xsp_sum: 0.167772E+08, xdp_sum: 0.400000000000000E+08, xdp_xsp_difference: 0.232227840000000E+08
n: 50000000, xsp_sum: 0.167772E+08, xdp_sum: 0.500000000000000E+08, xdp_xsp_difference: 0.332227840000000E+08
n: 60000000, xsp_sum: 0.167772E+08, xdp_sum: 0.600000000000000E+08, xdp_xsp_difference: 0.432227840000000E+08
n: 70000000, xsp_sum: 0.167772E+08, xdp_sum: 0.700000000000000E+08, xdp_xsp_difference: 0.532227840000000E+08
n: 80000000, xsp_sum: 0.167772E+08, xdp_sum: 0.800000000000000E+08, xdp_xsp_difference: 0.632227840000000E+08
n: 90000000, xsp_sum: 0.167772E+08, xdp_sum: 0.900000000000000E+08, xdp_xsp_difference: 0.732227840000000E+08
fpm: Leaving directory '/home/tyranids/projects/some-sums'
fpm: Entering directory '/home/tyranids/projects/some-sums'
Project is up to date
COMPILER:
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel
(R) 64, Version 2021.9.0 Build 20230302_000000
OPTIONS:
-Ibuild/ifort_D4C49DE7E65100D3 -c -O2 -xHost -free -module build/ifort_D4C49DE7
E65100D3 -o build/ifort_D4C49DE7E65100D3/some-sums/app_main.f90.o
fpm: Leaving directory '/home/tyranids/projects/some-sums'
fpm: Entering directory '/home/tyranids/projects/some-sums'
Project is up to date
COMPILER:
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2023
.1.0 Build 20230320
OPTIONS:
-Ibuild/ifx_D4C49DE7E65100D3 -c -O2 -xHost -free -module build/ifx_D4C49DE7E651
00D3 -o build/ifx_D4C49DE7E65100D3/some-sums/app_main.f90.o
n: 70000000, xsp_sum: 0.671089E+08, xdp_sum: 0.700000000000000E+08, xdp_xsp_difference: 0.289113600000000E+07
n: 80000000, xsp_sum: 0.671089E+08, xdp_sum: 0.800000000000000E+08, xdp_xsp_difference: 0.128911360000000E+08
n: 90000000, xsp_sum: 0.671089E+08, xdp_sum: 0.900000000000000E+08, xdp_xsp_difference: 0.228911360000000E+08
fpm: Leaving directory '/home/tyranids/projects/some-sums'
With “normal optimization,” gfortran’s behavior is identical to the debugging flags option. However, ifort now produces no errors, and ifx seemingly stops counting at 2**26
rather than 2**24
now.
Lastly, aggressive optimization:
fpm: Entering directory '/home/tyranids/projects/some-sums'
Project is up to date
COMPILER: GCC version 11.3.0
OPTIONS: -I build/gfortran_75FF7B055CBF6CA1 -march=core2 -mmmx -mno-popcnt -msse -msse2 -msse3 -mssse3 -msse4.1 -mno-sse4.2 -mno-avx -mno-avx2 -mno-sse4a -mno-fma4 -mno-xop -mno-fma -mno-avx512f -mno-bmi -mno-bmi2 -mno-aes -mno-pclmul -mno-avx512vl -mno-avx512bw -mno-avx512dq -mno-avx512cd -mno-avx512er -mno-avx512pf -mno-avx512vbmi -mno-avx512ifma -mno-avx5124vnniw -mno-avx5124fmaps -mno-avx512vpopcntdq -mno-avx512vbmi2 -mno-gfni -mno-vpclmulqdq -mno-avx512vnni -mno-avx512bitalg -mno-avx512bf16 -mno-avx512vp2intersect -mno-3dnow -mno-adx -mno-abm -mno-cldemote -mno-clflushopt -mno-clwb -mno-clzero -mcx16 -mno-enqcmd -mno-f16c -mno-fsgsbase -mfxsr -mno-hle -msahf -mno-lwp -mno-lzcnt -mno-movbe -mno-movdir64b -mno-movdiri -mno-mwaitx -mno-pconfig -mno-pku -mno-prefetchwt1 -mno-prfchw -mno-ptwrite -mno-rdpid -mno-rdrnd -mno-rdseed -mno-rtm -mno-serialize -mno-sgx -mno-sha -mno-shstk -mno-tbm -mno-tsxldtrk -mno-vaes -mno-waitpkg -mno-wbnoinvd -mno-xsave -mno-xsavec -mno-xsaveopt -mno-xsaves -mno-amx-tile -mno-amx-int8 -mno-amx-bf16 -mno-uintr -mno-hreset -mno-kl -mno-widekl -mno-avxvnni --param=l1-cache-size=32 --param=l1-cache-line-size=64 --param=l2-cache-size=3072 -mtune=core2 -Ofast -Werror=implicit-interface -flto -fwhole-program -fimplicit-none -ffree-form -J build/gfortran_75FF7B055CBF6CA1 -fpre-include=/usr/include/finclude/math-vector-fortran.h
n: 70000000, xsp_sum: 0.671089E+08, xdp_sum: 0.700000000000000E+08, xdp_xsp_difference: 0.289113600000000E+07
n: 80000000, xsp_sum: 0.671089E+08, xdp_sum: 0.800000000000000E+08, xdp_xsp_difference: 0.128911360000000E+08
n: 90000000, xsp_sum: 0.671089E+08, xdp_sum: 0.900000000000000E+08, xdp_xsp_difference: 0.228911360000000E+08
fpm: Leaving directory '/home/tyranids/projects/some-sums'
fpm: Entering directory '/home/tyranids/projects/some-sums'
Project is up to date
COMPILER:
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel
(R) 64, Version 2021.9.0 Build 20230302_000000
OPTIONS:
-Ibuild/ifort_83E883136EE047D1 -c -fast -free -module build/ifort_83E883136EE04
7D1 -o build/ifort_83E883136EE047D1/some-sums/app_main.f90.o
fpm: Leaving directory '/home/tyranids/projects/some-sums'
fpm: Entering directory '/home/tyranids/projects/some-sums'
Project is up to date
COMPILER:
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2023
.1.0 Build 20230320
OPTIONS:
-Ibuild/ifx_83E883136EE047D1 -c -fast -free -module build/ifx_83E883136EE047D1
-o build/ifx_83E883136EE047D1/some-sums/app_main.f90.o
n: 70000000, xsp_sum: 0.671089E+08, xdp_sum: 0.700000000000000E+08, xdp_xsp_difference: 0.289113600000000E+07
n: 80000000, xsp_sum: 0.671089E+08, xdp_sum: 0.800000000000000E+08, xdp_xsp_difference: 0.128911360000000E+08
n: 90000000, xsp_sum: 0.671089E+08, xdp_sum: 0.900000000000000E+08, xdp_xsp_difference: 0.228911360000000E+08
fpm: Leaving directory '/home/tyranids/projects/some-sums'
Here, gfortran appears to have joined ifx with stopping counting at 2**26
, while ifort once again produces the (expected) correct results.
Does anyone have insight to offer on this topic?