Interface definitions for assumed size arrays

I have a question regarding the interface definitions for assumed size.

Assume we have the following function (here just a dummy for what is a supposed to be written in C)

subroutine x(y)
  implicit none
  integer, dimension(*) :: y
  print*, y(1)
end subroutine x

A working solution is

program does_compile1

  implicit none

  interface
    subroutine x(y)
      integer, dimension(*) :: y
    end subroutine x
  end interface

  integer, dimension(3) :: a3
  integer, dimension(3,3) :: a33
  
  a3 = 3
  a33 = 3
  call x(a3) 
  call x(a33)

end program does_compile1

The following code, however, is rejected:

program does_not_compile

  implicit none

  interface x  !< added the name here
    subroutine x(y)
      integer, dimension(*) :: y
    end subroutine x
  end interface x

  integer, dimension(3,3) :: a33
  
  a33 = 3
  call x(a33)

end program does_not_compile

because there is no specific subroutine. I find this strange, because (*) should match everything.

Interestingly, the following works:

program does_compile2

  implicit none

  interface x
    subroutine x(y)
      integer, dimension(*) :: y
    end subroutine x
  end interface x

  integer, dimension(3) :: a3
  a3 = 3
  call x(a3)

end program does_compile2

This leaves me a little bit puzzled, because I thought that assumed size (*) does not care about the rank. But here it seems that it implies rank 1.

Tested with ifx 2025.0.4 and gfortran 14.2.1.

This looks related to the rule recently discussed in this thread: Binding multiple C functions under one Fortran interface - #9 by ivanpribec

When you call a procedure through a generic interface, the standard states:

15.4.3.4.5 Restrictions on generic declarations
[…]

A dummy argument is type, kind, and rank compatible, or TKR compatible, with another dummy argument if the first is type compatible with the second, the kind type parameters of the first have the same values as the corresponding kind type parameters of the second, and both have the same rank or either is assumed-rank.

In other words, when you call a procedure via the generic name, the rank must match too, otherwise the generic resolution fails.

To pass a 2-d array via the generic name, you will need to use rank remapping:

  integer, dimension(3,3), target :: a33
  
  a33 = 3

  block
     integer, pointer :: a1d(:)
     a1d(1:9) => a33
     call x(a1d)
  end block

Edit #1: a second idea (I didn’t test this) would be to introduce a rank-2 wrapper

interface x
   subroutine x(y)
     integer, dimension(*) :: y(*)
   end subroutine
   procedure :: x2d
end interface

! ...

contains

   subroutine x2d(y)
     integer, contiguous :: y(:,:)

     interface
       subroutine x(y)
         integer, dimension(*) :: y
      end subroutine x
     end interface

     call x(y(1))
   end subroutine
end subroutine

Edit #2: a rank-generic procedure is also an option, especially if you are wrapping a C function. The Fortran interface would use an assumed-rank argument:

interface
   subroutine x(y) bind(c,name="x_rank_generic")
     integer, contiguous :: y(..)
   end subroutine
end interface

and on the C side, you would have:

#include <ISO_Fortran_binding.h>

extern void x(int *y); // The actual C procedure

void x_rank_generic(CFI_cdesc_t *y) {
   x((int *) y->base_addr);
}
2 Likes

Then my question is: why is dimension(*) rank 1? I thought it matches any rank, as in the first example. That was also the answer here: Difference between assumed-size and assumed-shape arrays? - #6 by FedericoPerini

8.5.8.5 Assumed-size array says “The rank and extents may differ for the effective and dummy arguments”.

That is correct (in an observational sense). But it appears in the context of a generic interface, this has to be overriden with stricter rules from 15.4.3.4.5.

If rank were not part of the generic interface resolution, how would you distinguish these two interfaces?

  interface x
    subroutine x1(y)
      integer, dimension(*) :: y
    end subroutine x1
    subroutine x2(y)
      integer, dimension(3,*) :: y
    end subroutine x2
  end interface

Both have assumed-size arguments, so both could accept arguments of differing rank and extents. This would create an ambiguity.

1 Like

that is a convincing argument.

dimension(*) clearly defines a rank-1 array. The same section 8.5.8.5 states:

R823 assumed-implied-spec is [ lower-bound : ] *
R824 assumed-size-spec is explicit-shape-spec-list, assumed-implied-spec
[…]
The rank is equal to one plus the number of explicit-shape-specs.

So, if there is no explicit-shape-spec (as in dimension(*)), the rank is one.
You can pass actual argument of different rank and extent but in the subprogram you can only use the dummy argument according to its defined rank.

1 Like

Thanks for the clarifications. It totally makes sense for the case of a named interface (overloading) but the different behavior for the “external” interface (does_compile) is quite confusing for me.

Edit: does_compile should be does_compile1

You mean your does_compile1 code?
Why should it be confusing? You declare an external subroutine x(y) to have an assumed-size argument y of rank-1. According to the standard, the actual argument may be of any rank, so both calls (with rank-1 array a3 and rank-2 array a33) are accepted.

The confusing part is that it stops working when you have a generic interface (see does_not_compile):

  interface x       !<- generic interface, TKR match enforced
    subroutine x(y)  !<- assumed-size dummy, only TK match needed
      integer, dimension(*) :: y
    end subroutine x
  end interface x
1 Like

Ahh yes, this is highly annoying. Assumed size is great for one off routines because it lets you be generic for any rank arguments, but only if it’s a single routine floating by itself. I’ve run into the same confusion that putting it in an interface block suddenly makes it treated as rank 1 only. When I asked this question, I was told that the free routine works via storage association, the assumed size argument is rank 1, so once the compiler actually checks that for dispatch (from multiple routines in an interface block) it no longer works for any rank.

1 Like

yes, I meant does_compile1

This could be solved by allowing one and only one procedure with assumed size for a given dummy argument:

  interface x
    subroutine x1(y)
      integer, dimension(*) :: y
    end subroutine x1
  end interface

Would stand for an integer array of any rank>0. What would be the problem with that?

EDIT: it would have worked if designed like this from the beginning, but it would not be backward compatible…

I think the problem with this would be that a programmer might want generic resolution to choose x1() for 1D arrays and x2() for 2D arrays, the way TKR resolution now works (and has since f90). The above convention would not allow that resolution to occur, and existing codes that depend on the current TKR rules would no longer work.

To get TKR to work for some situations and not others requires some kind of additional flag or keyword in the generic resolution, it cannot occur just by changing the meaning of TKR. One possibility might be to allow assumed rank declarations (a f2018 feature) somehow within the generic resolution, although I’m unsure exactly how that could be done in a backwards compatible way either.

2 Likes