Function pointer array crashing

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

Welcome to the Discourse @eelis!

Proper syntax for your function interface would be

real, dimension(size(state,1), size(state,2)) :: dstate

See the fortran-lang documentation for size.

2 Likes

Thank you very much @FedericoPerini !

The fix you provide works perfectly on flang. However, on gfortran it still crashes with the same error message. Even with explicit definition of dimensions it does the same. I wonder if it is a compiler bug? I should test with a newer version. I have 9.4.0.

You may have hit a compiler bug. Compiler tests can be done with the compiler explorer

1 Like

Oh wow, thanks! I didn’t know about that site, very nice!
I will have to report the bug then.

Br,

Eelis

Hi @eelis, and welcome to the Fortraners’ discourse. There are many people here wanting to help and/or discuss things, I’m sure you will find this very helpful and productive.

I was typing my answer, but @FedericoPerini was faster. :laughing:
Your problem is a very common pitfall people have with the size intrinsic. Admittedly, gfortran’s documentation about size doesn’t clarify that, but if you don’t pass the optional (second) argument dim to it, size will return a vector, even if the array is one-dimensional. The frustration probably comes from the fact the dim argument was added in Fortran 2003; in Fortran 90 you just had to live with the less flexible version of size, where the result is always a vector.

Anyway, using dim with size(state,1) instead of size(state(:,1)) should fix the problem - except it doesn’t in gfortran (tested with version 12.2.0 and the latest stable release, 13.1.0) This is probably a bug, but I doubt it has to do with size iteself. It rather comes from the fact you define and use an array of type(pp) elements. If you replace func_array with a type(pp) scalar, it actually works.

Edit: It’s not relevant, but might worth mentioning: there is no need to add implicit none in zero_state’s body. The function is contained in the main program, therefore it inherits the implicit none from there.

2 Likes

Thank you for the very informative answer @Pap!
I am very happy about this forum. Also very happy to see the recent development in Fortran infrastructure and community.

I am happy to learn the three pieces of information that you provided in your answer. All new to me.

Cheers,

Eelis

Also tested with both ifort and ifx compilers. It works, as it should be. This is clearly a gfortran bug worth reporting. For some reason gfortan doesn’t like arrays of a derived type like this one, but doesn’t have any problem when it is a scalar. Weird…

1 Like

These are not correct. size always returns a scalar.

16.9.194 SIZE (ARRAY [, DIM, KIND])

Description. Size of an array or one extent.

Class. Inquiry function.

Arguments.

ARRAY shall be assumed-rank or an array. It shall not be an unallocated allocatable variable or a pointer that is not associated. If ARRAY is an assumed-size array, DIM shall be present with a value less than the rank of ARRAY.

DIM (optional) shall be an integer scalar with a value in the range 1 ≤ DIM ≤ n, where n is the rank of ARRAY.

KIND (optional) shall be a scalar integer constant expression.

Result Characteristics. Integer scalar. If KIND is present, the kind type parameter is that specified by the value of KIND; otherwise the kind type parameter is that of default integer type.

Result Value. If DIM is present, the result has a value equal to the extent of dimension DIM of ARRAY, except that if ARRAY is assumed-rank and associated with an assumed-size array and DIM is present with a value equal to the rank of ARRAY, the value is −1.

If DIM is absent and ARRAY is assumed-rank, the result has a value equal to PRODUCT(SHAPE(ARRAY, KIND)). Otherwise, the result has a value equal to the total number of elements of ARRAY.

That said, size(state,dim=1) is more appropriate clearer than size(state(:,1)), and works even if size(state,dim=2) == 0 where you would get a segfault in the latter case.

I am 1000% sure, not jut 100%, that size(x) used to return a vector, even if it was a vector of one element only. If they broke that rule later on, when dim was introduced, I don’t know, really. That’s because I always used dim since Fortran 2003, exactly because I was fed up with those one-element vectors I used to get all the time before dim.
So unless I’m terribly wrong here (and I am not,) that breaks backwards compatibility - admittedly, very slightly, but it does. Fortran is notorious for backwards compatibility.

1 Like

In my browser, I think there are some missing minus signs in this text. This

Examples. The value of SIZE (A (2:5,-1:1), DIM=2) is 3. The value of
SIZE (A (2:5,-1:1) ) is 12.

looks right.

2 Likes

I don’t really care what the standard says, and frankly, I won’t even check it out. That’s because I know what the Fortran 90 compilers I used did. And they did as I said, period.
It was so common that I had my own function ssize to return a scalar when the array only had one dimension. That’s because size(x)(1) won’t work, so I needed to temporarily store the result of size and extract its one and only element.

I do apologize @eelis for the mistake.

I believe @Pap and I got confused as this polymorphic behavior is indeed present in other array size functions (such as, for example, lbound, ubound ), and an error was being discussed, so my mind went immediately to that. Like @Pap suggests, I also like to never use size(x) without a dimension on a 1D array because I’m dumb and I know that it’s “safer” to always specify it.

1 Like

@FedericoPerini If you used Fortran compilers back when dim didn’t exist, they always returned a vector (yes, I insist that’s a fact, not an opinion.) So you aren’t dumb. It is quite plausible to assume they will always do the same, given Fortran’s backwards compatibility.

I actually found old projects of mine, where a custom ssize function is used instead of size, just to dodge the fact size(x) returned a vector no matter what.

Thanks man! I will try to report it. Unfortunately, I don’t remember my password to their bugzilla. I tried to recover it but the recovery email does not come through…

Thank you for the clarification. btw. I like your Youtube channel. Waiting for more content :wink:

@FedericoPerini All good! I appreciate the help and quick response. The code got better with your fixes. Thanks!

1 Like

And obviously you are not dumb!

1 Like

My content is ending up on the NERSC YouTube channel lately:

2 Likes

Or so you think… and you are so wrong. :laughing:
I don’t care what the standard said, I know the reality, what compilers did. My best guess is that you probably wasn’t programming back then to know that reality. And if you did, you obviously didn’t do it in Fortran. So maybe you should be more careful with your statements. Or not, I don’t really care.

What I do know is that you are not going to “teach” me what I know for a fact. P-E-R-I-O-D.
I hope that’s clear enough. That being said, I’m not going to comment again on your posts, which I honestly don’t know why they tend to be offensive.

And now for the important part: I apologize to @eelis for the false statement concerning size. It was based on the reality of Fortran compilers back when size didn’t have optional arguments, and the very plausible assumption they still do the same, given the notorious Fortran backwards compatibility.