Hello,
I am testing function pointers in Fortran. I wonder if this piece of code is legit:
program test_func_array
implicit none
type pp
procedure(func_template), pointer, nopass :: f =>null()
end type pp
abstract interface
function func_template(state) result(dstate)
implicit none
real, dimension(:,:), intent(in) :: state
real, dimension(size(state(:,1)), size(state(1,:))) :: dstate
end function
end interface
type(pp) :: func_array(4)
real, dimension(4,6) :: state
func_array(1)%f => zero_state
print*,func_array(1)%f(state)
contains
function zero_state(state) result(dstate)
implicit none
real, dimension(:,:), intent(in) :: state
real, dimension(size(state(:,1)), size(state(1,:))) :: dstate
dstate = 0.
end function zero_state
end program test_func_array
If I try to compile it with gfortran, I get a crash:
951: internal compiler error: spec_dimen_size(): Bad dimension
0x7f3db2946082 __libc_start_main
../csu/libc-start.c:308
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See <file:///usr/share/doc/gcc-9/README.Bugs> for instructions.
If I use flang, it compiles then at run time, I get this:
test_f_array: malloc.c:2379: sysmalloc: Assertion `(old_top == initial_top (av) && old_size == 0) || ((unsigned long) (old_size) >= MINSIZE && pr
ev_inuse (old_top) && ((unsigned long) old_end & (pagesize - 1)) == 0)' failed.
[1] 118664 abort (core dumped) ./test_f_array
The problem seems to relate to the dimensionality of the state variables. If I have just scalars. The code compiles fine on gfortran. And in flang, even explicit dimensions compile and run fine.
Any help on the topic is greatly appreciated (possibly, if someone has an easy access to different compilers, that would be interesting).
Thanks!
/Eelis