Thank everyone for the interesting and insightful discussions.
Up to now, there has been a good discussion on automatic arrays, but not as much on the segfault of intrinsic procedures. Let me give an example. It may take a few minutes to run, depending on your hardware.
! test_matmul.f90
module maprod_mod
implicit none
private
public :: maprod, rk
integer, parameter :: rk = kind(0.0D0)
contains
function maprod(X, Y) result(Z)
real(rk), intent(in) :: X(:, :), Y(:, :)
real(rk), allocatable :: Z(:, :)
integer :: i, j, k
if (size(X, 2) /= size(Y, 1)) then
write (*, *) "Wrong size"
stop
end if
allocate (Z(size(X, 1), size(Y, 2)))
Z = 0.0_rk
do j = 1, size(Y, 2)
do i = 1, size(X, 1)
do k = 1, size(X, 2)
Z(i, j) = Z(i, j) + X(i, k) * Y(k, j)
end do
end do
end do
end function maprod
end module maprod_mod
program test_matmul
use, non_intrinsic :: maprod_mod, only : maprod, rk
implicit none
integer, parameter :: n = 2000
real(rk), allocatable :: A(:, :), B(:, :)
write (*, *) 'Initialize'
allocate (A(n, n), B(n, n))
A = 0.0_rk
write (*, *) 'Loop'
B = maprod(A, A)
write (*, *) 'Succeed'
write (*, *) 'MATMUL'
B = matmul(A, A)
write (*, *) 'Succeed'
end program test_matmul
This is what I obtained on my laptop (Ubuntu 20.04, intel(R) Core™ i7-10610U CPU @ 1.80GHz) with ifort
.
$ uname -a
Linux zX18 5.11.15-051115-generic #202104161034 SMP Fri Apr 16 10:40:30 UTC 2021 x86_64 x86_64 x86_64 GNU/Linux
$ ulimit -s
8192
$ ifort -v
ifort version 2021.6.0
$ ifort -g -warn all test_matmul.f90 && ./a.out
Initialize
Loop
Succeed
MATMUL
forrtl: severe (174): SIGSEGV, segmentation fault occurred
Image PC Routine Line Source
a.out 000000000040666A Unknown Unknown Unknown
libpthread-2.31.s 00007FC387AC8420 Unknown Unknown Unknown
a.out 000000000040573A Unknown Unknown Unknown
a.out 0000000000403822 Unknown Unknown Unknown
libc-2.31.so 00007FC3878E4083 __libc_start_main Unknown Unknown
a.out 000000000040372E Unknown Unknown Unknown
N.B.:
-
The code does not involve automatic arrays.
-
Without special compiler options,
gfortran
andnagfor
did not segfault. -
I am well aware of the reason behind the segfault and how to resolve it. However, I take a viewpoint similar to @certik : a segfault of an intrinsic function (under the default settings) is hardly desirable for whatever reason. Imagine that we are not talking about Fortran but MATLAB or Python — or even C. How does this become OK when it comes to (a major implementation of) Fortran?
P.S.: This issue was reported to Intel more than 10 years ago (e.g., matmul segmentation fault for huge matrices - Intel Communities). Since the behavior persists, it seems that not many people regard it as a bug.