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
1,069 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
mecej4
Honored Contributor III
790 Views

If I guess your intentions correctly, what you should use is an abstract interface. Such an interface would let you state, in essence, "the argument q to dubbel_b is a procedure with the interface declared in the abstract interface. In other words, you need to describe the interface to the dummy argument rather than the interface to the actual argument.

Such an abstract interface is very useful when writing code to implement common algorithms such as solving a system of ODEs, etc.

Your example, modified:

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

 

0 Kudos
Steven_L_Intel1
Employee
790 Views

What the compiler is trying to tell you is that the language does not consider subroutine arguments in generic resolution. If it was a function, then the characteristics of the return value would be considered, but a subroutine has nothing that can be used in this context.

0 Kudos
JVanB
Valued Contributor II
790 Views

This doesn't reproduce on my older version of ifort, but I think the problem may be fixed by putting IMPLICIT NONE in each interface body. IMPLICIT none doesn't propagate into interface bodies the way it does into module procedures and internal procedures, so each interface body should normally start with IMPORT and IMPLICIT NONE.

 

0 Kudos
Robert_van_Amerongen
New Contributor III
790 Views

Thanks for the answers, but this forum member still remains in a confused state. If Steve's reply holds, I expect to appear the same warning if I change any of the names of the dummy arguments "q". But there is no warning in that case. Any addition of IMPLICIT NONE as RO proposed has no influence as far as the warning generation is concerned. (Compiler 16.0).

To have things clear, I have consulted the Fortran Standard 2015 (doc WG5/N2014) where I find the following: 12.4.3.4.5 "Restrictions on generic declarations", point 3, first bullet: "Two dummy arguments are distinguishable if ... one is a procedure and the other is a data object". This let me conclude that the original code example (#1) is standard conforming(, unless I made an error, of course). Can someone shed some new light?

Robert

0 Kudos
Steven_L_Intel1
Employee
790 Views

Hmm - I have to revisit my earlier comment. Please stand by....

0 Kudos
jimdempseyatthecove
Honored Contributor III
790 Views

>> "Two dummy arguments are distinguishable if ... one is a procedure and the other is a data object"

But this does not state if different procedures (distinguishable by interface and/or return/lack of return) are distinguished.

I would hope that it does. Can Steve clarify this?

Jim Dempsey

0 Kudos
andrew_4619
Honored Contributor II
790 Views

Interesting thread. Robert so my benefit what do you expect a call the dubbel (the dubbel_b case) to look like?

0 Kudos
IanH
Honored Contributor II
790 Views

Robert van Amerongen wrote:
To have things clear, I have consulted the Fortran Standard 2015 (doc WG5/N2014) where I find the following: 12.4.3.4.5 "Restrictions on generic declarations", point 3, first bullet: "Two dummy arguments are distinguishable if ... one is a procedure and the other is a data object". This let me conclude that the original code example (#1) is standard conforming(, unless I made an error, of course). Can someone shed some new light?
Note that procedures being distinguishable from data objects is a F2008 feature.

0 Kudos
Steven_L_Intel1
Employee
790 Views

Well spotted, Ian! As far as I know, we don't support that feature yet, but the diagnostic is misleading. I will make sure the developers know about this.

0 Kudos
Steven_L_Intel1
Employee
790 Views

Ok, let's try again.

We DO support the feature. But we're giving a bogus standards warning if you select F2008 or F2015 level. I will report that.

0 Kudos
Robert_van_Amerongen
New Contributor III
790 Views

Thanks all of you for your comments. It is clear now.

Andrew (#8) raised the issue on the application of this construction. It comes from the fact that sometimes (in OpenGL, OpenCL) a function can be called with one of the arguments being either a procedure or an indication that no procedure is supplied. Usually it then is NULL (C-style).

This behaviour can be achieved by writing an interface with ISO_C_BINDING stuff and with the dummy argument being of the form C_FUNPTR(some_routine),VALUE. The actual call then can be either C_FUNLOC(some_routine) or C_NULL_FUNPTR.

The alternative is to write a generic interface. One of the interface bodies has the dummy argument writen wih an interface (see MFE, section 5.12). The other body has the dummy argument of the form (example) INTEGER(KIND=C_INTPTR_T),VALUE. The actual call then can be done with either the name of the routine "some_routine" or with NULL. This form is found in my original post.

I do prefer the latter for two reasons. First it is more elegant. I do not like seeing an actual argument with a C_FUNLOC argument (The same applies to C_LOC). That is, of course, a matter of taste. But there is another big advantage. In the latter case, the compiler is so kind to check whether the supplied procedure has a correct argument list. And believe me, that is very helpful during program development as I have experienced!!

Robert

 

0 Kudos
Robert_van_Amerongen
New Contributor III
790 Views

Oeps, typo error in #12.

Dummy argument in the first case must be TYPE(C_FUNPTR),VALUE !

Robert

0 Kudos
JVanB
Valued Contributor II
790 Views

There is a third alternative: you can set the address of a procedure pointer to that of C_NULL_FUNPTR which will pass NULL to the subroutine.

module M
   implicit none
   abstract interface
      function F(x) bind(C)
         implicit none
         real F,x
      end function F
   end interface
   interface
      subroutine S(g,x) bind(C,name='really_S')
         import
         implicit none
         procedure(F) g
         real, value :: x
      end subroutine S
   end interface
   contains
      subroutine really_S(g,x) bind(C,name='really_S')
         use ISO_C_BINDING
         type(C_FUNPTR), value :: g
         real, value :: x
         procedure(F), pointer :: h

         if(.NOT.C_ASSOCIATED(g)) then
            write(*,'(a)') 'Informative from subroutine S: g == NULL'
         else
            call C_F_PROCPOINTER(g,h)
            write(*,*) 'g(x) = ',h(x)
         end if
      end subroutine really_S
end module M

program P
   use M
   use ISO_C_BINDING
   implicit none
   procedure(F), pointer :: g

   call C_F_PROCPOINTER(C_NULL_FUNPTR,g)
   call S(g,3.14)
   call S(e,1.59)
   contains
      function e(x) bind(C)
         real e,x
         e = 3.14+x/1000
      end function e
end program P

Output with gfortran:

Informative from subroutine S: g == NULL
 g(x) =    3.14159012

 

0 Kudos
IanH
Honored Contributor II
790 Views

Robert van Amerongen wrote:

Andrew (#8) raised the issue on the application of this construction. It comes from the fact that sometimes (in OpenGL, OpenCL) a function can be called with one of the arguments being either a procedure or an indication that no procedure is supplied. Usually it then is NULL (C-style).

This behaviour can be achieved by writing an interface with ISO_C_BINDING stuff and with the dummy argument being of the form C_FUNPTR(some_routine),VALUE. The actual call then can be either C_FUNLOC(some_routine) or C_NULL_FUNPTR.

The alternative is to write a generic interface. One of the interface bodies has the dummy argument writen wih an interface (see MFE, section 5.12). The other body has the dummy argument of the form (example) INTEGER(KIND=C_INTPTR_T),VALUE. The actual call then can be done with either the name of the routine "some_routine" or with NULL. This form is found in my original post.

I do prefer the latter for two reasons. First it is more elegant. I do not like seeing an actual argument with a C_FUNLOC argument (The same applies to C_LOC). That is, of course, a matter of taste. But there is another big advantage. In the latter case, the compiler is so kind to check whether the supplied procedure has a correct argument list. And believe me, that is very helpful during program development as I have experienced!!

What prevents you from using an OPTIONAL argument for the procedure?

(If you are writing BIND(C) interfaces for the one procedure, then you are not permitted to have more than one interface body for the same procedure accessible in a scope.)

0 Kudos
Robert_van_Amerongen
New Contributor III
790 Views

RO and Ian, thanks for the replies.

The example of RO is a nice one; I never realised this way of doing.

On the Optional issue of Ian : note that my problem is of Fortran calling C-routines from OpenGL and others libs. The interfaces thus define a function or subroutine with the BIND(C) attribute. The Fortran 2003 standard forbids the combination of OPTIONAL and BIND(C). The Fortran 2015 standard (TS29113 as it is in doc WG5/N1942)  is to some extent less restrictive in that an optional argument is allowed but NOT in combination with the value attribute (see document sec. 5.3, C1255a(R1230)) so it is not always guaranteed to work. Further, the C-routine must have an optional argument. As far as I known, I never saw such a routine in OpenGL and others (or I cannot remember that.).

It is not clear to me what you mean with your last remark that I cannot have more than one interface body for the same procedure. I have many examples with a generic interface and with two bodies. Of course, these bodies specify a procedure with different names, but they refer to the same procedure and thus have the same BIND(C) label name. Very strict speaking, this is not allowed in Fortran 2003, but it has been made possible in Fortran 2008. (Intel, by the way, never made it a problem!). (There was a discussion on CLF some time ago.) Is this what you mean?

Robert

0 Kudos
IanH
Honored Contributor II
790 Views

Robert van Amerongen wrote:
It is not clear to me what you mean with your last remark that I cannot have more than one interface body for the same procedure. I have many examples with a generic interface and with two bodies. Of course, these bodies specify a procedure with different names, but they refer to the same procedure and thus have the same BIND(C) label name. Very strict speaking, this is not allowed in Fortran 2003, but it has been made possible in Fortran 2008. (Intel, by the way, never made it a problem!). (There was a discussion on CLF some time ago.) Is this what you mean?

Yes, that is what I am referring to.

The relevant restriction is still in Fortran 2008 (12.4.3.2p7) and in the current draft for the next revision.  As you note, both interface bodies refer to the same procedure - each interface body declares an explicit specific interface - so you have two interfaces for the one procedure in the same scope, and that is not permitted.

See also http://mailman.j3-fortran.org/pipermail/j3/2013-May/006397.html.

I think the approach in #14 is non-conforming, due to the restrictions in the standard on the arguments to C_F_PROCPOINTER.  I may have had this discussion with RO before, though.

My approach in this situation has been for client code to invoke through a non-BIND(C) Fortran wrapper that has optional arguments, this wrapper then makes the appropriate transformations (including kind conversions) to supply appropriate arguments to the [single!] C interoperable interface.  This insulates Fortran code from the interface requirements of the C code.

(Unfortunately ifort hasn't yet implemented the F2008 relaxation of BIND(C) on internal procedures, so for optional procedures the process is not as neat as it could be.)

 

0 Kudos
Robert_van_Amerongen
New Contributor III
790 Views

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.

At present we observe that the current gfortran and the current Intel compiler do not complain irrrespective the standard that is selected. They both accept the form as that is given in the attachment. (Also in many, many other examples that I do have.)  So, we must conclude that both the leading compilers in the field have to do some work! I am very interested in Steve's opinion in this respect.

Robert

 

 

0 Kudos
Steven_L_Intel1
Employee
790 Views

I'm going to quote the Fortran 2015 draft as this has the latest relevant wording, though Fortran 2008 also has relevant text:

16.2 Global identifiers
1 Program units, common blocks, external procedures, entities with binding labels, external input/output units, pending data transfer operations, and images are global entities of a program. The name of a common block with no binding label, external procedure with no binding label, or program unit that is not a submodule is a global identifier. The submodule identifier of a submodule is a global identifier. A binding label of an entity of the program is a global identifier. An entity of the program shall not be identified by more than one binding label.

2 The global identifier of an entity shall not be the same as the global identifier of any other entity. Furthermore, a binding label shall not be the same as the global identifier of any other global entity, ignoring differences in case. A processor may assign a global identifier to an entity that is not specified by this part of ISO/IEC 1539 to have a global identifier (such as an intrinsic procedure); in such a case, the processor shall ensure that this assigned global identifier differs from all other global identifiers in the program.

In the example here, we have two external procedures with the same binding label - this makes the program nonconforming. But note that these rules are not numbered syntax rules or constraints, so compilers are not required to detect the conflict. Furthermore, a compiler can't possibly detect all such conflicts as they may be in separately compiled program units. Obviously if you have two Fortran procedures (not just interfaces) with the same binding label, the linker may complain (depending on whose linker you're using), but that's outside the scope of the language.

I will also point out that what this source does is extremely useful and we depend on it in various modules we provide.

0 Kudos
FortranFan
Honored Contributor II
790 Views

Steve Lionel (Intel) wrote:

.. In the example here, we have two external procedures with the same binding label - this makes the program nonconforming... I will also point out that what this source does is extremely useful and we depend on it in various modules we provide.

@Robert van Amerongen,

Given Steve's comment above, can you please confirm the use cases you in mind for all this is Fortran generic interfaces for functions in 3rd party libraries, the stated examples being Microsoft's Windows API (kernel32: GetVersionEx), OpenGL, OpenCL, etc?  Doesn't MSDN suggest GetVersionEx in kernel32 library is a C++ function, I assume an overloaded one?  

Since the Fortran standard makes it clear the interoperability feature is with C companion processor, would you know how to provide such generic interfaces in current standard C (is it C11?) for the use cases you have in mind?  If yes, can you post them here? 

Thanks,

0 Kudos
Steven_L_Intel1
Employee
710 Views

MSDN generically refers to C++ when it shows the prototype, but in all the cases we care about, it's really C. Microsoft does have some APIs that require C++ class libraries, but certainly not these.

The use of generic interfaces that map to the same external procedure are handy when the procedure can be called with various data types.In the case of GetVersionEx, it can be called with either an OSVERSIONINFO structure or OSVERSIONINFOEX structure. What I can't quite figure out is how this works in C/C++, since the function is declared as having an argument of LPOSVERSIONINFOA, which is not the same as LPOSVERSIONFOEXA.

I note that Microsoft has deprecated GetVersionEx and now suggests VerifyVersionInfo instead.

0 Kudos
Reply