How to have a generic interface for both allocatable and non allocatable dummy?

A toy example is better than long explanations:

module foo
    implicit none
    interface bar
        module procedure bar_na, bar_a
    end interface
contains
    subroutine bar_na(a,b)
    integer, intent(in   ) :: a(:)
    integer, intent(  out) :: b(:)
        b = -a
    end subroutine

    subroutine bar_a(a,b)
    integer, intent(in   ) :: a(:)
    integer, intent(  out), allocatable :: b(:)
        b = -a
    end subroutine
end module

This produces the following compilation error:

/app/example.f90:7:21:

    7 |     subroutine bar_na(a,b)
      |                     1
......
   13 |     subroutine bar_a(a,b)
      |                    2 
Error: Ambiguous interfaces in generic interface 'bar' for 'bar_na' at (1) and 'bar_a' at (2)

Is there a possible workaround?

I think they are theoretically distinguishable, but the standard has avoided it so far (perhaps for good reasons). Two approaches I often take to resolve the ambiguity are to either 1) merge the allocatable dummy argument b and a into a single allocatable, intent(inout) dummy argument, or 2) pass the length of b as an explicit intent(in) or more frequently intent(out) dummy argument in either of the two interfaces. The best approach depends on the problem being solved.

With inspired and willing compiler implementors, I too think the callee can be made to distinguish. However the issue is the caller side vis-a-vis the standard. The standard semantics, as arrived during the Fortran 8X saga during the 1980s, are such that the nonallocatable procedure instance is accessible to valid arrays of other attributes. Hence the caller faces ambiguity and it is at the root of the evil here.

With the work on Generics toward Fortran 202Y, I requested the J3 subgroups to get this specific aspect (and others) addressed by thinking out-of-the-box for some new standard extension that can help overcome the hurdle.

1 Like

This is because it is allowed for the programmer to pass an allocatable actual argument to bar_na(). Thus the compiler cannot know which routine you want. In contrast, an array without the alloctable attribute cannot be passed to bar_a(), and the compiler knows that and will warn you at compile time of the incompatibility.

So consider what it would take for a lay practitioner of Fortran to author a SWAP generic with the new template construct - this link has the likely 202Y syntax: So with this SWAP case, the challenge is rather similar to that in the original post here.

..
   template swap_t(T, N)
      private

      public :: swap
      public :: swap_dyn
   
      type :: T
      end type T
      integer, parameter :: N
   
      interface swap
         module procedure swap_
      end interface swap

      interface swap_dyn
         module procedure swap_ptr
         module procedure swap_alloc
      end interface swap_dyn

Frankly I think it is ridiculously verbose to ask a template author to do all this when a processor can be instructed to take care of this with good semantic improvement(s) in the language and a compact syntax to go with it.

Given the calling code:

a = [1, 2, 3]
b = [4, 5, 6]
call bar(a, b)

What should the compiler do? Deallocate b and call bar_a, or simply call bar_na?

So here, my take is Fortran 90 got off on the wrong foot when ALLOCATABLEs and POINTERs got introduced in a standard revision which also had generic interfaces. Thus when it came to disambiguation, Fortran 90 had statements such as:

where type, kind, and rank got considered which later, starting Fortran 2003, came to be referred to as TKR compatible semantics.

I truly believe, with some intent and inventiveness of the part of standard bearers, Fortran 90 could have started off with consideration of type, kind, rank, and attribute in disambiguation, or what I refer to as KART compatible semantics given what I think is the order of importance in actual practice with generic procedures. So with this, Fortran 90 would have been like so:

.
interface sub
   module procedure sub_a
   module procedure sub_b
   module procedure sub_c
end interface
,
subroutine sub_a( a, b )
   integer, intent(in) :: a(:)
   integer, intent(out) :: b(:)
.
subroutine sub_b( a, b )
   integer, intent(in) :: a(:)
   integer, intent(out), allocatable :: b(:)
.
subroutine sub_b( a, b )
   integer, intent(in) :: a(:)
   integer, intent(out), pointer :: b(:)
.
integer x(..), y(..)
call sub( x, y )  !  disambiguates to sub_a
.
integer u(..)
integer, allocatable, v(..)
call sub( u, v )  !  disambiguates to sub_b
.. and so forth   

Now, this would not have given the practitioners the short-cut to readily invoke procedures with nonallocatable, nonpointer array received arguments with actual that have either of these. But instead of a ready short-cut, in this case it might have worked out better if some other syntactical sugar, say the use of ( .. ), around the actual arguments was selected e.g.,

call sub( u, (v) )  ! disambiguates to sub_a due to `( .. )` around v denoting an expression a la ASSOCIATE construct

Oh well …

But I had very much wished for the Generics for Fortran 202Y to be designed around KART-compatible semantics, alas I failed.

1 Like

Agreed. There have been a few dozen instances among our library’s ~1500 generic interfaces where I wished the TKR rule could be more refined, particularly for allocatable arguments. We use the workarounds I mentioned above instead. It is manageable.

1 Like

I was initially expecting the compiler to give priority to the “allocatable routine” in such a case.

call bar_a because b is allocatable. This could have been a rule. But I can now see ambiguous cases if a 3rd routine was provided to the interface with only the a dummy argument being allocatable. If the two actual arguments are allocatable, the compiler could still not decide which routine to call. This is maybe the reason why such a rule was not set in the first place.

In my real use case, a and b don’t have the same type (so 1) won’t do) and/or the interface is the assignment(=) overload (so 2) won’t work).

bar_na is unsafe (non-conformance when shapes of a and b differ), bar_a is unsafe (if reallocation fails when shapes differ).
Why would you even want to marry these two?

I would imagine this might be implemented by the compiler first finding all specific interfaces that match the call statement. If there are more than one that match, then there would be some kind of point system, where each of the candidates earns bonus points when the attributes of the dummy arguments match those of the actual arguments. For example, an allocatable dummy argument that matches an allocatable actual argument would result in some bonus points given to that interface. Then the compiler would select the matching specific interface with the most bonus points. What happens when there are several interfaces with the same bonus points? Who sets the bonus point values, the programmer, or the standard committee, or can each compiler be different? As I said before, this general approach sounds like it could be complicated and make programming more difficult, not easier.

As it now exists with TKR matching, the rules are rigged so that there can’t be multiple matches, and either an interface matches the call statement or it doesn’t. Every compiler is required to resolve the matching in the same way, so codes can be portable. That makes things simple for the compiler and, perhaps more importantly, simple for the programmer, but of course it imposes constraints on the interfaces that are allowed. In the example being discussed, if the programmer has an allocatable argument that he wants to be treated as allocatable within the subroutine, then he must call the specific bar_a(), he cannot call a generic interface and expect the compiler to pick the one he wants.

A problem with this approach is that the meaning of a call can change when a procedure is added to the generic interface.

For example, you start with:

  interface bar
    module procedure bar_1, bar_2
  end interface
  ...
  call bar(...)

Assuming it compiles, bar is resolved to precisely one of bar_1 or bar_2.

But now you add:

  interface bar
    module procedure bar_3
  end interface

Under this proposal, if bar_3 is “better” by some measure, the meaning of the call bar
might change to call bar_3. I think this would be very surprising.

The way it works currently, if bar_3 can be added to the generic, it doesn’t change the meaning of calls that compile without it.

Compilers are good at implementing complex rules. What’s hard is specifying the rules unambiguously in the standard (look at how complicated the existing rules are already). And, as you mention, programmers have to understand them.

Nope, that’s not the case at all. What the compilers, starting from IBM FORTRAN circa 1956, are good at is in implementing code optimizations for which the few documented rules come after the fact, and the optimizations are approached more as fuzzy math, more black box, and perhaps even black art!

Instead when it comes to any rules with language semantics and syntax, there is great struggle to be good at their implementation.

1 Like

@RonShepard @ashe I agree, and it was also implied in my answer to @everythingfunctional: disambiguying between allocatable and non-allocatable dummies doesn’t look possible in the general case (only in simple cases).

So is any array assignement when the shapes differ. So what?

So is any allocation on assignment. So what?

For instance to overload the assignment(=) with optional allocation on assignement in the case the LHS is an allocatable.

If the new bar_3() were added for this purpose, (say to optimize some specific case), then it would not be surprising that the new routine were called, it would be the expected behavior. However, I do agree in general that this would be a complicated programming environment compared to the current situation. But if a programmer wants to handle some case separately, say due to an allocatable, pointer, or target attribute (i.e. something that is beyond TKR), with a generic interface, then what are the options?

One such option would be to allow the value of an argument to determine which specific procedure is called. This is now done within fortran within a few generic intrinsic functions. For example, when you specify REAL(x,KIND=wp), the return type depends on the value of wp. So this is equivalent to a situation where there are several REAL() functions, and the one that the compiler invokes depends (at compile time) on the TKR of the argument x and on the value of the dummy argument KIND (which I’ve invoked by keyword here, but that is not a requirement). For this particular case, wp must be known at compile time, so perhaps that kind of constraint could apply also to the situation with a user-written procedure. Although this capability is used by many intrinsic functions, it is not available currently for user-written procedures, so this would be a major advancement to the language.

BTW, this kind of language change occurred already for keyword arguments. Fortran 77 allowed keyword argument association only in some intrinsic procedures (e.g. OPEN, CLOSE, INQUIRE, READ, WRITE). Then f90 allowed this capability to be extended to user-written programs. Allowing a generic interface to select a specific procedure based on the value of one or more particular arguments would be a change of similar magnitude and scope.

Right, sometimes you want the meaning of call bar to change. But I think sometimes it is surprising. And good language design has to balance adding useful features to the language versus added complication for the programmers.

One (somewhat kludgy) solution is to add an extra argument that does nothing except help resolve the overload. A sort-of similar situation occurs in C++ when you define pre- and post-increment operators for a class. The pre-increment method is declared as operator++() while the post-increment must be declared as operator++(int). The int argument doesn’t do anything except giving the two methods different signatures.

Is there a way to detect unallocated variables, if I don’t know if it is an allocatable variable?

You mean when passed as argument to a procedure ?

Maybe use the optional attribute:

program main
   implicit none
   integer, target :: ints(4) = [1, 2, 3, 4]
   integer, allocatable, target :: iall(:)
   integer, pointer :: iptr(:) => null()

   call checkAlloc(1)
   call checkAlloc(ints)
   iptr => iall
   call checkAlloc(iall)
   call checkAlloc(iptr)
   allocate(iall(2))
   call checkAlloc(iall)
   call checkAlloc(iptr)
contains
   subroutine checkAlloc(var)
      integer, optional :: var(..)

      if (present(var)) then
         print *, ' Var is "allocated"'
         return
      endif
      print *, ' Var is NOT "allocated"'
   end subroutine
end program main
1 Like

Thanks, this should work in my case. But I was confused why the last call checkAlloc(iptr) says it’s NOT allocated. It’s because you have to associate the pointer after iall was allocated.