Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

Strange behaviour Generic Interface

Robert_van_Amerongen
New Contributor III
3,730 Views

The following example produces a warning #8219: "Fortran 2015 does not allow a subroutine dummy argument to be used in  generic selection [DUBBEL_B]". I do not understand the warning. The two arguments "q" are perfectly distinguisable, so the main requirement is satisfied. Moreover, if I change the name of one of the dummy arguments "q" the warning disapears. Do I miss a point somewhere?

Robert

  MODULE dgi_mod
  IMPLICIT none
!
  INTERFACE dubbel
!
    SUBROUTINE dubbel_a(q)
    REAL :: q
    END SUBROUTINE dubbel_a
!
    SUBROUTINE dubbel_b(q)
      INTERFACE
        SUBROUTINE q(i,j, k)
        INTEGER :: i,j,k
        END SUBROUTINE q
      END INTERFACE
    END SUBROUTINE dubbel_b
!
  END INTERFACE
!
  END MODULE dgi_mod

 

0 Kudos
33 Replies
IanH
Honored Contributor III
1,070 Views

Robert van Amerongen wrote:
Ian, thanks for the reply. For those who are interested in the details: the orgininal discussion can be found at comp.lang.fortran; search for subject "generic interface with multiple identical binding names". The (slightly altered) example on which the discussion was based, is attached to this mail.

My take of the conclusion at the end of that thread is "its non-conforming".

(When Tobias says "However, also Fortran 2003 requires that the interface matches the actual procedure declaration..", I think he meant to say "also Fortran 2008", because that requirement hasn't gone away.).

Just write the thin wrapper referenced in that thread for one of the variants... and then you can sleep easy at night.

Here's an approach for the philosophers to contemplate.

!   typedef struct { int comp; } t;
!   void SomeAPI(t* arg);    ! arg may be NULL

MODULE m
  USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_INT
  IMPLICIT NONE
  PRIVATE
  
  PUBLIC :: SomeAPI
  INTERFACE SomeAPI
    MODULE PROCEDURE SomeAPI_1
    MODULE PROCEDURE SomeAPI_2
  END INTERFACE SomeAPI
  
  TYPE, BIND(C) :: t
    INTEGER(C_INT) :: comp
  END TYPE t
CONTAINS
  SUBROUTINE SomeAPI_1(arg)
    TYPE(t), INTENT(INOUT) :: arg
    INTERFACE
      SUBROUTINE SomeAPI_c(arg) BIND(C, NAME='SomeAPI')
        IMPORT :: t
        IMPLICIT NONE
        TYPE(t), INTENT(INOUT) :: arg
      END SUBROUTINE SomeAPI_c
    END INTERFACE
    CALL SomeAPI_c(arg)
  END SUBROUTINE SomeAPI_1
  
  SUBROUTINE SomeAPI_2
    USE, INTRINSIC:: ISO_C_BINDING, ONLY: C_NULL_PTR
    INTERFACE
      SUBROUTINE SomeAPI_c(arg) BIND(C, NAME='SomeAPI')
        USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_PTR
        IMPLICIT NONE
        TYPE(C_PTR), VALUE :: arg
      END SUBROUTINE SomeAPI_c
    END INTERFACE
    CALL SomeAPI_C(C_NULL_PTR)
  END SUBROUTINE SomeAPI_2
END MODULE m

 

0 Kudos
JVanB
Valued Contributor II
1,070 Views

The issue is that most nobody on the standards committee outside of the Intel contingent has to maintain a compiler where interfacing with such a massive API is almost routine. Writing wrapper procedures instead of being able to tell the compiler how to directly invoke the procedure itself seems like a step back to the dark days of f95 when you had to do that.

My impression is that the committee is not unanimous that a program can remain standard-conforming after it uses one of the interoperability features. Given that, a program might as well be in for a dollar rather than just a dime when it invoke Win32 API functions. There should be more flexibility, not less, regarding interoperability. The restrictions in the standard provide no security because you can always hack around them, they just make it more tedious to write code that wants to interoperate with different languages and different compilers.

Thus: the restriction on multiple interfaces to the same procedure is bogus. The restriction on character components of LEN /= 1 is bogus (did you get all the bugs worked out with TRANSFER in constant expressions as a consequence of this restriction, Steve?) The restriction on C_FUNLOC and C_F_PROCPOINTER to interoperable procedures is bogus. Not having a standard mechanism for providing a linker name for non-interoperable procedures is bogus. No standard mechanism for specifying calling convention? Bogus; gfortran/ifort are the de facto standard in this regard, not to mention DLLEXPORT. No standard mechanism for writing out an interface body for a variadic procedure? I could go on, but the committee might at least recommend syntax for extensions that they would agree would be nonstandard, so we could use them in a transportable way in the real world.

 

0 Kudos
Steven_L_Intel1
Employee
1,070 Views

RO, the restriction on C_LOC and C_FUNLOC goes away in F2015. There is syntax which COULD be used to specify alternate calling conventions - there's nothing sacred about the C in BIND(C) - but there's really no advantage to using that over directives as the standard can't possibly specify all possible conventions. The C interoperability features have a bunch of handwaving about "companion C processor".

The rule about two procedures not having the same binding label is to avoid an ambiguity if you had two Fortran procedures with the same binding label.

But the funny thing is - it works.The standard specifies the behavior of a standard-conforming program. Once your program includes non-Fortran code (such as calls to the Windows API), it is by nature non-standard. Yet the language's specification is flexible enough to allow you to keep to standard syntax.

There's this fascinating article from 1982 that just surfaced and it's a worthwhile read, all about the early standardization process and the guiding philosophies. https://www.computer.org/csdl/proceedings/afips/1982/5089/00/50890817.pdf

0 Kudos
mecej4
Honored Contributor III
1,070 Views

Steve, that 1982 article is a gem. Many of the statements there are memorable, e.g.:

The standard is to be interpreted as permissive. That is, that the standard serves only to specify a part, not all, of the language. Anything not specified isn't unclean, bad, immoral, or even not kosher. It is simply not specified. ... Some nonconformance is encouraged. 

Also noteworthy is the change in the intended readership of the standard: mainly compiler writers, prior to Fortran 77, more general audience later.

0 Kudos
FortranFan
Honored Contributor III
1,070 Views

Repeat Offender wrote:

The .. standard .. restriction on .. is bogus. .. bogus .. bogus. .. bogus. .. .. the committee might at least ..

Have you join them!

0 Kudos
JVanB
Valued Contributor II
1,070 Views

Steve Lionel (Intel) wrote:

The rule about two procedures not having the same binding label is to avoid an ambiguity if you had two Fortran procedures with the same binding label.

But... what has been bandied about in this thread has not been a restriction on two procedures having the same binding label but on two different interface bodies that tell the compiler two different ways to marshal their actual arguments to compose calls to that one procedure. The existence of two such interface bodies makes sense to me because sometimes the actual argument will be an array (by reference) and sometimes the NULL pointer or an atom (by value), although these can be synthesized by making the address of the target of a Fortran pointer take on the desired value. In this thread there was the possibility of an argument whose actual type can only be determined by reading its first component, which gives the size of the actual argument structure, and in this case the two inconsistent interface bodies seem to be the most useful solution.

Is there going to be something in the next standard where a dummy argument to a BIND(C) procedure can have the OPTIONAL attribute where .NOT.PRESENT means that the procedure got C_NULL_PTR (or C_NULL_FUNPTR) passed by value? That would clean up some loose ends.

 

0 Kudos
Robert_van_Amerongen
New Contributor III
1,070 Views

All of you: thanks for the answers. It's clear now: a generic interface with two interface bodies where each body defines a procedure with a BIND(C) and with an identical  label name is not standard conforming. That is a pitty, but it is as it is.

I know how to handle these situations; I have added a modified version of the example of #18. It is similar to the example of Ian (#22) but not for 100%. Things do not have become simpler. Similar situations can be handled in a similar way.

FortranFan (#20) asks for some background: all of these example stems from using what you call third party software. All of them use struct C-language. I do not write myself C-code. The group consists of WinAPI, OpenGL and freeglut for many years now; in some more recent times OpenCL and I do expect the upcoming Vulkan also will belong to this group. All of them have functions that must be described by interfaces with C-binding labels. And some function can best be written with the generics as we discussed here before.

Robert

0 Kudos
Robert_van_Amerongen
New Contributor III
1,070 Views

Oeps, forgot the attachment!

0 Kudos
Steven_L_Intel1
Employee
1,070 Views

Repeat Offender wrote:
Is there going to be something in the next standard where a dummy argument to a BIND(C) procedure can have the OPTIONAL attribute where .NOT.PRESENT means that the procedure got C_NULL_PTR (or C_NULL_FUNPTR) passed by value? That would clean up some loose ends.

Yes, indeed. And Intel Fortran 16 supports that. This (and the lifting of restrictions on C_LOC and C_FUNLOC) are part of TS29113, "Further Interoperability with C", incorporated into Fortran 2015. Read more at ftp://ftp.nag.co.uk/sc22wg5/N1901-N1950/N1942.pdf

Regarding the interface bodies - those declare external procedures so the "no duplicates" rule applies. I don't disagree that this can be a very useful thing to do, but it is outside the standard.

0 Kudos
JVanB
Valued Contributor II
1,070 Views

Hopefully compilers won't start detecting and rejecting multiple interface bodies with the same binding name. It would just require more effort to hide the fact from the compiler, like making up multiple abstract interfaces and then pointing Fortran procedure pointers with those abstract interfaces at the same address at the start of program execution, sort of like you have to do already for most of the OpenGL subroutines already (except in the OpenGL case the addresses are all different).

But in the case of Quote #29, TS29113 would permit a single interface body with the argument declared TYPE(*), is that right?

 

0 Kudos
Steven_L_Intel1
Employee
1,070 Views

Yes, you could use TYPE(*) instead of TYPE(C_PTR) in the declaration of GetVersionEx_c, though I wouldn't as it reduces type safety somewhat. TYPE(*) is really intended for cases where the C argument is a "void". I would just go for Robert's original approach as it is clearer and more efficient. It's not as if you could take this program to Linux and run it there, even in the "standard conforming" version.

I very much doubt that any implementation will start checking for duplicate binding labels in interfaces to external procedures.

0 Kudos
Steven_L_Intel1
Employee
1,070 Views

The inappropriate standards warning, for the use of "procedureness" in generic resolutiion, has been fixed for a release later this year.

0 Kudos
Robert_van_Amerongen
New Contributor III
1,070 Views

Steve, thanks.

Robert

0 Kudos
Reply